singletons-2.6: A framework for generating singleton types
Copyright(C) 2016 Richard Eisenberg
LicenseBSD-style (see LICENSE)
MaintainerRyan Scott
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Singletons.Prelude.List.NonEmpty

Description

Defines functions and datatypes relating to the singleton for NonEmpty, including a singletons version of all the definitions in Data.List.NonEmpty.

Because many of these definitions are produced by Template Haskell, it is not possible to create proper Haddock documentation. Please look up the corresponding operation in Data.List.NonEmpty. Also, please excuse the apparent repeated variable names. This is due to an interaction between Template Haskell and Haddock.

Synopsis
  • type family Sing :: k -> Type
  • data SNonEmpty :: forall a. NonEmpty a -> Type where
  • type family Map (a :: (~>) a b) (a :: NonEmpty a) :: NonEmpty b where ...
  • sMap :: forall a b (t :: (~>) a b) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply MapSym0 t) t :: NonEmpty b)
  • type family Intersperse (a :: a) (a :: NonEmpty a) :: NonEmpty a where ...
  • sIntersperse :: forall a (t :: a) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply IntersperseSym0 t) t :: NonEmpty a)
  • type family Scanl (a :: (~>) b ((~>) a b)) (a :: b) (a :: [a]) :: NonEmpty b where ...
  • sScanl :: forall b a (t :: (~>) b ((~>) a b)) (t :: b) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ScanlSym0 t) t) t :: NonEmpty b)
  • type family Scanr (a :: (~>) a ((~>) b b)) (a :: b) (a :: [a]) :: NonEmpty b where ...
  • sScanr :: forall a b (t :: (~>) a ((~>) b b)) (t :: b) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ScanrSym0 t) t) t :: NonEmpty b)
  • type family Scanl1 (a :: (~>) a ((~>) a a)) (a :: NonEmpty a) :: NonEmpty a where ...
  • sScanl1 :: forall a (t :: (~>) a ((~>) a a)) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply Scanl1Sym0 t) t :: NonEmpty a)
  • type family Scanr1 (a :: (~>) a ((~>) a a)) (a :: NonEmpty a) :: NonEmpty a where ...
  • sScanr1 :: forall a (t :: (~>) a ((~>) a a)) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply Scanr1Sym0 t) t :: NonEmpty a)
  • type family Transpose (a :: NonEmpty (NonEmpty a)) :: NonEmpty (NonEmpty a) where ...
  • sTranspose :: forall a (t :: NonEmpty (NonEmpty a)). Sing t -> Sing (Apply TransposeSym0 t :: NonEmpty (NonEmpty a))
  • type family SortBy (a :: (~>) a ((~>) a Ordering)) (a :: NonEmpty a) :: NonEmpty a where ...
  • sSortBy :: forall a (t :: (~>) a ((~>) a Ordering)) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply SortBySym0 t) t :: NonEmpty a)
  • type family SortWith (a :: (~>) a o) (a :: NonEmpty a) :: NonEmpty a where ...
  • sSortWith :: forall a o (t :: (~>) a o) (t :: NonEmpty a). SOrd o => Sing t -> Sing t -> Sing (Apply (Apply SortWithSym0 t) t :: NonEmpty a)
  • type family Length (a :: NonEmpty a) :: Nat where ...
  • sLength :: forall a (t :: NonEmpty a). Sing t -> Sing (Apply LengthSym0 t :: Nat)
  • type family Head (a :: NonEmpty a) :: a where ...
  • sHead :: forall a (t :: NonEmpty a). Sing t -> Sing (Apply HeadSym0 t :: a)
  • type family Tail (a :: NonEmpty a) :: [a] where ...
  • sTail :: forall a (t :: NonEmpty a). Sing t -> Sing (Apply TailSym0 t :: [a])
  • type family Last (a :: NonEmpty a) :: a where ...
  • sLast :: forall a (t :: NonEmpty a). Sing t -> Sing (Apply LastSym0 t :: a)
  • type family Init (a :: NonEmpty a) :: [a] where ...
  • sInit :: forall a (t :: NonEmpty a). Sing t -> Sing (Apply InitSym0 t :: [a])
  • type family (a :: a) <| (a :: NonEmpty a) :: NonEmpty a where ...
  • (%<|) :: forall a (t :: a) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply (<|@#@$) t) t :: NonEmpty a)
  • type family Cons (a :: a) (a :: NonEmpty a) :: NonEmpty a where ...
  • sCons :: forall a (t :: a) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply ConsSym0 t) t :: NonEmpty a)
  • type family Uncons (a :: NonEmpty a) :: (a, Maybe (NonEmpty a)) where ...
  • sUncons :: forall a (t :: NonEmpty a). Sing t -> Sing (Apply UnconsSym0 t :: (a, Maybe (NonEmpty a)))
  • type family Unfoldr (a :: (~>) a (b, Maybe a)) (a :: a) :: NonEmpty b where ...
  • sUnfoldr :: forall a b (t :: (~>) a (b, Maybe a)) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply UnfoldrSym0 t) t :: NonEmpty b)
  • type family Sort (a :: NonEmpty a) :: NonEmpty a where ...
  • sSort :: forall a (t :: NonEmpty a). SOrd a => Sing t -> Sing (Apply SortSym0 t :: NonEmpty a)
  • type family Reverse (a :: NonEmpty a) :: NonEmpty a where ...
  • sReverse :: forall a (t :: NonEmpty a). Sing t -> Sing (Apply ReverseSym0 t :: NonEmpty a)
  • type family Inits (a :: [a]) :: NonEmpty [a] where ...
  • sInits :: forall a (t :: [a]). Sing t -> Sing (Apply InitsSym0 t :: NonEmpty [a])
  • type family Tails (a :: [a]) :: NonEmpty [a] where ...
  • sTails :: forall a (t :: [a]). Sing t -> Sing (Apply TailsSym0 t :: NonEmpty [a])
  • type family Unfold (a :: (~>) a (b, Maybe a)) (a :: a) :: NonEmpty b where ...
  • sUnfold :: forall a b (t :: (~>) a (b, Maybe a)) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply UnfoldSym0 t) t :: NonEmpty b)
  • type family Insert (a :: a) (a :: [a]) :: NonEmpty a where ...
  • sInsert :: forall a (t :: a) (t :: [a]). SOrd a => Sing t -> Sing t -> Sing (Apply (Apply InsertSym0 t) t :: NonEmpty a)
  • type family Take (a :: Nat) (a :: NonEmpty a) :: [a] where ...
  • sTake :: forall a (t :: Nat) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply TakeSym0 t) t :: [a])
  • type family Drop (a :: Nat) (a :: NonEmpty a) :: [a] where ...
  • sDrop :: forall a (t :: Nat) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply DropSym0 t) t :: [a])
  • type family SplitAt (a :: Nat) (a :: NonEmpty a) :: ([a], [a]) where ...
  • sSplitAt :: forall a (t :: Nat) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply SplitAtSym0 t) t :: ([a], [a]))
  • type family TakeWhile (a :: (~>) a Bool) (a :: NonEmpty a) :: [a] where ...
  • sTakeWhile :: forall a (t :: (~>) a Bool) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply TakeWhileSym0 t) t :: [a])
  • type family DropWhile (a :: (~>) a Bool) (a :: NonEmpty a) :: [a] where ...
  • sDropWhile :: forall a (t :: (~>) a Bool) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply DropWhileSym0 t) t :: [a])
  • type family Span (a :: (~>) a Bool) (a :: NonEmpty a) :: ([a], [a]) where ...
  • sSpan :: forall a (t :: (~>) a Bool) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply SpanSym0 t) t :: ([a], [a]))
  • type family Break (a :: (~>) a Bool) (a :: NonEmpty a) :: ([a], [a]) where ...
  • sBreak :: forall a (t :: (~>) a Bool) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply BreakSym0 t) t :: ([a], [a]))
  • type family Filter (a :: (~>) a Bool) (a :: NonEmpty a) :: [a] where ...
  • sFilter :: forall a (t :: (~>) a Bool) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply FilterSym0 t) t :: [a])
  • type family Partition (a :: (~>) a Bool) (a :: NonEmpty a) :: ([a], [a]) where ...
  • sPartition :: forall a (t :: (~>) a Bool) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply PartitionSym0 t) t :: ([a], [a]))
  • type family Group (a :: [a]) :: [NonEmpty a] where ...
  • sGroup :: forall a (t :: [a]). SEq a => Sing t -> Sing (Apply GroupSym0 t :: [NonEmpty a])
  • type family GroupBy (a :: (~>) a ((~>) a Bool)) (a :: [a]) :: [NonEmpty a] where ...
  • sGroupBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply GroupBySym0 t) t :: [NonEmpty a])
  • type family GroupWith (a :: (~>) a b) (a :: [a]) :: [NonEmpty a] where ...
  • sGroupWith :: forall a b (t :: (~>) a b) (t :: [a]). SEq b => Sing t -> Sing t -> Sing (Apply (Apply GroupWithSym0 t) t :: [NonEmpty a])
  • type family GroupAllWith (a :: (~>) a b) (a :: [a]) :: [NonEmpty a] where ...
  • sGroupAllWith :: forall a b (t :: (~>) a b) (t :: [a]). SOrd b => Sing t -> Sing t -> Sing (Apply (Apply GroupAllWithSym0 t) t :: [NonEmpty a])
  • type family Group1 (a :: NonEmpty a) :: NonEmpty (NonEmpty a) where ...
  • sGroup1 :: forall a (t :: NonEmpty a). SEq a => Sing t -> Sing (Apply Group1Sym0 t :: NonEmpty (NonEmpty a))
  • type family GroupBy1 (a :: (~>) a ((~>) a Bool)) (a :: NonEmpty a) :: NonEmpty (NonEmpty a) where ...
  • sGroupBy1 :: forall a (t :: (~>) a ((~>) a Bool)) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply GroupBy1Sym0 t) t :: NonEmpty (NonEmpty a))
  • type family GroupWith1 (a :: (~>) a b) (a :: NonEmpty a) :: NonEmpty (NonEmpty a) where ...
  • sGroupWith1 :: forall a b (t :: (~>) a b) (t :: NonEmpty a). SEq b => Sing t -> Sing t -> Sing (Apply (Apply GroupWith1Sym0 t) t :: NonEmpty (NonEmpty a))
  • type family GroupAllWith1 (a :: (~>) a b) (a :: NonEmpty a) :: NonEmpty (NonEmpty a) where ...
  • sGroupAllWith1 :: forall a b (t :: (~>) a b) (t :: NonEmpty a). SOrd b => Sing t -> Sing t -> Sing (Apply (Apply GroupAllWith1Sym0 t) t :: NonEmpty (NonEmpty a))
  • type family IsPrefixOf (a :: [a]) (a :: NonEmpty a) :: Bool where ...
  • sIsPrefixOf :: forall a (t :: [a]) (t :: NonEmpty a). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IsPrefixOfSym0 t) t :: Bool)
  • type family Nub (a :: NonEmpty a) :: NonEmpty a where ...
  • sNub :: forall a (t :: NonEmpty a). SEq a => Sing t -> Sing (Apply NubSym0 t :: NonEmpty a)
  • type family NubBy (a :: (~>) a ((~>) a Bool)) (a :: NonEmpty a) :: NonEmpty a where ...
  • sNubBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply NubBySym0 t) t :: NonEmpty a)
  • type family (a :: NonEmpty a) !! (a :: Nat) :: a where ...
  • (%!!) :: forall a (t :: NonEmpty a) (t :: Nat). Sing t -> Sing t -> Sing (Apply (Apply (!!@#@$) t) t :: a)
  • type family Zip (a :: NonEmpty a) (a :: NonEmpty b) :: NonEmpty (a, b) where ...
  • sZip :: forall a b (t :: NonEmpty a) (t :: NonEmpty b). Sing t -> Sing t -> Sing (Apply (Apply ZipSym0 t) t :: NonEmpty (a, b))
  • type family ZipWith (a :: (~>) a ((~>) b c)) (a :: NonEmpty a) (a :: NonEmpty b) :: NonEmpty c where ...
  • sZipWith :: forall a b c (t :: (~>) a ((~>) b c)) (t :: NonEmpty a) (t :: NonEmpty b). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ZipWithSym0 t) t) t :: NonEmpty c)
  • type family Unzip (a :: NonEmpty (a, b)) :: (NonEmpty a, NonEmpty b) where ...
  • sUnzip :: forall a b (t :: NonEmpty (a, b)). Sing t -> Sing (Apply UnzipSym0 t :: (NonEmpty a, NonEmpty b))
  • type family FromList (a :: [a]) :: NonEmpty a where ...
  • sFromList :: forall a (t :: [a]). Sing t -> Sing (Apply FromListSym0 t :: NonEmpty a)
  • type family ToList (a :: NonEmpty a) :: [a] where ...
  • sToList :: forall a (t :: NonEmpty a). Sing t -> Sing (Apply ToListSym0 t :: [a])
  • type family NonEmpty_ (a :: [a]) :: Maybe (NonEmpty a) where ...
  • sNonEmpty_ :: forall a (t :: [a]). Sing t -> Sing (Apply NonEmpty_Sym0 t :: Maybe (NonEmpty a))
  • type family Xor (a :: NonEmpty Bool) :: Bool where ...
  • sXor :: forall (t :: NonEmpty Bool). Sing t -> Sing (Apply XorSym0 t :: Bool)
  • data (:|@#@$) :: forall (a6989586621679059393 :: Type). (~>) a6989586621679059393 ((~>) [a6989586621679059393] (NonEmpty (a6989586621679059393 :: Type)))
  • data (:|@#@$$) (t6989586621679310995 :: a6989586621679059393 :: Type) :: (~>) [a6989586621679059393] (NonEmpty (a6989586621679059393 :: Type))
  • type (:|@#@$$$) (t6989586621679310995 :: a6989586621679059393) (t6989586621679310996 :: [a6989586621679059393]) = '(:|) t6989586621679310995 t6989586621679310996
  • data MapSym0 :: forall a6989586621681159673 b6989586621681159674. (~>) ((~>) a6989586621681159673 b6989586621681159674) ((~>) (NonEmpty a6989586621681159673) (NonEmpty b6989586621681159674))
  • data MapSym1 (a6989586621681161287 :: (~>) a6989586621681159673 b6989586621681159674) :: (~>) (NonEmpty a6989586621681159673) (NonEmpty b6989586621681159674)
  • type MapSym2 (a6989586621681161287 :: (~>) a6989586621681159673 b6989586621681159674) (a6989586621681161288 :: NonEmpty a6989586621681159673) = Map a6989586621681161287 a6989586621681161288
  • data IntersperseSym0 :: forall a6989586621681159663. (~>) a6989586621681159663 ((~>) (NonEmpty a6989586621681159663) (NonEmpty a6989586621681159663))
  • data IntersperseSym1 (a6989586621681161223 :: a6989586621681159663) :: (~>) (NonEmpty a6989586621681159663) (NonEmpty a6989586621681159663)
  • type IntersperseSym2 (a6989586621681161223 :: a6989586621681159663) (a6989586621681161224 :: NonEmpty a6989586621681159663) = Intersperse a6989586621681161223 a6989586621681161224
  • data ScanlSym0 :: forall b6989586621681159668 a6989586621681159669. (~>) ((~>) b6989586621681159668 ((~>) a6989586621681159669 b6989586621681159668)) ((~>) b6989586621681159668 ((~>) [a6989586621681159669] (NonEmpty b6989586621681159668)))
  • data ScanlSym1 (a6989586621681161258 :: (~>) b6989586621681159668 ((~>) a6989586621681159669 b6989586621681159668)) :: (~>) b6989586621681159668 ((~>) [a6989586621681159669] (NonEmpty b6989586621681159668))
  • data ScanlSym2 (a6989586621681161258 :: (~>) b6989586621681159668 ((~>) a6989586621681159669 b6989586621681159668)) (a6989586621681161259 :: b6989586621681159668) :: (~>) [a6989586621681159669] (NonEmpty b6989586621681159668)
  • type ScanlSym3 (a6989586621681161258 :: (~>) b6989586621681159668 ((~>) a6989586621681159669 b6989586621681159668)) (a6989586621681161259 :: b6989586621681159668) (a6989586621681161260 :: [a6989586621681159669]) = Scanl a6989586621681161258 a6989586621681161259 a6989586621681161260
  • data ScanrSym0 :: forall a6989586621681159666 b6989586621681159667. (~>) ((~>) a6989586621681159666 ((~>) b6989586621681159667 b6989586621681159667)) ((~>) b6989586621681159667 ((~>) [a6989586621681159666] (NonEmpty b6989586621681159667)))
  • data ScanrSym1 (a6989586621681161247 :: (~>) a6989586621681159666 ((~>) b6989586621681159667 b6989586621681159667)) :: (~>) b6989586621681159667 ((~>) [a6989586621681159666] (NonEmpty b6989586621681159667))
  • data ScanrSym2 (a6989586621681161247 :: (~>) a6989586621681159666 ((~>) b6989586621681159667 b6989586621681159667)) (a6989586621681161248 :: b6989586621681159667) :: (~>) [a6989586621681159666] (NonEmpty b6989586621681159667)
  • type ScanrSym3 (a6989586621681161247 :: (~>) a6989586621681159666 ((~>) b6989586621681159667 b6989586621681159667)) (a6989586621681161248 :: b6989586621681159667) (a6989586621681161249 :: [a6989586621681159666]) = Scanr a6989586621681161247 a6989586621681161248 a6989586621681161249
  • data Scanl1Sym0 :: forall a6989586621681159665. (~>) ((~>) a6989586621681159665 ((~>) a6989586621681159665 a6989586621681159665)) ((~>) (NonEmpty a6989586621681159665) (NonEmpty a6989586621681159665))
  • data Scanl1Sym1 (a6989586621681161240 :: (~>) a6989586621681159665 ((~>) a6989586621681159665 a6989586621681159665)) :: (~>) (NonEmpty a6989586621681159665) (NonEmpty a6989586621681159665)
  • type Scanl1Sym2 (a6989586621681161240 :: (~>) a6989586621681159665 ((~>) a6989586621681159665 a6989586621681159665)) (a6989586621681161241 :: NonEmpty a6989586621681159665) = Scanl1 a6989586621681161240 a6989586621681161241
  • data Scanr1Sym0 :: forall a6989586621681159664. (~>) ((~>) a6989586621681159664 ((~>) a6989586621681159664 a6989586621681159664)) ((~>) (NonEmpty a6989586621681159664) (NonEmpty a6989586621681159664))
  • data Scanr1Sym1 (a6989586621681161233 :: (~>) a6989586621681159664 ((~>) a6989586621681159664 a6989586621681159664)) :: (~>) (NonEmpty a6989586621681159664) (NonEmpty a6989586621681159664)
  • type Scanr1Sym2 (a6989586621681161233 :: (~>) a6989586621681159664 ((~>) a6989586621681159664 a6989586621681159664)) (a6989586621681161234 :: NonEmpty a6989586621681159664) = Scanr1 a6989586621681161233 a6989586621681161234
  • data TransposeSym0 :: forall a6989586621681159629. (~>) (NonEmpty (NonEmpty a6989586621681159629)) (NonEmpty (NonEmpty a6989586621681159629))
  • type TransposeSym1 (a6989586621681160928 :: NonEmpty (NonEmpty a6989586621681159629)) = Transpose a6989586621681160928
  • data SortBySym0 :: forall a6989586621681159628. (~>) ((~>) a6989586621681159628 ((~>) a6989586621681159628 Ordering)) ((~>) (NonEmpty a6989586621681159628) (NonEmpty a6989586621681159628))
  • data SortBySym1 (a6989586621681160918 :: (~>) a6989586621681159628 ((~>) a6989586621681159628 Ordering)) :: (~>) (NonEmpty a6989586621681159628) (NonEmpty a6989586621681159628)
  • type SortBySym2 (a6989586621681160918 :: (~>) a6989586621681159628 ((~>) a6989586621681159628 Ordering)) (a6989586621681160919 :: NonEmpty a6989586621681159628) = SortBy a6989586621681160918 a6989586621681160919
  • data SortWithSym0 :: forall a6989586621681159627 o6989586621681159626. (~>) ((~>) a6989586621681159627 o6989586621681159626) ((~>) (NonEmpty a6989586621681159627) (NonEmpty a6989586621681159627))
  • data SortWithSym1 (a6989586621681160912 :: (~>) a6989586621681159627 o6989586621681159626) :: (~>) (NonEmpty a6989586621681159627) (NonEmpty a6989586621681159627)
  • type SortWithSym2 (a6989586621681160912 :: (~>) a6989586621681159627 o6989586621681159626) (a6989586621681160913 :: NonEmpty a6989586621681159627) = SortWith a6989586621681160912 a6989586621681160913
  • data LengthSym0 :: forall a6989586621681159692. (~>) (NonEmpty a6989586621681159692) Nat
  • type LengthSym1 (a6989586621681161411 :: NonEmpty a6989586621681159692) = Length a6989586621681161411
  • data HeadSym0 :: forall a6989586621681159685. (~>) (NonEmpty a6989586621681159685) a6989586621681159685
  • type HeadSym1 (a6989586621681161343 :: NonEmpty a6989586621681159685) = Head a6989586621681161343
  • data TailSym0 :: forall a6989586621681159684. (~>) (NonEmpty a6989586621681159684) [a6989586621681159684]
  • type TailSym1 (a6989586621681161340 :: NonEmpty a6989586621681159684) = Tail a6989586621681161340
  • data LastSym0 :: forall a6989586621681159683. (~>) (NonEmpty a6989586621681159683) a6989586621681159683
  • type LastSym1 (a6989586621681161336 :: NonEmpty a6989586621681159683) = Last a6989586621681161336
  • data InitSym0 :: forall a6989586621681159682. (~>) (NonEmpty a6989586621681159682) [a6989586621681159682]
  • type InitSym1 (a6989586621681161332 :: NonEmpty a6989586621681159682) = Init a6989586621681161332
  • data (<|@#@$) :: forall a6989586621681159681. (~>) a6989586621681159681 ((~>) (NonEmpty a6989586621681159681) (NonEmpty a6989586621681159681))
  • data (<|@#@$$) (a6989586621681161325 :: a6989586621681159681) :: (~>) (NonEmpty a6989586621681159681) (NonEmpty a6989586621681159681)
  • type (<|@#@$$$) (a6989586621681161325 :: a6989586621681159681) (a6989586621681161326 :: NonEmpty a6989586621681159681) = (<|) a6989586621681161325 a6989586621681161326
  • data ConsSym0 :: forall a6989586621681159680. (~>) a6989586621681159680 ((~>) (NonEmpty a6989586621681159680) (NonEmpty a6989586621681159680))
  • data ConsSym1 (a6989586621681161319 :: a6989586621681159680) :: (~>) (NonEmpty a6989586621681159680) (NonEmpty a6989586621681159680)
  • type ConsSym2 (a6989586621681161319 :: a6989586621681159680) (a6989586621681161320 :: NonEmpty a6989586621681159680) = Cons a6989586621681161319 a6989586621681161320
  • data UnconsSym0 :: forall a6989586621681159688. (~>) (NonEmpty a6989586621681159688) (a6989586621681159688, Maybe (NonEmpty a6989586621681159688))
  • type UnconsSym1 (a6989586621681161375 :: NonEmpty a6989586621681159688) = Uncons a6989586621681161375
  • data UnfoldrSym0 :: forall a6989586621681159686 b6989586621681159687. (~>) ((~>) a6989586621681159686 (b6989586621681159687, Maybe a6989586621681159686)) ((~>) a6989586621681159686 (NonEmpty b6989586621681159687))
  • data UnfoldrSym1 (a6989586621681161346 :: (~>) a6989586621681159686 (b6989586621681159687, Maybe a6989586621681159686)) :: (~>) a6989586621681159686 (NonEmpty b6989586621681159687)
  • type UnfoldrSym2 (a6989586621681161346 :: (~>) a6989586621681159686 (b6989586621681159687, Maybe a6989586621681159686)) (a6989586621681161347 :: a6989586621681159686) = Unfoldr a6989586621681161346 a6989586621681161347
  • data SortSym0 :: forall a6989586621681159679. (~>) (NonEmpty a6989586621681159679) (NonEmpty a6989586621681159679)
  • type SortSym1 (a6989586621681161312 :: NonEmpty a6989586621681159679) = Sort a6989586621681161312
  • data ReverseSym0 :: forall a6989586621681159662. (~>) (NonEmpty a6989586621681159662) (NonEmpty a6989586621681159662)
  • type ReverseSym1 (a6989586621681161220 :: NonEmpty a6989586621681159662) = Reverse a6989586621681161220
  • data InitsSym0 :: forall a6989586621681159672. (~>) [a6989586621681159672] (NonEmpty [a6989586621681159672])
  • type InitsSym1 (a6989586621681161284 :: [a6989586621681159672]) = Inits a6989586621681161284
  • data TailsSym0 :: forall a6989586621681159671. (~>) [a6989586621681159671] (NonEmpty [a6989586621681159671])
  • type TailsSym1 (a6989586621681161279 :: [a6989586621681159671]) = Tails a6989586621681161279
  • data UnfoldSym0 :: forall a6989586621681159690 b6989586621681159691. (~>) ((~>) a6989586621681159690 (b6989586621681159691, Maybe a6989586621681159690)) ((~>) a6989586621681159690 (NonEmpty b6989586621681159691))
  • data UnfoldSym1 (a6989586621681161383 :: (~>) a6989586621681159690 (b6989586621681159691, Maybe a6989586621681159690)) :: (~>) a6989586621681159690 (NonEmpty b6989586621681159691)
  • data InsertSym0 :: forall a6989586621681159670. (~>) a6989586621681159670 ((~>) [a6989586621681159670] (NonEmpty a6989586621681159670))
  • data InsertSym1 (a6989586621681161269 :: a6989586621681159670) :: (~>) [a6989586621681159670] (NonEmpty a6989586621681159670)
  • type InsertSym2 (a6989586621681161269 :: a6989586621681159670) (a6989586621681161270 :: [a6989586621681159670]) = Insert a6989586621681161269 a6989586621681161270
  • data TakeSym0 :: forall a6989586621681159661. (~>) Nat ((~>) (NonEmpty a6989586621681159661) [a6989586621681159661])
  • data TakeSym1 (a6989586621681161210 :: Nat) :: forall a6989586621681159661. (~>) (NonEmpty a6989586621681159661) [a6989586621681159661]
  • type TakeSym2 (a6989586621681161210 :: Nat) (a6989586621681161211 :: NonEmpty a6989586621681159661) = Take a6989586621681161210 a6989586621681161211
  • data DropSym0 :: forall a6989586621681159660. (~>) Nat ((~>) (NonEmpty a6989586621681159660) [a6989586621681159660])
  • data DropSym1 (a6989586621681161202 :: Nat) :: forall a6989586621681159660. (~>) (NonEmpty a6989586621681159660) [a6989586621681159660]
  • type DropSym2 (a6989586621681161202 :: Nat) (a6989586621681161203 :: NonEmpty a6989586621681159660) = Drop a6989586621681161202 a6989586621681161203
  • data SplitAtSym0 :: forall a6989586621681159659. (~>) Nat ((~>) (NonEmpty a6989586621681159659) ([a6989586621681159659], [a6989586621681159659]))
  • data SplitAtSym1 (a6989586621681161194 :: Nat) :: forall a6989586621681159659. (~>) (NonEmpty a6989586621681159659) ([a6989586621681159659], [a6989586621681159659])
  • type SplitAtSym2 (a6989586621681161194 :: Nat) (a6989586621681161195 :: NonEmpty a6989586621681159659) = SplitAt a6989586621681161194 a6989586621681161195
  • data TakeWhileSym0 :: forall a6989586621681159658. (~>) ((~>) a6989586621681159658 Bool) ((~>) (NonEmpty a6989586621681159658) [a6989586621681159658])
  • data TakeWhileSym1 (a6989586621681161186 :: (~>) a6989586621681159658 Bool) :: (~>) (NonEmpty a6989586621681159658) [a6989586621681159658]
  • type TakeWhileSym2 (a6989586621681161186 :: (~>) a6989586621681159658 Bool) (a6989586621681161187 :: NonEmpty a6989586621681159658) = TakeWhile a6989586621681161186 a6989586621681161187
  • data DropWhileSym0 :: forall a6989586621681159657. (~>) ((~>) a6989586621681159657 Bool) ((~>) (NonEmpty a6989586621681159657) [a6989586621681159657])
  • data DropWhileSym1 (a6989586621681161178 :: (~>) a6989586621681159657 Bool) :: (~>) (NonEmpty a6989586621681159657) [a6989586621681159657]
  • type DropWhileSym2 (a6989586621681161178 :: (~>) a6989586621681159657 Bool) (a6989586621681161179 :: NonEmpty a6989586621681159657) = DropWhile a6989586621681161178 a6989586621681161179
  • data SpanSym0 :: forall a6989586621681159656. (~>) ((~>) a6989586621681159656 Bool) ((~>) (NonEmpty a6989586621681159656) ([a6989586621681159656], [a6989586621681159656]))
  • data SpanSym1 (a6989586621681161170 :: (~>) a6989586621681159656 Bool) :: (~>) (NonEmpty a6989586621681159656) ([a6989586621681159656], [a6989586621681159656])
  • type SpanSym2 (a6989586621681161170 :: (~>) a6989586621681159656 Bool) (a6989586621681161171 :: NonEmpty a6989586621681159656) = Span a6989586621681161170 a6989586621681161171
  • data BreakSym0 :: forall a6989586621681159655. (~>) ((~>) a6989586621681159655 Bool) ((~>) (NonEmpty a6989586621681159655) ([a6989586621681159655], [a6989586621681159655]))
  • data BreakSym1 (a6989586621681161162 :: (~>) a6989586621681159655 Bool) :: (~>) (NonEmpty a6989586621681159655) ([a6989586621681159655], [a6989586621681159655])
  • type BreakSym2 (a6989586621681161162 :: (~>) a6989586621681159655 Bool) (a6989586621681161163 :: NonEmpty a6989586621681159655) = Break a6989586621681161162 a6989586621681161163
  • data FilterSym0 :: forall a6989586621681159654. (~>) ((~>) a6989586621681159654 Bool) ((~>) (NonEmpty a6989586621681159654) [a6989586621681159654])
  • data FilterSym1 (a6989586621681161154 :: (~>) a6989586621681159654 Bool) :: (~>) (NonEmpty a6989586621681159654) [a6989586621681159654]
  • type FilterSym2 (a6989586621681161154 :: (~>) a6989586621681159654 Bool) (a6989586621681161155 :: NonEmpty a6989586621681159654) = Filter a6989586621681161154 a6989586621681161155
  • data PartitionSym0 :: forall a6989586621681159653. (~>) ((~>) a6989586621681159653 Bool) ((~>) (NonEmpty a6989586621681159653) ([a6989586621681159653], [a6989586621681159653]))
  • data PartitionSym1 (a6989586621681161146 :: (~>) a6989586621681159653 Bool) :: (~>) (NonEmpty a6989586621681159653) ([a6989586621681159653], [a6989586621681159653])
  • type PartitionSym2 (a6989586621681161146 :: (~>) a6989586621681159653 Bool) (a6989586621681161147 :: NonEmpty a6989586621681159653) = Partition a6989586621681161146 a6989586621681161147
  • data GroupSym0 :: forall a6989586621681159652. (~>) [a6989586621681159652] [NonEmpty a6989586621681159652]
  • type GroupSym1 (a6989586621681161143 :: [a6989586621681159652]) = Group a6989586621681161143
  • data GroupBySym0 :: forall a6989586621681159651. (~>) ((~>) a6989586621681159651 ((~>) a6989586621681159651 Bool)) ((~>) [a6989586621681159651] [NonEmpty a6989586621681159651])
  • data GroupBySym1 (a6989586621681161093 :: (~>) a6989586621681159651 ((~>) a6989586621681159651 Bool)) :: (~>) [a6989586621681159651] [NonEmpty a6989586621681159651]
  • type GroupBySym2 (a6989586621681161093 :: (~>) a6989586621681159651 ((~>) a6989586621681159651 Bool)) (a6989586621681161094 :: [a6989586621681159651]) = GroupBy a6989586621681161093 a6989586621681161094
  • data GroupWithSym0 :: forall a6989586621681159650 b6989586621681159649. (~>) ((~>) a6989586621681159650 b6989586621681159649) ((~>) [a6989586621681159650] [NonEmpty a6989586621681159650])
  • data GroupWithSym1 (a6989586621681161085 :: (~>) a6989586621681159650 b6989586621681159649) :: (~>) [a6989586621681159650] [NonEmpty a6989586621681159650]
  • type GroupWithSym2 (a6989586621681161085 :: (~>) a6989586621681159650 b6989586621681159649) (a6989586621681161086 :: [a6989586621681159650]) = GroupWith a6989586621681161085 a6989586621681161086
  • data GroupAllWithSym0 :: forall a6989586621681159648 b6989586621681159647. (~>) ((~>) a6989586621681159648 b6989586621681159647) ((~>) [a6989586621681159648] [NonEmpty a6989586621681159648])
  • data GroupAllWithSym1 (a6989586621681161077 :: (~>) a6989586621681159648 b6989586621681159647) :: (~>) [a6989586621681159648] [NonEmpty a6989586621681159648]
  • type GroupAllWithSym2 (a6989586621681161077 :: (~>) a6989586621681159648 b6989586621681159647) (a6989586621681161078 :: [a6989586621681159648]) = GroupAllWith a6989586621681161077 a6989586621681161078
  • data Group1Sym0 :: forall a6989586621681159646. (~>) (NonEmpty a6989586621681159646) (NonEmpty (NonEmpty a6989586621681159646))
  • type Group1Sym1 (a6989586621681161074 :: NonEmpty a6989586621681159646) = Group1 a6989586621681161074
  • data GroupBy1Sym0 :: forall a6989586621681159645. (~>) ((~>) a6989586621681159645 ((~>) a6989586621681159645 Bool)) ((~>) (NonEmpty a6989586621681159645) (NonEmpty (NonEmpty a6989586621681159645)))
  • data GroupBy1Sym1 (a6989586621681161041 :: (~>) a6989586621681159645 ((~>) a6989586621681159645 Bool)) :: (~>) (NonEmpty a6989586621681159645) (NonEmpty (NonEmpty a6989586621681159645))
  • type GroupBy1Sym2 (a6989586621681161041 :: (~>) a6989586621681159645 ((~>) a6989586621681159645 Bool)) (a6989586621681161042 :: NonEmpty a6989586621681159645) = GroupBy1 a6989586621681161041 a6989586621681161042
  • data GroupWith1Sym0 :: forall a6989586621681159644 b6989586621681159643. (~>) ((~>) a6989586621681159644 b6989586621681159643) ((~>) (NonEmpty a6989586621681159644) (NonEmpty (NonEmpty a6989586621681159644)))
  • data GroupWith1Sym1 (a6989586621681161033 :: (~>) a6989586621681159644 b6989586621681159643) :: (~>) (NonEmpty a6989586621681159644) (NonEmpty (NonEmpty a6989586621681159644))
  • type GroupWith1Sym2 (a6989586621681161033 :: (~>) a6989586621681159644 b6989586621681159643) (a6989586621681161034 :: NonEmpty a6989586621681159644) = GroupWith1 a6989586621681161033 a6989586621681161034
  • data GroupAllWith1Sym0 :: forall a6989586621681159642 b6989586621681159641. (~>) ((~>) a6989586621681159642 b6989586621681159641) ((~>) (NonEmpty a6989586621681159642) (NonEmpty (NonEmpty a6989586621681159642)))
  • data GroupAllWith1Sym1 (a6989586621681161025 :: (~>) a6989586621681159642 b6989586621681159641) :: (~>) (NonEmpty a6989586621681159642) (NonEmpty (NonEmpty a6989586621681159642))
  • type GroupAllWith1Sym2 (a6989586621681161025 :: (~>) a6989586621681159642 b6989586621681159641) (a6989586621681161026 :: NonEmpty a6989586621681159642) = GroupAllWith1 a6989586621681161025 a6989586621681161026
  • data IsPrefixOfSym0 :: forall a6989586621681159640. (~>) [a6989586621681159640] ((~>) (NonEmpty a6989586621681159640) Bool)
  • data IsPrefixOfSym1 (a6989586621681161017 :: [a6989586621681159640]) :: (~>) (NonEmpty a6989586621681159640) Bool
  • type IsPrefixOfSym2 (a6989586621681161017 :: [a6989586621681159640]) (a6989586621681161018 :: NonEmpty a6989586621681159640) = IsPrefixOf a6989586621681161017 a6989586621681161018
  • data NubSym0 :: forall a6989586621681159631. (~>) (NonEmpty a6989586621681159631) (NonEmpty a6989586621681159631)
  • type NubSym1 (a6989586621681160948 :: NonEmpty a6989586621681159631) = Nub a6989586621681160948
  • data NubBySym0 :: forall a6989586621681159630. (~>) ((~>) a6989586621681159630 ((~>) a6989586621681159630 Bool)) ((~>) (NonEmpty a6989586621681159630) (NonEmpty a6989586621681159630))
  • data NubBySym1 (a6989586621681160931 :: (~>) a6989586621681159630 ((~>) a6989586621681159630 Bool)) :: (~>) (NonEmpty a6989586621681159630) (NonEmpty a6989586621681159630)
  • type NubBySym2 (a6989586621681160931 :: (~>) a6989586621681159630 ((~>) a6989586621681159630 Bool)) (a6989586621681160932 :: NonEmpty a6989586621681159630) = NubBy a6989586621681160931 a6989586621681160932
  • data (!!@#@$) :: forall a6989586621681159639. (~>) (NonEmpty a6989586621681159639) ((~>) Nat a6989586621681159639)
  • data (!!@#@$$) (a6989586621681160999 :: NonEmpty a6989586621681159639) :: (~>) Nat a6989586621681159639
  • type (!!@#@$$$) (a6989586621681160999 :: NonEmpty a6989586621681159639) (a6989586621681161000 :: Nat) = (!!) a6989586621681160999 a6989586621681161000
  • data ZipSym0 :: forall a6989586621681159637 b6989586621681159638. (~>) (NonEmpty a6989586621681159637) ((~>) (NonEmpty b6989586621681159638) (NonEmpty (a6989586621681159637, b6989586621681159638)))
  • data ZipSym1 (a6989586621681160991 :: NonEmpty a6989586621681159637) :: forall b6989586621681159638. (~>) (NonEmpty b6989586621681159638) (NonEmpty (a6989586621681159637, b6989586621681159638))
  • type ZipSym2 (a6989586621681160991 :: NonEmpty a6989586621681159637) (a6989586621681160992 :: NonEmpty b6989586621681159638) = Zip a6989586621681160991 a6989586621681160992
  • data ZipWithSym0 :: forall a6989586621681159634 b6989586621681159635 c6989586621681159636. (~>) ((~>) a6989586621681159634 ((~>) b6989586621681159635 c6989586621681159636)) ((~>) (NonEmpty a6989586621681159634) ((~>) (NonEmpty b6989586621681159635) (NonEmpty c6989586621681159636)))
  • data ZipWithSym1 (a6989586621681160980 :: (~>) a6989586621681159634 ((~>) b6989586621681159635 c6989586621681159636)) :: (~>) (NonEmpty a6989586621681159634) ((~>) (NonEmpty b6989586621681159635) (NonEmpty c6989586621681159636))
  • data ZipWithSym2 (a6989586621681160980 :: (~>) a6989586621681159634 ((~>) b6989586621681159635 c6989586621681159636)) (a6989586621681160981 :: NonEmpty a6989586621681159634) :: (~>) (NonEmpty b6989586621681159635) (NonEmpty c6989586621681159636)
  • type ZipWithSym3 (a6989586621681160980 :: (~>) a6989586621681159634 ((~>) b6989586621681159635 c6989586621681159636)) (a6989586621681160981 :: NonEmpty a6989586621681159634) (a6989586621681160982 :: NonEmpty b6989586621681159635) = ZipWith a6989586621681160980 a6989586621681160981 a6989586621681160982
  • data UnzipSym0 :: forall a6989586621681159632 b6989586621681159633. (~>) (NonEmpty (a6989586621681159632, b6989586621681159633)) (NonEmpty a6989586621681159632, NonEmpty b6989586621681159633)
  • type UnzipSym1 (a6989586621681160951 :: NonEmpty (a6989586621681159632, b6989586621681159633)) = Unzip a6989586621681160951
  • data FromListSym0 :: forall a6989586621681159678. (~>) [a6989586621681159678] (NonEmpty a6989586621681159678)
  • type FromListSym1 (a6989586621681161306 :: [a6989586621681159678]) = FromList a6989586621681161306
  • data ToListSym0 :: forall a6989586621681159677. (~>) (NonEmpty a6989586621681159677) [a6989586621681159677]
  • type ToListSym1 (a6989586621681161302 :: NonEmpty a6989586621681159677) = ToList a6989586621681161302
  • data NonEmpty_Sym0 :: forall a6989586621681159689. (~>) [a6989586621681159689] (Maybe (NonEmpty a6989586621681159689))
  • type NonEmpty_Sym1 (a6989586621681161379 :: [a6989586621681159689]) = NonEmpty_ a6989586621681161379
  • data XorSym0 :: (~>) (NonEmpty Bool) Bool
  • type XorSym1 (a6989586621681161398 :: NonEmpty Bool) = Xor a6989586621681161398

The NonEmpty singleton

type family Sing :: k -> Type Source #

The singleton kind-indexed type family.

Instances

Instances details
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Sing = SBool
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Sing Source # 
Instance details

Defined in Data.Singletons.TypeLits.Internal

type Sing = SNat
type Sing Source # 
Instance details

Defined in Data.Singletons.TypeLits.Internal

type Sing = SSymbol
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Sing = STuple0
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Sing = SVoid
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Sing = SAll
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Sing = SAny
type Sing Source # 
Instance details

Defined in Data.Singletons.TypeError

type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Sing = SList :: [a] -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Sing = SMaybe :: Maybe a -> Type
type Sing Source #

A choice of singleton for the kind TYPE rep (for some RuntimeRep rep), an instantiation of which is the famous kind Type.

Conceivably, one could generalize this instance to `Sing @k` for any kind k, and remove all other Sing instances. We don't adopt this design, however, since it is far more convenient in practice to work with explicit singleton values than TypeReps (for instance, TypeReps are more difficult to pattern match on, and require extra runtime checks).

We cannot produce explicit singleton values for everything in TYPE rep, however, since it is an open kind, so we reach for TypeRep in this one particular case.

Instance details

Defined in Data.Singletons.TypeRepTYPE

type Sing = TypeRep :: TYPE rep -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Sing = SNonEmpty :: NonEmpty a -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Sing = SDown :: Down a -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Sing = SIdentity :: Identity a -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Sing = SFirst :: First a -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Sing = SLast :: Last a -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Sing = SMax :: Max a -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Sing = SMin :: Min a -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Sing = SOption :: Option a -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Sing = SWrappedMonoid :: WrappedMonoid m -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Sing = SDual :: Dual a -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Sing = SProduct :: Product a -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Sing = SSum :: Sum a -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

type Sing = SFirst :: First a -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

type Sing = SLast :: Last a -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Sing = SEither :: Either a b -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Sing = STuple2 :: (a, b) -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Internal

type Sing = SLambda :: (k1 ~> k2) -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Internal

type Sing = SWrappedSing :: WrappedSing a -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Sing = SArg :: Arg a b -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Sigma

type Sing = SSigma :: Sigma s t -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Sing = STuple3 :: (a, b, c) -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Const

type Sing = SConst :: Const a b -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Sing = STuple4 :: (a, b, c, d) -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Sing = STuple5 :: (a, b, c, d, e) -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Sing = STuple6 :: (a, b, c, d, e, f) -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Sing = STuple7 :: (a, b, c, d, e, f, g) -> Type

data SNonEmpty :: forall a. NonEmpty a -> Type where Source #

Constructors

(:%|) :: forall a (n :: a) (n :: [a]). (Sing (n :: a)) -> (Sing (n :: [a])) -> SNonEmpty ('(:|) n n) infixr 5 

Instances

Instances details
(SDecide a, SDecide [a]) => TestCoercion (SNonEmpty :: NonEmpty a -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

Methods

testCoercion :: forall (a0 :: k) (b :: k). SNonEmpty a0 -> SNonEmpty b -> Maybe (Coercion a0 b)

(SDecide a, SDecide [a]) => TestEquality (SNonEmpty :: NonEmpty a -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

Methods

testEquality :: forall (a0 :: k) (b :: k). SNonEmpty a0 -> SNonEmpty b -> Maybe (a0 :~: b)

(ShowSing a, ShowSing [a]) => Show (SNonEmpty z) 
Instance details

Defined in Data.Singletons.ShowSing

Methods

showsPrec :: Int -> SNonEmpty z -> ShowS

show :: SNonEmpty z -> String

showList :: [SNonEmpty z] -> ShowS

Non-empty stream transformations

type family Map (a :: (~>) a b) (a :: NonEmpty a) :: NonEmpty b where ... Source #

Equations

Map f ('(:|) a as) = Apply (Apply (:|@#@$) (Apply f a)) (Apply (Apply ListmapSym0 f) as) 

sMap :: forall a b (t :: (~>) a b) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply MapSym0 t) t :: NonEmpty b) Source #

type family Intersperse (a :: a) (a :: NonEmpty a) :: NonEmpty a where ... Source #

Equations

Intersperse a ('(:|) b bs) = Apply (Apply (:|@#@$) b) (Case_6989586621681161230 a b bs bs) 

sIntersperse :: forall a (t :: a) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply IntersperseSym0 t) t :: NonEmpty a) Source #

type family Scanl (a :: (~>) b ((~>) a b)) (a :: b) (a :: [a]) :: NonEmpty b where ... Source #

Equations

Scanl f z a_6989586621681161264 = Apply (Apply (Apply (.@#@$) FromListSym0) (Apply (Apply ListscanlSym0 f) z)) a_6989586621681161264 

sScanl :: forall b a (t :: (~>) b ((~>) a b)) (t :: b) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ScanlSym0 t) t) t :: NonEmpty b) Source #

type family Scanr (a :: (~>) a ((~>) b b)) (a :: b) (a :: [a]) :: NonEmpty b where ... Source #

Equations

Scanr f z a_6989586621681161253 = Apply (Apply (Apply (.@#@$) FromListSym0) (Apply (Apply ListscanrSym0 f) z)) a_6989586621681161253 

sScanr :: forall a b (t :: (~>) a ((~>) b b)) (t :: b) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ScanrSym0 t) t) t :: NonEmpty b) Source #

type family Scanl1 (a :: (~>) a ((~>) a a)) (a :: NonEmpty a) :: NonEmpty a where ... Source #

Equations

Scanl1 f ('(:|) a as) = Apply FromListSym0 (Apply (Apply (Apply ListscanlSym0 f) a) as) 

sScanl1 :: forall a (t :: (~>) a ((~>) a a)) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply Scanl1Sym0 t) t :: NonEmpty a) Source #

type family Scanr1 (a :: (~>) a ((~>) a a)) (a :: NonEmpty a) :: NonEmpty a where ... Source #

Equations

Scanr1 f ('(:|) a as) = Apply FromListSym0 (Apply (Apply Listscanr1Sym0 f) (Apply (Apply (:@#@$) a) as)) 

sScanr1 :: forall a (t :: (~>) a ((~>) a a)) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply Scanr1Sym0 t) t :: NonEmpty a) Source #

type family Transpose (a :: NonEmpty (NonEmpty a)) :: NonEmpty (NonEmpty a) where ... Source #

Equations

Transpose a_6989586621681160926 = Apply (Apply (Apply (.@#@$) (Apply FmapSym0 FromListSym0)) (Apply (Apply (.@#@$) FromListSym0) (Apply (Apply (.@#@$) ListtransposeSym0) (Apply (Apply (.@#@$) ToListSym0) (Apply FmapSym0 ToListSym0))))) a_6989586621681160926 

sTranspose :: forall a (t :: NonEmpty (NonEmpty a)). Sing t -> Sing (Apply TransposeSym0 t :: NonEmpty (NonEmpty a)) Source #

type family SortBy (a :: (~>) a ((~>) a Ordering)) (a :: NonEmpty a) :: NonEmpty a where ... Source #

Equations

SortBy f a_6989586621681160922 = Apply (Apply LiftSym0 (Apply ListsortBySym0 f)) a_6989586621681160922 

sSortBy :: forall a (t :: (~>) a ((~>) a Ordering)) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply SortBySym0 t) t :: NonEmpty a) Source #

type family SortWith (a :: (~>) a o) (a :: NonEmpty a) :: NonEmpty a where ... Source #

Equations

SortWith a_6989586621681160908 a_6989586621681160910 = Apply (Apply (Apply (Apply (.@#@$) SortBySym0) ComparingSym0) a_6989586621681160908) a_6989586621681160910 

sSortWith :: forall a o (t :: (~>) a o) (t :: NonEmpty a). SOrd o => Sing t -> Sing t -> Sing (Apply (Apply SortWithSym0 t) t :: NonEmpty a) Source #

type family Length (a :: NonEmpty a) :: Nat where ... Source #

Equations

Length ('(:|) _ xs) = Apply (Apply (+@#@$) (FromInteger 1)) (Apply ListlengthSym0 xs) 

sLength :: forall a (t :: NonEmpty a). Sing t -> Sing (Apply LengthSym0 t :: Nat) Source #

type family Head (a :: NonEmpty a) :: a where ... Source #

Equations

Head ('(:|) a _) = a 

sHead :: forall a (t :: NonEmpty a). Sing t -> Sing (Apply HeadSym0 t :: a) Source #

type family Tail (a :: NonEmpty a) :: [a] where ... Source #

Equations

Tail ('(:|) _ as) = as 

sTail :: forall a (t :: NonEmpty a). Sing t -> Sing (Apply TailSym0 t :: [a]) Source #

type family Last (a :: NonEmpty a) :: a where ... Source #

Equations

Last ('(:|) a as) = Apply ListlastSym0 (Apply (Apply (:@#@$) a) as) 

sLast :: forall a (t :: NonEmpty a). Sing t -> Sing (Apply LastSym0 t :: a) Source #

type family Init (a :: NonEmpty a) :: [a] where ... Source #

Equations

Init ('(:|) a as) = Apply ListinitSym0 (Apply (Apply (:@#@$) a) as) 

sInit :: forall a (t :: NonEmpty a). Sing t -> Sing (Apply InitSym0 t :: [a]) Source #

type family (a :: a) <| (a :: NonEmpty a) :: NonEmpty a where ... Source #

Equations

a <| ('(:|) b bs) = Apply (Apply (:|@#@$) a) (Apply (Apply (:@#@$) b) bs) 

(%<|) :: forall a (t :: a) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply (<|@#@$) t) t :: NonEmpty a) Source #

type family Cons (a :: a) (a :: NonEmpty a) :: NonEmpty a where ... Source #

Equations

Cons a_6989586621681161315 a_6989586621681161317 = Apply (Apply (<|@#@$) a_6989586621681161315) a_6989586621681161317 

sCons :: forall a (t :: a) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply ConsSym0 t) t :: NonEmpty a) Source #

type family Uncons (a :: NonEmpty a) :: (a, Maybe (NonEmpty a)) where ... Source #

Equations

Uncons ('(:|) a as) = Apply (Apply Tuple2Sym0 a) (Apply NonEmpty_Sym0 as) 

sUncons :: forall a (t :: NonEmpty a). Sing t -> Sing (Apply UnconsSym0 t :: (a, Maybe (NonEmpty a))) Source #

type family Unfoldr (a :: (~>) a (b, Maybe a)) (a :: a) :: NonEmpty b where ... Source #

Equations

Unfoldr f a = Case_6989586621681161370 f a (Let6989586621681161367Scrutinee_6989586621681159867Sym2 f a) 

sUnfoldr :: forall a b (t :: (~>) a (b, Maybe a)) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply UnfoldrSym0 t) t :: NonEmpty b) Source #

type family Sort (a :: NonEmpty a) :: NonEmpty a where ... Source #

Equations

Sort a_6989586621681161310 = Apply (Apply LiftSym0 ListsortSym0) a_6989586621681161310 

sSort :: forall a (t :: NonEmpty a). SOrd a => Sing t -> Sing (Apply SortSym0 t :: NonEmpty a) Source #

type family Reverse (a :: NonEmpty a) :: NonEmpty a where ... Source #

Equations

Reverse a_6989586621681161218 = Apply (Apply LiftSym0 ListreverseSym0) a_6989586621681161218 

sReverse :: forall a (t :: NonEmpty a). Sing t -> Sing (Apply ReverseSym0 t :: NonEmpty a) Source #

type family Inits (a :: [a]) :: NonEmpty [a] where ... Source #

Equations

Inits a_6989586621681161282 = Apply (Apply (Apply (.@#@$) FromListSym0) ListinitsSym0) a_6989586621681161282 

sInits :: forall a (t :: [a]). Sing t -> Sing (Apply InitsSym0 t :: NonEmpty [a]) Source #

type family Tails (a :: [a]) :: NonEmpty [a] where ... Source #

Equations

Tails a_6989586621681161277 = Apply (Apply (Apply (.@#@$) FromListSym0) ListtailsSym0) a_6989586621681161277 

sTails :: forall a (t :: [a]). Sing t -> Sing (Apply TailsSym0 t :: NonEmpty [a]) Source #

type family Unfold (a :: (~>) a (b, Maybe a)) (a :: a) :: NonEmpty b where ... Source #

Equations

Unfold f a = Case_6989586621681161392 f a (Let6989586621681161389Scrutinee_6989586621681159857Sym2 f a) 

sUnfold :: forall a b (t :: (~>) a (b, Maybe a)) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply UnfoldSym0 t) t :: NonEmpty b) Source #

type family Insert (a :: a) (a :: [a]) :: NonEmpty a where ... Source #

Equations

Insert a a_6989586621681161273 = Apply (Apply (Apply (.@#@$) FromListSym0) (Apply ListinsertSym0 a)) a_6989586621681161273 

sInsert :: forall a (t :: a) (t :: [a]). SOrd a => Sing t -> Sing t -> Sing (Apply (Apply InsertSym0 t) t :: NonEmpty a) Source #

type family Take (a :: Nat) (a :: NonEmpty a) :: [a] where ... Source #

Equations

Take n a_6989586621681161214 = Apply (Apply (Apply (.@#@$) (Apply ListtakeSym0 n)) ToListSym0) a_6989586621681161214 

sTake :: forall a (t :: Nat) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply TakeSym0 t) t :: [a]) Source #

type family Drop (a :: Nat) (a :: NonEmpty a) :: [a] where ... Source #

Equations

Drop n a_6989586621681161206 = Apply (Apply (Apply (.@#@$) (Apply ListdropSym0 n)) ToListSym0) a_6989586621681161206 

sDrop :: forall a (t :: Nat) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply DropSym0 t) t :: [a]) Source #

type family SplitAt (a :: Nat) (a :: NonEmpty a) :: ([a], [a]) where ... Source #

Equations

SplitAt n a_6989586621681161198 = Apply (Apply (Apply (.@#@$) (Apply ListsplitAtSym0 n)) ToListSym0) a_6989586621681161198 

sSplitAt :: forall a (t :: Nat) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply SplitAtSym0 t) t :: ([a], [a])) Source #

type family TakeWhile (a :: (~>) a Bool) (a :: NonEmpty a) :: [a] where ... Source #

Equations

TakeWhile p a_6989586621681161190 = Apply (Apply (Apply (.@#@$) (Apply ListtakeWhileSym0 p)) ToListSym0) a_6989586621681161190 

sTakeWhile :: forall a (t :: (~>) a Bool) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply TakeWhileSym0 t) t :: [a]) Source #

type family DropWhile (a :: (~>) a Bool) (a :: NonEmpty a) :: [a] where ... Source #

Equations

DropWhile p a_6989586621681161182 = Apply (Apply (Apply (.@#@$) (Apply ListdropWhileSym0 p)) ToListSym0) a_6989586621681161182 

sDropWhile :: forall a (t :: (~>) a Bool) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply DropWhileSym0 t) t :: [a]) Source #

type family Span (a :: (~>) a Bool) (a :: NonEmpty a) :: ([a], [a]) where ... Source #

Equations

Span p a_6989586621681161174 = Apply (Apply (Apply (.@#@$) (Apply ListspanSym0 p)) ToListSym0) a_6989586621681161174 

sSpan :: forall a (t :: (~>) a Bool) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply SpanSym0 t) t :: ([a], [a])) Source #

type family Break (a :: (~>) a Bool) (a :: NonEmpty a) :: ([a], [a]) where ... Source #

Equations

Break p a_6989586621681161166 = Apply (Apply SpanSym0 (Apply (Apply (.@#@$) NotSym0) p)) a_6989586621681161166 

sBreak :: forall a (t :: (~>) a Bool) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply BreakSym0 t) t :: ([a], [a])) Source #

type family Filter (a :: (~>) a Bool) (a :: NonEmpty a) :: [a] where ... Source #

Equations

Filter p a_6989586621681161158 = Apply (Apply (Apply (.@#@$) (Apply ListfilterSym0 p)) ToListSym0) a_6989586621681161158 

sFilter :: forall a (t :: (~>) a Bool) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply FilterSym0 t) t :: [a]) Source #

type family Partition (a :: (~>) a Bool) (a :: NonEmpty a) :: ([a], [a]) where ... Source #

Equations

Partition p a_6989586621681161150 = Apply (Apply (Apply (.@#@$) (Apply ListpartitionSym0 p)) ToListSym0) a_6989586621681161150 

sPartition :: forall a (t :: (~>) a Bool) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply PartitionSym0 t) t :: ([a], [a])) Source #

type family Group (a :: [a]) :: [NonEmpty a] where ... Source #

Equations

Group a_6989586621681161141 = Apply (Apply GroupBySym0 (==@#@$)) a_6989586621681161141 

sGroup :: forall a (t :: [a]). SEq a => Sing t -> Sing (Apply GroupSym0 t :: [NonEmpty a]) Source #

type family GroupBy (a :: (~>) a ((~>) a Bool)) (a :: [a]) :: [NonEmpty a] where ... Source #

Equations

GroupBy eq0 a_6989586621681161097 = Apply (Apply (Let6989586621681161101GoSym2 eq0 a_6989586621681161097) eq0) a_6989586621681161097 

sGroupBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply GroupBySym0 t) t :: [NonEmpty a]) Source #

type family GroupWith (a :: (~>) a b) (a :: [a]) :: [NonEmpty a] where ... Source #

Equations

GroupWith f a_6989586621681161089 = Apply (Apply GroupBySym0 (Apply (Apply OnSym0 (==@#@$)) f)) a_6989586621681161089 

sGroupWith :: forall a b (t :: (~>) a b) (t :: [a]). SEq b => Sing t -> Sing t -> Sing (Apply (Apply GroupWithSym0 t) t :: [NonEmpty a]) Source #

type family GroupAllWith (a :: (~>) a b) (a :: [a]) :: [NonEmpty a] where ... Source #

Equations

GroupAllWith f a_6989586621681161081 = Apply (Apply (Apply (.@#@$) (Apply GroupWithSym0 f)) (Apply ListsortBySym0 (Apply (Apply OnSym0 CompareSym0) f))) a_6989586621681161081 

sGroupAllWith :: forall a b (t :: (~>) a b) (t :: [a]). SOrd b => Sing t -> Sing t -> Sing (Apply (Apply GroupAllWithSym0 t) t :: [NonEmpty a]) Source #

type family Group1 (a :: NonEmpty a) :: NonEmpty (NonEmpty a) where ... Source #

Equations

Group1 a_6989586621681161072 = Apply (Apply GroupBy1Sym0 (==@#@$)) a_6989586621681161072 

sGroup1 :: forall a (t :: NonEmpty a). SEq a => Sing t -> Sing (Apply Group1Sym0 t :: NonEmpty (NonEmpty a)) Source #

type family GroupBy1 (a :: (~>) a ((~>) a Bool)) (a :: NonEmpty a) :: NonEmpty (NonEmpty a) where ... Source #

Equations

GroupBy1 eq ('(:|) x xs) = Apply (Apply (:|@#@$) (Apply (Apply (:|@#@$) x) (Let6989586621681161048YsSym3 eq x xs))) (Apply (Apply GroupBySym0 eq) (Let6989586621681161048ZsSym3 eq x xs)) 

sGroupBy1 :: forall a (t :: (~>) a ((~>) a Bool)) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply GroupBy1Sym0 t) t :: NonEmpty (NonEmpty a)) Source #

type family GroupWith1 (a :: (~>) a b) (a :: NonEmpty a) :: NonEmpty (NonEmpty a) where ... Source #

Equations

GroupWith1 f a_6989586621681161037 = Apply (Apply GroupBy1Sym0 (Apply (Apply OnSym0 (==@#@$)) f)) a_6989586621681161037 

sGroupWith1 :: forall a b (t :: (~>) a b) (t :: NonEmpty a). SEq b => Sing t -> Sing t -> Sing (Apply (Apply GroupWith1Sym0 t) t :: NonEmpty (NonEmpty a)) Source #

type family GroupAllWith1 (a :: (~>) a b) (a :: NonEmpty a) :: NonEmpty (NonEmpty a) where ... Source #

Equations

GroupAllWith1 f a_6989586621681161029 = Apply (Apply (Apply (.@#@$) (Apply GroupWith1Sym0 f)) (Apply SortWithSym0 f)) a_6989586621681161029 

sGroupAllWith1 :: forall a b (t :: (~>) a b) (t :: NonEmpty a). SOrd b => Sing t -> Sing t -> Sing (Apply (Apply GroupAllWith1Sym0 t) t :: NonEmpty (NonEmpty a)) Source #

type family IsPrefixOf (a :: [a]) (a :: NonEmpty a) :: Bool where ... Source #

Equations

IsPrefixOf '[] _ = TrueSym0 
IsPrefixOf ('(:) y ys) ('(:|) x xs) = Apply (Apply (&&@#@$) (Apply (Apply (==@#@$) y) x)) (Apply (Apply ListisPrefixOfSym0 ys) xs) 

sIsPrefixOf :: forall a (t :: [a]) (t :: NonEmpty a). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IsPrefixOfSym0 t) t :: Bool) Source #

type family Nub (a :: NonEmpty a) :: NonEmpty a where ... Source #

Equations

Nub a_6989586621681160946 = Apply (Apply NubBySym0 (==@#@$)) a_6989586621681160946 

sNub :: forall a (t :: NonEmpty a). SEq a => Sing t -> Sing (Apply NubSym0 t :: NonEmpty a) Source #

type family NubBy (a :: (~>) a ((~>) a Bool)) (a :: NonEmpty a) :: NonEmpty a where ... Source #

Equations

NubBy eq ('(:|) a as) = Apply (Apply (:|@#@$) a) (Apply (Apply ListnubBySym0 eq) (Apply (Apply ListfilterSym0 (Apply (Apply (Apply Lambda_6989586621681160938Sym0 eq) a) as)) as)) 

sNubBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply NubBySym0 t) t :: NonEmpty a) Source #

type family (a :: NonEmpty a) !! (a :: Nat) :: a where ... Source #

Equations

arg_6989586621681159879 !! arg_6989586621681159881 = Case_6989586621681161005 arg_6989586621681159879 arg_6989586621681159881 (Apply (Apply Tuple2Sym0 arg_6989586621681159879) arg_6989586621681159881) 

(%!!) :: forall a (t :: NonEmpty a) (t :: Nat). Sing t -> Sing t -> Sing (Apply (Apply (!!@#@$) t) t :: a) Source #

type family Zip (a :: NonEmpty a) (a :: NonEmpty b) :: NonEmpty (a, b) where ... Source #

Equations

Zip ('(:|) x xs) ('(:|) y ys) = Apply (Apply (:|@#@$) (Apply (Apply Tuple2Sym0 x) y)) (Apply (Apply ListzipSym0 xs) ys) 

sZip :: forall a b (t :: NonEmpty a) (t :: NonEmpty b). Sing t -> Sing t -> Sing (Apply (Apply ZipSym0 t) t :: NonEmpty (a, b)) Source #

type family ZipWith (a :: (~>) a ((~>) b c)) (a :: NonEmpty a) (a :: NonEmpty b) :: NonEmpty c where ... Source #

Equations

ZipWith f ('(:|) x xs) ('(:|) y ys) = Apply (Apply (:|@#@$) (Apply (Apply f x) y)) (Apply (Apply (Apply ListzipWithSym0 f) xs) ys) 

sZipWith :: forall a b c (t :: (~>) a ((~>) b c)) (t :: NonEmpty a) (t :: NonEmpty b). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ZipWithSym0 t) t) t :: NonEmpty c) Source #

type family Unzip (a :: NonEmpty (a, b)) :: (NonEmpty a, NonEmpty b) where ... Source #

Equations

Unzip ('(:|) '(a, b) asbs) = Apply (Apply Tuple2Sym0 (Apply (Apply (:|@#@$) a) (Let6989586621681160956AsSym3 a b asbs))) (Apply (Apply (:|@#@$) b) (Let6989586621681160956BsSym3 a b asbs)) 

sUnzip :: forall a b (t :: NonEmpty (a, b)). Sing t -> Sing (Apply UnzipSym0 t :: (NonEmpty a, NonEmpty b)) Source #

type family FromList (a :: [a]) :: NonEmpty a where ... Source #

Equations

FromList ('(:) a as) = Apply (Apply (:|@#@$) a) as 
FromList '[] = Apply ErrorSym0 "NonEmpty.fromList: empty list" 

sFromList :: forall a (t :: [a]). Sing t -> Sing (Apply FromListSym0 t :: NonEmpty a) Source #

type family ToList (a :: NonEmpty a) :: [a] where ... Source #

Equations

ToList ('(:|) a as) = Apply (Apply (:@#@$) a) as 

sToList :: forall a (t :: NonEmpty a). Sing t -> Sing (Apply ToListSym0 t :: [a]) Source #

type family NonEmpty_ (a :: [a]) :: Maybe (NonEmpty a) where ... Source #

Equations

NonEmpty_ '[] = NothingSym0 
NonEmpty_ ('(:) a as) = Apply JustSym0 (Apply (Apply (:|@#@$) a) as) 

sNonEmpty_ :: forall a (t :: [a]). Sing t -> Sing (Apply NonEmpty_Sym0 t :: Maybe (NonEmpty a)) Source #

type family Xor (a :: NonEmpty Bool) :: Bool where ... Source #

Equations

Xor ('(:|) x xs) = Apply (Apply (Apply FoldrSym0 (Let6989586621681161402Xor'Sym2 x xs)) x) xs 

sXor :: forall (t :: NonEmpty Bool). Sing t -> Sing (Apply XorSym0 t :: Bool) Source #

Defunctionalization symbols

data (:|@#@$) :: forall (a6989586621679059393 :: Type). (~>) a6989586621679059393 ((~>) [a6989586621679059393] (NonEmpty (a6989586621679059393 :: Type))) infixr 5 Source #

Instances

Instances details
SingI ((:|@#@$) :: TyFun a ([a] ~> NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

SuppressUnusedWarnings ((:|@#@$) :: TyFun a6989586621679059393 ([a6989586621679059393] ~> NonEmpty a6989586621679059393) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Apply ((:|@#@$) :: TyFun a6989586621679059393 ([a6989586621679059393] ~> NonEmpty a6989586621679059393) -> Type) (t6989586621679310995 :: a6989586621679059393) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Apply ((:|@#@$) :: TyFun a6989586621679059393 ([a6989586621679059393] ~> NonEmpty a6989586621679059393) -> Type) (t6989586621679310995 :: a6989586621679059393) = (:|@#@$$) t6989586621679310995

data (:|@#@$$) (t6989586621679310995 :: a6989586621679059393 :: Type) :: (~>) [a6989586621679059393] (NonEmpty (a6989586621679059393 :: Type)) infixr 5 Source #

Instances

Instances details
SingI d => SingI ((:|@#@$$) d :: TyFun [a] (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

Methods

sing :: Sing ((:|@#@$$) d) Source #

SuppressUnusedWarnings ((:|@#@$$) t6989586621679310995 :: TyFun [a6989586621679059393] (NonEmpty a6989586621679059393) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Apply ((:|@#@$$) t6989586621679310995 :: TyFun [a] (NonEmpty a) -> Type) (t6989586621679310996 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Apply ((:|@#@$$) t6989586621679310995 :: TyFun [a] (NonEmpty a) -> Type) (t6989586621679310996 :: [a]) = t6989586621679310995 :| t6989586621679310996

type (:|@#@$$$) (t6989586621679310995 :: a6989586621679059393) (t6989586621679310996 :: [a6989586621679059393]) = '(:|) t6989586621679310995 t6989586621679310996 Source #

data MapSym0 :: forall a6989586621681159673 b6989586621681159674. (~>) ((~>) a6989586621681159673 b6989586621681159674) ((~>) (NonEmpty a6989586621681159673) (NonEmpty b6989586621681159674)) Source #

Instances

Instances details
SingI (MapSym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (MapSym0 :: TyFun (a6989586621681159673 ~> b6989586621681159674) (NonEmpty a6989586621681159673 ~> NonEmpty b6989586621681159674) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (MapSym0 :: TyFun (a6989586621681159673 ~> b6989586621681159674) (NonEmpty a6989586621681159673 ~> NonEmpty b6989586621681159674) -> Type) (a6989586621681161287 :: a6989586621681159673 ~> b6989586621681159674) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (MapSym0 :: TyFun (a6989586621681159673 ~> b6989586621681159674) (NonEmpty a6989586621681159673 ~> NonEmpty b6989586621681159674) -> Type) (a6989586621681161287 :: a6989586621681159673 ~> b6989586621681159674) = MapSym1 a6989586621681161287

data MapSym1 (a6989586621681161287 :: (~>) a6989586621681159673 b6989586621681159674) :: (~>) (NonEmpty a6989586621681159673) (NonEmpty b6989586621681159674) Source #

Instances

Instances details
SingI d => SingI (MapSym1 d :: TyFun (NonEmpty a) (NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

Methods

sing :: Sing (MapSym1 d) Source #

SuppressUnusedWarnings (MapSym1 a6989586621681161287 :: TyFun (NonEmpty a6989586621681159673) (NonEmpty b6989586621681159674) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (MapSym1 a6989586621681161287 :: TyFun (NonEmpty a) (NonEmpty b) -> Type) (a6989586621681161288 :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (MapSym1 a6989586621681161287 :: TyFun (NonEmpty a) (NonEmpty b) -> Type) (a6989586621681161288 :: NonEmpty a) = Map a6989586621681161287 a6989586621681161288

type MapSym2 (a6989586621681161287 :: (~>) a6989586621681159673 b6989586621681159674) (a6989586621681161288 :: NonEmpty a6989586621681159673) = Map a6989586621681161287 a6989586621681161288 Source #

data IntersperseSym0 :: forall a6989586621681159663. (~>) a6989586621681159663 ((~>) (NonEmpty a6989586621681159663) (NonEmpty a6989586621681159663)) Source #

Instances

Instances details
SingI (IntersperseSym0 :: TyFun a (NonEmpty a ~> NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (IntersperseSym0 :: TyFun a6989586621681159663 (NonEmpty a6989586621681159663 ~> NonEmpty a6989586621681159663) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (IntersperseSym0 :: TyFun a6989586621681159663 (NonEmpty a6989586621681159663 ~> NonEmpty a6989586621681159663) -> Type) (a6989586621681161223 :: a6989586621681159663) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (IntersperseSym0 :: TyFun a6989586621681159663 (NonEmpty a6989586621681159663 ~> NonEmpty a6989586621681159663) -> Type) (a6989586621681161223 :: a6989586621681159663) = IntersperseSym1 a6989586621681161223

data IntersperseSym1 (a6989586621681161223 :: a6989586621681159663) :: (~>) (NonEmpty a6989586621681159663) (NonEmpty a6989586621681159663) Source #

Instances

Instances details
SingI d => SingI (IntersperseSym1 d :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (IntersperseSym1 a6989586621681161223 :: TyFun (NonEmpty a6989586621681159663) (NonEmpty a6989586621681159663) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (IntersperseSym1 a6989586621681161223 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681161224 :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (IntersperseSym1 a6989586621681161223 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681161224 :: NonEmpty a) = Intersperse a6989586621681161223 a6989586621681161224

type IntersperseSym2 (a6989586621681161223 :: a6989586621681159663) (a6989586621681161224 :: NonEmpty a6989586621681159663) = Intersperse a6989586621681161223 a6989586621681161224 Source #

data ScanlSym0 :: forall b6989586621681159668 a6989586621681159669. (~>) ((~>) b6989586621681159668 ((~>) a6989586621681159669 b6989586621681159668)) ((~>) b6989586621681159668 ((~>) [a6989586621681159669] (NonEmpty b6989586621681159668))) Source #

Instances

Instances details
SingI (ScanlSym0 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> NonEmpty b)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (ScanlSym0 :: TyFun (b6989586621681159668 ~> (a6989586621681159669 ~> b6989586621681159668)) (b6989586621681159668 ~> ([a6989586621681159669] ~> NonEmpty b6989586621681159668)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ScanlSym0 :: TyFun (b6989586621681159668 ~> (a6989586621681159669 ~> b6989586621681159668)) (b6989586621681159668 ~> ([a6989586621681159669] ~> NonEmpty b6989586621681159668)) -> Type) (a6989586621681161258 :: b6989586621681159668 ~> (a6989586621681159669 ~> b6989586621681159668)) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ScanlSym0 :: TyFun (b6989586621681159668 ~> (a6989586621681159669 ~> b6989586621681159668)) (b6989586621681159668 ~> ([a6989586621681159669] ~> NonEmpty b6989586621681159668)) -> Type) (a6989586621681161258 :: b6989586621681159668 ~> (a6989586621681159669 ~> b6989586621681159668)) = ScanlSym1 a6989586621681161258

data ScanlSym1 (a6989586621681161258 :: (~>) b6989586621681159668 ((~>) a6989586621681159669 b6989586621681159668)) :: (~>) b6989586621681159668 ((~>) [a6989586621681159669] (NonEmpty b6989586621681159668)) Source #

Instances

Instances details
SingI d => SingI (ScanlSym1 d :: TyFun b ([a] ~> NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

Methods

sing :: Sing (ScanlSym1 d) Source #

SuppressUnusedWarnings (ScanlSym1 a6989586621681161258 :: TyFun b6989586621681159668 ([a6989586621681159669] ~> NonEmpty b6989586621681159668) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ScanlSym1 a6989586621681161258 :: TyFun b6989586621681159668 ([a6989586621681159669] ~> NonEmpty b6989586621681159668) -> Type) (a6989586621681161259 :: b6989586621681159668) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ScanlSym1 a6989586621681161258 :: TyFun b6989586621681159668 ([a6989586621681159669] ~> NonEmpty b6989586621681159668) -> Type) (a6989586621681161259 :: b6989586621681159668) = ScanlSym2 a6989586621681161258 a6989586621681161259

data ScanlSym2 (a6989586621681161258 :: (~>) b6989586621681159668 ((~>) a6989586621681159669 b6989586621681159668)) (a6989586621681161259 :: b6989586621681159668) :: (~>) [a6989586621681159669] (NonEmpty b6989586621681159668) Source #

Instances

Instances details
(SingI d1, SingI d2) => SingI (ScanlSym2 d1 d2 :: TyFun [a] (NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

Methods

sing :: Sing (ScanlSym2 d1 d2) Source #

SuppressUnusedWarnings (ScanlSym2 a6989586621681161259 a6989586621681161258 :: TyFun [a6989586621681159669] (NonEmpty b6989586621681159668) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ScanlSym2 a6989586621681161259 a6989586621681161258 :: TyFun [a] (NonEmpty b) -> Type) (a6989586621681161260 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ScanlSym2 a6989586621681161259 a6989586621681161258 :: TyFun [a] (NonEmpty b) -> Type) (a6989586621681161260 :: [a]) = Scanl a6989586621681161259 a6989586621681161258 a6989586621681161260

type ScanlSym3 (a6989586621681161258 :: (~>) b6989586621681159668 ((~>) a6989586621681159669 b6989586621681159668)) (a6989586621681161259 :: b6989586621681159668) (a6989586621681161260 :: [a6989586621681159669]) = Scanl a6989586621681161258 a6989586621681161259 a6989586621681161260 Source #

data ScanrSym0 :: forall a6989586621681159666 b6989586621681159667. (~>) ((~>) a6989586621681159666 ((~>) b6989586621681159667 b6989586621681159667)) ((~>) b6989586621681159667 ((~>) [a6989586621681159666] (NonEmpty b6989586621681159667))) Source #

Instances

Instances details
SingI (ScanrSym0 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> NonEmpty b)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (ScanrSym0 :: TyFun (a6989586621681159666 ~> (b6989586621681159667 ~> b6989586621681159667)) (b6989586621681159667 ~> ([a6989586621681159666] ~> NonEmpty b6989586621681159667)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ScanrSym0 :: TyFun (a6989586621681159666 ~> (b6989586621681159667 ~> b6989586621681159667)) (b6989586621681159667 ~> ([a6989586621681159666] ~> NonEmpty b6989586621681159667)) -> Type) (a6989586621681161247 :: a6989586621681159666 ~> (b6989586621681159667 ~> b6989586621681159667)) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ScanrSym0 :: TyFun (a6989586621681159666 ~> (b6989586621681159667 ~> b6989586621681159667)) (b6989586621681159667 ~> ([a6989586621681159666] ~> NonEmpty b6989586621681159667)) -> Type) (a6989586621681161247 :: a6989586621681159666 ~> (b6989586621681159667 ~> b6989586621681159667)) = ScanrSym1 a6989586621681161247

data ScanrSym1 (a6989586621681161247 :: (~>) a6989586621681159666 ((~>) b6989586621681159667 b6989586621681159667)) :: (~>) b6989586621681159667 ((~>) [a6989586621681159666] (NonEmpty b6989586621681159667)) Source #

Instances

Instances details
SingI d => SingI (ScanrSym1 d :: TyFun b ([a] ~> NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

Methods

sing :: Sing (ScanrSym1 d) Source #

SuppressUnusedWarnings (ScanrSym1 a6989586621681161247 :: TyFun b6989586621681159667 ([a6989586621681159666] ~> NonEmpty b6989586621681159667) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ScanrSym1 a6989586621681161247 :: TyFun b6989586621681159667 ([a6989586621681159666] ~> NonEmpty b6989586621681159667) -> Type) (a6989586621681161248 :: b6989586621681159667) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ScanrSym1 a6989586621681161247 :: TyFun b6989586621681159667 ([a6989586621681159666] ~> NonEmpty b6989586621681159667) -> Type) (a6989586621681161248 :: b6989586621681159667) = ScanrSym2 a6989586621681161247 a6989586621681161248

data ScanrSym2 (a6989586621681161247 :: (~>) a6989586621681159666 ((~>) b6989586621681159667 b6989586621681159667)) (a6989586621681161248 :: b6989586621681159667) :: (~>) [a6989586621681159666] (NonEmpty b6989586621681159667) Source #

Instances

Instances details
(SingI d1, SingI d2) => SingI (ScanrSym2 d1 d2 :: TyFun [a] (NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

Methods

sing :: Sing (ScanrSym2 d1 d2) Source #

SuppressUnusedWarnings (ScanrSym2 a6989586621681161248 a6989586621681161247 :: TyFun [a6989586621681159666] (NonEmpty b6989586621681159667) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ScanrSym2 a6989586621681161248 a6989586621681161247 :: TyFun [a] (NonEmpty b) -> Type) (a6989586621681161249 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ScanrSym2 a6989586621681161248 a6989586621681161247 :: TyFun [a] (NonEmpty b) -> Type) (a6989586621681161249 :: [a]) = Scanr a6989586621681161248 a6989586621681161247 a6989586621681161249

type ScanrSym3 (a6989586621681161247 :: (~>) a6989586621681159666 ((~>) b6989586621681159667 b6989586621681159667)) (a6989586621681161248 :: b6989586621681159667) (a6989586621681161249 :: [a6989586621681159666]) = Scanr a6989586621681161247 a6989586621681161248 a6989586621681161249 Source #

data Scanl1Sym0 :: forall a6989586621681159665. (~>) ((~>) a6989586621681159665 ((~>) a6989586621681159665 a6989586621681159665)) ((~>) (NonEmpty a6989586621681159665) (NonEmpty a6989586621681159665)) Source #

Instances

Instances details
SingI (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) (NonEmpty a ~> NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (Scanl1Sym0 :: TyFun (a6989586621681159665 ~> (a6989586621681159665 ~> a6989586621681159665)) (NonEmpty a6989586621681159665 ~> NonEmpty a6989586621681159665) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (Scanl1Sym0 :: TyFun (a6989586621681159665 ~> (a6989586621681159665 ~> a6989586621681159665)) (NonEmpty a6989586621681159665 ~> NonEmpty a6989586621681159665) -> Type) (a6989586621681161240 :: a6989586621681159665 ~> (a6989586621681159665 ~> a6989586621681159665)) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (Scanl1Sym0 :: TyFun (a6989586621681159665 ~> (a6989586621681159665 ~> a6989586621681159665)) (NonEmpty a6989586621681159665 ~> NonEmpty a6989586621681159665) -> Type) (a6989586621681161240 :: a6989586621681159665 ~> (a6989586621681159665 ~> a6989586621681159665)) = Scanl1Sym1 a6989586621681161240

data Scanl1Sym1 (a6989586621681161240 :: (~>) a6989586621681159665 ((~>) a6989586621681159665 a6989586621681159665)) :: (~>) (NonEmpty a6989586621681159665) (NonEmpty a6989586621681159665) Source #

Instances

Instances details
SingI d => SingI (Scanl1Sym1 d :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

Methods

sing :: Sing (Scanl1Sym1 d) Source #

SuppressUnusedWarnings (Scanl1Sym1 a6989586621681161240 :: TyFun (NonEmpty a6989586621681159665) (NonEmpty a6989586621681159665) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (Scanl1Sym1 a6989586621681161240 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681161241 :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (Scanl1Sym1 a6989586621681161240 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681161241 :: NonEmpty a) = Scanl1 a6989586621681161240 a6989586621681161241

type Scanl1Sym2 (a6989586621681161240 :: (~>) a6989586621681159665 ((~>) a6989586621681159665 a6989586621681159665)) (a6989586621681161241 :: NonEmpty a6989586621681159665) = Scanl1 a6989586621681161240 a6989586621681161241 Source #

data Scanr1Sym0 :: forall a6989586621681159664. (~>) ((~>) a6989586621681159664 ((~>) a6989586621681159664 a6989586621681159664)) ((~>) (NonEmpty a6989586621681159664) (NonEmpty a6989586621681159664)) Source #

Instances

Instances details
SingI (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) (NonEmpty a ~> NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (Scanr1Sym0 :: TyFun (a6989586621681159664 ~> (a6989586621681159664 ~> a6989586621681159664)) (NonEmpty a6989586621681159664 ~> NonEmpty a6989586621681159664) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (Scanr1Sym0 :: TyFun (a6989586621681159664 ~> (a6989586621681159664 ~> a6989586621681159664)) (NonEmpty a6989586621681159664 ~> NonEmpty a6989586621681159664) -> Type) (a6989586621681161233 :: a6989586621681159664 ~> (a6989586621681159664 ~> a6989586621681159664)) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (Scanr1Sym0 :: TyFun (a6989586621681159664 ~> (a6989586621681159664 ~> a6989586621681159664)) (NonEmpty a6989586621681159664 ~> NonEmpty a6989586621681159664) -> Type) (a6989586621681161233 :: a6989586621681159664 ~> (a6989586621681159664 ~> a6989586621681159664)) = Scanr1Sym1 a6989586621681161233

data Scanr1Sym1 (a6989586621681161233 :: (~>) a6989586621681159664 ((~>) a6989586621681159664 a6989586621681159664)) :: (~>) (NonEmpty a6989586621681159664) (NonEmpty a6989586621681159664) Source #

Instances

Instances details
SingI d => SingI (Scanr1Sym1 d :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

Methods

sing :: Sing (Scanr1Sym1 d) Source #

SuppressUnusedWarnings (Scanr1Sym1 a6989586621681161233 :: TyFun (NonEmpty a6989586621681159664) (NonEmpty a6989586621681159664) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (Scanr1Sym1 a6989586621681161233 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681161234 :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (Scanr1Sym1 a6989586621681161233 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681161234 :: NonEmpty a) = Scanr1 a6989586621681161233 a6989586621681161234

type Scanr1Sym2 (a6989586621681161233 :: (~>) a6989586621681159664 ((~>) a6989586621681159664 a6989586621681159664)) (a6989586621681161234 :: NonEmpty a6989586621681159664) = Scanr1 a6989586621681161233 a6989586621681161234 Source #

data TransposeSym0 :: forall a6989586621681159629. (~>) (NonEmpty (NonEmpty a6989586621681159629)) (NonEmpty (NonEmpty a6989586621681159629)) Source #

Instances

Instances details
SingI (TransposeSym0 :: TyFun (NonEmpty (NonEmpty a)) (NonEmpty (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (TransposeSym0 :: TyFun (NonEmpty (NonEmpty a6989586621681159629)) (NonEmpty (NonEmpty a6989586621681159629)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (TransposeSym0 :: TyFun (NonEmpty (NonEmpty a)) (NonEmpty (NonEmpty a)) -> Type) (a6989586621681160928 :: NonEmpty (NonEmpty a)) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (TransposeSym0 :: TyFun (NonEmpty (NonEmpty a)) (NonEmpty (NonEmpty a)) -> Type) (a6989586621681160928 :: NonEmpty (NonEmpty a)) = Transpose a6989586621681160928

type TransposeSym1 (a6989586621681160928 :: NonEmpty (NonEmpty a6989586621681159629)) = Transpose a6989586621681160928 Source #

data SortBySym0 :: forall a6989586621681159628. (~>) ((~>) a6989586621681159628 ((~>) a6989586621681159628 Ordering)) ((~>) (NonEmpty a6989586621681159628) (NonEmpty a6989586621681159628)) Source #

Instances

Instances details
SingI (SortBySym0 :: TyFun (a ~> (a ~> Ordering)) (NonEmpty a ~> NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (SortBySym0 :: TyFun (a6989586621681159628 ~> (a6989586621681159628 ~> Ordering)) (NonEmpty a6989586621681159628 ~> NonEmpty a6989586621681159628) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (SortBySym0 :: TyFun (a6989586621681159628 ~> (a6989586621681159628 ~> Ordering)) (NonEmpty a6989586621681159628 ~> NonEmpty a6989586621681159628) -> Type) (a6989586621681160918 :: a6989586621681159628 ~> (a6989586621681159628 ~> Ordering)) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (SortBySym0 :: TyFun (a6989586621681159628 ~> (a6989586621681159628 ~> Ordering)) (NonEmpty a6989586621681159628 ~> NonEmpty a6989586621681159628) -> Type) (a6989586621681160918 :: a6989586621681159628 ~> (a6989586621681159628 ~> Ordering)) = SortBySym1 a6989586621681160918

data SortBySym1 (a6989586621681160918 :: (~>) a6989586621681159628 ((~>) a6989586621681159628 Ordering)) :: (~>) (NonEmpty a6989586621681159628) (NonEmpty a6989586621681159628) Source #

Instances

Instances details
SingI d => SingI (SortBySym1 d :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

Methods

sing :: Sing (SortBySym1 d) Source #

SuppressUnusedWarnings (SortBySym1 a6989586621681160918 :: TyFun (NonEmpty a6989586621681159628) (NonEmpty a6989586621681159628) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (SortBySym1 a6989586621681160918 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681160919 :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (SortBySym1 a6989586621681160918 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681160919 :: NonEmpty a) = SortBy a6989586621681160918 a6989586621681160919

type SortBySym2 (a6989586621681160918 :: (~>) a6989586621681159628 ((~>) a6989586621681159628 Ordering)) (a6989586621681160919 :: NonEmpty a6989586621681159628) = SortBy a6989586621681160918 a6989586621681160919 Source #

data SortWithSym0 :: forall a6989586621681159627 o6989586621681159626. (~>) ((~>) a6989586621681159627 o6989586621681159626) ((~>) (NonEmpty a6989586621681159627) (NonEmpty a6989586621681159627)) Source #

Instances

Instances details
SOrd o => SingI (SortWithSym0 :: TyFun (a ~> o) (NonEmpty a ~> NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (SortWithSym0 :: TyFun (a6989586621681159627 ~> o6989586621681159626) (NonEmpty a6989586621681159627 ~> NonEmpty a6989586621681159627) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (SortWithSym0 :: TyFun (a6989586621681159627 ~> o6989586621681159626) (NonEmpty a6989586621681159627 ~> NonEmpty a6989586621681159627) -> Type) (a6989586621681160912 :: a6989586621681159627 ~> o6989586621681159626) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (SortWithSym0 :: TyFun (a6989586621681159627 ~> o6989586621681159626) (NonEmpty a6989586621681159627 ~> NonEmpty a6989586621681159627) -> Type) (a6989586621681160912 :: a6989586621681159627 ~> o6989586621681159626) = SortWithSym1 a6989586621681160912

data SortWithSym1 (a6989586621681160912 :: (~>) a6989586621681159627 o6989586621681159626) :: (~>) (NonEmpty a6989586621681159627) (NonEmpty a6989586621681159627) Source #

Instances

Instances details
(SOrd o, SingI d) => SingI (SortWithSym1 d :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

Methods

sing :: Sing (SortWithSym1 d) Source #

SuppressUnusedWarnings (SortWithSym1 a6989586621681160912 :: TyFun (NonEmpty a6989586621681159627) (NonEmpty a6989586621681159627) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (SortWithSym1 a6989586621681160912 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681160913 :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (SortWithSym1 a6989586621681160912 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681160913 :: NonEmpty a) = SortWith a6989586621681160912 a6989586621681160913

type SortWithSym2 (a6989586621681160912 :: (~>) a6989586621681159627 o6989586621681159626) (a6989586621681160913 :: NonEmpty a6989586621681159627) = SortWith a6989586621681160912 a6989586621681160913 Source #

data LengthSym0 :: forall a6989586621681159692. (~>) (NonEmpty a6989586621681159692) Nat Source #

Instances

Instances details
SingI (LengthSym0 :: TyFun (NonEmpty a) Nat -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (LengthSym0 :: TyFun (NonEmpty a6989586621681159692) Nat -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (LengthSym0 :: TyFun (NonEmpty a) Nat -> Type) (a6989586621681161411 :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (LengthSym0 :: TyFun (NonEmpty a) Nat -> Type) (a6989586621681161411 :: NonEmpty a) = Length a6989586621681161411

type LengthSym1 (a6989586621681161411 :: NonEmpty a6989586621681159692) = Length a6989586621681161411 Source #

data HeadSym0 :: forall a6989586621681159685. (~>) (NonEmpty a6989586621681159685) a6989586621681159685 Source #

Instances

Instances details
SingI (HeadSym0 :: TyFun (NonEmpty a) a -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (HeadSym0 :: TyFun (NonEmpty a6989586621681159685) a6989586621681159685 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (HeadSym0 :: TyFun (NonEmpty a) a -> Type) (a6989586621681161343 :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (HeadSym0 :: TyFun (NonEmpty a) a -> Type) (a6989586621681161343 :: NonEmpty a) = Head a6989586621681161343

type HeadSym1 (a6989586621681161343 :: NonEmpty a6989586621681159685) = Head a6989586621681161343 Source #

data TailSym0 :: forall a6989586621681159684. (~>) (NonEmpty a6989586621681159684) [a6989586621681159684] Source #

Instances

Instances details
SingI (TailSym0 :: TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (TailSym0 :: TyFun (NonEmpty a6989586621681159684) [a6989586621681159684] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (TailSym0 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681161340 :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (TailSym0 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681161340 :: NonEmpty a) = Tail a6989586621681161340

type TailSym1 (a6989586621681161340 :: NonEmpty a6989586621681159684) = Tail a6989586621681161340 Source #

data LastSym0 :: forall a6989586621681159683. (~>) (NonEmpty a6989586621681159683) a6989586621681159683 Source #

Instances

Instances details
SingI (LastSym0 :: TyFun (NonEmpty a) a -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (LastSym0 :: TyFun (NonEmpty a6989586621681159683) a6989586621681159683 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (LastSym0 :: TyFun (NonEmpty a) a -> Type) (a6989586621681161336 :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (LastSym0 :: TyFun (NonEmpty a) a -> Type) (a6989586621681161336 :: NonEmpty a) = Last a6989586621681161336

type LastSym1 (a6989586621681161336 :: NonEmpty a6989586621681159683) = Last a6989586621681161336 Source #

data InitSym0 :: forall a6989586621681159682. (~>) (NonEmpty a6989586621681159682) [a6989586621681159682] Source #

Instances

Instances details
SingI (InitSym0 :: TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (InitSym0 :: TyFun (NonEmpty a6989586621681159682) [a6989586621681159682] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (InitSym0 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681161332 :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (InitSym0 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681161332 :: NonEmpty a) = Init a6989586621681161332

type InitSym1 (a6989586621681161332 :: NonEmpty a6989586621681159682) = Init a6989586621681161332 Source #

data (<|@#@$) :: forall a6989586621681159681. (~>) a6989586621681159681 ((~>) (NonEmpty a6989586621681159681) (NonEmpty a6989586621681159681)) Source #

Instances

Instances details
SingI ((<|@#@$) :: TyFun a (NonEmpty a ~> NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings ((<|@#@$) :: TyFun a6989586621681159681 (NonEmpty a6989586621681159681 ~> NonEmpty a6989586621681159681) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply ((<|@#@$) :: TyFun a6989586621681159681 (NonEmpty a6989586621681159681 ~> NonEmpty a6989586621681159681) -> Type) (a6989586621681161325 :: a6989586621681159681) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply ((<|@#@$) :: TyFun a6989586621681159681 (NonEmpty a6989586621681159681 ~> NonEmpty a6989586621681159681) -> Type) (a6989586621681161325 :: a6989586621681159681) = (<|@#@$$) a6989586621681161325

data (<|@#@$$) (a6989586621681161325 :: a6989586621681159681) :: (~>) (NonEmpty a6989586621681159681) (NonEmpty a6989586621681159681) Source #

Instances

Instances details
SingI d => SingI ((<|@#@$$) d :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

Methods

sing :: Sing ((<|@#@$$) d) Source #

SuppressUnusedWarnings ((<|@#@$$) a6989586621681161325 :: TyFun (NonEmpty a6989586621681159681) (NonEmpty a6989586621681159681) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply ((<|@#@$$) a6989586621681161325 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681161326 :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply ((<|@#@$$) a6989586621681161325 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681161326 :: NonEmpty a) = a6989586621681161325 <| a6989586621681161326

type (<|@#@$$$) (a6989586621681161325 :: a6989586621681159681) (a6989586621681161326 :: NonEmpty a6989586621681159681) = (<|) a6989586621681161325 a6989586621681161326 Source #

data ConsSym0 :: forall a6989586621681159680. (~>) a6989586621681159680 ((~>) (NonEmpty a6989586621681159680) (NonEmpty a6989586621681159680)) Source #

Instances

Instances details
SingI (ConsSym0 :: TyFun a (NonEmpty a ~> NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (ConsSym0 :: TyFun a6989586621681159680 (NonEmpty a6989586621681159680 ~> NonEmpty a6989586621681159680) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ConsSym0 :: TyFun a6989586621681159680 (NonEmpty a6989586621681159680 ~> NonEmpty a6989586621681159680) -> Type) (a6989586621681161319 :: a6989586621681159680) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ConsSym0 :: TyFun a6989586621681159680 (NonEmpty a6989586621681159680 ~> NonEmpty a6989586621681159680) -> Type) (a6989586621681161319 :: a6989586621681159680) = ConsSym1 a6989586621681161319

data ConsSym1 (a6989586621681161319 :: a6989586621681159680) :: (~>) (NonEmpty a6989586621681159680) (NonEmpty a6989586621681159680) Source #

Instances

Instances details
SingI d => SingI (ConsSym1 d :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

Methods

sing :: Sing (ConsSym1 d) Source #

SuppressUnusedWarnings (ConsSym1 a6989586621681161319 :: TyFun (NonEmpty a6989586621681159680) (NonEmpty a6989586621681159680) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ConsSym1 a6989586621681161319 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681161320 :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ConsSym1 a6989586621681161319 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681161320 :: NonEmpty a) = Cons a6989586621681161319 a6989586621681161320

type ConsSym2 (a6989586621681161319 :: a6989586621681159680) (a6989586621681161320 :: NonEmpty a6989586621681159680) = Cons a6989586621681161319 a6989586621681161320 Source #

data UnconsSym0 :: forall a6989586621681159688. (~>) (NonEmpty a6989586621681159688) (a6989586621681159688, Maybe (NonEmpty a6989586621681159688)) Source #

Instances

Instances details
SingI (UnconsSym0 :: TyFun (NonEmpty a) (a, Maybe (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (UnconsSym0 :: TyFun (NonEmpty a6989586621681159688) (a6989586621681159688, Maybe (NonEmpty a6989586621681159688)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (UnconsSym0 :: TyFun (NonEmpty a) (a, Maybe (NonEmpty a)) -> Type) (a6989586621681161375 :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (UnconsSym0 :: TyFun (NonEmpty a) (a, Maybe (NonEmpty a)) -> Type) (a6989586621681161375 :: NonEmpty a) = Uncons a6989586621681161375

type UnconsSym1 (a6989586621681161375 :: NonEmpty a6989586621681159688) = Uncons a6989586621681161375 Source #

data UnfoldrSym0 :: forall a6989586621681159686 b6989586621681159687. (~>) ((~>) a6989586621681159686 (b6989586621681159687, Maybe a6989586621681159686)) ((~>) a6989586621681159686 (NonEmpty b6989586621681159687)) Source #

Instances

Instances details
SingI (UnfoldrSym0 :: TyFun (a ~> (b, Maybe a)) (a ~> NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (UnfoldrSym0 :: TyFun (a6989586621681159686 ~> (b6989586621681159687, Maybe a6989586621681159686)) (a6989586621681159686 ~> NonEmpty b6989586621681159687) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (UnfoldrSym0 :: TyFun (a6989586621681159686 ~> (b6989586621681159687, Maybe a6989586621681159686)) (a6989586621681159686 ~> NonEmpty b6989586621681159687) -> Type) (a6989586621681161346 :: a6989586621681159686 ~> (b6989586621681159687, Maybe a6989586621681159686)) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (UnfoldrSym0 :: TyFun (a6989586621681159686 ~> (b6989586621681159687, Maybe a6989586621681159686)) (a6989586621681159686 ~> NonEmpty b6989586621681159687) -> Type) (a6989586621681161346 :: a6989586621681159686 ~> (b6989586621681159687, Maybe a6989586621681159686)) = UnfoldrSym1 a6989586621681161346

data UnfoldrSym1 (a6989586621681161346 :: (~>) a6989586621681159686 (b6989586621681159687, Maybe a6989586621681159686)) :: (~>) a6989586621681159686 (NonEmpty b6989586621681159687) Source #

Instances

Instances details
SingI d => SingI (UnfoldrSym1 d :: TyFun a (NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

Methods

sing :: Sing (UnfoldrSym1 d) Source #

SuppressUnusedWarnings (UnfoldrSym1 a6989586621681161346 :: TyFun a6989586621681159686 (NonEmpty b6989586621681159687) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (UnfoldrSym1 a6989586621681161346 :: TyFun a (NonEmpty b) -> Type) (a6989586621681161347 :: a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (UnfoldrSym1 a6989586621681161346 :: TyFun a (NonEmpty b) -> Type) (a6989586621681161347 :: a) = Unfoldr a6989586621681161346 a6989586621681161347

type UnfoldrSym2 (a6989586621681161346 :: (~>) a6989586621681159686 (b6989586621681159687, Maybe a6989586621681159686)) (a6989586621681161347 :: a6989586621681159686) = Unfoldr a6989586621681161346 a6989586621681161347 Source #

data SortSym0 :: forall a6989586621681159679. (~>) (NonEmpty a6989586621681159679) (NonEmpty a6989586621681159679) Source #

Instances

Instances details
SOrd a => SingI (SortSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (SortSym0 :: TyFun (NonEmpty a6989586621681159679) (NonEmpty a6989586621681159679) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (SortSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681161312 :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (SortSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681161312 :: NonEmpty a) = Sort a6989586621681161312

type SortSym1 (a6989586621681161312 :: NonEmpty a6989586621681159679) = Sort a6989586621681161312 Source #

data ReverseSym0 :: forall a6989586621681159662. (~>) (NonEmpty a6989586621681159662) (NonEmpty a6989586621681159662) Source #

Instances

Instances details
SingI (ReverseSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (ReverseSym0 :: TyFun (NonEmpty a6989586621681159662) (NonEmpty a6989586621681159662) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ReverseSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681161220 :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ReverseSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681161220 :: NonEmpty a) = Reverse a6989586621681161220

type ReverseSym1 (a6989586621681161220 :: NonEmpty a6989586621681159662) = Reverse a6989586621681161220 Source #

data InitsSym0 :: forall a6989586621681159672. (~>) [a6989586621681159672] (NonEmpty [a6989586621681159672]) Source #

Instances

Instances details
SingI (InitsSym0 :: TyFun [a] (NonEmpty [a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (InitsSym0 :: TyFun [a6989586621681159672] (NonEmpty [a6989586621681159672]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (InitsSym0 :: TyFun [a] (NonEmpty [a]) -> Type) (a6989586621681161284 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (InitsSym0 :: TyFun [a] (NonEmpty [a]) -> Type) (a6989586621681161284 :: [a]) = Inits a6989586621681161284

type InitsSym1 (a6989586621681161284 :: [a6989586621681159672]) = Inits a6989586621681161284 Source #

data TailsSym0 :: forall a6989586621681159671. (~>) [a6989586621681159671] (NonEmpty [a6989586621681159671]) Source #

Instances

Instances details
SingI (TailsSym0 :: TyFun [a] (NonEmpty [a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (TailsSym0 :: TyFun [a6989586621681159671] (NonEmpty [a6989586621681159671]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (TailsSym0 :: TyFun [a] (NonEmpty [a]) -> Type) (a6989586621681161279 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (TailsSym0 :: TyFun [a] (NonEmpty [a]) -> Type) (a6989586621681161279 :: [a]) = Tails a6989586621681161279

type TailsSym1 (a6989586621681161279 :: [a6989586621681159671]) = Tails a6989586621681161279 Source #

data UnfoldSym0 :: forall a6989586621681159690 b6989586621681159691. (~>) ((~>) a6989586621681159690 (b6989586621681159691, Maybe a6989586621681159690)) ((~>) a6989586621681159690 (NonEmpty b6989586621681159691)) Source #

Instances

Instances details
SingI (UnfoldSym0 :: TyFun (a ~> (b, Maybe a)) (a ~> NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (UnfoldSym0 :: TyFun (a6989586621681159690 ~> (b6989586621681159691, Maybe a6989586621681159690)) (a6989586621681159690 ~> NonEmpty b6989586621681159691) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (UnfoldSym0 :: TyFun (a6989586621681159690 ~> (b6989586621681159691, Maybe a6989586621681159690)) (a6989586621681159690 ~> NonEmpty b6989586621681159691) -> Type) (a6989586621681161383 :: a6989586621681159690 ~> (b6989586621681159691, Maybe a6989586621681159690)) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (UnfoldSym0 :: TyFun (a6989586621681159690 ~> (b6989586621681159691, Maybe a6989586621681159690)) (a6989586621681159690 ~> NonEmpty b6989586621681159691) -> Type) (a6989586621681161383 :: a6989586621681159690 ~> (b6989586621681159691, Maybe a6989586621681159690)) = UnfoldSym1 a6989586621681161383

data UnfoldSym1 (a6989586621681161383 :: (~>) a6989586621681159690 (b6989586621681159691, Maybe a6989586621681159690)) :: (~>) a6989586621681159690 (NonEmpty b6989586621681159691) Source #

Instances

Instances details
SingI d => SingI (UnfoldSym1 d :: TyFun a (NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

Methods

sing :: Sing (UnfoldSym1 d) Source #

SuppressUnusedWarnings (UnfoldSym1 a6989586621681161383 :: TyFun a6989586621681159690 (NonEmpty b6989586621681159691) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (UnfoldSym1 a6989586621681161383 :: TyFun a (NonEmpty b) -> Type) (a6989586621681161384 :: a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (UnfoldSym1 a6989586621681161383 :: TyFun a (NonEmpty b) -> Type) (a6989586621681161384 :: a) = Unfold a6989586621681161383 a6989586621681161384

data InsertSym0 :: forall a6989586621681159670. (~>) a6989586621681159670 ((~>) [a6989586621681159670] (NonEmpty a6989586621681159670)) Source #

Instances

Instances details
SOrd a => SingI (InsertSym0 :: TyFun a ([a] ~> NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (InsertSym0 :: TyFun a6989586621681159670 ([a6989586621681159670] ~> NonEmpty a6989586621681159670) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (InsertSym0 :: TyFun a6989586621681159670 ([a6989586621681159670] ~> NonEmpty a6989586621681159670) -> Type) (a6989586621681161269 :: a6989586621681159670) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (InsertSym0 :: TyFun a6989586621681159670 ([a6989586621681159670] ~> NonEmpty a6989586621681159670) -> Type) (a6989586621681161269 :: a6989586621681159670) = InsertSym1 a6989586621681161269

data InsertSym1 (a6989586621681161269 :: a6989586621681159670) :: (~>) [a6989586621681159670] (NonEmpty a6989586621681159670) Source #

Instances

Instances details
(SOrd a, SingI d) => SingI (InsertSym1 d :: TyFun [a] (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

Methods

sing :: Sing (InsertSym1 d) Source #

SuppressUnusedWarnings (InsertSym1 a6989586621681161269 :: TyFun [a6989586621681159670] (NonEmpty a6989586621681159670) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (InsertSym1 a6989586621681161269 :: TyFun [a] (NonEmpty a) -> Type) (a6989586621681161270 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (InsertSym1 a6989586621681161269 :: TyFun [a] (NonEmpty a) -> Type) (a6989586621681161270 :: [a]) = Insert a6989586621681161269 a6989586621681161270

type InsertSym2 (a6989586621681161269 :: a6989586621681159670) (a6989586621681161270 :: [a6989586621681159670]) = Insert a6989586621681161269 a6989586621681161270 Source #

data TakeSym0 :: forall a6989586621681159661. (~>) Nat ((~>) (NonEmpty a6989586621681159661) [a6989586621681159661]) Source #

Instances

Instances details
SingI (TakeSym0 :: TyFun Nat (NonEmpty a ~> [a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (TakeSym0 :: TyFun Nat (NonEmpty a6989586621681159661 ~> [a6989586621681159661]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (TakeSym0 :: TyFun Nat (NonEmpty a6989586621681159661 ~> [a6989586621681159661]) -> Type) (a6989586621681161210 :: Nat) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (TakeSym0 :: TyFun Nat (NonEmpty a6989586621681159661 ~> [a6989586621681159661]) -> Type) (a6989586621681161210 :: Nat) = TakeSym1 a6989586621681161210 a6989586621681159661 :: TyFun (NonEmpty a6989586621681159661) [a6989586621681159661] -> Type

data TakeSym1 (a6989586621681161210 :: Nat) :: forall a6989586621681159661. (~>) (NonEmpty a6989586621681159661) [a6989586621681159661] Source #

Instances

Instances details
SingI d => SingI (TakeSym1 d a :: TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

Methods

sing :: Sing (TakeSym1 d a) Source #

SuppressUnusedWarnings (TakeSym1 a6989586621681161210 a6989586621681159661 :: TyFun (NonEmpty a6989586621681159661) [a6989586621681159661] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (TakeSym1 a6989586621681161210 a :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681161211 :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (TakeSym1 a6989586621681161210 a :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681161211 :: NonEmpty a) = Take a6989586621681161210 a6989586621681161211

type TakeSym2 (a6989586621681161210 :: Nat) (a6989586621681161211 :: NonEmpty a6989586621681159661) = Take a6989586621681161210 a6989586621681161211 Source #

data DropSym0 :: forall a6989586621681159660. (~>) Nat ((~>) (NonEmpty a6989586621681159660) [a6989586621681159660]) Source #

Instances

Instances details
SingI (DropSym0 :: TyFun Nat (NonEmpty a ~> [a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (DropSym0 :: TyFun Nat (NonEmpty a6989586621681159660 ~> [a6989586621681159660]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (DropSym0 :: TyFun Nat (NonEmpty a6989586621681159660 ~> [a6989586621681159660]) -> Type) (a6989586621681161202 :: Nat) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (DropSym0 :: TyFun Nat (NonEmpty a6989586621681159660 ~> [a6989586621681159660]) -> Type) (a6989586621681161202 :: Nat) = DropSym1 a6989586621681161202 a6989586621681159660 :: TyFun (NonEmpty a6989586621681159660) [a6989586621681159660] -> Type

data DropSym1 (a6989586621681161202 :: Nat) :: forall a6989586621681159660. (~>) (NonEmpty a6989586621681159660) [a6989586621681159660] Source #

Instances

Instances details
SingI d => SingI (DropSym1 d a :: TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

Methods

sing :: Sing (DropSym1 d a) Source #

SuppressUnusedWarnings (DropSym1 a6989586621681161202 a6989586621681159660 :: TyFun (NonEmpty a6989586621681159660) [a6989586621681159660] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (DropSym1 a6989586621681161202 a :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681161203 :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (DropSym1 a6989586621681161202 a :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681161203 :: NonEmpty a) = Drop a6989586621681161202 a6989586621681161203

type DropSym2 (a6989586621681161202 :: Nat) (a6989586621681161203 :: NonEmpty a6989586621681159660) = Drop a6989586621681161202 a6989586621681161203 Source #

data SplitAtSym0 :: forall a6989586621681159659. (~>) Nat ((~>) (NonEmpty a6989586621681159659) ([a6989586621681159659], [a6989586621681159659])) Source #

Instances

Instances details
SingI (SplitAtSym0 :: TyFun Nat (NonEmpty a ~> ([a], [a])) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (SplitAtSym0 :: TyFun Nat (NonEmpty a6989586621681159659 ~> ([a6989586621681159659], [a6989586621681159659])) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (SplitAtSym0 :: TyFun Nat (NonEmpty a6989586621681159659 ~> ([a6989586621681159659], [a6989586621681159659])) -> Type) (a6989586621681161194 :: Nat) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (SplitAtSym0 :: TyFun Nat (NonEmpty a6989586621681159659 ~> ([a6989586621681159659], [a6989586621681159659])) -> Type) (a6989586621681161194 :: Nat) = SplitAtSym1 a6989586621681161194 a6989586621681159659 :: TyFun (NonEmpty a6989586621681159659) ([a6989586621681159659], [a6989586621681159659]) -> Type

data SplitAtSym1 (a6989586621681161194 :: Nat) :: forall a6989586621681159659. (~>) (NonEmpty a6989586621681159659) ([a6989586621681159659], [a6989586621681159659]) Source #

Instances

Instances details
SingI d => SingI (SplitAtSym1 d a :: TyFun (NonEmpty a) ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

Methods

sing :: Sing (SplitAtSym1 d a) Source #

SuppressUnusedWarnings (SplitAtSym1 a6989586621681161194 a6989586621681159659 :: TyFun (NonEmpty a6989586621681159659) ([a6989586621681159659], [a6989586621681159659]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (SplitAtSym1 a6989586621681161194 a :: TyFun (NonEmpty a) ([a], [a]) -> Type) (a6989586621681161195 :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (SplitAtSym1 a6989586621681161194 a :: TyFun (NonEmpty a) ([a], [a]) -> Type) (a6989586621681161195 :: NonEmpty a) = SplitAt a6989586621681161194 a6989586621681161195

type SplitAtSym2 (a6989586621681161194 :: Nat) (a6989586621681161195 :: NonEmpty a6989586621681159659) = SplitAt a6989586621681161194 a6989586621681161195 Source #

data TakeWhileSym0 :: forall a6989586621681159658. (~>) ((~>) a6989586621681159658 Bool) ((~>) (NonEmpty a6989586621681159658) [a6989586621681159658]) Source #

Instances

Instances details
SingI (TakeWhileSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (TakeWhileSym0 :: TyFun (a6989586621681159658 ~> Bool) (NonEmpty a6989586621681159658 ~> [a6989586621681159658]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (TakeWhileSym0 :: TyFun (a6989586621681159658 ~> Bool) (NonEmpty a6989586621681159658 ~> [a6989586621681159658]) -> Type) (a6989586621681161186 :: a6989586621681159658 ~> Bool) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (TakeWhileSym0 :: TyFun (a6989586621681159658 ~> Bool) (NonEmpty a6989586621681159658 ~> [a6989586621681159658]) -> Type) (a6989586621681161186 :: a6989586621681159658 ~> Bool) = TakeWhileSym1 a6989586621681161186

data TakeWhileSym1 (a6989586621681161186 :: (~>) a6989586621681159658 Bool) :: (~>) (NonEmpty a6989586621681159658) [a6989586621681159658] Source #

Instances

Instances details
SingI d => SingI (TakeWhileSym1 d :: TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (TakeWhileSym1 a6989586621681161186 :: TyFun (NonEmpty a6989586621681159658) [a6989586621681159658] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (TakeWhileSym1 a6989586621681161186 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681161187 :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (TakeWhileSym1 a6989586621681161186 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681161187 :: NonEmpty a) = TakeWhile a6989586621681161186 a6989586621681161187

type TakeWhileSym2 (a6989586621681161186 :: (~>) a6989586621681159658 Bool) (a6989586621681161187 :: NonEmpty a6989586621681159658) = TakeWhile a6989586621681161186 a6989586621681161187 Source #

data DropWhileSym0 :: forall a6989586621681159657. (~>) ((~>) a6989586621681159657 Bool) ((~>) (NonEmpty a6989586621681159657) [a6989586621681159657]) Source #

Instances

Instances details
SingI (DropWhileSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (DropWhileSym0 :: TyFun (a6989586621681159657 ~> Bool) (NonEmpty a6989586621681159657 ~> [a6989586621681159657]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (DropWhileSym0 :: TyFun (a6989586621681159657 ~> Bool) (NonEmpty a6989586621681159657 ~> [a6989586621681159657]) -> Type) (a6989586621681161178 :: a6989586621681159657 ~> Bool) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (DropWhileSym0 :: TyFun (a6989586621681159657 ~> Bool) (NonEmpty a6989586621681159657 ~> [a6989586621681159657]) -> Type) (a6989586621681161178 :: a6989586621681159657 ~> Bool) = DropWhileSym1 a6989586621681161178

data DropWhileSym1 (a6989586621681161178 :: (~>) a6989586621681159657 Bool) :: (~>) (NonEmpty a6989586621681159657) [a6989586621681159657] Source #

Instances

Instances details
SingI d => SingI (DropWhileSym1 d :: TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (DropWhileSym1 a6989586621681161178 :: TyFun (NonEmpty a6989586621681159657) [a6989586621681159657] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (DropWhileSym1 a6989586621681161178 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681161179 :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (DropWhileSym1 a6989586621681161178 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681161179 :: NonEmpty a) = DropWhile a6989586621681161178 a6989586621681161179

type DropWhileSym2 (a6989586621681161178 :: (~>) a6989586621681159657 Bool) (a6989586621681161179 :: NonEmpty a6989586621681159657) = DropWhile a6989586621681161178 a6989586621681161179 Source #

data SpanSym0 :: forall a6989586621681159656. (~>) ((~>) a6989586621681159656 Bool) ((~>) (NonEmpty a6989586621681159656) ([a6989586621681159656], [a6989586621681159656])) Source #

Instances

Instances details
SingI (SpanSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (SpanSym0 :: TyFun (a6989586621681159656 ~> Bool) (NonEmpty a6989586621681159656 ~> ([a6989586621681159656], [a6989586621681159656])) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (SpanSym0 :: TyFun (a6989586621681159656 ~> Bool) (NonEmpty a6989586621681159656 ~> ([a6989586621681159656], [a6989586621681159656])) -> Type) (a6989586621681161170 :: a6989586621681159656 ~> Bool) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (SpanSym0 :: TyFun (a6989586621681159656 ~> Bool) (NonEmpty a6989586621681159656 ~> ([a6989586621681159656], [a6989586621681159656])) -> Type) (a6989586621681161170 :: a6989586621681159656 ~> Bool) = SpanSym1 a6989586621681161170

data SpanSym1 (a6989586621681161170 :: (~>) a6989586621681159656 Bool) :: (~>) (NonEmpty a6989586621681159656) ([a6989586621681159656], [a6989586621681159656]) Source #

Instances

Instances details
SingI d => SingI (SpanSym1 d :: TyFun (NonEmpty a) ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

Methods

sing :: Sing (SpanSym1 d) Source #

SuppressUnusedWarnings (SpanSym1 a6989586621681161170 :: TyFun (NonEmpty a6989586621681159656) ([a6989586621681159656], [a6989586621681159656]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (SpanSym1 a6989586621681161170 :: TyFun (NonEmpty a) ([a], [a]) -> Type) (a6989586621681161171 :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (SpanSym1 a6989586621681161170 :: TyFun (NonEmpty a) ([a], [a]) -> Type) (a6989586621681161171 :: NonEmpty a) = Span a6989586621681161170 a6989586621681161171

type SpanSym2 (a6989586621681161170 :: (~>) a6989586621681159656 Bool) (a6989586621681161171 :: NonEmpty a6989586621681159656) = Span a6989586621681161170 a6989586621681161171 Source #

data BreakSym0 :: forall a6989586621681159655. (~>) ((~>) a6989586621681159655 Bool) ((~>) (NonEmpty a6989586621681159655) ([a6989586621681159655], [a6989586621681159655])) Source #

Instances

Instances details
SingI (BreakSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (BreakSym0 :: TyFun (a6989586621681159655 ~> Bool) (NonEmpty a6989586621681159655 ~> ([a6989586621681159655], [a6989586621681159655])) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (BreakSym0 :: TyFun (a6989586621681159655 ~> Bool) (NonEmpty a6989586621681159655 ~> ([a6989586621681159655], [a6989586621681159655])) -> Type) (a6989586621681161162 :: a6989586621681159655 ~> Bool) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (BreakSym0 :: TyFun (a6989586621681159655 ~> Bool) (NonEmpty a6989586621681159655 ~> ([a6989586621681159655], [a6989586621681159655])) -> Type) (a6989586621681161162 :: a6989586621681159655 ~> Bool) = BreakSym1 a6989586621681161162

data BreakSym1 (a6989586621681161162 :: (~>) a6989586621681159655 Bool) :: (~>) (NonEmpty a6989586621681159655) ([a6989586621681159655], [a6989586621681159655]) Source #

Instances

Instances details
SingI d => SingI (BreakSym1 d :: TyFun (NonEmpty a) ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

Methods

sing :: Sing (BreakSym1 d) Source #

SuppressUnusedWarnings (BreakSym1 a6989586621681161162 :: TyFun (NonEmpty a6989586621681159655) ([a6989586621681159655], [a6989586621681159655]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (BreakSym1 a6989586621681161162 :: TyFun (NonEmpty a) ([a], [a]) -> Type) (a6989586621681161163 :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (BreakSym1 a6989586621681161162 :: TyFun (NonEmpty a) ([a], [a]) -> Type) (a6989586621681161163 :: NonEmpty a) = Break a6989586621681161162 a6989586621681161163

type BreakSym2 (a6989586621681161162 :: (~>) a6989586621681159655 Bool) (a6989586621681161163 :: NonEmpty a6989586621681159655) = Break a6989586621681161162 a6989586621681161163 Source #

data FilterSym0 :: forall a6989586621681159654. (~>) ((~>) a6989586621681159654 Bool) ((~>) (NonEmpty a6989586621681159654) [a6989586621681159654]) Source #

Instances

Instances details
SingI (FilterSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (FilterSym0 :: TyFun (a6989586621681159654 ~> Bool) (NonEmpty a6989586621681159654 ~> [a6989586621681159654]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (FilterSym0 :: TyFun (a6989586621681159654 ~> Bool) (NonEmpty a6989586621681159654 ~> [a6989586621681159654]) -> Type) (a6989586621681161154 :: a6989586621681159654 ~> Bool) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (FilterSym0 :: TyFun (a6989586621681159654 ~> Bool) (NonEmpty a6989586621681159654 ~> [a6989586621681159654]) -> Type) (a6989586621681161154 :: a6989586621681159654 ~> Bool) = FilterSym1 a6989586621681161154

data FilterSym1 (a6989586621681161154 :: (~>) a6989586621681159654 Bool) :: (~>) (NonEmpty a6989586621681159654) [a6989586621681159654] Source #

Instances

Instances details
SingI d => SingI (FilterSym1 d :: TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

Methods

sing :: Sing (FilterSym1 d) Source #

SuppressUnusedWarnings (FilterSym1 a6989586621681161154 :: TyFun (NonEmpty a6989586621681159654) [a6989586621681159654] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (FilterSym1 a6989586621681161154 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681161155 :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (FilterSym1 a6989586621681161154 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681161155 :: NonEmpty a) = Filter a6989586621681161154 a6989586621681161155

type FilterSym2 (a6989586621681161154 :: (~>) a6989586621681159654 Bool) (a6989586621681161155 :: NonEmpty a6989586621681159654) = Filter a6989586621681161154 a6989586621681161155 Source #

data PartitionSym0 :: forall a6989586621681159653. (~>) ((~>) a6989586621681159653 Bool) ((~>) (NonEmpty a6989586621681159653) ([a6989586621681159653], [a6989586621681159653])) Source #

Instances

Instances details
SingI (PartitionSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (PartitionSym0 :: TyFun (a6989586621681159653 ~> Bool) (NonEmpty a6989586621681159653 ~> ([a6989586621681159653], [a6989586621681159653])) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (PartitionSym0 :: TyFun (a6989586621681159653 ~> Bool) (NonEmpty a6989586621681159653 ~> ([a6989586621681159653], [a6989586621681159653])) -> Type) (a6989586621681161146 :: a6989586621681159653 ~> Bool) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (PartitionSym0 :: TyFun (a6989586621681159653 ~> Bool) (NonEmpty a6989586621681159653 ~> ([a6989586621681159653], [a6989586621681159653])) -> Type) (a6989586621681161146 :: a6989586621681159653 ~> Bool) = PartitionSym1 a6989586621681161146

data PartitionSym1 (a6989586621681161146 :: (~>) a6989586621681159653 Bool) :: (~>) (NonEmpty a6989586621681159653) ([a6989586621681159653], [a6989586621681159653]) Source #

Instances

Instances details
SingI d => SingI (PartitionSym1 d :: TyFun (NonEmpty a) ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (PartitionSym1 a6989586621681161146 :: TyFun (NonEmpty a6989586621681159653) ([a6989586621681159653], [a6989586621681159653]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (PartitionSym1 a6989586621681161146 :: TyFun (NonEmpty a) ([a], [a]) -> Type) (a6989586621681161147 :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (PartitionSym1 a6989586621681161146 :: TyFun (NonEmpty a) ([a], [a]) -> Type) (a6989586621681161147 :: NonEmpty a) = Partition a6989586621681161146 a6989586621681161147

type PartitionSym2 (a6989586621681161146 :: (~>) a6989586621681159653 Bool) (a6989586621681161147 :: NonEmpty a6989586621681159653) = Partition a6989586621681161146 a6989586621681161147 Source #

data GroupSym0 :: forall a6989586621681159652. (~>) [a6989586621681159652] [NonEmpty a6989586621681159652] Source #

Instances

Instances details
SEq a => SingI (GroupSym0 :: TyFun [a] [NonEmpty a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (GroupSym0 :: TyFun [a6989586621681159652] [NonEmpty a6989586621681159652] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupSym0 :: TyFun [a] [NonEmpty a] -> Type) (a6989586621681161143 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupSym0 :: TyFun [a] [NonEmpty a] -> Type) (a6989586621681161143 :: [a]) = Group a6989586621681161143

type GroupSym1 (a6989586621681161143 :: [a6989586621681159652]) = Group a6989586621681161143 Source #

data GroupBySym0 :: forall a6989586621681159651. (~>) ((~>) a6989586621681159651 ((~>) a6989586621681159651 Bool)) ((~>) [a6989586621681159651] [NonEmpty a6989586621681159651]) Source #

Instances

Instances details
SingI (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [NonEmpty a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (GroupBySym0 :: TyFun (a6989586621681159651 ~> (a6989586621681159651 ~> Bool)) ([a6989586621681159651] ~> [NonEmpty a6989586621681159651]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupBySym0 :: TyFun (a6989586621681159651 ~> (a6989586621681159651 ~> Bool)) ([a6989586621681159651] ~> [NonEmpty a6989586621681159651]) -> Type) (a6989586621681161093 :: a6989586621681159651 ~> (a6989586621681159651 ~> Bool)) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupBySym0 :: TyFun (a6989586621681159651 ~> (a6989586621681159651 ~> Bool)) ([a6989586621681159651] ~> [NonEmpty a6989586621681159651]) -> Type) (a6989586621681161093 :: a6989586621681159651 ~> (a6989586621681159651 ~> Bool)) = GroupBySym1 a6989586621681161093

data GroupBySym1 (a6989586621681161093 :: (~>) a6989586621681159651 ((~>) a6989586621681159651 Bool)) :: (~>) [a6989586621681159651] [NonEmpty a6989586621681159651] Source #

Instances

Instances details
SingI d => SingI (GroupBySym1 d :: TyFun [a] [NonEmpty a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

Methods

sing :: Sing (GroupBySym1 d) Source #

SuppressUnusedWarnings (GroupBySym1 a6989586621681161093 :: TyFun [a6989586621681159651] [NonEmpty a6989586621681159651] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupBySym1 a6989586621681161093 :: TyFun [a] [NonEmpty a] -> Type) (a6989586621681161094 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupBySym1 a6989586621681161093 :: TyFun [a] [NonEmpty a] -> Type) (a6989586621681161094 :: [a]) = GroupBy a6989586621681161093 a6989586621681161094

type GroupBySym2 (a6989586621681161093 :: (~>) a6989586621681159651 ((~>) a6989586621681159651 Bool)) (a6989586621681161094 :: [a6989586621681159651]) = GroupBy a6989586621681161093 a6989586621681161094 Source #

data GroupWithSym0 :: forall a6989586621681159650 b6989586621681159649. (~>) ((~>) a6989586621681159650 b6989586621681159649) ((~>) [a6989586621681159650] [NonEmpty a6989586621681159650]) Source #

Instances

Instances details
SEq b => SingI (GroupWithSym0 :: TyFun (a ~> b) ([a] ~> [NonEmpty a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (GroupWithSym0 :: TyFun (a6989586621681159650 ~> b6989586621681159649) ([a6989586621681159650] ~> [NonEmpty a6989586621681159650]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupWithSym0 :: TyFun (a6989586621681159650 ~> b6989586621681159649) ([a6989586621681159650] ~> [NonEmpty a6989586621681159650]) -> Type) (a6989586621681161085 :: a6989586621681159650 ~> b6989586621681159649) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupWithSym0 :: TyFun (a6989586621681159650 ~> b6989586621681159649) ([a6989586621681159650] ~> [NonEmpty a6989586621681159650]) -> Type) (a6989586621681161085 :: a6989586621681159650 ~> b6989586621681159649) = GroupWithSym1 a6989586621681161085

data GroupWithSym1 (a6989586621681161085 :: (~>) a6989586621681159650 b6989586621681159649) :: (~>) [a6989586621681159650] [NonEmpty a6989586621681159650] Source #

Instances

Instances details
(SEq b, SingI d) => SingI (GroupWithSym1 d :: TyFun [a] [NonEmpty a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (GroupWithSym1 a6989586621681161085 :: TyFun [a6989586621681159650] [NonEmpty a6989586621681159650] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupWithSym1 a6989586621681161085 :: TyFun [a] [NonEmpty a] -> Type) (a6989586621681161086 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupWithSym1 a6989586621681161085 :: TyFun [a] [NonEmpty a] -> Type) (a6989586621681161086 :: [a]) = GroupWith a6989586621681161085 a6989586621681161086

type GroupWithSym2 (a6989586621681161085 :: (~>) a6989586621681159650 b6989586621681159649) (a6989586621681161086 :: [a6989586621681159650]) = GroupWith a6989586621681161085 a6989586621681161086 Source #

data GroupAllWithSym0 :: forall a6989586621681159648 b6989586621681159647. (~>) ((~>) a6989586621681159648 b6989586621681159647) ((~>) [a6989586621681159648] [NonEmpty a6989586621681159648]) Source #

Instances

Instances details
SOrd b => SingI (GroupAllWithSym0 :: TyFun (a ~> b) ([a] ~> [NonEmpty a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (GroupAllWithSym0 :: TyFun (a6989586621681159648 ~> b6989586621681159647) ([a6989586621681159648] ~> [NonEmpty a6989586621681159648]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupAllWithSym0 :: TyFun (a6989586621681159648 ~> b6989586621681159647) ([a6989586621681159648] ~> [NonEmpty a6989586621681159648]) -> Type) (a6989586621681161077 :: a6989586621681159648 ~> b6989586621681159647) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupAllWithSym0 :: TyFun (a6989586621681159648 ~> b6989586621681159647) ([a6989586621681159648] ~> [NonEmpty a6989586621681159648]) -> Type) (a6989586621681161077 :: a6989586621681159648 ~> b6989586621681159647) = GroupAllWithSym1 a6989586621681161077

data GroupAllWithSym1 (a6989586621681161077 :: (~>) a6989586621681159648 b6989586621681159647) :: (~>) [a6989586621681159648] [NonEmpty a6989586621681159648] Source #

Instances

Instances details
(SOrd b, SingI d) => SingI (GroupAllWithSym1 d :: TyFun [a] [NonEmpty a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (GroupAllWithSym1 a6989586621681161077 :: TyFun [a6989586621681159648] [NonEmpty a6989586621681159648] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupAllWithSym1 a6989586621681161077 :: TyFun [a] [NonEmpty a] -> Type) (a6989586621681161078 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupAllWithSym1 a6989586621681161077 :: TyFun [a] [NonEmpty a] -> Type) (a6989586621681161078 :: [a]) = GroupAllWith a6989586621681161077 a6989586621681161078

type GroupAllWithSym2 (a6989586621681161077 :: (~>) a6989586621681159648 b6989586621681159647) (a6989586621681161078 :: [a6989586621681159648]) = GroupAllWith a6989586621681161077 a6989586621681161078 Source #

data Group1Sym0 :: forall a6989586621681159646. (~>) (NonEmpty a6989586621681159646) (NonEmpty (NonEmpty a6989586621681159646)) Source #

Instances

Instances details
SEq a => SingI (Group1Sym0 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (Group1Sym0 :: TyFun (NonEmpty a6989586621681159646) (NonEmpty (NonEmpty a6989586621681159646)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (Group1Sym0 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621681161074 :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (Group1Sym0 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621681161074 :: NonEmpty a) = Group1 a6989586621681161074

type Group1Sym1 (a6989586621681161074 :: NonEmpty a6989586621681159646) = Group1 a6989586621681161074 Source #

data GroupBy1Sym0 :: forall a6989586621681159645. (~>) ((~>) a6989586621681159645 ((~>) a6989586621681159645 Bool)) ((~>) (NonEmpty a6989586621681159645) (NonEmpty (NonEmpty a6989586621681159645))) Source #

Instances

Instances details
SingI (GroupBy1Sym0 :: TyFun (a ~> (a ~> Bool)) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (GroupBy1Sym0 :: TyFun (a6989586621681159645 ~> (a6989586621681159645 ~> Bool)) (NonEmpty a6989586621681159645 ~> NonEmpty (NonEmpty a6989586621681159645)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupBy1Sym0 :: TyFun (a6989586621681159645 ~> (a6989586621681159645 ~> Bool)) (NonEmpty a6989586621681159645 ~> NonEmpty (NonEmpty a6989586621681159645)) -> Type) (a6989586621681161041 :: a6989586621681159645 ~> (a6989586621681159645 ~> Bool)) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupBy1Sym0 :: TyFun (a6989586621681159645 ~> (a6989586621681159645 ~> Bool)) (NonEmpty a6989586621681159645 ~> NonEmpty (NonEmpty a6989586621681159645)) -> Type) (a6989586621681161041 :: a6989586621681159645 ~> (a6989586621681159645 ~> Bool)) = GroupBy1Sym1 a6989586621681161041

data GroupBy1Sym1 (a6989586621681161041 :: (~>) a6989586621681159645 ((~>) a6989586621681159645 Bool)) :: (~>) (NonEmpty a6989586621681159645) (NonEmpty (NonEmpty a6989586621681159645)) Source #

Instances

Instances details
SingI d => SingI (GroupBy1Sym1 d :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

Methods

sing :: Sing (GroupBy1Sym1 d) Source #

SuppressUnusedWarnings (GroupBy1Sym1 a6989586621681161041 :: TyFun (NonEmpty a6989586621681159645) (NonEmpty (NonEmpty a6989586621681159645)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupBy1Sym1 a6989586621681161041 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621681161042 :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupBy1Sym1 a6989586621681161041 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621681161042 :: NonEmpty a) = GroupBy1 a6989586621681161041 a6989586621681161042

type GroupBy1Sym2 (a6989586621681161041 :: (~>) a6989586621681159645 ((~>) a6989586621681159645 Bool)) (a6989586621681161042 :: NonEmpty a6989586621681159645) = GroupBy1 a6989586621681161041 a6989586621681161042 Source #

data GroupWith1Sym0 :: forall a6989586621681159644 b6989586621681159643. (~>) ((~>) a6989586621681159644 b6989586621681159643) ((~>) (NonEmpty a6989586621681159644) (NonEmpty (NonEmpty a6989586621681159644))) Source #

Instances

Instances details
SEq b => SingI (GroupWith1Sym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (GroupWith1Sym0 :: TyFun (a6989586621681159644 ~> b6989586621681159643) (NonEmpty a6989586621681159644 ~> NonEmpty (NonEmpty a6989586621681159644)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupWith1Sym0 :: TyFun (a6989586621681159644 ~> b6989586621681159643) (NonEmpty a6989586621681159644 ~> NonEmpty (NonEmpty a6989586621681159644)) -> Type) (a6989586621681161033 :: a6989586621681159644 ~> b6989586621681159643) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupWith1Sym0 :: TyFun (a6989586621681159644 ~> b6989586621681159643) (NonEmpty a6989586621681159644 ~> NonEmpty (NonEmpty a6989586621681159644)) -> Type) (a6989586621681161033 :: a6989586621681159644 ~> b6989586621681159643) = GroupWith1Sym1 a6989586621681161033

data GroupWith1Sym1 (a6989586621681161033 :: (~>) a6989586621681159644 b6989586621681159643) :: (~>) (NonEmpty a6989586621681159644) (NonEmpty (NonEmpty a6989586621681159644)) Source #

Instances

Instances details
(SEq b, SingI d) => SingI (GroupWith1Sym1 d :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (GroupWith1Sym1 a6989586621681161033 :: TyFun (NonEmpty a6989586621681159644) (NonEmpty (NonEmpty a6989586621681159644)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupWith1Sym1 a6989586621681161033 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621681161034 :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupWith1Sym1 a6989586621681161033 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621681161034 :: NonEmpty a) = GroupWith1 a6989586621681161033 a6989586621681161034

type GroupWith1Sym2 (a6989586621681161033 :: (~>) a6989586621681159644 b6989586621681159643) (a6989586621681161034 :: NonEmpty a6989586621681159644) = GroupWith1 a6989586621681161033 a6989586621681161034 Source #

data GroupAllWith1Sym0 :: forall a6989586621681159642 b6989586621681159641. (~>) ((~>) a6989586621681159642 b6989586621681159641) ((~>) (NonEmpty a6989586621681159642) (NonEmpty (NonEmpty a6989586621681159642))) Source #

Instances

Instances details
SOrd b => SingI (GroupAllWith1Sym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (GroupAllWith1Sym0 :: TyFun (a6989586621681159642 ~> b6989586621681159641) (NonEmpty a6989586621681159642 ~> NonEmpty (NonEmpty a6989586621681159642)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupAllWith1Sym0 :: TyFun (a6989586621681159642 ~> b6989586621681159641) (NonEmpty a6989586621681159642 ~> NonEmpty (NonEmpty a6989586621681159642)) -> Type) (a6989586621681161025 :: a6989586621681159642 ~> b6989586621681159641) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupAllWith1Sym0 :: TyFun (a6989586621681159642 ~> b6989586621681159641) (NonEmpty a6989586621681159642 ~> NonEmpty (NonEmpty a6989586621681159642)) -> Type) (a6989586621681161025 :: a6989586621681159642 ~> b6989586621681159641) = GroupAllWith1Sym1 a6989586621681161025

data GroupAllWith1Sym1 (a6989586621681161025 :: (~>) a6989586621681159642 b6989586621681159641) :: (~>) (NonEmpty a6989586621681159642) (NonEmpty (NonEmpty a6989586621681159642)) Source #

Instances

Instances details
(SOrd b, SingI d) => SingI (GroupAllWith1Sym1 d :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (GroupAllWith1Sym1 a6989586621681161025 :: TyFun (NonEmpty a6989586621681159642) (NonEmpty (NonEmpty a6989586621681159642)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupAllWith1Sym1 a6989586621681161025 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621681161026 :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupAllWith1Sym1 a6989586621681161025 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621681161026 :: NonEmpty a) = GroupAllWith1 a6989586621681161025 a6989586621681161026

type GroupAllWith1Sym2 (a6989586621681161025 :: (~>) a6989586621681159642 b6989586621681159641) (a6989586621681161026 :: NonEmpty a6989586621681159642) = GroupAllWith1 a6989586621681161025 a6989586621681161026 Source #

data IsPrefixOfSym0 :: forall a6989586621681159640. (~>) [a6989586621681159640] ((~>) (NonEmpty a6989586621681159640) Bool) Source #

Instances

Instances details
SEq a => SingI (IsPrefixOfSym0 :: TyFun [a] (NonEmpty a ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (IsPrefixOfSym0 :: TyFun [a6989586621681159640] (NonEmpty a6989586621681159640 ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (IsPrefixOfSym0 :: TyFun [a6989586621681159640] (NonEmpty a6989586621681159640 ~> Bool) -> Type) (a6989586621681161017 :: [a6989586621681159640]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (IsPrefixOfSym0 :: TyFun [a6989586621681159640] (NonEmpty a6989586621681159640 ~> Bool) -> Type) (a6989586621681161017 :: [a6989586621681159640]) = IsPrefixOfSym1 a6989586621681161017

data IsPrefixOfSym1 (a6989586621681161017 :: [a6989586621681159640]) :: (~>) (NonEmpty a6989586621681159640) Bool Source #

Instances

Instances details
(SEq a, SingI d) => SingI (IsPrefixOfSym1 d :: TyFun (NonEmpty a) Bool -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (IsPrefixOfSym1 a6989586621681161017 :: TyFun (NonEmpty a6989586621681159640) Bool -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (IsPrefixOfSym1 a6989586621681161017 :: TyFun (NonEmpty a) Bool -> Type) (a6989586621681161018 :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (IsPrefixOfSym1 a6989586621681161017 :: TyFun (NonEmpty a) Bool -> Type) (a6989586621681161018 :: NonEmpty a) = IsPrefixOf a6989586621681161017 a6989586621681161018

type IsPrefixOfSym2 (a6989586621681161017 :: [a6989586621681159640]) (a6989586621681161018 :: NonEmpty a6989586621681159640) = IsPrefixOf a6989586621681161017 a6989586621681161018 Source #

data NubSym0 :: forall a6989586621681159631. (~>) (NonEmpty a6989586621681159631) (NonEmpty a6989586621681159631) Source #

Instances

Instances details
SEq a => SingI (NubSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (NubSym0 :: TyFun (NonEmpty a6989586621681159631) (NonEmpty a6989586621681159631) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (NubSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681160948 :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (NubSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681160948 :: NonEmpty a) = Nub a6989586621681160948

type NubSym1 (a6989586621681160948 :: NonEmpty a6989586621681159631) = Nub a6989586621681160948 Source #

data NubBySym0 :: forall a6989586621681159630. (~>) ((~>) a6989586621681159630 ((~>) a6989586621681159630 Bool)) ((~>) (NonEmpty a6989586621681159630) (NonEmpty a6989586621681159630)) Source #

Instances

Instances details
SingI (NubBySym0 :: TyFun (a ~> (a ~> Bool)) (NonEmpty a ~> NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (NubBySym0 :: TyFun (a6989586621681159630 ~> (a6989586621681159630 ~> Bool)) (NonEmpty a6989586621681159630 ~> NonEmpty a6989586621681159630) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (NubBySym0 :: TyFun (a6989586621681159630 ~> (a6989586621681159630 ~> Bool)) (NonEmpty a6989586621681159630 ~> NonEmpty a6989586621681159630) -> Type) (a6989586621681160931 :: a6989586621681159630 ~> (a6989586621681159630 ~> Bool)) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (NubBySym0 :: TyFun (a6989586621681159630 ~> (a6989586621681159630 ~> Bool)) (NonEmpty a6989586621681159630 ~> NonEmpty a6989586621681159630) -> Type) (a6989586621681160931 :: a6989586621681159630 ~> (a6989586621681159630 ~> Bool)) = NubBySym1 a6989586621681160931

data NubBySym1 (a6989586621681160931 :: (~>) a6989586621681159630 ((~>) a6989586621681159630 Bool)) :: (~>) (NonEmpty a6989586621681159630) (NonEmpty a6989586621681159630) Source #

Instances

Instances details
SingI d => SingI (NubBySym1 d :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

Methods

sing :: Sing (NubBySym1 d) Source #

SuppressUnusedWarnings (NubBySym1 a6989586621681160931 :: TyFun (NonEmpty a6989586621681159630) (NonEmpty a6989586621681159630) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (NubBySym1 a6989586621681160931 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681160932 :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (NubBySym1 a6989586621681160931 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681160932 :: NonEmpty a) = NubBy a6989586621681160931 a6989586621681160932

type NubBySym2 (a6989586621681160931 :: (~>) a6989586621681159630 ((~>) a6989586621681159630 Bool)) (a6989586621681160932 :: NonEmpty a6989586621681159630) = NubBy a6989586621681160931 a6989586621681160932 Source #

data (!!@#@$) :: forall a6989586621681159639. (~>) (NonEmpty a6989586621681159639) ((~>) Nat a6989586621681159639) Source #

Instances

Instances details
SingI ((!!@#@$) :: TyFun (NonEmpty a) (Nat ~> a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings ((!!@#@$) :: TyFun (NonEmpty a6989586621681159639) (Nat ~> a6989586621681159639) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply ((!!@#@$) :: TyFun (NonEmpty a6989586621681159639) (Nat ~> a6989586621681159639) -> Type) (a6989586621681160999 :: NonEmpty a6989586621681159639) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply ((!!@#@$) :: TyFun (NonEmpty a6989586621681159639) (Nat ~> a6989586621681159639) -> Type) (a6989586621681160999 :: NonEmpty a6989586621681159639) = (!!@#@$$) a6989586621681160999

data (!!@#@$$) (a6989586621681160999 :: NonEmpty a6989586621681159639) :: (~>) Nat a6989586621681159639 Source #

Instances

Instances details
SingI d => SingI ((!!@#@$$) d :: TyFun Nat a -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

Methods

sing :: Sing ((!!@#@$$) d) Source #

SuppressUnusedWarnings ((!!@#@$$) a6989586621681160999 :: TyFun Nat a6989586621681159639 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply ((!!@#@$$) a6989586621681160999 :: TyFun Nat a -> Type) (a6989586621681161000 :: Nat) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply ((!!@#@$$) a6989586621681160999 :: TyFun Nat a -> Type) (a6989586621681161000 :: Nat) = a6989586621681160999 !! a6989586621681161000

type (!!@#@$$$) (a6989586621681160999 :: NonEmpty a6989586621681159639) (a6989586621681161000 :: Nat) = (!!) a6989586621681160999 a6989586621681161000 Source #

data ZipSym0 :: forall a6989586621681159637 b6989586621681159638. (~>) (NonEmpty a6989586621681159637) ((~>) (NonEmpty b6989586621681159638) (NonEmpty (a6989586621681159637, b6989586621681159638))) Source #

Instances

Instances details
SingI (ZipSym0 :: TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty (a, b)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (ZipSym0 :: TyFun (NonEmpty a6989586621681159637) (NonEmpty b6989586621681159638 ~> NonEmpty (a6989586621681159637, b6989586621681159638)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ZipSym0 :: TyFun (NonEmpty a6989586621681159637) (NonEmpty b6989586621681159638 ~> NonEmpty (a6989586621681159637, b6989586621681159638)) -> Type) (a6989586621681160991 :: NonEmpty a6989586621681159637) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ZipSym0 :: TyFun (NonEmpty a6989586621681159637) (NonEmpty b6989586621681159638 ~> NonEmpty (a6989586621681159637, b6989586621681159638)) -> Type) (a6989586621681160991 :: NonEmpty a6989586621681159637) = ZipSym1 a6989586621681160991 b6989586621681159638 :: TyFun (NonEmpty b6989586621681159638) (NonEmpty (a6989586621681159637, b6989586621681159638)) -> Type

data ZipSym1 (a6989586621681160991 :: NonEmpty a6989586621681159637) :: forall b6989586621681159638. (~>) (NonEmpty b6989586621681159638) (NonEmpty (a6989586621681159637, b6989586621681159638)) Source #

Instances

Instances details
SingI d => SingI (ZipSym1 d b :: TyFun (NonEmpty b) (NonEmpty (a, b)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

Methods

sing :: Sing (ZipSym1 d b) Source #

SuppressUnusedWarnings (ZipSym1 a6989586621681160991 b6989586621681159638 :: TyFun (NonEmpty b6989586621681159638) (NonEmpty (a6989586621681159637, b6989586621681159638)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ZipSym1 a6989586621681160991 b :: TyFun (NonEmpty b) (NonEmpty (a, b)) -> Type) (a6989586621681160992 :: NonEmpty b) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ZipSym1 a6989586621681160991 b :: TyFun (NonEmpty b) (NonEmpty (a, b)) -> Type) (a6989586621681160992 :: NonEmpty b) = Zip a6989586621681160991 a6989586621681160992

type ZipSym2 (a6989586621681160991 :: NonEmpty a6989586621681159637) (a6989586621681160992 :: NonEmpty b6989586621681159638) = Zip a6989586621681160991 a6989586621681160992 Source #

data ZipWithSym0 :: forall a6989586621681159634 b6989586621681159635 c6989586621681159636. (~>) ((~>) a6989586621681159634 ((~>) b6989586621681159635 c6989586621681159636)) ((~>) (NonEmpty a6989586621681159634) ((~>) (NonEmpty b6989586621681159635) (NonEmpty c6989586621681159636))) Source #

Instances

Instances details
SingI (ZipWithSym0 :: TyFun (a ~> (b ~> c)) (NonEmpty a ~> (NonEmpty b ~> NonEmpty c)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (ZipWithSym0 :: TyFun (a6989586621681159634 ~> (b6989586621681159635 ~> c6989586621681159636)) (NonEmpty a6989586621681159634 ~> (NonEmpty b6989586621681159635 ~> NonEmpty c6989586621681159636)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ZipWithSym0 :: TyFun (a6989586621681159634 ~> (b6989586621681159635 ~> c6989586621681159636)) (NonEmpty a6989586621681159634 ~> (NonEmpty b6989586621681159635 ~> NonEmpty c6989586621681159636)) -> Type) (a6989586621681160980 :: a6989586621681159634 ~> (b6989586621681159635 ~> c6989586621681159636)) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ZipWithSym0 :: TyFun (a6989586621681159634 ~> (b6989586621681159635 ~> c6989586621681159636)) (NonEmpty a6989586621681159634 ~> (NonEmpty b6989586621681159635 ~> NonEmpty c6989586621681159636)) -> Type) (a6989586621681160980 :: a6989586621681159634 ~> (b6989586621681159635 ~> c6989586621681159636)) = ZipWithSym1 a6989586621681160980

data ZipWithSym1 (a6989586621681160980 :: (~>) a6989586621681159634 ((~>) b6989586621681159635 c6989586621681159636)) :: (~>) (NonEmpty a6989586621681159634) ((~>) (NonEmpty b6989586621681159635) (NonEmpty c6989586621681159636)) Source #

Instances

Instances details
SingI d => SingI (ZipWithSym1 d :: TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty c) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

Methods

sing :: Sing (ZipWithSym1 d) Source #

SuppressUnusedWarnings (ZipWithSym1 a6989586621681160980 :: TyFun (NonEmpty a6989586621681159634) (NonEmpty b6989586621681159635 ~> NonEmpty c6989586621681159636) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ZipWithSym1 a6989586621681160980 :: TyFun (NonEmpty a6989586621681159634) (NonEmpty b6989586621681159635 ~> NonEmpty c6989586621681159636) -> Type) (a6989586621681160981 :: NonEmpty a6989586621681159634) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ZipWithSym1 a6989586621681160980 :: TyFun (NonEmpty a6989586621681159634) (NonEmpty b6989586621681159635 ~> NonEmpty c6989586621681159636) -> Type) (a6989586621681160981 :: NonEmpty a6989586621681159634) = ZipWithSym2 a6989586621681160980 a6989586621681160981

data ZipWithSym2 (a6989586621681160980 :: (~>) a6989586621681159634 ((~>) b6989586621681159635 c6989586621681159636)) (a6989586621681160981 :: NonEmpty a6989586621681159634) :: (~>) (NonEmpty b6989586621681159635) (NonEmpty c6989586621681159636) Source #

Instances

Instances details
(SingI d1, SingI d2) => SingI (ZipWithSym2 d1 d2 :: TyFun (NonEmpty b) (NonEmpty c) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

Methods

sing :: Sing (ZipWithSym2 d1 d2) Source #

SuppressUnusedWarnings (ZipWithSym2 a6989586621681160981 a6989586621681160980 :: TyFun (NonEmpty b6989586621681159635) (NonEmpty c6989586621681159636) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ZipWithSym2 a6989586621681160981 a6989586621681160980 :: TyFun (NonEmpty b) (NonEmpty c) -> Type) (a6989586621681160982 :: NonEmpty b) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ZipWithSym2 a6989586621681160981 a6989586621681160980 :: TyFun (NonEmpty b) (NonEmpty c) -> Type) (a6989586621681160982 :: NonEmpty b) = ZipWith a6989586621681160981 a6989586621681160980 a6989586621681160982

type ZipWithSym3 (a6989586621681160980 :: (~>) a6989586621681159634 ((~>) b6989586621681159635 c6989586621681159636)) (a6989586621681160981 :: NonEmpty a6989586621681159634) (a6989586621681160982 :: NonEmpty b6989586621681159635) = ZipWith a6989586621681160980 a6989586621681160981 a6989586621681160982 Source #

data UnzipSym0 :: forall a6989586621681159632 b6989586621681159633. (~>) (NonEmpty (a6989586621681159632, b6989586621681159633)) (NonEmpty a6989586621681159632, NonEmpty b6989586621681159633) Source #

Instances

Instances details
SingI (UnzipSym0 :: TyFun (NonEmpty (a, b)) (NonEmpty a, NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (UnzipSym0 :: TyFun (NonEmpty (a6989586621681159632, b6989586621681159633)) (NonEmpty a6989586621681159632, NonEmpty b6989586621681159633) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (UnzipSym0 :: TyFun (NonEmpty (a, b)) (NonEmpty a, NonEmpty b) -> Type) (a6989586621681160951 :: NonEmpty (a, b)) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (UnzipSym0 :: TyFun (NonEmpty (a, b)) (NonEmpty a, NonEmpty b) -> Type) (a6989586621681160951 :: NonEmpty (a, b)) = Unzip a6989586621681160951

type UnzipSym1 (a6989586621681160951 :: NonEmpty (a6989586621681159632, b6989586621681159633)) = Unzip a6989586621681160951 Source #

data FromListSym0 :: forall a6989586621681159678. (~>) [a6989586621681159678] (NonEmpty a6989586621681159678) Source #

Instances

Instances details
SingI (FromListSym0 :: TyFun [a] (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (FromListSym0 :: TyFun [a6989586621681159678] (NonEmpty a6989586621681159678) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (FromListSym0 :: TyFun [a] (NonEmpty a) -> Type) (a6989586621681161306 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (FromListSym0 :: TyFun [a] (NonEmpty a) -> Type) (a6989586621681161306 :: [a]) = FromList a6989586621681161306

type FromListSym1 (a6989586621681161306 :: [a6989586621681159678]) = FromList a6989586621681161306 Source #

data ToListSym0 :: forall a6989586621681159677. (~>) (NonEmpty a6989586621681159677) [a6989586621681159677] Source #

Instances

Instances details
SingI (ToListSym0 :: TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (ToListSym0 :: TyFun (NonEmpty a6989586621681159677) [a6989586621681159677] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ToListSym0 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681161302 :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ToListSym0 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681161302 :: NonEmpty a) = ToList a6989586621681161302

type ToListSym1 (a6989586621681161302 :: NonEmpty a6989586621681159677) = ToList a6989586621681161302 Source #

data NonEmpty_Sym0 :: forall a6989586621681159689. (~>) [a6989586621681159689] (Maybe (NonEmpty a6989586621681159689)) Source #

Instances

Instances details
SingI (NonEmpty_Sym0 :: TyFun [a] (Maybe (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings (NonEmpty_Sym0 :: TyFun [a6989586621681159689] (Maybe (NonEmpty a6989586621681159689)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (NonEmpty_Sym0 :: TyFun [a] (Maybe (NonEmpty a)) -> Type) (a6989586621681161379 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (NonEmpty_Sym0 :: TyFun [a] (Maybe (NonEmpty a)) -> Type) (a6989586621681161379 :: [a]) = NonEmpty_ a6989586621681161379

type NonEmpty_Sym1 (a6989586621681161379 :: [a6989586621681159689]) = NonEmpty_ a6989586621681161379 Source #

data XorSym0 :: (~>) (NonEmpty Bool) Bool Source #

Instances

Instances details
SingI XorSym0 Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings XorSym0 Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply XorSym0 (a6989586621681161398 :: NonEmpty Bool) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply XorSym0 (a6989586621681161398 :: NonEmpty Bool) = Xor a6989586621681161398

type XorSym1 (a6989586621681161398 :: NonEmpty Bool) = Xor a6989586621681161398 Source #

Orphan instances

SMonadZip NonEmpty Source # 
Instance details

Methods

sMzip :: forall a b (t :: NonEmpty a) (t :: NonEmpty b). Sing t -> Sing t -> Sing (Apply (Apply MzipSym0 t) t) Source #

sMzipWith :: forall a b c (t :: a ~> (b ~> c)) (t :: NonEmpty a) (t :: NonEmpty b). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply MzipWithSym0 t) t) t) Source #

sMunzip :: forall a b (t :: NonEmpty (a, b)). Sing t -> Sing (Apply MunzipSym0 t) Source #

PMonadZip NonEmpty Source # 
Instance details

Associated Types

type Mzip arg arg :: m (a, b) Source #

type MzipWith arg arg arg :: m c Source #

type Munzip arg :: (m a, m b) Source #