singletons-2.4.1: A framework for generating singleton types

Copyright(C) 2016 Richard Eisenberg
LicenseBSD-style (see LICENSE)
MaintainerRichard Eisenberg (rae@cs.brynmawr.edu)
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Promotion.Prelude.List.NonEmpty

Contents

Description

Defines functions and datatypes relating to promoting NonEmpty, including promoted versions of many of the definitions in Data.List.NonEmpty.

Synopsis

Non-empty stream transformations

type family Map (a :: TyFun a b -> Type) (a :: NonEmpty a) :: NonEmpty b where ... Source #

Equations

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

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

Equations

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

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

Equations

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

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

Equations

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

type family Scanl1 (a :: TyFun a (TyFun a a -> Type) -> Type) (a :: NonEmpty a) :: NonEmpty a where ... Source #

Equations

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

type family Scanr1 (a :: TyFun a (TyFun a a -> Type) -> Type) (a :: NonEmpty a) :: NonEmpty a where ... Source #

Equations

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

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

Equations

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

type family SortBy (a :: TyFun a (TyFun a Ordering -> Type) -> Type) (a :: NonEmpty a) :: NonEmpty a where ... Source #

Equations

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

type family SortWith (a :: TyFun a o -> Type) (a :: NonEmpty a) :: NonEmpty a where ... Source #

Equations

SortWith a_6989586621679836017 a_6989586621679836019 = Apply (Apply (Apply (Apply (.@#@$) SortBySym0) ComparingSym0) a_6989586621679836017) a_6989586621679836019 

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

Equations

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

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

Equations

Head ((:|) a _) = a 

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

Equations

Tail ((:|) _ as) = as 

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

Equations

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

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

Equations

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

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

Equations

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

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

Equations

Cons a_6989586621679836155 a_6989586621679836157 = Apply (Apply (<|@#@$) a_6989586621679836155) a_6989586621679836157 

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

Equations

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

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

Equations

Unfoldr f a = Case_6989586621679836244 f a (Let6989586621679836236Scrutinee_6989586621679834204Sym2 f a) 

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

Equations

Sort a_6989586621679836136 = Apply (Apply LiftSym0 ListsortSym0) a_6989586621679836136 

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

Equations

Reverse a_6989586621679835997 = Apply (Apply LiftSym0 ListreverseSym0) a_6989586621679835997 

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

Equations

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

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

Equations

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

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

Equations

Unfold f a = Case_6989586621679836280 f a (Let6989586621679836272Scrutinee_6989586621679834194Sym2 f a) 

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

Equations

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

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

Equations

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

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

Equations

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

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

Equations

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

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

Equations

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

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

Equations

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

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

Equations

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

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

Equations

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

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

Equations

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

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

Equations

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

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

Equations

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

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

Equations

GroupBy eq0 a_6989586621679835594 = Apply (Apply (Let6989586621679835598GoSym2 eq0 a_6989586621679835594) eq0) a_6989586621679835594 

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

Equations

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

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

Equations

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

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

Equations

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

type family GroupBy1 (a :: TyFun a (TyFun a Bool -> Type) -> Type) (a :: NonEmpty a) :: NonEmpty (NonEmpty a) where ... Source #

Equations

GroupBy1 eq ((:|) x xs) = Apply (Apply (:|@#@$) (Apply (Apply (:|@#@$) x) (Let6989586621679835750YsSym3 eq x xs))) (Apply (Apply GroupBySym0 eq) (Let6989586621679835750ZsSym3 eq x xs)) 

type family GroupWith1 (a :: TyFun a b -> Type) (a :: NonEmpty a) :: NonEmpty (NonEmpty a) where ... Source #

Equations

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

type family GroupAllWith1 (a :: TyFun a b -> Type) (a :: NonEmpty a) :: NonEmpty (NonEmpty a) where ... Source #

Equations

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

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) 

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

Equations

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

type family NubBy (a :: TyFun a (TyFun a Bool -> Type) -> Type) (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_6989586621679835429Sym0 eq) a) as)) as)) 

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

Equations

arg_6989586621679834216 !! arg_6989586621679834218 = Case_6989586621679835560 arg_6989586621679834216 arg_6989586621679834218 (Apply (Apply Tuple2Sym0 arg_6989586621679834216) arg_6989586621679834218) 

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) 

type family ZipWith (a :: TyFun a (TyFun b c -> Type) -> Type) (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) 

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

Equations

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

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

Equations

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

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

Equations

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

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

Equations

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

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

Equations

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

Defunctionalization symbols

data (:|@#@$) (l :: TyFun a6989586621679068306 (TyFun [a6989586621679068306] (NonEmpty a6989586621679068306) -> Type)) Source #

Instances
SuppressUnusedWarnings ((:|@#@$) :: TyFun a6989586621679068306 (TyFun [a6989586621679068306] (NonEmpty a6989586621679068306) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Apply ((:|@#@$) :: TyFun a6989586621679068306 (TyFun [a6989586621679068306] (NonEmpty a6989586621679068306) -> Type) -> *) (l :: a6989586621679068306) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Apply ((:|@#@$) :: TyFun a6989586621679068306 (TyFun [a6989586621679068306] (NonEmpty a6989586621679068306) -> Type) -> *) (l :: a6989586621679068306) = (:|@#@$$) l

data (l :: a6989586621679068306) :|@#@$$ (l :: TyFun [a6989586621679068306] (NonEmpty a6989586621679068306)) Source #

Instances
SuppressUnusedWarnings ((:|@#@$$) :: a6989586621679068306 -> TyFun [a6989586621679068306] (NonEmpty a6989586621679068306) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Apply ((:|@#@$$) l1 :: TyFun [a] (NonEmpty a) -> *) (l2 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Apply ((:|@#@$$) l1 :: TyFun [a] (NonEmpty a) -> *) (l2 :: [a]) = l1 :| l2

type (:|@#@$$$) (t :: a6989586621679068306) (t :: [a6989586621679068306]) = (:|) t t Source #

data MapSym0 (l :: TyFun (TyFun a6989586621679834010 b6989586621679834011 -> Type) (TyFun (NonEmpty a6989586621679834010) (NonEmpty b6989586621679834011) -> Type)) Source #

Instances
SuppressUnusedWarnings (MapSym0 :: TyFun (TyFun a6989586621679834010 b6989586621679834011 -> Type) (TyFun (NonEmpty a6989586621679834010) (NonEmpty b6989586621679834011) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (MapSym0 :: TyFun (TyFun a6989586621679834010 b6989586621679834011 -> Type) (TyFun (NonEmpty a6989586621679834010) (NonEmpty b6989586621679834011) -> Type) -> *) (l :: TyFun a6989586621679834010 b6989586621679834011 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (MapSym0 :: TyFun (TyFun a6989586621679834010 b6989586621679834011 -> Type) (TyFun (NonEmpty a6989586621679834010) (NonEmpty b6989586621679834011) -> Type) -> *) (l :: TyFun a6989586621679834010 b6989586621679834011 -> Type) = MapSym1 l

data MapSym1 (l :: TyFun a6989586621679834010 b6989586621679834011 -> Type) (l :: TyFun (NonEmpty a6989586621679834010) (NonEmpty b6989586621679834011)) Source #

Instances
SuppressUnusedWarnings (MapSym1 :: (TyFun a6989586621679834010 b6989586621679834011 -> Type) -> TyFun (NonEmpty a6989586621679834010) (NonEmpty b6989586621679834011) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (MapSym1 l1 :: TyFun (NonEmpty a) (NonEmpty b) -> *) (l2 :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (MapSym1 l1 :: TyFun (NonEmpty a) (NonEmpty b) -> *) (l2 :: NonEmpty a) = Map l1 l2

type MapSym2 (t :: TyFun a6989586621679834010 b6989586621679834011 -> Type) (t :: NonEmpty a6989586621679834010) = Map t t Source #

data IntersperseSym0 (l :: TyFun a6989586621679834000 (TyFun (NonEmpty a6989586621679834000) (NonEmpty a6989586621679834000) -> Type)) Source #

Instances
SuppressUnusedWarnings (IntersperseSym0 :: TyFun a6989586621679834000 (TyFun (NonEmpty a6989586621679834000) (NonEmpty a6989586621679834000) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (IntersperseSym0 :: TyFun a6989586621679834000 (TyFun (NonEmpty a6989586621679834000) (NonEmpty a6989586621679834000) -> Type) -> *) (l :: a6989586621679834000) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (IntersperseSym0 :: TyFun a6989586621679834000 (TyFun (NonEmpty a6989586621679834000) (NonEmpty a6989586621679834000) -> Type) -> *) (l :: a6989586621679834000) = IntersperseSym1 l

data IntersperseSym1 (l :: a6989586621679834000) (l :: TyFun (NonEmpty a6989586621679834000) (NonEmpty a6989586621679834000)) Source #

Instances
SuppressUnusedWarnings (IntersperseSym1 :: a6989586621679834000 -> TyFun (NonEmpty a6989586621679834000) (NonEmpty a6989586621679834000) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (IntersperseSym1 l1 :: TyFun (NonEmpty a) (NonEmpty a) -> *) (l2 :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (IntersperseSym1 l1 :: TyFun (NonEmpty a) (NonEmpty a) -> *) (l2 :: NonEmpty a) = Intersperse l1 l2

type IntersperseSym2 (t :: a6989586621679834000) (t :: NonEmpty a6989586621679834000) = Intersperse t t Source #

data ScanlSym0 (l :: TyFun (TyFun b6989586621679834005 (TyFun a6989586621679834006 b6989586621679834005 -> Type) -> Type) (TyFun b6989586621679834005 (TyFun [a6989586621679834006] (NonEmpty b6989586621679834005) -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (ScanlSym0 :: TyFun (TyFun b6989586621679834005 (TyFun a6989586621679834006 b6989586621679834005 -> Type) -> Type) (TyFun b6989586621679834005 (TyFun [a6989586621679834006] (NonEmpty b6989586621679834005) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ScanlSym0 :: TyFun (TyFun b6989586621679834005 (TyFun a6989586621679834006 b6989586621679834005 -> Type) -> Type) (TyFun b6989586621679834005 (TyFun [a6989586621679834006] (NonEmpty b6989586621679834005) -> Type) -> Type) -> *) (l :: TyFun b6989586621679834005 (TyFun a6989586621679834006 b6989586621679834005 -> Type) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ScanlSym0 :: TyFun (TyFun b6989586621679834005 (TyFun a6989586621679834006 b6989586621679834005 -> Type) -> Type) (TyFun b6989586621679834005 (TyFun [a6989586621679834006] (NonEmpty b6989586621679834005) -> Type) -> Type) -> *) (l :: TyFun b6989586621679834005 (TyFun a6989586621679834006 b6989586621679834005 -> Type) -> Type) = ScanlSym1 l

data ScanlSym1 (l :: TyFun b6989586621679834005 (TyFun a6989586621679834006 b6989586621679834005 -> Type) -> Type) (l :: TyFun b6989586621679834005 (TyFun [a6989586621679834006] (NonEmpty b6989586621679834005) -> Type)) Source #

Instances
SuppressUnusedWarnings (ScanlSym1 :: (TyFun b6989586621679834005 (TyFun a6989586621679834006 b6989586621679834005 -> Type) -> Type) -> TyFun b6989586621679834005 (TyFun [a6989586621679834006] (NonEmpty b6989586621679834005) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ScanlSym1 l1 :: TyFun b6989586621679834005 (TyFun [a6989586621679834006] (NonEmpty b6989586621679834005) -> Type) -> *) (l2 :: b6989586621679834005) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ScanlSym1 l1 :: TyFun b6989586621679834005 (TyFun [a6989586621679834006] (NonEmpty b6989586621679834005) -> Type) -> *) (l2 :: b6989586621679834005) = ScanlSym2 l1 l2

data ScanlSym2 (l :: TyFun b6989586621679834005 (TyFun a6989586621679834006 b6989586621679834005 -> Type) -> Type) (l :: b6989586621679834005) (l :: TyFun [a6989586621679834006] (NonEmpty b6989586621679834005)) Source #

Instances
SuppressUnusedWarnings (ScanlSym2 :: (TyFun b6989586621679834005 (TyFun a6989586621679834006 b6989586621679834005 -> Type) -> Type) -> b6989586621679834005 -> TyFun [a6989586621679834006] (NonEmpty b6989586621679834005) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ScanlSym2 l1 l2 :: TyFun [a] (NonEmpty b) -> *) (l3 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ScanlSym2 l1 l2 :: TyFun [a] (NonEmpty b) -> *) (l3 :: [a]) = Scanl l1 l2 l3

type ScanlSym3 (t :: TyFun b6989586621679834005 (TyFun a6989586621679834006 b6989586621679834005 -> Type) -> Type) (t :: b6989586621679834005) (t :: [a6989586621679834006]) = Scanl t t t Source #

data ScanrSym0 (l :: TyFun (TyFun a6989586621679834003 (TyFun b6989586621679834004 b6989586621679834004 -> Type) -> Type) (TyFun b6989586621679834004 (TyFun [a6989586621679834003] (NonEmpty b6989586621679834004) -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (ScanrSym0 :: TyFun (TyFun a6989586621679834003 (TyFun b6989586621679834004 b6989586621679834004 -> Type) -> Type) (TyFun b6989586621679834004 (TyFun [a6989586621679834003] (NonEmpty b6989586621679834004) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ScanrSym0 :: TyFun (TyFun a6989586621679834003 (TyFun b6989586621679834004 b6989586621679834004 -> Type) -> Type) (TyFun b6989586621679834004 (TyFun [a6989586621679834003] (NonEmpty b6989586621679834004) -> Type) -> Type) -> *) (l :: TyFun a6989586621679834003 (TyFun b6989586621679834004 b6989586621679834004 -> Type) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ScanrSym0 :: TyFun (TyFun a6989586621679834003 (TyFun b6989586621679834004 b6989586621679834004 -> Type) -> Type) (TyFun b6989586621679834004 (TyFun [a6989586621679834003] (NonEmpty b6989586621679834004) -> Type) -> Type) -> *) (l :: TyFun a6989586621679834003 (TyFun b6989586621679834004 b6989586621679834004 -> Type) -> Type) = ScanrSym1 l

data ScanrSym1 (l :: TyFun a6989586621679834003 (TyFun b6989586621679834004 b6989586621679834004 -> Type) -> Type) (l :: TyFun b6989586621679834004 (TyFun [a6989586621679834003] (NonEmpty b6989586621679834004) -> Type)) Source #

Instances
SuppressUnusedWarnings (ScanrSym1 :: (TyFun a6989586621679834003 (TyFun b6989586621679834004 b6989586621679834004 -> Type) -> Type) -> TyFun b6989586621679834004 (TyFun [a6989586621679834003] (NonEmpty b6989586621679834004) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ScanrSym1 l1 :: TyFun b6989586621679834004 (TyFun [a6989586621679834003] (NonEmpty b6989586621679834004) -> Type) -> *) (l2 :: b6989586621679834004) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ScanrSym1 l1 :: TyFun b6989586621679834004 (TyFun [a6989586621679834003] (NonEmpty b6989586621679834004) -> Type) -> *) (l2 :: b6989586621679834004) = ScanrSym2 l1 l2

data ScanrSym2 (l :: TyFun a6989586621679834003 (TyFun b6989586621679834004 b6989586621679834004 -> Type) -> Type) (l :: b6989586621679834004) (l :: TyFun [a6989586621679834003] (NonEmpty b6989586621679834004)) Source #

Instances
SuppressUnusedWarnings (ScanrSym2 :: (TyFun a6989586621679834003 (TyFun b6989586621679834004 b6989586621679834004 -> Type) -> Type) -> b6989586621679834004 -> TyFun [a6989586621679834003] (NonEmpty b6989586621679834004) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ScanrSym2 l1 l2 :: TyFun [a] (NonEmpty b) -> *) (l3 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ScanrSym2 l1 l2 :: TyFun [a] (NonEmpty b) -> *) (l3 :: [a]) = Scanr l1 l2 l3

type ScanrSym3 (t :: TyFun a6989586621679834003 (TyFun b6989586621679834004 b6989586621679834004 -> Type) -> Type) (t :: b6989586621679834004) (t :: [a6989586621679834003]) = Scanr t t t Source #

data Scanl1Sym0 (l :: TyFun (TyFun a6989586621679834002 (TyFun a6989586621679834002 a6989586621679834002 -> Type) -> Type) (TyFun (NonEmpty a6989586621679834002) (NonEmpty a6989586621679834002) -> Type)) Source #

Instances
SuppressUnusedWarnings (Scanl1Sym0 :: TyFun (TyFun a6989586621679834002 (TyFun a6989586621679834002 a6989586621679834002 -> Type) -> Type) (TyFun (NonEmpty a6989586621679834002) (NonEmpty a6989586621679834002) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (Scanl1Sym0 :: TyFun (TyFun a6989586621679834002 (TyFun a6989586621679834002 a6989586621679834002 -> Type) -> Type) (TyFun (NonEmpty a6989586621679834002) (NonEmpty a6989586621679834002) -> Type) -> *) (l :: TyFun a6989586621679834002 (TyFun a6989586621679834002 a6989586621679834002 -> Type) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (Scanl1Sym0 :: TyFun (TyFun a6989586621679834002 (TyFun a6989586621679834002 a6989586621679834002 -> Type) -> Type) (TyFun (NonEmpty a6989586621679834002) (NonEmpty a6989586621679834002) -> Type) -> *) (l :: TyFun a6989586621679834002 (TyFun a6989586621679834002 a6989586621679834002 -> Type) -> Type) = Scanl1Sym1 l

data Scanl1Sym1 (l :: TyFun a6989586621679834002 (TyFun a6989586621679834002 a6989586621679834002 -> Type) -> Type) (l :: TyFun (NonEmpty a6989586621679834002) (NonEmpty a6989586621679834002)) Source #

Instances
SuppressUnusedWarnings (Scanl1Sym1 :: (TyFun a6989586621679834002 (TyFun a6989586621679834002 a6989586621679834002 -> Type) -> Type) -> TyFun (NonEmpty a6989586621679834002) (NonEmpty a6989586621679834002) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (Scanl1Sym1 l1 :: TyFun (NonEmpty a) (NonEmpty a) -> *) (l2 :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (Scanl1Sym1 l1 :: TyFun (NonEmpty a) (NonEmpty a) -> *) (l2 :: NonEmpty a) = Scanl1 l1 l2

type Scanl1Sym2 (t :: TyFun a6989586621679834002 (TyFun a6989586621679834002 a6989586621679834002 -> Type) -> Type) (t :: NonEmpty a6989586621679834002) = Scanl1 t t Source #

data Scanr1Sym0 (l :: TyFun (TyFun a6989586621679834001 (TyFun a6989586621679834001 a6989586621679834001 -> Type) -> Type) (TyFun (NonEmpty a6989586621679834001) (NonEmpty a6989586621679834001) -> Type)) Source #

Instances
SuppressUnusedWarnings (Scanr1Sym0 :: TyFun (TyFun a6989586621679834001 (TyFun a6989586621679834001 a6989586621679834001 -> Type) -> Type) (TyFun (NonEmpty a6989586621679834001) (NonEmpty a6989586621679834001) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (Scanr1Sym0 :: TyFun (TyFun a6989586621679834001 (TyFun a6989586621679834001 a6989586621679834001 -> Type) -> Type) (TyFun (NonEmpty a6989586621679834001) (NonEmpty a6989586621679834001) -> Type) -> *) (l :: TyFun a6989586621679834001 (TyFun a6989586621679834001 a6989586621679834001 -> Type) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (Scanr1Sym0 :: TyFun (TyFun a6989586621679834001 (TyFun a6989586621679834001 a6989586621679834001 -> Type) -> Type) (TyFun (NonEmpty a6989586621679834001) (NonEmpty a6989586621679834001) -> Type) -> *) (l :: TyFun a6989586621679834001 (TyFun a6989586621679834001 a6989586621679834001 -> Type) -> Type) = Scanr1Sym1 l

data Scanr1Sym1 (l :: TyFun a6989586621679834001 (TyFun a6989586621679834001 a6989586621679834001 -> Type) -> Type) (l :: TyFun (NonEmpty a6989586621679834001) (NonEmpty a6989586621679834001)) Source #

Instances
SuppressUnusedWarnings (Scanr1Sym1 :: (TyFun a6989586621679834001 (TyFun a6989586621679834001 a6989586621679834001 -> Type) -> Type) -> TyFun (NonEmpty a6989586621679834001) (NonEmpty a6989586621679834001) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (Scanr1Sym1 l1 :: TyFun (NonEmpty a) (NonEmpty a) -> *) (l2 :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (Scanr1Sym1 l1 :: TyFun (NonEmpty a) (NonEmpty a) -> *) (l2 :: NonEmpty a) = Scanr1 l1 l2

type Scanr1Sym2 (t :: TyFun a6989586621679834001 (TyFun a6989586621679834001 a6989586621679834001 -> Type) -> Type) (t :: NonEmpty a6989586621679834001) = Scanr1 t t Source #

data TransposeSym0 (l :: TyFun (NonEmpty (NonEmpty a6989586621679833966)) (NonEmpty (NonEmpty a6989586621679833966))) Source #

Instances
SuppressUnusedWarnings (TransposeSym0 :: TyFun (NonEmpty (NonEmpty a6989586621679833966)) (NonEmpty (NonEmpty a6989586621679833966)) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (TransposeSym0 :: TyFun (NonEmpty (NonEmpty a)) (NonEmpty (NonEmpty a)) -> *) (l :: NonEmpty (NonEmpty a)) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type TransposeSym1 (t :: NonEmpty (NonEmpty a6989586621679833966)) = Transpose t Source #

data SortBySym0 (l :: TyFun (TyFun a6989586621679833965 (TyFun a6989586621679833965 Ordering -> Type) -> Type) (TyFun (NonEmpty a6989586621679833965) (NonEmpty a6989586621679833965) -> Type)) Source #

Instances
SuppressUnusedWarnings (SortBySym0 :: TyFun (TyFun a6989586621679833965 (TyFun a6989586621679833965 Ordering -> Type) -> Type) (TyFun (NonEmpty a6989586621679833965) (NonEmpty a6989586621679833965) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (SortBySym0 :: TyFun (TyFun a6989586621679833965 (TyFun a6989586621679833965 Ordering -> Type) -> Type) (TyFun (NonEmpty a6989586621679833965) (NonEmpty a6989586621679833965) -> Type) -> *) (l :: TyFun a6989586621679833965 (TyFun a6989586621679833965 Ordering -> Type) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (SortBySym0 :: TyFun (TyFun a6989586621679833965 (TyFun a6989586621679833965 Ordering -> Type) -> Type) (TyFun (NonEmpty a6989586621679833965) (NonEmpty a6989586621679833965) -> Type) -> *) (l :: TyFun a6989586621679833965 (TyFun a6989586621679833965 Ordering -> Type) -> Type) = SortBySym1 l

data SortBySym1 (l :: TyFun a6989586621679833965 (TyFun a6989586621679833965 Ordering -> Type) -> Type) (l :: TyFun (NonEmpty a6989586621679833965) (NonEmpty a6989586621679833965)) Source #

Instances
SuppressUnusedWarnings (SortBySym1 :: (TyFun a6989586621679833965 (TyFun a6989586621679833965 Ordering -> Type) -> Type) -> TyFun (NonEmpty a6989586621679833965) (NonEmpty a6989586621679833965) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (SortBySym1 l1 :: TyFun (NonEmpty a) (NonEmpty a) -> *) (l2 :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (SortBySym1 l1 :: TyFun (NonEmpty a) (NonEmpty a) -> *) (l2 :: NonEmpty a) = SortBy l1 l2

type SortBySym2 (t :: TyFun a6989586621679833965 (TyFun a6989586621679833965 Ordering -> Type) -> Type) (t :: NonEmpty a6989586621679833965) = SortBy t t Source #

data SortWithSym0 (l :: TyFun (TyFun a6989586621679833964 o6989586621679833963 -> Type) (TyFun (NonEmpty a6989586621679833964) (NonEmpty a6989586621679833964) -> Type)) Source #

Instances
SuppressUnusedWarnings (SortWithSym0 :: TyFun (TyFun a6989586621679833964 o6989586621679833963 -> Type) (TyFun (NonEmpty a6989586621679833964) (NonEmpty a6989586621679833964) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (SortWithSym0 :: TyFun (TyFun a6989586621679833964 o6989586621679833963 -> Type) (TyFun (NonEmpty a6989586621679833964) (NonEmpty a6989586621679833964) -> Type) -> *) (l :: TyFun a6989586621679833964 o6989586621679833963 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (SortWithSym0 :: TyFun (TyFun a6989586621679833964 o6989586621679833963 -> Type) (TyFun (NonEmpty a6989586621679833964) (NonEmpty a6989586621679833964) -> Type) -> *) (l :: TyFun a6989586621679833964 o6989586621679833963 -> Type) = SortWithSym1 l

data SortWithSym1 (l :: TyFun a6989586621679833964 o6989586621679833963 -> Type) (l :: TyFun (NonEmpty a6989586621679833964) (NonEmpty a6989586621679833964)) Source #

Instances
SuppressUnusedWarnings (SortWithSym1 :: (TyFun a6989586621679833964 o6989586621679833963 -> Type) -> TyFun (NonEmpty a6989586621679833964) (NonEmpty a6989586621679833964) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (SortWithSym1 l1 :: TyFun (NonEmpty a) (NonEmpty a) -> *) (l2 :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (SortWithSym1 l1 :: TyFun (NonEmpty a) (NonEmpty a) -> *) (l2 :: NonEmpty a) = SortWith l1 l2

type SortWithSym2 (t :: TyFun a6989586621679833964 o6989586621679833963 -> Type) (t :: NonEmpty a6989586621679833964) = SortWith t t Source #

data LengthSym0 (l :: TyFun (NonEmpty a6989586621679834029) Nat) Source #

Instances
SuppressUnusedWarnings (LengthSym0 :: TyFun (NonEmpty a6989586621679834029) Nat -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (LengthSym0 :: TyFun (NonEmpty a) Nat -> *) (l :: NonEmpty a) = Length l

type LengthSym1 (t :: NonEmpty a6989586621679834029) = Length t Source #

data HeadSym0 (l :: TyFun (NonEmpty a6989586621679834022) a6989586621679834022) Source #

Instances
SuppressUnusedWarnings (HeadSym0 :: TyFun (NonEmpty a6989586621679834022) a6989586621679834022 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (HeadSym0 :: TyFun (NonEmpty a) a -> *) (l :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (HeadSym0 :: TyFun (NonEmpty a) a -> *) (l :: NonEmpty a) = Head l

type HeadSym1 (t :: NonEmpty a6989586621679834022) = Head t Source #

data TailSym0 (l :: TyFun (NonEmpty a6989586621679834021) [a6989586621679834021]) Source #

Instances
SuppressUnusedWarnings (TailSym0 :: TyFun (NonEmpty a6989586621679834021) [a6989586621679834021] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (TailSym0 :: TyFun (NonEmpty a) [a] -> *) (l :: NonEmpty a) = Tail l

type TailSym1 (t :: NonEmpty a6989586621679834021) = Tail t Source #

data LastSym0 (l :: TyFun (NonEmpty a6989586621679834020) a6989586621679834020) Source #

Instances
SuppressUnusedWarnings (LastSym0 :: TyFun (NonEmpty a6989586621679834020) a6989586621679834020 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (LastSym0 :: TyFun (NonEmpty a) a -> *) (l :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (LastSym0 :: TyFun (NonEmpty a) a -> *) (l :: NonEmpty a) = Last l

type LastSym1 (t :: NonEmpty a6989586621679834020) = Last t Source #

data InitSym0 (l :: TyFun (NonEmpty a6989586621679834019) [a6989586621679834019]) Source #

Instances
SuppressUnusedWarnings (InitSym0 :: TyFun (NonEmpty a6989586621679834019) [a6989586621679834019] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (InitSym0 :: TyFun (NonEmpty a) [a] -> *) (l :: NonEmpty a) = Init l

type InitSym1 (t :: NonEmpty a6989586621679834019) = Init t Source #

data (<|@#@$) (l :: TyFun a6989586621679834018 (TyFun (NonEmpty a6989586621679834018) (NonEmpty a6989586621679834018) -> Type)) Source #

Instances
SuppressUnusedWarnings ((<|@#@$) :: TyFun a6989586621679834018 (TyFun (NonEmpty a6989586621679834018) (NonEmpty a6989586621679834018) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply ((<|@#@$) :: TyFun a6989586621679834018 (TyFun (NonEmpty a6989586621679834018) (NonEmpty a6989586621679834018) -> Type) -> *) (l :: a6989586621679834018) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply ((<|@#@$) :: TyFun a6989586621679834018 (TyFun (NonEmpty a6989586621679834018) (NonEmpty a6989586621679834018) -> Type) -> *) (l :: a6989586621679834018) = (<|@#@$$) l

data (l :: a6989586621679834018) <|@#@$$ (l :: TyFun (NonEmpty a6989586621679834018) (NonEmpty a6989586621679834018)) Source #

Instances
SuppressUnusedWarnings ((<|@#@$$) :: a6989586621679834018 -> TyFun (NonEmpty a6989586621679834018) (NonEmpty a6989586621679834018) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply ((<|@#@$$) l1 :: TyFun (NonEmpty a) (NonEmpty a) -> *) (l2 :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply ((<|@#@$$) l1 :: TyFun (NonEmpty a) (NonEmpty a) -> *) (l2 :: NonEmpty a) = l1 <| l2

type (<|@#@$$$) (t :: a6989586621679834018) (t :: NonEmpty a6989586621679834018) = (<|) t t Source #

data ConsSym0 (l :: TyFun a6989586621679834017 (TyFun (NonEmpty a6989586621679834017) (NonEmpty a6989586621679834017) -> Type)) Source #

Instances
SuppressUnusedWarnings (ConsSym0 :: TyFun a6989586621679834017 (TyFun (NonEmpty a6989586621679834017) (NonEmpty a6989586621679834017) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ConsSym0 :: TyFun a6989586621679834017 (TyFun (NonEmpty a6989586621679834017) (NonEmpty a6989586621679834017) -> Type) -> *) (l :: a6989586621679834017) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ConsSym0 :: TyFun a6989586621679834017 (TyFun (NonEmpty a6989586621679834017) (NonEmpty a6989586621679834017) -> Type) -> *) (l :: a6989586621679834017) = ConsSym1 l

data ConsSym1 (l :: a6989586621679834017) (l :: TyFun (NonEmpty a6989586621679834017) (NonEmpty a6989586621679834017)) Source #

Instances
SuppressUnusedWarnings (ConsSym1 :: a6989586621679834017 -> TyFun (NonEmpty a6989586621679834017) (NonEmpty a6989586621679834017) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ConsSym1 l1 :: TyFun (NonEmpty a) (NonEmpty a) -> *) (l2 :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ConsSym1 l1 :: TyFun (NonEmpty a) (NonEmpty a) -> *) (l2 :: NonEmpty a) = Cons l1 l2

type ConsSym2 (t :: a6989586621679834017) (t :: NonEmpty a6989586621679834017) = Cons t t Source #

data UnconsSym0 (l :: TyFun (NonEmpty a6989586621679834025) (a6989586621679834025, Maybe (NonEmpty a6989586621679834025))) Source #

Instances
SuppressUnusedWarnings (UnconsSym0 :: TyFun (NonEmpty a6989586621679834025) (a6989586621679834025, Maybe (NonEmpty a6989586621679834025)) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (UnconsSym0 :: TyFun (NonEmpty a) (a, Maybe (NonEmpty a)) -> *) (l :: NonEmpty a) = Uncons l

type UnconsSym1 (t :: NonEmpty a6989586621679834025) = Uncons t Source #

data UnfoldrSym0 (l :: TyFun (TyFun a6989586621679834023 (b6989586621679834024, Maybe a6989586621679834023) -> Type) (TyFun a6989586621679834023 (NonEmpty b6989586621679834024) -> Type)) Source #

Instances
SuppressUnusedWarnings (UnfoldrSym0 :: TyFun (TyFun a6989586621679834023 (b6989586621679834024, Maybe a6989586621679834023) -> Type) (TyFun a6989586621679834023 (NonEmpty b6989586621679834024) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (UnfoldrSym0 :: TyFun (TyFun a6989586621679834023 (b6989586621679834024, Maybe a6989586621679834023) -> Type) (TyFun a6989586621679834023 (NonEmpty b6989586621679834024) -> Type) -> *) (l :: TyFun a6989586621679834023 (b6989586621679834024, Maybe a6989586621679834023) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (UnfoldrSym0 :: TyFun (TyFun a6989586621679834023 (b6989586621679834024, Maybe a6989586621679834023) -> Type) (TyFun a6989586621679834023 (NonEmpty b6989586621679834024) -> Type) -> *) (l :: TyFun a6989586621679834023 (b6989586621679834024, Maybe a6989586621679834023) -> Type) = UnfoldrSym1 l

data UnfoldrSym1 (l :: TyFun a6989586621679834023 (b6989586621679834024, Maybe a6989586621679834023) -> Type) (l :: TyFun a6989586621679834023 (NonEmpty b6989586621679834024)) Source #

Instances
SuppressUnusedWarnings (UnfoldrSym1 :: (TyFun a6989586621679834023 (b6989586621679834024, Maybe a6989586621679834023) -> Type) -> TyFun a6989586621679834023 (NonEmpty b6989586621679834024) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (UnfoldrSym1 l1 :: TyFun a (NonEmpty b) -> *) (l2 :: a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (UnfoldrSym1 l1 :: TyFun a (NonEmpty b) -> *) (l2 :: a) = Unfoldr l1 l2

type UnfoldrSym2 (t :: TyFun a6989586621679834023 (b6989586621679834024, Maybe a6989586621679834023) -> Type) (t :: a6989586621679834023) = Unfoldr t t Source #

data SortSym0 (l :: TyFun (NonEmpty a6989586621679834016) (NonEmpty a6989586621679834016)) Source #

Instances
SuppressUnusedWarnings (SortSym0 :: TyFun (NonEmpty a6989586621679834016) (NonEmpty a6989586621679834016) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (SortSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> *) (l :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (SortSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> *) (l :: NonEmpty a) = Sort l

type SortSym1 (t :: NonEmpty a6989586621679834016) = Sort t Source #

data ReverseSym0 (l :: TyFun (NonEmpty a6989586621679833999) (NonEmpty a6989586621679833999)) Source #

Instances
SuppressUnusedWarnings (ReverseSym0 :: TyFun (NonEmpty a6989586621679833999) (NonEmpty a6989586621679833999) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ReverseSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> *) (l :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ReverseSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> *) (l :: NonEmpty a) = Reverse l

type ReverseSym1 (t :: NonEmpty a6989586621679833999) = Reverse t Source #

data InitsSym0 (l :: TyFun [a6989586621679834009] (NonEmpty [a6989586621679834009])) Source #

Instances
SuppressUnusedWarnings (InitsSym0 :: TyFun [a6989586621679834009] (NonEmpty [a6989586621679834009]) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (InitsSym0 :: TyFun [a] (NonEmpty [a]) -> *) (l :: [a]) = Inits l

type InitsSym1 (t :: [a6989586621679834009]) = Inits t Source #

data TailsSym0 (l :: TyFun [a6989586621679834008] (NonEmpty [a6989586621679834008])) Source #

Instances
SuppressUnusedWarnings (TailsSym0 :: TyFun [a6989586621679834008] (NonEmpty [a6989586621679834008]) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (TailsSym0 :: TyFun [a] (NonEmpty [a]) -> *) (l :: [a]) = Tails l

type TailsSym1 (t :: [a6989586621679834008]) = Tails t Source #

data UnfoldSym0 (l :: TyFun (TyFun a6989586621679834027 (b6989586621679834028, Maybe a6989586621679834027) -> Type) (TyFun a6989586621679834027 (NonEmpty b6989586621679834028) -> Type)) Source #

Instances
SuppressUnusedWarnings (UnfoldSym0 :: TyFun (TyFun a6989586621679834027 (b6989586621679834028, Maybe a6989586621679834027) -> Type) (TyFun a6989586621679834027 (NonEmpty b6989586621679834028) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (UnfoldSym0 :: TyFun (TyFun a6989586621679834027 (b6989586621679834028, Maybe a6989586621679834027) -> Type) (TyFun a6989586621679834027 (NonEmpty b6989586621679834028) -> Type) -> *) (l :: TyFun a6989586621679834027 (b6989586621679834028, Maybe a6989586621679834027) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (UnfoldSym0 :: TyFun (TyFun a6989586621679834027 (b6989586621679834028, Maybe a6989586621679834027) -> Type) (TyFun a6989586621679834027 (NonEmpty b6989586621679834028) -> Type) -> *) (l :: TyFun a6989586621679834027 (b6989586621679834028, Maybe a6989586621679834027) -> Type) = UnfoldSym1 l

data UnfoldSym1 (l :: TyFun a6989586621679834027 (b6989586621679834028, Maybe a6989586621679834027) -> Type) (l :: TyFun a6989586621679834027 (NonEmpty b6989586621679834028)) Source #

Instances
SuppressUnusedWarnings (UnfoldSym1 :: (TyFun a6989586621679834027 (b6989586621679834028, Maybe a6989586621679834027) -> Type) -> TyFun a6989586621679834027 (NonEmpty b6989586621679834028) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (UnfoldSym1 l1 :: TyFun a (NonEmpty b) -> *) (l2 :: a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (UnfoldSym1 l1 :: TyFun a (NonEmpty b) -> *) (l2 :: a) = Unfold l1 l2

data InsertSym0 (l :: TyFun a6989586621679834007 (TyFun [a6989586621679834007] (NonEmpty a6989586621679834007) -> Type)) Source #

Instances
SuppressUnusedWarnings (InsertSym0 :: TyFun a6989586621679834007 (TyFun [a6989586621679834007] (NonEmpty a6989586621679834007) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (InsertSym0 :: TyFun a6989586621679834007 (TyFun [a6989586621679834007] (NonEmpty a6989586621679834007) -> Type) -> *) (l :: a6989586621679834007) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (InsertSym0 :: TyFun a6989586621679834007 (TyFun [a6989586621679834007] (NonEmpty a6989586621679834007) -> Type) -> *) (l :: a6989586621679834007) = InsertSym1 l

data InsertSym1 (l :: a6989586621679834007) (l :: TyFun [a6989586621679834007] (NonEmpty a6989586621679834007)) Source #

Instances
SuppressUnusedWarnings (InsertSym1 :: a6989586621679834007 -> TyFun [a6989586621679834007] (NonEmpty a6989586621679834007) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (InsertSym1 l1 :: TyFun [a] (NonEmpty a) -> *) (l2 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (InsertSym1 l1 :: TyFun [a] (NonEmpty a) -> *) (l2 :: [a]) = Insert l1 l2

type InsertSym2 (t :: a6989586621679834007) (t :: [a6989586621679834007]) = Insert t t Source #

data TakeSym0 (l :: TyFun Nat (TyFun (NonEmpty a6989586621679833998) [a6989586621679833998] -> Type)) Source #

Instances
SuppressUnusedWarnings (TakeSym0 :: TyFun Nat (TyFun (NonEmpty a6989586621679833998) [a6989586621679833998] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (TakeSym0 :: TyFun Nat (TyFun (NonEmpty a6989586621679833998) [a6989586621679833998] -> Type) -> *) (l :: Nat) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (TakeSym0 :: TyFun Nat (TyFun (NonEmpty a6989586621679833998) [a6989586621679833998] -> Type) -> *) (l :: Nat) = (TakeSym1 l :: TyFun (NonEmpty a6989586621679833998) [a6989586621679833998] -> *)

data TakeSym1 (l :: Nat) (l :: TyFun (NonEmpty a6989586621679833998) [a6989586621679833998]) Source #

Instances
SuppressUnusedWarnings (TakeSym1 :: Nat -> TyFun (NonEmpty a6989586621679833998) [a6989586621679833998] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (TakeSym1 l1 :: TyFun (NonEmpty a) [a] -> *) (l2 :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (TakeSym1 l1 :: TyFun (NonEmpty a) [a] -> *) (l2 :: NonEmpty a) = Take l1 l2

type TakeSym2 (t :: Nat) (t :: NonEmpty a6989586621679833998) = Take t t Source #

data DropSym0 (l :: TyFun Nat (TyFun (NonEmpty a6989586621679833997) [a6989586621679833997] -> Type)) Source #

Instances
SuppressUnusedWarnings (DropSym0 :: TyFun Nat (TyFun (NonEmpty a6989586621679833997) [a6989586621679833997] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (DropSym0 :: TyFun Nat (TyFun (NonEmpty a6989586621679833997) [a6989586621679833997] -> Type) -> *) (l :: Nat) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (DropSym0 :: TyFun Nat (TyFun (NonEmpty a6989586621679833997) [a6989586621679833997] -> Type) -> *) (l :: Nat) = (DropSym1 l :: TyFun (NonEmpty a6989586621679833997) [a6989586621679833997] -> *)

data DropSym1 (l :: Nat) (l :: TyFun (NonEmpty a6989586621679833997) [a6989586621679833997]) Source #

Instances
SuppressUnusedWarnings (DropSym1 :: Nat -> TyFun (NonEmpty a6989586621679833997) [a6989586621679833997] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (DropSym1 l1 :: TyFun (NonEmpty a) [a] -> *) (l2 :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (DropSym1 l1 :: TyFun (NonEmpty a) [a] -> *) (l2 :: NonEmpty a) = Drop l1 l2

type DropSym2 (t :: Nat) (t :: NonEmpty a6989586621679833997) = Drop t t Source #

data SplitAtSym0 (l :: TyFun Nat (TyFun (NonEmpty a6989586621679833996) ([a6989586621679833996], [a6989586621679833996]) -> Type)) Source #

Instances
SuppressUnusedWarnings (SplitAtSym0 :: TyFun Nat (TyFun (NonEmpty a6989586621679833996) ([a6989586621679833996], [a6989586621679833996]) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (SplitAtSym0 :: TyFun Nat (TyFun (NonEmpty a6989586621679833996) ([a6989586621679833996], [a6989586621679833996]) -> Type) -> *) (l :: Nat) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (SplitAtSym0 :: TyFun Nat (TyFun (NonEmpty a6989586621679833996) ([a6989586621679833996], [a6989586621679833996]) -> Type) -> *) (l :: Nat) = (SplitAtSym1 l :: TyFun (NonEmpty a6989586621679833996) ([a6989586621679833996], [a6989586621679833996]) -> *)

data SplitAtSym1 (l :: Nat) (l :: TyFun (NonEmpty a6989586621679833996) ([a6989586621679833996], [a6989586621679833996])) Source #

Instances
SuppressUnusedWarnings (SplitAtSym1 :: Nat -> TyFun (NonEmpty a6989586621679833996) ([a6989586621679833996], [a6989586621679833996]) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (SplitAtSym1 l1 :: TyFun (NonEmpty a) ([a], [a]) -> *) (l2 :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (SplitAtSym1 l1 :: TyFun (NonEmpty a) ([a], [a]) -> *) (l2 :: NonEmpty a) = SplitAt l1 l2

type SplitAtSym2 (t :: Nat) (t :: NonEmpty a6989586621679833996) = SplitAt t t Source #

data TakeWhileSym0 (l :: TyFun (TyFun a6989586621679833995 Bool -> Type) (TyFun (NonEmpty a6989586621679833995) [a6989586621679833995] -> Type)) Source #

Instances
SuppressUnusedWarnings (TakeWhileSym0 :: TyFun (TyFun a6989586621679833995 Bool -> Type) (TyFun (NonEmpty a6989586621679833995) [a6989586621679833995] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (TakeWhileSym0 :: TyFun (TyFun a6989586621679833995 Bool -> Type) (TyFun (NonEmpty a6989586621679833995) [a6989586621679833995] -> Type) -> *) (l :: TyFun a6989586621679833995 Bool -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (TakeWhileSym0 :: TyFun (TyFun a6989586621679833995 Bool -> Type) (TyFun (NonEmpty a6989586621679833995) [a6989586621679833995] -> Type) -> *) (l :: TyFun a6989586621679833995 Bool -> Type) = TakeWhileSym1 l

data TakeWhileSym1 (l :: TyFun a6989586621679833995 Bool -> Type) (l :: TyFun (NonEmpty a6989586621679833995) [a6989586621679833995]) Source #

Instances
SuppressUnusedWarnings (TakeWhileSym1 :: (TyFun a6989586621679833995 Bool -> Type) -> TyFun (NonEmpty a6989586621679833995) [a6989586621679833995] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (TakeWhileSym1 l1 :: TyFun (NonEmpty a) [a] -> *) (l2 :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (TakeWhileSym1 l1 :: TyFun (NonEmpty a) [a] -> *) (l2 :: NonEmpty a) = TakeWhile l1 l2

type TakeWhileSym2 (t :: TyFun a6989586621679833995 Bool -> Type) (t :: NonEmpty a6989586621679833995) = TakeWhile t t Source #

data DropWhileSym0 (l :: TyFun (TyFun a6989586621679833994 Bool -> Type) (TyFun (NonEmpty a6989586621679833994) [a6989586621679833994] -> Type)) Source #

Instances
SuppressUnusedWarnings (DropWhileSym0 :: TyFun (TyFun a6989586621679833994 Bool -> Type) (TyFun (NonEmpty a6989586621679833994) [a6989586621679833994] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (DropWhileSym0 :: TyFun (TyFun a6989586621679833994 Bool -> Type) (TyFun (NonEmpty a6989586621679833994) [a6989586621679833994] -> Type) -> *) (l :: TyFun a6989586621679833994 Bool -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (DropWhileSym0 :: TyFun (TyFun a6989586621679833994 Bool -> Type) (TyFun (NonEmpty a6989586621679833994) [a6989586621679833994] -> Type) -> *) (l :: TyFun a6989586621679833994 Bool -> Type) = DropWhileSym1 l

data DropWhileSym1 (l :: TyFun a6989586621679833994 Bool -> Type) (l :: TyFun (NonEmpty a6989586621679833994) [a6989586621679833994]) Source #

Instances
SuppressUnusedWarnings (DropWhileSym1 :: (TyFun a6989586621679833994 Bool -> Type) -> TyFun (NonEmpty a6989586621679833994) [a6989586621679833994] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (DropWhileSym1 l1 :: TyFun (NonEmpty a) [a] -> *) (l2 :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (DropWhileSym1 l1 :: TyFun (NonEmpty a) [a] -> *) (l2 :: NonEmpty a) = DropWhile l1 l2

type DropWhileSym2 (t :: TyFun a6989586621679833994 Bool -> Type) (t :: NonEmpty a6989586621679833994) = DropWhile t t Source #

data SpanSym0 (l :: TyFun (TyFun a6989586621679833993 Bool -> Type) (TyFun (NonEmpty a6989586621679833993) ([a6989586621679833993], [a6989586621679833993]) -> Type)) Source #

Instances
SuppressUnusedWarnings (SpanSym0 :: TyFun (TyFun a6989586621679833993 Bool -> Type) (TyFun (NonEmpty a6989586621679833993) ([a6989586621679833993], [a6989586621679833993]) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (SpanSym0 :: TyFun (TyFun a6989586621679833993 Bool -> Type) (TyFun (NonEmpty a6989586621679833993) ([a6989586621679833993], [a6989586621679833993]) -> Type) -> *) (l :: TyFun a6989586621679833993 Bool -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (SpanSym0 :: TyFun (TyFun a6989586621679833993 Bool -> Type) (TyFun (NonEmpty a6989586621679833993) ([a6989586621679833993], [a6989586621679833993]) -> Type) -> *) (l :: TyFun a6989586621679833993 Bool -> Type) = SpanSym1 l

data SpanSym1 (l :: TyFun a6989586621679833993 Bool -> Type) (l :: TyFun (NonEmpty a6989586621679833993) ([a6989586621679833993], [a6989586621679833993])) Source #

Instances
SuppressUnusedWarnings (SpanSym1 :: (TyFun a6989586621679833993 Bool -> Type) -> TyFun (NonEmpty a6989586621679833993) ([a6989586621679833993], [a6989586621679833993]) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (SpanSym1 l1 :: TyFun (NonEmpty a) ([a], [a]) -> *) (l2 :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (SpanSym1 l1 :: TyFun (NonEmpty a) ([a], [a]) -> *) (l2 :: NonEmpty a) = Span l1 l2

type SpanSym2 (t :: TyFun a6989586621679833993 Bool -> Type) (t :: NonEmpty a6989586621679833993) = Span t t Source #

data BreakSym0 (l :: TyFun (TyFun a6989586621679833992 Bool -> Type) (TyFun (NonEmpty a6989586621679833992) ([a6989586621679833992], [a6989586621679833992]) -> Type)) Source #

Instances
SuppressUnusedWarnings (BreakSym0 :: TyFun (TyFun a6989586621679833992 Bool -> Type) (TyFun (NonEmpty a6989586621679833992) ([a6989586621679833992], [a6989586621679833992]) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (BreakSym0 :: TyFun (TyFun a6989586621679833992 Bool -> Type) (TyFun (NonEmpty a6989586621679833992) ([a6989586621679833992], [a6989586621679833992]) -> Type) -> *) (l :: TyFun a6989586621679833992 Bool -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (BreakSym0 :: TyFun (TyFun a6989586621679833992 Bool -> Type) (TyFun (NonEmpty a6989586621679833992) ([a6989586621679833992], [a6989586621679833992]) -> Type) -> *) (l :: TyFun a6989586621679833992 Bool -> Type) = BreakSym1 l

data BreakSym1 (l :: TyFun a6989586621679833992 Bool -> Type) (l :: TyFun (NonEmpty a6989586621679833992) ([a6989586621679833992], [a6989586621679833992])) Source #

Instances
SuppressUnusedWarnings (BreakSym1 :: (TyFun a6989586621679833992 Bool -> Type) -> TyFun (NonEmpty a6989586621679833992) ([a6989586621679833992], [a6989586621679833992]) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (BreakSym1 l1 :: TyFun (NonEmpty a) ([a], [a]) -> *) (l2 :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (BreakSym1 l1 :: TyFun (NonEmpty a) ([a], [a]) -> *) (l2 :: NonEmpty a) = Break l1 l2

type BreakSym2 (t :: TyFun a6989586621679833992 Bool -> Type) (t :: NonEmpty a6989586621679833992) = Break t t Source #

data FilterSym0 (l :: TyFun (TyFun a6989586621679833991 Bool -> Type) (TyFun (NonEmpty a6989586621679833991) [a6989586621679833991] -> Type)) Source #

Instances
SuppressUnusedWarnings (FilterSym0 :: TyFun (TyFun a6989586621679833991 Bool -> Type) (TyFun (NonEmpty a6989586621679833991) [a6989586621679833991] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (FilterSym0 :: TyFun (TyFun a6989586621679833991 Bool -> Type) (TyFun (NonEmpty a6989586621679833991) [a6989586621679833991] -> Type) -> *) (l :: TyFun a6989586621679833991 Bool -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (FilterSym0 :: TyFun (TyFun a6989586621679833991 Bool -> Type) (TyFun (NonEmpty a6989586621679833991) [a6989586621679833991] -> Type) -> *) (l :: TyFun a6989586621679833991 Bool -> Type) = FilterSym1 l

data FilterSym1 (l :: TyFun a6989586621679833991 Bool -> Type) (l :: TyFun (NonEmpty a6989586621679833991) [a6989586621679833991]) Source #

Instances
SuppressUnusedWarnings (FilterSym1 :: (TyFun a6989586621679833991 Bool -> Type) -> TyFun (NonEmpty a6989586621679833991) [a6989586621679833991] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (FilterSym1 l1 :: TyFun (NonEmpty a) [a] -> *) (l2 :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (FilterSym1 l1 :: TyFun (NonEmpty a) [a] -> *) (l2 :: NonEmpty a) = Filter l1 l2

type FilterSym2 (t :: TyFun a6989586621679833991 Bool -> Type) (t :: NonEmpty a6989586621679833991) = Filter t t Source #

data PartitionSym0 (l :: TyFun (TyFun a6989586621679833990 Bool -> Type) (TyFun (NonEmpty a6989586621679833990) ([a6989586621679833990], [a6989586621679833990]) -> Type)) Source #

Instances
SuppressUnusedWarnings (PartitionSym0 :: TyFun (TyFun a6989586621679833990 Bool -> Type) (TyFun (NonEmpty a6989586621679833990) ([a6989586621679833990], [a6989586621679833990]) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (PartitionSym0 :: TyFun (TyFun a6989586621679833990 Bool -> Type) (TyFun (NonEmpty a6989586621679833990) ([a6989586621679833990], [a6989586621679833990]) -> Type) -> *) (l :: TyFun a6989586621679833990 Bool -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (PartitionSym0 :: TyFun (TyFun a6989586621679833990 Bool -> Type) (TyFun (NonEmpty a6989586621679833990) ([a6989586621679833990], [a6989586621679833990]) -> Type) -> *) (l :: TyFun a6989586621679833990 Bool -> Type) = PartitionSym1 l

data PartitionSym1 (l :: TyFun a6989586621679833990 Bool -> Type) (l :: TyFun (NonEmpty a6989586621679833990) ([a6989586621679833990], [a6989586621679833990])) Source #

Instances
SuppressUnusedWarnings (PartitionSym1 :: (TyFun a6989586621679833990 Bool -> Type) -> TyFun (NonEmpty a6989586621679833990) ([a6989586621679833990], [a6989586621679833990]) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (PartitionSym1 l1 :: TyFun (NonEmpty a) ([a], [a]) -> *) (l2 :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (PartitionSym1 l1 :: TyFun (NonEmpty a) ([a], [a]) -> *) (l2 :: NonEmpty a) = Partition l1 l2

type PartitionSym2 (t :: TyFun a6989586621679833990 Bool -> Type) (t :: NonEmpty a6989586621679833990) = Partition t t Source #

data GroupSym0 (l :: TyFun [a6989586621679833989] [NonEmpty a6989586621679833989]) Source #

Instances
SuppressUnusedWarnings (GroupSym0 :: TyFun [a6989586621679833989] [NonEmpty a6989586621679833989] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupSym0 :: TyFun [a] [NonEmpty a] -> *) (l :: [a]) = Group l

type GroupSym1 (t :: [a6989586621679833989]) = Group t Source #

data GroupBySym0 (l :: TyFun (TyFun a6989586621679833988 (TyFun a6989586621679833988 Bool -> Type) -> Type) (TyFun [a6989586621679833988] [NonEmpty a6989586621679833988] -> Type)) Source #

Instances
SuppressUnusedWarnings (GroupBySym0 :: TyFun (TyFun a6989586621679833988 (TyFun a6989586621679833988 Bool -> Type) -> Type) (TyFun [a6989586621679833988] [NonEmpty a6989586621679833988] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupBySym0 :: TyFun (TyFun a6989586621679833988 (TyFun a6989586621679833988 Bool -> Type) -> Type) (TyFun [a6989586621679833988] [NonEmpty a6989586621679833988] -> Type) -> *) (l :: TyFun a6989586621679833988 (TyFun a6989586621679833988 Bool -> Type) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupBySym0 :: TyFun (TyFun a6989586621679833988 (TyFun a6989586621679833988 Bool -> Type) -> Type) (TyFun [a6989586621679833988] [NonEmpty a6989586621679833988] -> Type) -> *) (l :: TyFun a6989586621679833988 (TyFun a6989586621679833988 Bool -> Type) -> Type) = GroupBySym1 l

data GroupBySym1 (l :: TyFun a6989586621679833988 (TyFun a6989586621679833988 Bool -> Type) -> Type) (l :: TyFun [a6989586621679833988] [NonEmpty a6989586621679833988]) Source #

Instances
SuppressUnusedWarnings (GroupBySym1 :: (TyFun a6989586621679833988 (TyFun a6989586621679833988 Bool -> Type) -> Type) -> TyFun [a6989586621679833988] [NonEmpty a6989586621679833988] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupBySym1 l1 :: TyFun [a] [NonEmpty a] -> *) (l2 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupBySym1 l1 :: TyFun [a] [NonEmpty a] -> *) (l2 :: [a]) = GroupBy l1 l2

type GroupBySym2 (t :: TyFun a6989586621679833988 (TyFun a6989586621679833988 Bool -> Type) -> Type) (t :: [a6989586621679833988]) = GroupBy t t Source #

data GroupWithSym0 (l :: TyFun (TyFun a6989586621679833987 b6989586621679833986 -> Type) (TyFun [a6989586621679833987] [NonEmpty a6989586621679833987] -> Type)) Source #

Instances
SuppressUnusedWarnings (GroupWithSym0 :: TyFun (TyFun a6989586621679833987 b6989586621679833986 -> Type) (TyFun [a6989586621679833987] [NonEmpty a6989586621679833987] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupWithSym0 :: TyFun (TyFun a6989586621679833987 b6989586621679833986 -> Type) (TyFun [a6989586621679833987] [NonEmpty a6989586621679833987] -> Type) -> *) (l :: TyFun a6989586621679833987 b6989586621679833986 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupWithSym0 :: TyFun (TyFun a6989586621679833987 b6989586621679833986 -> Type) (TyFun [a6989586621679833987] [NonEmpty a6989586621679833987] -> Type) -> *) (l :: TyFun a6989586621679833987 b6989586621679833986 -> Type) = GroupWithSym1 l

data GroupWithSym1 (l :: TyFun a6989586621679833987 b6989586621679833986 -> Type) (l :: TyFun [a6989586621679833987] [NonEmpty a6989586621679833987]) Source #

Instances
SuppressUnusedWarnings (GroupWithSym1 :: (TyFun a6989586621679833987 b6989586621679833986 -> Type) -> TyFun [a6989586621679833987] [NonEmpty a6989586621679833987] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupWithSym1 l1 :: TyFun [a] [NonEmpty a] -> *) (l2 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupWithSym1 l1 :: TyFun [a] [NonEmpty a] -> *) (l2 :: [a]) = GroupWith l1 l2

type GroupWithSym2 (t :: TyFun a6989586621679833987 b6989586621679833986 -> Type) (t :: [a6989586621679833987]) = GroupWith t t Source #

data GroupAllWithSym0 (l :: TyFun (TyFun a6989586621679833985 b6989586621679833984 -> Type) (TyFun [a6989586621679833985] [NonEmpty a6989586621679833985] -> Type)) Source #

Instances
SuppressUnusedWarnings (GroupAllWithSym0 :: TyFun (TyFun a6989586621679833985 b6989586621679833984 -> Type) (TyFun [a6989586621679833985] [NonEmpty a6989586621679833985] -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupAllWithSym0 :: TyFun (TyFun a6989586621679833985 b6989586621679833984 -> Type) (TyFun [a6989586621679833985] [NonEmpty a6989586621679833985] -> Type) -> *) (l :: TyFun a6989586621679833985 b6989586621679833984 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupAllWithSym0 :: TyFun (TyFun a6989586621679833985 b6989586621679833984 -> Type) (TyFun [a6989586621679833985] [NonEmpty a6989586621679833985] -> Type) -> *) (l :: TyFun a6989586621679833985 b6989586621679833984 -> Type) = GroupAllWithSym1 l

data GroupAllWithSym1 (l :: TyFun a6989586621679833985 b6989586621679833984 -> Type) (l :: TyFun [a6989586621679833985] [NonEmpty a6989586621679833985]) Source #

Instances
SuppressUnusedWarnings (GroupAllWithSym1 :: (TyFun a6989586621679833985 b6989586621679833984 -> Type) -> TyFun [a6989586621679833985] [NonEmpty a6989586621679833985] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupAllWithSym1 l1 :: TyFun [a] [NonEmpty a] -> *) (l2 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupAllWithSym1 l1 :: TyFun [a] [NonEmpty a] -> *) (l2 :: [a]) = GroupAllWith l1 l2

type GroupAllWithSym2 (t :: TyFun a6989586621679833985 b6989586621679833984 -> Type) (t :: [a6989586621679833985]) = GroupAllWith t t Source #

data Group1Sym0 (l :: TyFun (NonEmpty a6989586621679833983) (NonEmpty (NonEmpty a6989586621679833983))) Source #

Instances
SuppressUnusedWarnings (Group1Sym0 :: TyFun (NonEmpty a6989586621679833983) (NonEmpty (NonEmpty a6989586621679833983)) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (Group1Sym0 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> *) (l :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (Group1Sym0 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> *) (l :: NonEmpty a) = Group1 l

type Group1Sym1 (t :: NonEmpty a6989586621679833983) = Group1 t Source #

data GroupBy1Sym0 (l :: TyFun (TyFun a6989586621679833982 (TyFun a6989586621679833982 Bool -> Type) -> Type) (TyFun (NonEmpty a6989586621679833982) (NonEmpty (NonEmpty a6989586621679833982)) -> Type)) Source #

Instances
SuppressUnusedWarnings (GroupBy1Sym0 :: TyFun (TyFun a6989586621679833982 (TyFun a6989586621679833982 Bool -> Type) -> Type) (TyFun (NonEmpty a6989586621679833982) (NonEmpty (NonEmpty a6989586621679833982)) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupBy1Sym0 :: TyFun (TyFun a6989586621679833982 (TyFun a6989586621679833982 Bool -> Type) -> Type) (TyFun (NonEmpty a6989586621679833982) (NonEmpty (NonEmpty a6989586621679833982)) -> Type) -> *) (l :: TyFun a6989586621679833982 (TyFun a6989586621679833982 Bool -> Type) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupBy1Sym0 :: TyFun (TyFun a6989586621679833982 (TyFun a6989586621679833982 Bool -> Type) -> Type) (TyFun (NonEmpty a6989586621679833982) (NonEmpty (NonEmpty a6989586621679833982)) -> Type) -> *) (l :: TyFun a6989586621679833982 (TyFun a6989586621679833982 Bool -> Type) -> Type) = GroupBy1Sym1 l

data GroupBy1Sym1 (l :: TyFun a6989586621679833982 (TyFun a6989586621679833982 Bool -> Type) -> Type) (l :: TyFun (NonEmpty a6989586621679833982) (NonEmpty (NonEmpty a6989586621679833982))) Source #

Instances
SuppressUnusedWarnings (GroupBy1Sym1 :: (TyFun a6989586621679833982 (TyFun a6989586621679833982 Bool -> Type) -> Type) -> TyFun (NonEmpty a6989586621679833982) (NonEmpty (NonEmpty a6989586621679833982)) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupBy1Sym1 l1 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> *) (l2 :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupBy1Sym1 l1 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> *) (l2 :: NonEmpty a) = GroupBy1 l1 l2

type GroupBy1Sym2 (t :: TyFun a6989586621679833982 (TyFun a6989586621679833982 Bool -> Type) -> Type) (t :: NonEmpty a6989586621679833982) = GroupBy1 t t Source #

data GroupWith1Sym0 (l :: TyFun (TyFun a6989586621679833981 b6989586621679833980 -> Type) (TyFun (NonEmpty a6989586621679833981) (NonEmpty (NonEmpty a6989586621679833981)) -> Type)) Source #

Instances
SuppressUnusedWarnings (GroupWith1Sym0 :: TyFun (TyFun a6989586621679833981 b6989586621679833980 -> Type) (TyFun (NonEmpty a6989586621679833981) (NonEmpty (NonEmpty a6989586621679833981)) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupWith1Sym0 :: TyFun (TyFun a6989586621679833981 b6989586621679833980 -> Type) (TyFun (NonEmpty a6989586621679833981) (NonEmpty (NonEmpty a6989586621679833981)) -> Type) -> *) (l :: TyFun a6989586621679833981 b6989586621679833980 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupWith1Sym0 :: TyFun (TyFun a6989586621679833981 b6989586621679833980 -> Type) (TyFun (NonEmpty a6989586621679833981) (NonEmpty (NonEmpty a6989586621679833981)) -> Type) -> *) (l :: TyFun a6989586621679833981 b6989586621679833980 -> Type) = GroupWith1Sym1 l

data GroupWith1Sym1 (l :: TyFun a6989586621679833981 b6989586621679833980 -> Type) (l :: TyFun (NonEmpty a6989586621679833981) (NonEmpty (NonEmpty a6989586621679833981))) Source #

Instances
SuppressUnusedWarnings (GroupWith1Sym1 :: (TyFun a6989586621679833981 b6989586621679833980 -> Type) -> TyFun (NonEmpty a6989586621679833981) (NonEmpty (NonEmpty a6989586621679833981)) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupWith1Sym1 l1 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> *) (l2 :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupWith1Sym1 l1 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> *) (l2 :: NonEmpty a) = GroupWith1 l1 l2

type GroupWith1Sym2 (t :: TyFun a6989586621679833981 b6989586621679833980 -> Type) (t :: NonEmpty a6989586621679833981) = GroupWith1 t t Source #

data GroupAllWith1Sym0 (l :: TyFun (TyFun a6989586621679833979 b6989586621679833978 -> Type) (TyFun (NonEmpty a6989586621679833979) (NonEmpty (NonEmpty a6989586621679833979)) -> Type)) Source #

Instances
SuppressUnusedWarnings (GroupAllWith1Sym0 :: TyFun (TyFun a6989586621679833979 b6989586621679833978 -> Type) (TyFun (NonEmpty a6989586621679833979) (NonEmpty (NonEmpty a6989586621679833979)) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupAllWith1Sym0 :: TyFun (TyFun a6989586621679833979 b6989586621679833978 -> Type) (TyFun (NonEmpty a6989586621679833979) (NonEmpty (NonEmpty a6989586621679833979)) -> Type) -> *) (l :: TyFun a6989586621679833979 b6989586621679833978 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupAllWith1Sym0 :: TyFun (TyFun a6989586621679833979 b6989586621679833978 -> Type) (TyFun (NonEmpty a6989586621679833979) (NonEmpty (NonEmpty a6989586621679833979)) -> Type) -> *) (l :: TyFun a6989586621679833979 b6989586621679833978 -> Type) = GroupAllWith1Sym1 l

data GroupAllWith1Sym1 (l :: TyFun a6989586621679833979 b6989586621679833978 -> Type) (l :: TyFun (NonEmpty a6989586621679833979) (NonEmpty (NonEmpty a6989586621679833979))) Source #

Instances
SuppressUnusedWarnings (GroupAllWith1Sym1 :: (TyFun a6989586621679833979 b6989586621679833978 -> Type) -> TyFun (NonEmpty a6989586621679833979) (NonEmpty (NonEmpty a6989586621679833979)) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupAllWith1Sym1 l1 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> *) (l2 :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupAllWith1Sym1 l1 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> *) (l2 :: NonEmpty a) = GroupAllWith1 l1 l2

type GroupAllWith1Sym2 (t :: TyFun a6989586621679833979 b6989586621679833978 -> Type) (t :: NonEmpty a6989586621679833979) = GroupAllWith1 t t Source #

data IsPrefixOfSym0 (l :: TyFun [a6989586621679833977] (TyFun (NonEmpty a6989586621679833977) Bool -> Type)) Source #

Instances
SuppressUnusedWarnings (IsPrefixOfSym0 :: TyFun [a6989586621679833977] (TyFun (NonEmpty a6989586621679833977) Bool -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (IsPrefixOfSym0 :: TyFun [a6989586621679833977] (TyFun (NonEmpty a6989586621679833977) Bool -> Type) -> *) (l :: [a6989586621679833977]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (IsPrefixOfSym0 :: TyFun [a6989586621679833977] (TyFun (NonEmpty a6989586621679833977) Bool -> Type) -> *) (l :: [a6989586621679833977]) = IsPrefixOfSym1 l

data IsPrefixOfSym1 (l :: [a6989586621679833977]) (l :: TyFun (NonEmpty a6989586621679833977) Bool) Source #

Instances
SuppressUnusedWarnings (IsPrefixOfSym1 :: [a6989586621679833977] -> TyFun (NonEmpty a6989586621679833977) Bool -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (IsPrefixOfSym1 l1 :: TyFun (NonEmpty a) Bool -> *) (l2 :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (IsPrefixOfSym1 l1 :: TyFun (NonEmpty a) Bool -> *) (l2 :: NonEmpty a) = IsPrefixOf l1 l2

type IsPrefixOfSym2 (t :: [a6989586621679833977]) (t :: NonEmpty a6989586621679833977) = IsPrefixOf t t Source #

data NubSym0 (l :: TyFun (NonEmpty a6989586621679833968) (NonEmpty a6989586621679833968)) Source #

Instances
SuppressUnusedWarnings (NubSym0 :: TyFun (NonEmpty a6989586621679833968) (NonEmpty a6989586621679833968) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (NubSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> *) (l :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (NubSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> *) (l :: NonEmpty a) = Nub l

type NubSym1 (t :: NonEmpty a6989586621679833968) = Nub t Source #

data NubBySym0 (l :: TyFun (TyFun a6989586621679833967 (TyFun a6989586621679833967 Bool -> Type) -> Type) (TyFun (NonEmpty a6989586621679833967) (NonEmpty a6989586621679833967) -> Type)) Source #

Instances
SuppressUnusedWarnings (NubBySym0 :: TyFun (TyFun a6989586621679833967 (TyFun a6989586621679833967 Bool -> Type) -> Type) (TyFun (NonEmpty a6989586621679833967) (NonEmpty a6989586621679833967) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (NubBySym0 :: TyFun (TyFun a6989586621679833967 (TyFun a6989586621679833967 Bool -> Type) -> Type) (TyFun (NonEmpty a6989586621679833967) (NonEmpty a6989586621679833967) -> Type) -> *) (l :: TyFun a6989586621679833967 (TyFun a6989586621679833967 Bool -> Type) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (NubBySym0 :: TyFun (TyFun a6989586621679833967 (TyFun a6989586621679833967 Bool -> Type) -> Type) (TyFun (NonEmpty a6989586621679833967) (NonEmpty a6989586621679833967) -> Type) -> *) (l :: TyFun a6989586621679833967 (TyFun a6989586621679833967 Bool -> Type) -> Type) = NubBySym1 l

data NubBySym1 (l :: TyFun a6989586621679833967 (TyFun a6989586621679833967 Bool -> Type) -> Type) (l :: TyFun (NonEmpty a6989586621679833967) (NonEmpty a6989586621679833967)) Source #

Instances
SuppressUnusedWarnings (NubBySym1 :: (TyFun a6989586621679833967 (TyFun a6989586621679833967 Bool -> Type) -> Type) -> TyFun (NonEmpty a6989586621679833967) (NonEmpty a6989586621679833967) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (NubBySym1 l1 :: TyFun (NonEmpty a) (NonEmpty a) -> *) (l2 :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (NubBySym1 l1 :: TyFun (NonEmpty a) (NonEmpty a) -> *) (l2 :: NonEmpty a) = NubBy l1 l2

type NubBySym2 (t :: TyFun a6989586621679833967 (TyFun a6989586621679833967 Bool -> Type) -> Type) (t :: NonEmpty a6989586621679833967) = NubBy t t Source #

data (!!@#@$) (l :: TyFun (NonEmpty a6989586621679833976) (TyFun Nat a6989586621679833976 -> Type)) Source #

Instances
SuppressUnusedWarnings ((!!@#@$) :: TyFun (NonEmpty a6989586621679833976) (TyFun Nat a6989586621679833976 -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply ((!!@#@$) :: TyFun (NonEmpty a6989586621679833976) (TyFun Nat a6989586621679833976 -> Type) -> *) (l :: NonEmpty a6989586621679833976) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply ((!!@#@$) :: TyFun (NonEmpty a6989586621679833976) (TyFun Nat a6989586621679833976 -> Type) -> *) (l :: NonEmpty a6989586621679833976) = (!!@#@$$) l

data (l :: NonEmpty a6989586621679833976) !!@#@$$ (l :: TyFun Nat a6989586621679833976) Source #

Instances
SuppressUnusedWarnings ((!!@#@$$) :: NonEmpty a6989586621679833976 -> TyFun Nat a6989586621679833976 -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply ((!!@#@$$) l1 :: TyFun Nat a -> *) (l2 :: Nat) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply ((!!@#@$$) l1 :: TyFun Nat a -> *) (l2 :: Nat) = l1 !! l2

type (!!@#@$$$) (t :: NonEmpty a6989586621679833976) (t :: Nat) = (!!) t t Source #

data ZipSym0 (l :: TyFun (NonEmpty a6989586621679833974) (TyFun (NonEmpty b6989586621679833975) (NonEmpty (a6989586621679833974, b6989586621679833975)) -> Type)) Source #

Instances
SuppressUnusedWarnings (ZipSym0 :: TyFun (NonEmpty a6989586621679833974) (TyFun (NonEmpty b6989586621679833975) (NonEmpty (a6989586621679833974, b6989586621679833975)) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ZipSym0 :: TyFun (NonEmpty a6989586621679833974) (TyFun (NonEmpty b6989586621679833975) (NonEmpty (a6989586621679833974, b6989586621679833975)) -> Type) -> *) (l :: NonEmpty a6989586621679833974) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ZipSym0 :: TyFun (NonEmpty a6989586621679833974) (TyFun (NonEmpty b6989586621679833975) (NonEmpty (a6989586621679833974, b6989586621679833975)) -> Type) -> *) (l :: NonEmpty a6989586621679833974) = (ZipSym1 l :: TyFun (NonEmpty b6989586621679833975) (NonEmpty (a6989586621679833974, b6989586621679833975)) -> *)

data ZipSym1 (l :: NonEmpty a6989586621679833974) (l :: TyFun (NonEmpty b6989586621679833975) (NonEmpty (a6989586621679833974, b6989586621679833975))) Source #

Instances
SuppressUnusedWarnings (ZipSym1 :: NonEmpty a6989586621679833974 -> TyFun (NonEmpty b6989586621679833975) (NonEmpty (a6989586621679833974, b6989586621679833975)) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ZipSym1 l1 :: TyFun (NonEmpty b) (NonEmpty (a, b)) -> *) (l2 :: NonEmpty b) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ZipSym1 l1 :: TyFun (NonEmpty b) (NonEmpty (a, b)) -> *) (l2 :: NonEmpty b) = Zip l1 l2

type ZipSym2 (t :: NonEmpty a6989586621679833974) (t :: NonEmpty b6989586621679833975) = Zip t t Source #

data ZipWithSym0 (l :: TyFun (TyFun a6989586621679833971 (TyFun b6989586621679833972 c6989586621679833973 -> Type) -> Type) (TyFun (NonEmpty a6989586621679833971) (TyFun (NonEmpty b6989586621679833972) (NonEmpty c6989586621679833973) -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (ZipWithSym0 :: TyFun (TyFun a6989586621679833971 (TyFun b6989586621679833972 c6989586621679833973 -> Type) -> Type) (TyFun (NonEmpty a6989586621679833971) (TyFun (NonEmpty b6989586621679833972) (NonEmpty c6989586621679833973) -> Type) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ZipWithSym0 :: TyFun (TyFun a6989586621679833971 (TyFun b6989586621679833972 c6989586621679833973 -> Type) -> Type) (TyFun (NonEmpty a6989586621679833971) (TyFun (NonEmpty b6989586621679833972) (NonEmpty c6989586621679833973) -> Type) -> Type) -> *) (l :: TyFun a6989586621679833971 (TyFun b6989586621679833972 c6989586621679833973 -> Type) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ZipWithSym0 :: TyFun (TyFun a6989586621679833971 (TyFun b6989586621679833972 c6989586621679833973 -> Type) -> Type) (TyFun (NonEmpty a6989586621679833971) (TyFun (NonEmpty b6989586621679833972) (NonEmpty c6989586621679833973) -> Type) -> Type) -> *) (l :: TyFun a6989586621679833971 (TyFun b6989586621679833972 c6989586621679833973 -> Type) -> Type) = ZipWithSym1 l

data ZipWithSym1 (l :: TyFun a6989586621679833971 (TyFun b6989586621679833972 c6989586621679833973 -> Type) -> Type) (l :: TyFun (NonEmpty a6989586621679833971) (TyFun (NonEmpty b6989586621679833972) (NonEmpty c6989586621679833973) -> Type)) Source #

Instances
SuppressUnusedWarnings (ZipWithSym1 :: (TyFun a6989586621679833971 (TyFun b6989586621679833972 c6989586621679833973 -> Type) -> Type) -> TyFun (NonEmpty a6989586621679833971) (TyFun (NonEmpty b6989586621679833972) (NonEmpty c6989586621679833973) -> Type) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ZipWithSym1 l1 :: TyFun (NonEmpty a6989586621679833971) (TyFun (NonEmpty b6989586621679833972) (NonEmpty c6989586621679833973) -> Type) -> *) (l2 :: NonEmpty a6989586621679833971) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ZipWithSym1 l1 :: TyFun (NonEmpty a6989586621679833971) (TyFun (NonEmpty b6989586621679833972) (NonEmpty c6989586621679833973) -> Type) -> *) (l2 :: NonEmpty a6989586621679833971) = ZipWithSym2 l1 l2

data ZipWithSym2 (l :: TyFun a6989586621679833971 (TyFun b6989586621679833972 c6989586621679833973 -> Type) -> Type) (l :: NonEmpty a6989586621679833971) (l :: TyFun (NonEmpty b6989586621679833972) (NonEmpty c6989586621679833973)) Source #

Instances
SuppressUnusedWarnings (ZipWithSym2 :: (TyFun a6989586621679833971 (TyFun b6989586621679833972 c6989586621679833973 -> Type) -> Type) -> NonEmpty a6989586621679833971 -> TyFun (NonEmpty b6989586621679833972) (NonEmpty c6989586621679833973) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ZipWithSym2 l1 l2 :: TyFun (NonEmpty b) (NonEmpty c) -> *) (l3 :: NonEmpty b) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ZipWithSym2 l1 l2 :: TyFun (NonEmpty b) (NonEmpty c) -> *) (l3 :: NonEmpty b) = ZipWith l1 l2 l3

type ZipWithSym3 (t :: TyFun a6989586621679833971 (TyFun b6989586621679833972 c6989586621679833973 -> Type) -> Type) (t :: NonEmpty a6989586621679833971) (t :: NonEmpty b6989586621679833972) = ZipWith t t t Source #

data UnzipSym0 (l :: TyFun (NonEmpty (a6989586621679833969, b6989586621679833970)) (NonEmpty a6989586621679833969, NonEmpty b6989586621679833970)) Source #

Instances
SuppressUnusedWarnings (UnzipSym0 :: TyFun (NonEmpty (a6989586621679833969, b6989586621679833970)) (NonEmpty a6989586621679833969, NonEmpty b6989586621679833970) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (UnzipSym0 :: TyFun (NonEmpty (a, b)) (NonEmpty a, NonEmpty b) -> *) (l :: NonEmpty (a, b)) = Unzip l

type UnzipSym1 (t :: NonEmpty (a6989586621679833969, b6989586621679833970)) = Unzip t Source #

data FromListSym0 (l :: TyFun [a6989586621679834015] (NonEmpty a6989586621679834015)) Source #

Instances
SuppressUnusedWarnings (FromListSym0 :: TyFun [a6989586621679834015] (NonEmpty a6989586621679834015) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (FromListSym0 :: TyFun [a] (NonEmpty a) -> *) (l :: [a]) = FromList l

type FromListSym1 (t :: [a6989586621679834015]) = FromList t Source #

data ToListSym0 (l :: TyFun (NonEmpty a6989586621679834014) [a6989586621679834014]) Source #

Instances
SuppressUnusedWarnings (ToListSym0 :: TyFun (NonEmpty a6989586621679834014) [a6989586621679834014] -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ToListSym0 :: TyFun (NonEmpty a) [a] -> *) (l :: NonEmpty a) = ToList l

type ToListSym1 (t :: NonEmpty a6989586621679834014) = ToList t Source #

data NonEmpty_Sym0 (l :: TyFun [a6989586621679834026] (Maybe (NonEmpty a6989586621679834026))) Source #

Instances
SuppressUnusedWarnings (NonEmpty_Sym0 :: TyFun [a6989586621679834026] (Maybe (NonEmpty a6989586621679834026)) -> *) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

type NonEmpty_Sym1 (t :: [a6989586621679834026]) = NonEmpty_ t Source #

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