singletons-2.3.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.Singletons.Prelude.List.NonEmpty

Contents

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

The NonEmpty singleton

data family Sing (a :: k) Source #

The singleton kind-indexed data family.

Instances

data Sing Bool Source # 
data Sing Bool where
data Sing Ordering Source # 
data Sing * Source # 
data Sing * where
data Sing Nat Source # 
data Sing Nat where
data Sing Symbol Source # 
data Sing Symbol where
data Sing () Source # 
data Sing () where
data Sing [a] Source # 
data Sing [a] where
data Sing (Maybe a) Source # 
data Sing (Maybe a) where
data Sing (NonEmpty a) Source # 
data Sing (NonEmpty a) where
data Sing (Either a b) Source # 
data Sing (Either a b) where
data Sing (a, b) Source # 
data Sing (a, b) where
data Sing ((~>) k1 k2) Source # 
data Sing ((~>) k1 k2) = SLambda {}
data Sing (a, b, c) Source # 
data Sing (a, b, c) where
data Sing (a, b, c, d) Source # 
data Sing (a, b, c, d) where
data Sing (a, b, c, d, e) Source # 
data Sing (a, b, c, d, e) where
data Sing (a, b, c, d, e, f) Source # 
data Sing (a, b, c, d, e, f) where
data Sing (a, b, c, d, e, f, g) Source # 
data Sing (a, b, c, d, e, f, g) where

Though Haddock doesn't show it, the Sing instance above declares constructor

(:%|) :: Sing h -> Sing t -> Sing (h :| t)

type SNonEmpty = (Sing :: NonEmpty a -> Type) Source #

SNonEmpty is a kind-restricted synonym for Sing: type SNonEmpty (a :: NonEmpty) = Sing a

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) 

sMap :: forall (t :: TyFun a b -> Type) (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_6989586621679730292 a b bs bs) 

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

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

Equations

Scanl f z a_6989586621679730545 = Apply (Apply (Apply (:.$) FromListSym0) (Apply (Apply ListscanlSym0 f) z)) a_6989586621679730545 

sScanl :: forall (t :: TyFun b (TyFun a b -> Type) -> Type) (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 :: TyFun a (TyFun b b -> Type) -> Type) (a :: b) (a :: [a]) :: NonEmpty b where ... Source #

Equations

Scanr f z a_6989586621679730565 = Apply (Apply (Apply (:.$) FromListSym0) (Apply (Apply ListscanrSym0 f) z)) a_6989586621679730565 

sScanr :: forall (t :: TyFun a (TyFun b b -> Type) -> Type) (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 :: 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) 

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

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)) 

sScanr1 :: forall (t :: TyFun a (TyFun a a -> Type) -> Type) (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_6989586621679730799 = Apply (Apply (Apply (:.$) (Apply FmapSym0 FromListSym0)) (Apply (Apply (:.$) FromListSym0) (Apply (Apply (:.$) ListtransposeSym0) (Apply (Apply (:.$) ToListSym0) (Apply FmapSym0 ToListSym0))))) a_6989586621679730799 

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

Equations

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

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

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

Equations

SortWith a_6989586621679730475 a_6989586621679730477 = Apply (Apply (Apply (Apply (:.$) SortBySym0) ComparingSym0) a_6989586621679730475) a_6989586621679730477 

sSortWith :: forall (t :: TyFun a o -> Type) (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 ((:|) _z_6989586621679730783 xs) = Apply (Apply (:+$) (FromInteger 1)) (Apply ListlengthSym0 xs) 

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

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

Equations

Head ((:|) a _z_6989586621679730653) = a 

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

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

Equations

Tail ((:|) _z_6989586621679730644 as) = as 

sTail :: forall (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 (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 (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 (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_6989586621679730613 a_6989586621679730615 = Apply (Apply (:<|$) a_6989586621679730613) a_6989586621679730615 

sCons :: forall (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 (t :: NonEmpty a). Sing t -> Sing (Apply UnconsSym0 t :: (a, Maybe (NonEmpty a))) Source #

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

Equations

Unfoldr f a = Case_6989586621679730708 f a (Let6989586621679730700Scrutinee_6989586621679729831Sym2 f a) 

sUnfoldr :: forall (t :: TyFun a (b, Maybe a) -> Type) (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_6989586621679730594 = Apply (Apply LiftSym0 ListsortSym0) a_6989586621679730594 

sSort :: forall (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_6989586621679730455 = Apply (Apply LiftSym0 ListreverseSym0) a_6989586621679730455 

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

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

Equations

Inits a_6989586621679730503 = Apply (Apply (Apply (:.$) FromListSym0) ListinitsSym0) a_6989586621679730503 

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

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

Equations

Tails a_6989586621679730510 = Apply (Apply (Apply (:.$) FromListSym0) ListtailsSym0) a_6989586621679730510 

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

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

Equations

Unfold f a = Case_6989586621679730744 f a (Let6989586621679730736Scrutinee_6989586621679729829Sym2 f a) 

sUnfold :: forall (t :: TyFun a (b, Maybe a) -> Type) (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_6989586621679730526 = Apply (Apply (Apply (:.$) FromListSym0) (Apply ListinsertSym0 a)) a_6989586621679730526 

sInsert :: forall (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_6989586621679730328 = Apply (Apply (Apply (:.$) (Apply ListtakeSym0 n)) ToListSym0) a_6989586621679730328 

sTake :: forall (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_6989586621679730341 = Apply (Apply (Apply (:.$) (Apply ListdropSym0 n)) ToListSym0) a_6989586621679730341 

sDrop :: forall (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_6989586621679730354 = Apply (Apply (Apply (:.$) (Apply ListsplitAtSym0 n)) ToListSym0) a_6989586621679730354 

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

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

Equations

TakeWhile p a_6989586621679730367 = Apply (Apply (Apply (:.$) (Apply ListtakeWhileSym0 p)) ToListSym0) a_6989586621679730367 

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

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

Equations

DropWhile p a_6989586621679730380 = Apply (Apply (Apply (:.$) (Apply ListdropWhileSym0 p)) ToListSym0) a_6989586621679730380 

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

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

Equations

Span p a_6989586621679730393 = Apply (Apply (Apply (:.$) (Apply ListspanSym0 p)) ToListSym0) a_6989586621679730393 

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

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

Equations

Break p a_6989586621679730406 = Apply (Apply SpanSym0 (Apply (Apply (:.$) NotSym0) p)) a_6989586621679730406 

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

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

Equations

Filter p a_6989586621679730419 = Apply (Apply (Apply (:.$) (Apply ListfilterSym0 p)) ToListSym0) a_6989586621679730419 

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

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

Equations

Partition p a_6989586621679730432 = Apply (Apply (Apply (:.$) (Apply ListpartitionSym0 p)) ToListSym0) a_6989586621679730432 

sPartition :: forall (t :: TyFun a Bool -> Type) (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_6989586621679730273 = Apply (Apply GroupBySym0 (:==$)) a_6989586621679730273 

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

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

Equations

GroupBy eq0 a_6989586621679730031 = Apply (Apply (Let6989586621679730035GoSym2 eq0 a_6989586621679730031) eq0) a_6989586621679730031 

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

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

Equations

GroupWith f a_6989586621679730167 = Apply (Apply GroupBySym0 (Apply (Apply OnSym0 (:==$)) f)) a_6989586621679730167 

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

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

Equations

GroupAllWith f a_6989586621679730180 = Apply (Apply (Apply (:.$) (Apply GroupWithSym0 f)) (Apply ListsortBySym0 (Apply (Apply OnSym0 CompareSym0) f))) a_6989586621679730180 

sGroupAllWith :: forall (t :: TyFun a b -> Type) (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_6989586621679730253 = Apply (Apply GroupBy1Sym0 (:==$)) a_6989586621679730253 

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

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) (Let6989586621679730196YsSym3 eq x xs))) (Apply (Apply GroupBySym0 eq) (Let6989586621679730196ZsSym3 eq x xs)) 

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

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

Equations

GroupWith1 f a_6989586621679730269 = Apply (Apply GroupBy1Sym0 (Apply (Apply OnSym0 (:==$)) f)) a_6989586621679730269 

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

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

Equations

GroupAllWith1 f a_6989586621679730499 = Apply (Apply (Apply (:.$) (Apply GroupWith1Sym0 f)) (Apply SortWithSym0 f)) a_6989586621679730499 

sGroupAllWith1 :: forall (t :: TyFun a b -> Type) (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 '[] _z_6989586621679730015 = TrueSym0 
IsPrefixOf ((:) y ys) ((:|) x xs) = Apply (Apply (:&&$) (Apply (Apply (:==$) y) x)) (Apply (Apply ListisPrefixOfSym0 ys) xs) 

sIsPrefixOf :: forall (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_6989586621679729879 = Apply (Apply NubBySym0 (:==$)) a_6989586621679729879 

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

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_6989586621679729857Sym0 eq) a) as)) as)) 

sNubBy :: forall (t :: TyFun a (TyFun a Bool -> Type) -> Type) (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_6989586621679729835 :!! arg_6989586621679729837 = Case_6989586621679729994 arg_6989586621679729835 arg_6989586621679729837 (Apply (Apply Tuple2Sym0 arg_6989586621679729835) arg_6989586621679729837) 

(%:!!) :: forall (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 (t :: NonEmpty a) (t :: NonEmpty b). Sing t -> Sing t -> Sing (Apply (Apply ZipSym0 t) t :: NonEmpty (a, b)) Source #

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) 

sZipWith :: forall (t :: TyFun a (TyFun b c -> Type) -> Type) (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) (Let6989586621679729893AsSym3 a b asbs))) (Apply (Apply (:|$) b) (Let6989586621679729893BsSym3 a b asbs)) 

sUnzip :: forall (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 (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 (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 (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 (Let6989586621679730756Xor'Sym2 x xs)) x) xs 

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

Defunctionalization symbols

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

Instances

SuppressUnusedWarnings (TyFun a6989586621679075408 (TyFun [a6989586621679075408] (NonEmpty a6989586621679075408) -> Type) -> *) ((:|$) a6989586621679075408) Source # 

Methods

suppressUnusedWarnings :: Proxy ((:|$) a6989586621679075408) t -> () Source #

type Apply a6989586621679075408 (TyFun [a6989586621679075408] (NonEmpty a6989586621679075408) -> Type) ((:|$) a6989586621679075408) l Source # 
type Apply a6989586621679075408 (TyFun [a6989586621679075408] (NonEmpty a6989586621679075408) -> Type) ((:|$) a6989586621679075408) l = (:|$$) a6989586621679075408 l

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

Instances

SuppressUnusedWarnings (a6989586621679075408 -> TyFun [a6989586621679075408] (NonEmpty a6989586621679075408) -> *) ((:|$$) a6989586621679075408) Source # 

Methods

suppressUnusedWarnings :: Proxy ((:|$$) a6989586621679075408) t -> () Source #

type Apply [a] (NonEmpty a) ((:|$$) a l1) l2 Source # 
type Apply [a] (NonEmpty a) ((:|$$) a l1) l2 = (:|) a l1 l2

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

data MapSym0 (l :: TyFun (TyFun a6989586621679729645 b6989586621679729646 -> Type) (TyFun (NonEmpty a6989586621679729645) (NonEmpty b6989586621679729646) -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679729645 b6989586621679729646 -> Type) (TyFun (NonEmpty a6989586621679729645) (NonEmpty b6989586621679729646) -> Type) -> *) (MapSym0 a6989586621679729645 b6989586621679729646) Source # 

Methods

suppressUnusedWarnings :: Proxy (MapSym0 a6989586621679729645 b6989586621679729646) t -> () Source #

type Apply (TyFun a6989586621679729645 b6989586621679729646 -> Type) (TyFun (NonEmpty a6989586621679729645) (NonEmpty b6989586621679729646) -> Type) (MapSym0 a6989586621679729645 b6989586621679729646) l Source # 
type Apply (TyFun a6989586621679729645 b6989586621679729646 -> Type) (TyFun (NonEmpty a6989586621679729645) (NonEmpty b6989586621679729646) -> Type) (MapSym0 a6989586621679729645 b6989586621679729646) l = MapSym1 a6989586621679729645 b6989586621679729646 l

data MapSym1 (l :: TyFun a6989586621679729645 b6989586621679729646 -> Type) (l :: TyFun (NonEmpty a6989586621679729645) (NonEmpty b6989586621679729646)) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679729645 b6989586621679729646 -> Type) -> TyFun (NonEmpty a6989586621679729645) (NonEmpty b6989586621679729646) -> *) (MapSym1 a6989586621679729645 b6989586621679729646) Source # 

Methods

suppressUnusedWarnings :: Proxy (MapSym1 a6989586621679729645 b6989586621679729646) t -> () Source #

type Apply (NonEmpty a) (NonEmpty b) (MapSym1 a b l1) l2 Source # 
type Apply (NonEmpty a) (NonEmpty b) (MapSym1 a b l1) l2 = Map a b l1 l2

type MapSym2 (t :: TyFun a6989586621679729645 b6989586621679729646 -> Type) (t :: NonEmpty a6989586621679729645) = Map t t Source #

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

Instances

SuppressUnusedWarnings (TyFun a6989586621679729635 (TyFun (NonEmpty a6989586621679729635) (NonEmpty a6989586621679729635) -> Type) -> *) (IntersperseSym0 a6989586621679729635) Source # 

Methods

suppressUnusedWarnings :: Proxy (IntersperseSym0 a6989586621679729635) t -> () Source #

type Apply a6989586621679729635 (TyFun (NonEmpty a6989586621679729635) (NonEmpty a6989586621679729635) -> Type) (IntersperseSym0 a6989586621679729635) l Source # 
type Apply a6989586621679729635 (TyFun (NonEmpty a6989586621679729635) (NonEmpty a6989586621679729635) -> Type) (IntersperseSym0 a6989586621679729635) l = IntersperseSym1 a6989586621679729635 l

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

Instances

SuppressUnusedWarnings (a6989586621679729635 -> TyFun (NonEmpty a6989586621679729635) (NonEmpty a6989586621679729635) -> *) (IntersperseSym1 a6989586621679729635) Source # 

Methods

suppressUnusedWarnings :: Proxy (IntersperseSym1 a6989586621679729635) t -> () Source #

type Apply (NonEmpty a) (NonEmpty a) (IntersperseSym1 a l1) l2 Source # 
type Apply (NonEmpty a) (NonEmpty a) (IntersperseSym1 a l1) l2 = Intersperse a l1 l2

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

data ScanlSym0 (l :: TyFun (TyFun b6989586621679729640 (TyFun a6989586621679729641 b6989586621679729640 -> Type) -> Type) (TyFun b6989586621679729640 (TyFun [a6989586621679729641] (NonEmpty b6989586621679729640) -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun (TyFun b6989586621679729640 (TyFun a6989586621679729641 b6989586621679729640 -> Type) -> Type) (TyFun b6989586621679729640 (TyFun [a6989586621679729641] (NonEmpty b6989586621679729640) -> Type) -> Type) -> *) (ScanlSym0 a6989586621679729641 b6989586621679729640) Source # 

Methods

suppressUnusedWarnings :: Proxy (ScanlSym0 a6989586621679729641 b6989586621679729640) t -> () Source #

type Apply (TyFun b6989586621679729640 (TyFun a6989586621679729641 b6989586621679729640 -> Type) -> Type) (TyFun b6989586621679729640 (TyFun [a6989586621679729641] (NonEmpty b6989586621679729640) -> Type) -> Type) (ScanlSym0 a6989586621679729641 b6989586621679729640) l Source # 
type Apply (TyFun b6989586621679729640 (TyFun a6989586621679729641 b6989586621679729640 -> Type) -> Type) (TyFun b6989586621679729640 (TyFun [a6989586621679729641] (NonEmpty b6989586621679729640) -> Type) -> Type) (ScanlSym0 a6989586621679729641 b6989586621679729640) l = ScanlSym1 a6989586621679729641 b6989586621679729640 l

data ScanlSym1 (l :: TyFun b6989586621679729640 (TyFun a6989586621679729641 b6989586621679729640 -> Type) -> Type) (l :: TyFun b6989586621679729640 (TyFun [a6989586621679729641] (NonEmpty b6989586621679729640) -> Type)) Source #

Instances

SuppressUnusedWarnings ((TyFun b6989586621679729640 (TyFun a6989586621679729641 b6989586621679729640 -> Type) -> Type) -> TyFun b6989586621679729640 (TyFun [a6989586621679729641] (NonEmpty b6989586621679729640) -> Type) -> *) (ScanlSym1 a6989586621679729641 b6989586621679729640) Source # 

Methods

suppressUnusedWarnings :: Proxy (ScanlSym1 a6989586621679729641 b6989586621679729640) t -> () Source #

type Apply b6989586621679729640 (TyFun [a6989586621679729641] (NonEmpty b6989586621679729640) -> Type) (ScanlSym1 a6989586621679729641 b6989586621679729640 l1) l2 Source # 
type Apply b6989586621679729640 (TyFun [a6989586621679729641] (NonEmpty b6989586621679729640) -> Type) (ScanlSym1 a6989586621679729641 b6989586621679729640 l1) l2 = ScanlSym2 a6989586621679729641 b6989586621679729640 l1 l2

data ScanlSym2 (l :: TyFun b6989586621679729640 (TyFun a6989586621679729641 b6989586621679729640 -> Type) -> Type) (l :: b6989586621679729640) (l :: TyFun [a6989586621679729641] (NonEmpty b6989586621679729640)) Source #

Instances

SuppressUnusedWarnings ((TyFun b6989586621679729640 (TyFun a6989586621679729641 b6989586621679729640 -> Type) -> Type) -> b6989586621679729640 -> TyFun [a6989586621679729641] (NonEmpty b6989586621679729640) -> *) (ScanlSym2 a6989586621679729641 b6989586621679729640) Source # 

Methods

suppressUnusedWarnings :: Proxy (ScanlSym2 a6989586621679729641 b6989586621679729640) t -> () Source #

type Apply [a] (NonEmpty b) (ScanlSym2 a b l1 l2) l3 Source # 
type Apply [a] (NonEmpty b) (ScanlSym2 a b l1 l2) l3 = Scanl a b l1 l2 l3

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

data ScanrSym0 (l :: TyFun (TyFun a6989586621679729638 (TyFun b6989586621679729639 b6989586621679729639 -> Type) -> Type) (TyFun b6989586621679729639 (TyFun [a6989586621679729638] (NonEmpty b6989586621679729639) -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679729638 (TyFun b6989586621679729639 b6989586621679729639 -> Type) -> Type) (TyFun b6989586621679729639 (TyFun [a6989586621679729638] (NonEmpty b6989586621679729639) -> Type) -> Type) -> *) (ScanrSym0 a6989586621679729638 b6989586621679729639) Source # 

Methods

suppressUnusedWarnings :: Proxy (ScanrSym0 a6989586621679729638 b6989586621679729639) t -> () Source #

type Apply (TyFun a6989586621679729638 (TyFun b6989586621679729639 b6989586621679729639 -> Type) -> Type) (TyFun b6989586621679729639 (TyFun [a6989586621679729638] (NonEmpty b6989586621679729639) -> Type) -> Type) (ScanrSym0 a6989586621679729638 b6989586621679729639) l Source # 
type Apply (TyFun a6989586621679729638 (TyFun b6989586621679729639 b6989586621679729639 -> Type) -> Type) (TyFun b6989586621679729639 (TyFun [a6989586621679729638] (NonEmpty b6989586621679729639) -> Type) -> Type) (ScanrSym0 a6989586621679729638 b6989586621679729639) l = ScanrSym1 a6989586621679729638 b6989586621679729639 l

data ScanrSym1 (l :: TyFun a6989586621679729638 (TyFun b6989586621679729639 b6989586621679729639 -> Type) -> Type) (l :: TyFun b6989586621679729639 (TyFun [a6989586621679729638] (NonEmpty b6989586621679729639) -> Type)) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679729638 (TyFun b6989586621679729639 b6989586621679729639 -> Type) -> Type) -> TyFun b6989586621679729639 (TyFun [a6989586621679729638] (NonEmpty b6989586621679729639) -> Type) -> *) (ScanrSym1 a6989586621679729638 b6989586621679729639) Source # 

Methods

suppressUnusedWarnings :: Proxy (ScanrSym1 a6989586621679729638 b6989586621679729639) t -> () Source #

type Apply b6989586621679729639 (TyFun [a6989586621679729638] (NonEmpty b6989586621679729639) -> Type) (ScanrSym1 a6989586621679729638 b6989586621679729639 l1) l2 Source # 
type Apply b6989586621679729639 (TyFun [a6989586621679729638] (NonEmpty b6989586621679729639) -> Type) (ScanrSym1 a6989586621679729638 b6989586621679729639 l1) l2 = ScanrSym2 a6989586621679729638 b6989586621679729639 l1 l2

data ScanrSym2 (l :: TyFun a6989586621679729638 (TyFun b6989586621679729639 b6989586621679729639 -> Type) -> Type) (l :: b6989586621679729639) (l :: TyFun [a6989586621679729638] (NonEmpty b6989586621679729639)) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679729638 (TyFun b6989586621679729639 b6989586621679729639 -> Type) -> Type) -> b6989586621679729639 -> TyFun [a6989586621679729638] (NonEmpty b6989586621679729639) -> *) (ScanrSym2 a6989586621679729638 b6989586621679729639) Source # 

Methods

suppressUnusedWarnings :: Proxy (ScanrSym2 a6989586621679729638 b6989586621679729639) t -> () Source #

type Apply [a] (NonEmpty b) (ScanrSym2 a b l1 l2) l3 Source # 
type Apply [a] (NonEmpty b) (ScanrSym2 a b l1 l2) l3 = Scanr a b l1 l2 l3

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

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

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679729637 (TyFun a6989586621679729637 a6989586621679729637 -> Type) -> Type) (TyFun (NonEmpty a6989586621679729637) (NonEmpty a6989586621679729637) -> Type) -> *) (Scanl1Sym0 a6989586621679729637) Source # 

Methods

suppressUnusedWarnings :: Proxy (Scanl1Sym0 a6989586621679729637) t -> () Source #

type Apply (TyFun a6989586621679729637 (TyFun a6989586621679729637 a6989586621679729637 -> Type) -> Type) (TyFun (NonEmpty a6989586621679729637) (NonEmpty a6989586621679729637) -> Type) (Scanl1Sym0 a6989586621679729637) l Source # 
type Apply (TyFun a6989586621679729637 (TyFun a6989586621679729637 a6989586621679729637 -> Type) -> Type) (TyFun (NonEmpty a6989586621679729637) (NonEmpty a6989586621679729637) -> Type) (Scanl1Sym0 a6989586621679729637) l = Scanl1Sym1 a6989586621679729637 l

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

Instances

SuppressUnusedWarnings ((TyFun a6989586621679729637 (TyFun a6989586621679729637 a6989586621679729637 -> Type) -> Type) -> TyFun (NonEmpty a6989586621679729637) (NonEmpty a6989586621679729637) -> *) (Scanl1Sym1 a6989586621679729637) Source # 

Methods

suppressUnusedWarnings :: Proxy (Scanl1Sym1 a6989586621679729637) t -> () Source #

type Apply (NonEmpty a) (NonEmpty a) (Scanl1Sym1 a l1) l2 Source # 
type Apply (NonEmpty a) (NonEmpty a) (Scanl1Sym1 a l1) l2 = Scanl1 a l1 l2

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

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

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679729636 (TyFun a6989586621679729636 a6989586621679729636 -> Type) -> Type) (TyFun (NonEmpty a6989586621679729636) (NonEmpty a6989586621679729636) -> Type) -> *) (Scanr1Sym0 a6989586621679729636) Source # 

Methods

suppressUnusedWarnings :: Proxy (Scanr1Sym0 a6989586621679729636) t -> () Source #

type Apply (TyFun a6989586621679729636 (TyFun a6989586621679729636 a6989586621679729636 -> Type) -> Type) (TyFun (NonEmpty a6989586621679729636) (NonEmpty a6989586621679729636) -> Type) (Scanr1Sym0 a6989586621679729636) l Source # 
type Apply (TyFun a6989586621679729636 (TyFun a6989586621679729636 a6989586621679729636 -> Type) -> Type) (TyFun (NonEmpty a6989586621679729636) (NonEmpty a6989586621679729636) -> Type) (Scanr1Sym0 a6989586621679729636) l = Scanr1Sym1 a6989586621679729636 l

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

Instances

SuppressUnusedWarnings ((TyFun a6989586621679729636 (TyFun a6989586621679729636 a6989586621679729636 -> Type) -> Type) -> TyFun (NonEmpty a6989586621679729636) (NonEmpty a6989586621679729636) -> *) (Scanr1Sym1 a6989586621679729636) Source # 

Methods

suppressUnusedWarnings :: Proxy (Scanr1Sym1 a6989586621679729636) t -> () Source #

type Apply (NonEmpty a) (NonEmpty a) (Scanr1Sym1 a l1) l2 Source # 
type Apply (NonEmpty a) (NonEmpty a) (Scanr1Sym1 a l1) l2 = Scanr1 a l1 l2

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

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

Instances

SuppressUnusedWarnings (TyFun (NonEmpty (NonEmpty a6989586621679729601)) (NonEmpty (NonEmpty a6989586621679729601)) -> *) (TransposeSym0 a6989586621679729601) Source # 

Methods

suppressUnusedWarnings :: Proxy (TransposeSym0 a6989586621679729601) t -> () Source #

type Apply (NonEmpty (NonEmpty a)) (NonEmpty (NonEmpty a)) (TransposeSym0 a) l Source # 

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

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

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679729600 (TyFun a6989586621679729600 Ordering -> Type) -> Type) (TyFun (NonEmpty a6989586621679729600) (NonEmpty a6989586621679729600) -> Type) -> *) (SortBySym0 a6989586621679729600) Source # 

Methods

suppressUnusedWarnings :: Proxy (SortBySym0 a6989586621679729600) t -> () Source #

type Apply (TyFun a6989586621679729600 (TyFun a6989586621679729600 Ordering -> Type) -> Type) (TyFun (NonEmpty a6989586621679729600) (NonEmpty a6989586621679729600) -> Type) (SortBySym0 a6989586621679729600) l Source # 
type Apply (TyFun a6989586621679729600 (TyFun a6989586621679729600 Ordering -> Type) -> Type) (TyFun (NonEmpty a6989586621679729600) (NonEmpty a6989586621679729600) -> Type) (SortBySym0 a6989586621679729600) l = SortBySym1 a6989586621679729600 l

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

Instances

SuppressUnusedWarnings ((TyFun a6989586621679729600 (TyFun a6989586621679729600 Ordering -> Type) -> Type) -> TyFun (NonEmpty a6989586621679729600) (NonEmpty a6989586621679729600) -> *) (SortBySym1 a6989586621679729600) Source # 

Methods

suppressUnusedWarnings :: Proxy (SortBySym1 a6989586621679729600) t -> () Source #

type Apply (NonEmpty a) (NonEmpty a) (SortBySym1 a l1) l2 Source # 
type Apply (NonEmpty a) (NonEmpty a) (SortBySym1 a l1) l2 = SortBy a l1 l2

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

data SortWithSym0 (l :: TyFun (TyFun a6989586621679729599 o6989586621679729598 -> Type) (TyFun (NonEmpty a6989586621679729599) (NonEmpty a6989586621679729599) -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679729599 o6989586621679729598 -> Type) (TyFun (NonEmpty a6989586621679729599) (NonEmpty a6989586621679729599) -> Type) -> *) (SortWithSym0 o6989586621679729598 a6989586621679729599) Source # 

Methods

suppressUnusedWarnings :: Proxy (SortWithSym0 o6989586621679729598 a6989586621679729599) t -> () Source #

type Apply (TyFun a6989586621679729599 o6989586621679729598 -> Type) (TyFun (NonEmpty a6989586621679729599) (NonEmpty a6989586621679729599) -> Type) (SortWithSym0 o6989586621679729598 a6989586621679729599) l Source # 
type Apply (TyFun a6989586621679729599 o6989586621679729598 -> Type) (TyFun (NonEmpty a6989586621679729599) (NonEmpty a6989586621679729599) -> Type) (SortWithSym0 o6989586621679729598 a6989586621679729599) l = SortWithSym1 o6989586621679729598 a6989586621679729599 l

data SortWithSym1 (l :: TyFun a6989586621679729599 o6989586621679729598 -> Type) (l :: TyFun (NonEmpty a6989586621679729599) (NonEmpty a6989586621679729599)) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679729599 o6989586621679729598 -> Type) -> TyFun (NonEmpty a6989586621679729599) (NonEmpty a6989586621679729599) -> *) (SortWithSym1 o6989586621679729598 a6989586621679729599) Source # 

Methods

suppressUnusedWarnings :: Proxy (SortWithSym1 o6989586621679729598 a6989586621679729599) t -> () Source #

type Apply (NonEmpty a) (NonEmpty a) (SortWithSym1 o a l1) l2 Source # 
type Apply (NonEmpty a) (NonEmpty a) (SortWithSym1 o a l1) l2 = SortWith o a l1 l2

type SortWithSym2 (t :: TyFun a6989586621679729599 o6989586621679729598 -> Type) (t :: NonEmpty a6989586621679729599) = SortWith t t Source #

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

Instances

SuppressUnusedWarnings (TyFun (NonEmpty a6989586621679729664) Nat -> *) (LengthSym0 a6989586621679729664) Source # 

Methods

suppressUnusedWarnings :: Proxy (LengthSym0 a6989586621679729664) t -> () Source #

type Apply (NonEmpty a) Nat (LengthSym0 a) l Source # 
type Apply (NonEmpty a) Nat (LengthSym0 a) l = Length a l

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

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

Instances

SuppressUnusedWarnings (TyFun (NonEmpty a6989586621679729657) a6989586621679729657 -> *) (HeadSym0 a6989586621679729657) Source # 

Methods

suppressUnusedWarnings :: Proxy (HeadSym0 a6989586621679729657) t -> () Source #

type Apply (NonEmpty a) a (HeadSym0 a) l Source # 
type Apply (NonEmpty a) a (HeadSym0 a) l = Head a l

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

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

Instances

SuppressUnusedWarnings (TyFun (NonEmpty a6989586621679729656) [a6989586621679729656] -> *) (TailSym0 a6989586621679729656) Source # 

Methods

suppressUnusedWarnings :: Proxy (TailSym0 a6989586621679729656) t -> () Source #

type Apply (NonEmpty a) [a] (TailSym0 a) l Source # 
type Apply (NonEmpty a) [a] (TailSym0 a) l = Tail a l

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

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

Instances

SuppressUnusedWarnings (TyFun (NonEmpty a6989586621679729655) a6989586621679729655 -> *) (LastSym0 a6989586621679729655) Source # 

Methods

suppressUnusedWarnings :: Proxy (LastSym0 a6989586621679729655) t -> () Source #

type Apply (NonEmpty a) a (LastSym0 a) l Source # 
type Apply (NonEmpty a) a (LastSym0 a) l = Last a l

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

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

Instances

SuppressUnusedWarnings (TyFun (NonEmpty a6989586621679729654) [a6989586621679729654] -> *) (InitSym0 a6989586621679729654) Source # 

Methods

suppressUnusedWarnings :: Proxy (InitSym0 a6989586621679729654) t -> () Source #

type Apply (NonEmpty a) [a] (InitSym0 a) l Source # 
type Apply (NonEmpty a) [a] (InitSym0 a) l = Init a l

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

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

Instances

SuppressUnusedWarnings (TyFun a6989586621679729653 (TyFun (NonEmpty a6989586621679729653) (NonEmpty a6989586621679729653) -> Type) -> *) ((:<|$) a6989586621679729653) Source # 

Methods

suppressUnusedWarnings :: Proxy ((:<|$) a6989586621679729653) t -> () Source #

type Apply a6989586621679729653 (TyFun (NonEmpty a6989586621679729653) (NonEmpty a6989586621679729653) -> Type) ((:<|$) a6989586621679729653) l Source # 
type Apply a6989586621679729653 (TyFun (NonEmpty a6989586621679729653) (NonEmpty a6989586621679729653) -> Type) ((:<|$) a6989586621679729653) l = (:<|$$) a6989586621679729653 l

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

Instances

SuppressUnusedWarnings (a6989586621679729653 -> TyFun (NonEmpty a6989586621679729653) (NonEmpty a6989586621679729653) -> *) ((:<|$$) a6989586621679729653) Source # 

Methods

suppressUnusedWarnings :: Proxy ((:<|$$) a6989586621679729653) t -> () Source #

type Apply (NonEmpty a) (NonEmpty a) ((:<|$$) a l1) l2 Source # 
type Apply (NonEmpty a) (NonEmpty a) ((:<|$$) a l1) l2 = (:<|) a l1 l2

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

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

Instances

SuppressUnusedWarnings (TyFun a6989586621679729652 (TyFun (NonEmpty a6989586621679729652) (NonEmpty a6989586621679729652) -> Type) -> *) (ConsSym0 a6989586621679729652) Source # 

Methods

suppressUnusedWarnings :: Proxy (ConsSym0 a6989586621679729652) t -> () Source #

type Apply a6989586621679729652 (TyFun (NonEmpty a6989586621679729652) (NonEmpty a6989586621679729652) -> Type) (ConsSym0 a6989586621679729652) l Source # 
type Apply a6989586621679729652 (TyFun (NonEmpty a6989586621679729652) (NonEmpty a6989586621679729652) -> Type) (ConsSym0 a6989586621679729652) l = ConsSym1 a6989586621679729652 l

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

Instances

SuppressUnusedWarnings (a6989586621679729652 -> TyFun (NonEmpty a6989586621679729652) (NonEmpty a6989586621679729652) -> *) (ConsSym1 a6989586621679729652) Source # 

Methods

suppressUnusedWarnings :: Proxy (ConsSym1 a6989586621679729652) t -> () Source #

type Apply (NonEmpty a) (NonEmpty a) (ConsSym1 a l1) l2 Source # 
type Apply (NonEmpty a) (NonEmpty a) (ConsSym1 a l1) l2 = Cons a l1 l2

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

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

Instances

SuppressUnusedWarnings (TyFun (NonEmpty a6989586621679729660) (a6989586621679729660, Maybe (NonEmpty a6989586621679729660)) -> *) (UnconsSym0 a6989586621679729660) Source # 

Methods

suppressUnusedWarnings :: Proxy (UnconsSym0 a6989586621679729660) t -> () Source #

type Apply (NonEmpty a) (a, Maybe (NonEmpty a)) (UnconsSym0 a) l Source # 
type Apply (NonEmpty a) (a, Maybe (NonEmpty a)) (UnconsSym0 a) l = Uncons a l

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

data UnfoldrSym0 (l :: TyFun (TyFun a6989586621679729658 (b6989586621679729659, Maybe a6989586621679729658) -> Type) (TyFun a6989586621679729658 (NonEmpty b6989586621679729659) -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679729658 (b6989586621679729659, Maybe a6989586621679729658) -> Type) (TyFun a6989586621679729658 (NonEmpty b6989586621679729659) -> Type) -> *) (UnfoldrSym0 a6989586621679729658 b6989586621679729659) Source # 

Methods

suppressUnusedWarnings :: Proxy (UnfoldrSym0 a6989586621679729658 b6989586621679729659) t -> () Source #

type Apply (TyFun a6989586621679729658 (b6989586621679729659, Maybe a6989586621679729658) -> Type) (TyFun a6989586621679729658 (NonEmpty b6989586621679729659) -> Type) (UnfoldrSym0 a6989586621679729658 b6989586621679729659) l Source # 
type Apply (TyFun a6989586621679729658 (b6989586621679729659, Maybe a6989586621679729658) -> Type) (TyFun a6989586621679729658 (NonEmpty b6989586621679729659) -> Type) (UnfoldrSym0 a6989586621679729658 b6989586621679729659) l = UnfoldrSym1 a6989586621679729658 b6989586621679729659 l

data UnfoldrSym1 (l :: TyFun a6989586621679729658 (b6989586621679729659, Maybe a6989586621679729658) -> Type) (l :: TyFun a6989586621679729658 (NonEmpty b6989586621679729659)) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679729658 (b6989586621679729659, Maybe a6989586621679729658) -> Type) -> TyFun a6989586621679729658 (NonEmpty b6989586621679729659) -> *) (UnfoldrSym1 a6989586621679729658 b6989586621679729659) Source # 

Methods

suppressUnusedWarnings :: Proxy (UnfoldrSym1 a6989586621679729658 b6989586621679729659) t -> () Source #

type Apply a (NonEmpty b) (UnfoldrSym1 a b l1) l2 Source # 
type Apply a (NonEmpty b) (UnfoldrSym1 a b l1) l2 = Unfoldr a b l1 l2

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

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

Instances

SuppressUnusedWarnings (TyFun (NonEmpty a6989586621679729651) (NonEmpty a6989586621679729651) -> *) (SortSym0 a6989586621679729651) Source # 

Methods

suppressUnusedWarnings :: Proxy (SortSym0 a6989586621679729651) t -> () Source #

type Apply (NonEmpty a) (NonEmpty a) (SortSym0 a) l Source # 
type Apply (NonEmpty a) (NonEmpty a) (SortSym0 a) l = Sort a l

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

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

Instances

SuppressUnusedWarnings (TyFun (NonEmpty a6989586621679729634) (NonEmpty a6989586621679729634) -> *) (ReverseSym0 a6989586621679729634) Source # 

Methods

suppressUnusedWarnings :: Proxy (ReverseSym0 a6989586621679729634) t -> () Source #

type Apply (NonEmpty a) (NonEmpty a) (ReverseSym0 a) l Source # 
type Apply (NonEmpty a) (NonEmpty a) (ReverseSym0 a) l = Reverse a l

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

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

Instances

SuppressUnusedWarnings (TyFun [a6989586621679729644] (NonEmpty [a6989586621679729644]) -> *) (InitsSym0 a6989586621679729644) Source # 

Methods

suppressUnusedWarnings :: Proxy (InitsSym0 a6989586621679729644) t -> () Source #

type Apply [a] (NonEmpty [a]) (InitsSym0 a) l Source # 
type Apply [a] (NonEmpty [a]) (InitsSym0 a) l = Inits a l

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

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

Instances

SuppressUnusedWarnings (TyFun [a6989586621679729643] (NonEmpty [a6989586621679729643]) -> *) (TailsSym0 a6989586621679729643) Source # 

Methods

suppressUnusedWarnings :: Proxy (TailsSym0 a6989586621679729643) t -> () Source #

type Apply [a] (NonEmpty [a]) (TailsSym0 a) l Source # 
type Apply [a] (NonEmpty [a]) (TailsSym0 a) l = Tails a l

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

data UnfoldSym0 (l :: TyFun (TyFun a6989586621679729662 (b6989586621679729663, Maybe a6989586621679729662) -> Type) (TyFun a6989586621679729662 (NonEmpty b6989586621679729663) -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679729662 (b6989586621679729663, Maybe a6989586621679729662) -> Type) (TyFun a6989586621679729662 (NonEmpty b6989586621679729663) -> Type) -> *) (UnfoldSym0 a6989586621679729662 b6989586621679729663) Source # 

Methods

suppressUnusedWarnings :: Proxy (UnfoldSym0 a6989586621679729662 b6989586621679729663) t -> () Source #

type Apply (TyFun a6989586621679729662 (b6989586621679729663, Maybe a6989586621679729662) -> Type) (TyFun a6989586621679729662 (NonEmpty b6989586621679729663) -> Type) (UnfoldSym0 a6989586621679729662 b6989586621679729663) l Source # 
type Apply (TyFun a6989586621679729662 (b6989586621679729663, Maybe a6989586621679729662) -> Type) (TyFun a6989586621679729662 (NonEmpty b6989586621679729663) -> Type) (UnfoldSym0 a6989586621679729662 b6989586621679729663) l = UnfoldSym1 a6989586621679729662 b6989586621679729663 l

data UnfoldSym1 (l :: TyFun a6989586621679729662 (b6989586621679729663, Maybe a6989586621679729662) -> Type) (l :: TyFun a6989586621679729662 (NonEmpty b6989586621679729663)) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679729662 (b6989586621679729663, Maybe a6989586621679729662) -> Type) -> TyFun a6989586621679729662 (NonEmpty b6989586621679729663) -> *) (UnfoldSym1 a6989586621679729662 b6989586621679729663) Source # 

Methods

suppressUnusedWarnings :: Proxy (UnfoldSym1 a6989586621679729662 b6989586621679729663) t -> () Source #

type Apply a (NonEmpty b) (UnfoldSym1 a b l1) l2 Source # 
type Apply a (NonEmpty b) (UnfoldSym1 a b l1) l2 = Unfold a b l1 l2

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

Instances

SuppressUnusedWarnings (TyFun a6989586621679729642 (TyFun [a6989586621679729642] (NonEmpty a6989586621679729642) -> Type) -> *) (InsertSym0 a6989586621679729642) Source # 

Methods

suppressUnusedWarnings :: Proxy (InsertSym0 a6989586621679729642) t -> () Source #

type Apply a6989586621679729642 (TyFun [a6989586621679729642] (NonEmpty a6989586621679729642) -> Type) (InsertSym0 a6989586621679729642) l Source # 
type Apply a6989586621679729642 (TyFun [a6989586621679729642] (NonEmpty a6989586621679729642) -> Type) (InsertSym0 a6989586621679729642) l = InsertSym1 a6989586621679729642 l

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

Instances

SuppressUnusedWarnings (a6989586621679729642 -> TyFun [a6989586621679729642] (NonEmpty a6989586621679729642) -> *) (InsertSym1 a6989586621679729642) Source # 

Methods

suppressUnusedWarnings :: Proxy (InsertSym1 a6989586621679729642) t -> () Source #

type Apply [a] (NonEmpty a) (InsertSym1 a l1) l2 Source # 
type Apply [a] (NonEmpty a) (InsertSym1 a l1) l2 = Insert a l1 l2

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

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

Instances

SuppressUnusedWarnings (TyFun Nat (TyFun (NonEmpty a6989586621679729633) [a6989586621679729633] -> Type) -> *) (TakeSym0 a6989586621679729633) Source # 

Methods

suppressUnusedWarnings :: Proxy (TakeSym0 a6989586621679729633) t -> () Source #

type Apply Nat (TyFun (NonEmpty a6989586621679729633) [a6989586621679729633] -> Type) (TakeSym0 a6989586621679729633) l Source # 
type Apply Nat (TyFun (NonEmpty a6989586621679729633) [a6989586621679729633] -> Type) (TakeSym0 a6989586621679729633) l = TakeSym1 a6989586621679729633 l

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

Instances

SuppressUnusedWarnings (Nat -> TyFun (NonEmpty a6989586621679729633) [a6989586621679729633] -> *) (TakeSym1 a6989586621679729633) Source # 

Methods

suppressUnusedWarnings :: Proxy (TakeSym1 a6989586621679729633) t -> () Source #

type Apply (NonEmpty a) [a] (TakeSym1 a l1) l2 Source # 
type Apply (NonEmpty a) [a] (TakeSym1 a l1) l2 = Take a l1 l2

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

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

Instances

SuppressUnusedWarnings (TyFun Nat (TyFun (NonEmpty a6989586621679729632) [a6989586621679729632] -> Type) -> *) (DropSym0 a6989586621679729632) Source # 

Methods

suppressUnusedWarnings :: Proxy (DropSym0 a6989586621679729632) t -> () Source #

type Apply Nat (TyFun (NonEmpty a6989586621679729632) [a6989586621679729632] -> Type) (DropSym0 a6989586621679729632) l Source # 
type Apply Nat (TyFun (NonEmpty a6989586621679729632) [a6989586621679729632] -> Type) (DropSym0 a6989586621679729632) l = DropSym1 a6989586621679729632 l

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

Instances

SuppressUnusedWarnings (Nat -> TyFun (NonEmpty a6989586621679729632) [a6989586621679729632] -> *) (DropSym1 a6989586621679729632) Source # 

Methods

suppressUnusedWarnings :: Proxy (DropSym1 a6989586621679729632) t -> () Source #

type Apply (NonEmpty a) [a] (DropSym1 a l1) l2 Source # 
type Apply (NonEmpty a) [a] (DropSym1 a l1) l2 = Drop a l1 l2

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

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

Instances

SuppressUnusedWarnings (TyFun Nat (TyFun (NonEmpty a6989586621679729631) ([a6989586621679729631], [a6989586621679729631]) -> Type) -> *) (SplitAtSym0 a6989586621679729631) Source # 

Methods

suppressUnusedWarnings :: Proxy (SplitAtSym0 a6989586621679729631) t -> () Source #

type Apply Nat (TyFun (NonEmpty a6989586621679729631) ([a6989586621679729631], [a6989586621679729631]) -> Type) (SplitAtSym0 a6989586621679729631) l Source # 
type Apply Nat (TyFun (NonEmpty a6989586621679729631) ([a6989586621679729631], [a6989586621679729631]) -> Type) (SplitAtSym0 a6989586621679729631) l = SplitAtSym1 a6989586621679729631 l

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

Instances

SuppressUnusedWarnings (Nat -> TyFun (NonEmpty a6989586621679729631) ([a6989586621679729631], [a6989586621679729631]) -> *) (SplitAtSym1 a6989586621679729631) Source # 

Methods

suppressUnusedWarnings :: Proxy (SplitAtSym1 a6989586621679729631) t -> () Source #

type Apply (NonEmpty a) ([a], [a]) (SplitAtSym1 a l1) l2 Source # 
type Apply (NonEmpty a) ([a], [a]) (SplitAtSym1 a l1) l2 = SplitAt a l1 l2

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

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

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679729630 Bool -> Type) (TyFun (NonEmpty a6989586621679729630) [a6989586621679729630] -> Type) -> *) (TakeWhileSym0 a6989586621679729630) Source # 

Methods

suppressUnusedWarnings :: Proxy (TakeWhileSym0 a6989586621679729630) t -> () Source #

type Apply (TyFun a6989586621679729630 Bool -> Type) (TyFun (NonEmpty a6989586621679729630) [a6989586621679729630] -> Type) (TakeWhileSym0 a6989586621679729630) l Source # 
type Apply (TyFun a6989586621679729630 Bool -> Type) (TyFun (NonEmpty a6989586621679729630) [a6989586621679729630] -> Type) (TakeWhileSym0 a6989586621679729630) l = TakeWhileSym1 a6989586621679729630 l

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

Instances

SuppressUnusedWarnings ((TyFun a6989586621679729630 Bool -> Type) -> TyFun (NonEmpty a6989586621679729630) [a6989586621679729630] -> *) (TakeWhileSym1 a6989586621679729630) Source # 

Methods

suppressUnusedWarnings :: Proxy (TakeWhileSym1 a6989586621679729630) t -> () Source #

type Apply (NonEmpty a) [a] (TakeWhileSym1 a l1) l2 Source # 
type Apply (NonEmpty a) [a] (TakeWhileSym1 a l1) l2 = TakeWhile a l1 l2

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

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

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679729629 Bool -> Type) (TyFun (NonEmpty a6989586621679729629) [a6989586621679729629] -> Type) -> *) (DropWhileSym0 a6989586621679729629) Source # 

Methods

suppressUnusedWarnings :: Proxy (DropWhileSym0 a6989586621679729629) t -> () Source #

type Apply (TyFun a6989586621679729629 Bool -> Type) (TyFun (NonEmpty a6989586621679729629) [a6989586621679729629] -> Type) (DropWhileSym0 a6989586621679729629) l Source # 
type Apply (TyFun a6989586621679729629 Bool -> Type) (TyFun (NonEmpty a6989586621679729629) [a6989586621679729629] -> Type) (DropWhileSym0 a6989586621679729629) l = DropWhileSym1 a6989586621679729629 l

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

Instances

SuppressUnusedWarnings ((TyFun a6989586621679729629 Bool -> Type) -> TyFun (NonEmpty a6989586621679729629) [a6989586621679729629] -> *) (DropWhileSym1 a6989586621679729629) Source # 

Methods

suppressUnusedWarnings :: Proxy (DropWhileSym1 a6989586621679729629) t -> () Source #

type Apply (NonEmpty a) [a] (DropWhileSym1 a l1) l2 Source # 
type Apply (NonEmpty a) [a] (DropWhileSym1 a l1) l2 = DropWhile a l1 l2

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

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

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679729628 Bool -> Type) (TyFun (NonEmpty a6989586621679729628) ([a6989586621679729628], [a6989586621679729628]) -> Type) -> *) (SpanSym0 a6989586621679729628) Source # 

Methods

suppressUnusedWarnings :: Proxy (SpanSym0 a6989586621679729628) t -> () Source #

type Apply (TyFun a6989586621679729628 Bool -> Type) (TyFun (NonEmpty a6989586621679729628) ([a6989586621679729628], [a6989586621679729628]) -> Type) (SpanSym0 a6989586621679729628) l Source # 
type Apply (TyFun a6989586621679729628 Bool -> Type) (TyFun (NonEmpty a6989586621679729628) ([a6989586621679729628], [a6989586621679729628]) -> Type) (SpanSym0 a6989586621679729628) l = SpanSym1 a6989586621679729628 l

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

Instances

SuppressUnusedWarnings ((TyFun a6989586621679729628 Bool -> Type) -> TyFun (NonEmpty a6989586621679729628) ([a6989586621679729628], [a6989586621679729628]) -> *) (SpanSym1 a6989586621679729628) Source # 

Methods

suppressUnusedWarnings :: Proxy (SpanSym1 a6989586621679729628) t -> () Source #

type Apply (NonEmpty a) ([a], [a]) (SpanSym1 a l1) l2 Source # 
type Apply (NonEmpty a) ([a], [a]) (SpanSym1 a l1) l2 = Span a l1 l2

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

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

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679729627 Bool -> Type) (TyFun (NonEmpty a6989586621679729627) ([a6989586621679729627], [a6989586621679729627]) -> Type) -> *) (BreakSym0 a6989586621679729627) Source # 

Methods

suppressUnusedWarnings :: Proxy (BreakSym0 a6989586621679729627) t -> () Source #

type Apply (TyFun a6989586621679729627 Bool -> Type) (TyFun (NonEmpty a6989586621679729627) ([a6989586621679729627], [a6989586621679729627]) -> Type) (BreakSym0 a6989586621679729627) l Source # 
type Apply (TyFun a6989586621679729627 Bool -> Type) (TyFun (NonEmpty a6989586621679729627) ([a6989586621679729627], [a6989586621679729627]) -> Type) (BreakSym0 a6989586621679729627) l = BreakSym1 a6989586621679729627 l

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

Instances

SuppressUnusedWarnings ((TyFun a6989586621679729627 Bool -> Type) -> TyFun (NonEmpty a6989586621679729627) ([a6989586621679729627], [a6989586621679729627]) -> *) (BreakSym1 a6989586621679729627) Source # 

Methods

suppressUnusedWarnings :: Proxy (BreakSym1 a6989586621679729627) t -> () Source #

type Apply (NonEmpty a) ([a], [a]) (BreakSym1 a l1) l2 Source # 
type Apply (NonEmpty a) ([a], [a]) (BreakSym1 a l1) l2 = Break a l1 l2

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

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

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679729626 Bool -> Type) (TyFun (NonEmpty a6989586621679729626) [a6989586621679729626] -> Type) -> *) (FilterSym0 a6989586621679729626) Source # 

Methods

suppressUnusedWarnings :: Proxy (FilterSym0 a6989586621679729626) t -> () Source #

type Apply (TyFun a6989586621679729626 Bool -> Type) (TyFun (NonEmpty a6989586621679729626) [a6989586621679729626] -> Type) (FilterSym0 a6989586621679729626) l Source # 
type Apply (TyFun a6989586621679729626 Bool -> Type) (TyFun (NonEmpty a6989586621679729626) [a6989586621679729626] -> Type) (FilterSym0 a6989586621679729626) l = FilterSym1 a6989586621679729626 l

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

Instances

SuppressUnusedWarnings ((TyFun a6989586621679729626 Bool -> Type) -> TyFun (NonEmpty a6989586621679729626) [a6989586621679729626] -> *) (FilterSym1 a6989586621679729626) Source # 

Methods

suppressUnusedWarnings :: Proxy (FilterSym1 a6989586621679729626) t -> () Source #

type Apply (NonEmpty a) [a] (FilterSym1 a l1) l2 Source # 
type Apply (NonEmpty a) [a] (FilterSym1 a l1) l2 = Filter a l1 l2

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

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

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679729625 Bool -> Type) (TyFun (NonEmpty a6989586621679729625) ([a6989586621679729625], [a6989586621679729625]) -> Type) -> *) (PartitionSym0 a6989586621679729625) Source # 

Methods

suppressUnusedWarnings :: Proxy (PartitionSym0 a6989586621679729625) t -> () Source #

type Apply (TyFun a6989586621679729625 Bool -> Type) (TyFun (NonEmpty a6989586621679729625) ([a6989586621679729625], [a6989586621679729625]) -> Type) (PartitionSym0 a6989586621679729625) l Source # 
type Apply (TyFun a6989586621679729625 Bool -> Type) (TyFun (NonEmpty a6989586621679729625) ([a6989586621679729625], [a6989586621679729625]) -> Type) (PartitionSym0 a6989586621679729625) l = PartitionSym1 a6989586621679729625 l

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

Instances

SuppressUnusedWarnings ((TyFun a6989586621679729625 Bool -> Type) -> TyFun (NonEmpty a6989586621679729625) ([a6989586621679729625], [a6989586621679729625]) -> *) (PartitionSym1 a6989586621679729625) Source # 

Methods

suppressUnusedWarnings :: Proxy (PartitionSym1 a6989586621679729625) t -> () Source #

type Apply (NonEmpty a) ([a], [a]) (PartitionSym1 a l1) l2 Source # 
type Apply (NonEmpty a) ([a], [a]) (PartitionSym1 a l1) l2 = Partition a l1 l2

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

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

Instances

SuppressUnusedWarnings (TyFun [a6989586621679729624] [NonEmpty a6989586621679729624] -> *) (GroupSym0 a6989586621679729624) Source # 

Methods

suppressUnusedWarnings :: Proxy (GroupSym0 a6989586621679729624) t -> () Source #

type Apply [a] [NonEmpty a] (GroupSym0 a) l Source # 
type Apply [a] [NonEmpty a] (GroupSym0 a) l = Group a l

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

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

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679729623 (TyFun a6989586621679729623 Bool -> Type) -> Type) (TyFun [a6989586621679729623] [NonEmpty a6989586621679729623] -> Type) -> *) (GroupBySym0 a6989586621679729623) Source # 

Methods

suppressUnusedWarnings :: Proxy (GroupBySym0 a6989586621679729623) t -> () Source #

type Apply (TyFun a6989586621679729623 (TyFun a6989586621679729623 Bool -> Type) -> Type) (TyFun [a6989586621679729623] [NonEmpty a6989586621679729623] -> Type) (GroupBySym0 a6989586621679729623) l Source # 
type Apply (TyFun a6989586621679729623 (TyFun a6989586621679729623 Bool -> Type) -> Type) (TyFun [a6989586621679729623] [NonEmpty a6989586621679729623] -> Type) (GroupBySym0 a6989586621679729623) l = GroupBySym1 a6989586621679729623 l

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

Instances

SuppressUnusedWarnings ((TyFun a6989586621679729623 (TyFun a6989586621679729623 Bool -> Type) -> Type) -> TyFun [a6989586621679729623] [NonEmpty a6989586621679729623] -> *) (GroupBySym1 a6989586621679729623) Source # 

Methods

suppressUnusedWarnings :: Proxy (GroupBySym1 a6989586621679729623) t -> () Source #

type Apply [a] [NonEmpty a] (GroupBySym1 a l1) l2 Source # 
type Apply [a] [NonEmpty a] (GroupBySym1 a l1) l2 = GroupBy a l1 l2

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

data GroupWithSym0 (l :: TyFun (TyFun a6989586621679729622 b6989586621679729621 -> Type) (TyFun [a6989586621679729622] [NonEmpty a6989586621679729622] -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679729622 b6989586621679729621 -> Type) (TyFun [a6989586621679729622] [NonEmpty a6989586621679729622] -> Type) -> *) (GroupWithSym0 b6989586621679729621 a6989586621679729622) Source # 

Methods

suppressUnusedWarnings :: Proxy (GroupWithSym0 b6989586621679729621 a6989586621679729622) t -> () Source #

type Apply (TyFun a6989586621679729622 b6989586621679729621 -> Type) (TyFun [a6989586621679729622] [NonEmpty a6989586621679729622] -> Type) (GroupWithSym0 b6989586621679729621 a6989586621679729622) l Source # 
type Apply (TyFun a6989586621679729622 b6989586621679729621 -> Type) (TyFun [a6989586621679729622] [NonEmpty a6989586621679729622] -> Type) (GroupWithSym0 b6989586621679729621 a6989586621679729622) l = GroupWithSym1 b6989586621679729621 a6989586621679729622 l

data GroupWithSym1 (l :: TyFun a6989586621679729622 b6989586621679729621 -> Type) (l :: TyFun [a6989586621679729622] [NonEmpty a6989586621679729622]) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679729622 b6989586621679729621 -> Type) -> TyFun [a6989586621679729622] [NonEmpty a6989586621679729622] -> *) (GroupWithSym1 b6989586621679729621 a6989586621679729622) Source # 

Methods

suppressUnusedWarnings :: Proxy (GroupWithSym1 b6989586621679729621 a6989586621679729622) t -> () Source #

type Apply [a] [NonEmpty a] (GroupWithSym1 b a l1) l2 Source # 
type Apply [a] [NonEmpty a] (GroupWithSym1 b a l1) l2 = GroupWith b a l1 l2

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

data GroupAllWithSym0 (l :: TyFun (TyFun a6989586621679729620 b6989586621679729619 -> Type) (TyFun [a6989586621679729620] [NonEmpty a6989586621679729620] -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679729620 b6989586621679729619 -> Type) (TyFun [a6989586621679729620] [NonEmpty a6989586621679729620] -> Type) -> *) (GroupAllWithSym0 b6989586621679729619 a6989586621679729620) Source # 

Methods

suppressUnusedWarnings :: Proxy (GroupAllWithSym0 b6989586621679729619 a6989586621679729620) t -> () Source #

type Apply (TyFun a6989586621679729620 b6989586621679729619 -> Type) (TyFun [a6989586621679729620] [NonEmpty a6989586621679729620] -> Type) (GroupAllWithSym0 b6989586621679729619 a6989586621679729620) l Source # 
type Apply (TyFun a6989586621679729620 b6989586621679729619 -> Type) (TyFun [a6989586621679729620] [NonEmpty a6989586621679729620] -> Type) (GroupAllWithSym0 b6989586621679729619 a6989586621679729620) l = GroupAllWithSym1 b6989586621679729619 a6989586621679729620 l

data GroupAllWithSym1 (l :: TyFun a6989586621679729620 b6989586621679729619 -> Type) (l :: TyFun [a6989586621679729620] [NonEmpty a6989586621679729620]) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679729620 b6989586621679729619 -> Type) -> TyFun [a6989586621679729620] [NonEmpty a6989586621679729620] -> *) (GroupAllWithSym1 b6989586621679729619 a6989586621679729620) Source # 

Methods

suppressUnusedWarnings :: Proxy (GroupAllWithSym1 b6989586621679729619 a6989586621679729620) t -> () Source #

type Apply [a] [NonEmpty a] (GroupAllWithSym1 b a l1) l2 Source # 
type Apply [a] [NonEmpty a] (GroupAllWithSym1 b a l1) l2 = GroupAllWith b a l1 l2

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

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

Instances

SuppressUnusedWarnings (TyFun (NonEmpty a6989586621679729618) (NonEmpty (NonEmpty a6989586621679729618)) -> *) (Group1Sym0 a6989586621679729618) Source # 

Methods

suppressUnusedWarnings :: Proxy (Group1Sym0 a6989586621679729618) t -> () Source #

type Apply (NonEmpty a) (NonEmpty (NonEmpty a)) (Group1Sym0 a) l Source # 
type Apply (NonEmpty a) (NonEmpty (NonEmpty a)) (Group1Sym0 a) l = Group1 a l

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

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

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679729617 (TyFun a6989586621679729617 Bool -> Type) -> Type) (TyFun (NonEmpty a6989586621679729617) (NonEmpty (NonEmpty a6989586621679729617)) -> Type) -> *) (GroupBy1Sym0 a6989586621679729617) Source # 

Methods

suppressUnusedWarnings :: Proxy (GroupBy1Sym0 a6989586621679729617) t -> () Source #

type Apply (TyFun a6989586621679729617 (TyFun a6989586621679729617 Bool -> Type) -> Type) (TyFun (NonEmpty a6989586621679729617) (NonEmpty (NonEmpty a6989586621679729617)) -> Type) (GroupBy1Sym0 a6989586621679729617) l Source # 
type Apply (TyFun a6989586621679729617 (TyFun a6989586621679729617 Bool -> Type) -> Type) (TyFun (NonEmpty a6989586621679729617) (NonEmpty (NonEmpty a6989586621679729617)) -> Type) (GroupBy1Sym0 a6989586621679729617) l = GroupBy1Sym1 a6989586621679729617 l

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

Instances

SuppressUnusedWarnings ((TyFun a6989586621679729617 (TyFun a6989586621679729617 Bool -> Type) -> Type) -> TyFun (NonEmpty a6989586621679729617) (NonEmpty (NonEmpty a6989586621679729617)) -> *) (GroupBy1Sym1 a6989586621679729617) Source # 

Methods

suppressUnusedWarnings :: Proxy (GroupBy1Sym1 a6989586621679729617) t -> () Source #

type Apply (NonEmpty a) (NonEmpty (NonEmpty a)) (GroupBy1Sym1 a l1) l2 Source # 
type Apply (NonEmpty a) (NonEmpty (NonEmpty a)) (GroupBy1Sym1 a l1) l2 = GroupBy1 a l1 l2

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

data GroupWith1Sym0 (l :: TyFun (TyFun a6989586621679729616 b6989586621679729615 -> Type) (TyFun (NonEmpty a6989586621679729616) (NonEmpty (NonEmpty a6989586621679729616)) -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679729616 b6989586621679729615 -> Type) (TyFun (NonEmpty a6989586621679729616) (NonEmpty (NonEmpty a6989586621679729616)) -> Type) -> *) (GroupWith1Sym0 b6989586621679729615 a6989586621679729616) Source # 

Methods

suppressUnusedWarnings :: Proxy (GroupWith1Sym0 b6989586621679729615 a6989586621679729616) t -> () Source #

type Apply (TyFun a6989586621679729616 b6989586621679729615 -> Type) (TyFun (NonEmpty a6989586621679729616) (NonEmpty (NonEmpty a6989586621679729616)) -> Type) (GroupWith1Sym0 b6989586621679729615 a6989586621679729616) l Source # 
type Apply (TyFun a6989586621679729616 b6989586621679729615 -> Type) (TyFun (NonEmpty a6989586621679729616) (NonEmpty (NonEmpty a6989586621679729616)) -> Type) (GroupWith1Sym0 b6989586621679729615 a6989586621679729616) l = GroupWith1Sym1 b6989586621679729615 a6989586621679729616 l

data GroupWith1Sym1 (l :: TyFun a6989586621679729616 b6989586621679729615 -> Type) (l :: TyFun (NonEmpty a6989586621679729616) (NonEmpty (NonEmpty a6989586621679729616))) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679729616 b6989586621679729615 -> Type) -> TyFun (NonEmpty a6989586621679729616) (NonEmpty (NonEmpty a6989586621679729616)) -> *) (GroupWith1Sym1 b6989586621679729615 a6989586621679729616) Source # 

Methods

suppressUnusedWarnings :: Proxy (GroupWith1Sym1 b6989586621679729615 a6989586621679729616) t -> () Source #

type Apply (NonEmpty a) (NonEmpty (NonEmpty a)) (GroupWith1Sym1 b a l1) l2 Source # 
type Apply (NonEmpty a) (NonEmpty (NonEmpty a)) (GroupWith1Sym1 b a l1) l2 = GroupWith1 b a l1 l2

type GroupWith1Sym2 (t :: TyFun a6989586621679729616 b6989586621679729615 -> Type) (t :: NonEmpty a6989586621679729616) = GroupWith1 t t Source #

data GroupAllWith1Sym0 (l :: TyFun (TyFun a6989586621679729614 b6989586621679729613 -> Type) (TyFun (NonEmpty a6989586621679729614) (NonEmpty (NonEmpty a6989586621679729614)) -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679729614 b6989586621679729613 -> Type) (TyFun (NonEmpty a6989586621679729614) (NonEmpty (NonEmpty a6989586621679729614)) -> Type) -> *) (GroupAllWith1Sym0 b6989586621679729613 a6989586621679729614) Source # 

Methods

suppressUnusedWarnings :: Proxy (GroupAllWith1Sym0 b6989586621679729613 a6989586621679729614) t -> () Source #

type Apply (TyFun a6989586621679729614 b6989586621679729613 -> Type) (TyFun (NonEmpty a6989586621679729614) (NonEmpty (NonEmpty a6989586621679729614)) -> Type) (GroupAllWith1Sym0 b6989586621679729613 a6989586621679729614) l Source # 
type Apply (TyFun a6989586621679729614 b6989586621679729613 -> Type) (TyFun (NonEmpty a6989586621679729614) (NonEmpty (NonEmpty a6989586621679729614)) -> Type) (GroupAllWith1Sym0 b6989586621679729613 a6989586621679729614) l = GroupAllWith1Sym1 b6989586621679729613 a6989586621679729614 l

data GroupAllWith1Sym1 (l :: TyFun a6989586621679729614 b6989586621679729613 -> Type) (l :: TyFun (NonEmpty a6989586621679729614) (NonEmpty (NonEmpty a6989586621679729614))) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679729614 b6989586621679729613 -> Type) -> TyFun (NonEmpty a6989586621679729614) (NonEmpty (NonEmpty a6989586621679729614)) -> *) (GroupAllWith1Sym1 b6989586621679729613 a6989586621679729614) Source # 

Methods

suppressUnusedWarnings :: Proxy (GroupAllWith1Sym1 b6989586621679729613 a6989586621679729614) t -> () Source #

type Apply (NonEmpty a) (NonEmpty (NonEmpty a)) (GroupAllWith1Sym1 b a l1) l2 Source # 
type Apply (NonEmpty a) (NonEmpty (NonEmpty a)) (GroupAllWith1Sym1 b a l1) l2 = GroupAllWith1 b a l1 l2

type GroupAllWith1Sym2 (t :: TyFun a6989586621679729614 b6989586621679729613 -> Type) (t :: NonEmpty a6989586621679729614) = GroupAllWith1 t t Source #

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

Instances

SuppressUnusedWarnings (TyFun [a6989586621679729612] (TyFun (NonEmpty a6989586621679729612) Bool -> Type) -> *) (IsPrefixOfSym0 a6989586621679729612) Source # 

Methods

suppressUnusedWarnings :: Proxy (IsPrefixOfSym0 a6989586621679729612) t -> () Source #

type Apply [a6989586621679729612] (TyFun (NonEmpty a6989586621679729612) Bool -> Type) (IsPrefixOfSym0 a6989586621679729612) l Source # 
type Apply [a6989586621679729612] (TyFun (NonEmpty a6989586621679729612) Bool -> Type) (IsPrefixOfSym0 a6989586621679729612) l = IsPrefixOfSym1 a6989586621679729612 l

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

Instances

SuppressUnusedWarnings ([a6989586621679729612] -> TyFun (NonEmpty a6989586621679729612) Bool -> *) (IsPrefixOfSym1 a6989586621679729612) Source # 

Methods

suppressUnusedWarnings :: Proxy (IsPrefixOfSym1 a6989586621679729612) t -> () Source #

type Apply (NonEmpty a) Bool (IsPrefixOfSym1 a l1) l2 Source # 
type Apply (NonEmpty a) Bool (IsPrefixOfSym1 a l1) l2 = IsPrefixOf a l1 l2

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

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

Instances

SuppressUnusedWarnings (TyFun (NonEmpty a6989586621679729603) (NonEmpty a6989586621679729603) -> *) (NubSym0 a6989586621679729603) Source # 

Methods

suppressUnusedWarnings :: Proxy (NubSym0 a6989586621679729603) t -> () Source #

type Apply (NonEmpty a) (NonEmpty a) (NubSym0 a) l Source # 
type Apply (NonEmpty a) (NonEmpty a) (NubSym0 a) l = Nub a l

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

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

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679729602 (TyFun a6989586621679729602 Bool -> Type) -> Type) (TyFun (NonEmpty a6989586621679729602) (NonEmpty a6989586621679729602) -> Type) -> *) (NubBySym0 a6989586621679729602) Source # 

Methods

suppressUnusedWarnings :: Proxy (NubBySym0 a6989586621679729602) t -> () Source #

type Apply (TyFun a6989586621679729602 (TyFun a6989586621679729602 Bool -> Type) -> Type) (TyFun (NonEmpty a6989586621679729602) (NonEmpty a6989586621679729602) -> Type) (NubBySym0 a6989586621679729602) l Source # 
type Apply (TyFun a6989586621679729602 (TyFun a6989586621679729602 Bool -> Type) -> Type) (TyFun (NonEmpty a6989586621679729602) (NonEmpty a6989586621679729602) -> Type) (NubBySym0 a6989586621679729602) l = NubBySym1 a6989586621679729602 l

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

Instances

SuppressUnusedWarnings ((TyFun a6989586621679729602 (TyFun a6989586621679729602 Bool -> Type) -> Type) -> TyFun (NonEmpty a6989586621679729602) (NonEmpty a6989586621679729602) -> *) (NubBySym1 a6989586621679729602) Source # 

Methods

suppressUnusedWarnings :: Proxy (NubBySym1 a6989586621679729602) t -> () Source #

type Apply (NonEmpty a) (NonEmpty a) (NubBySym1 a l1) l2 Source # 
type Apply (NonEmpty a) (NonEmpty a) (NubBySym1 a l1) l2 = NubBy a l1 l2

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

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

Instances

SuppressUnusedWarnings (TyFun (NonEmpty a6989586621679729611) (TyFun Nat a6989586621679729611 -> Type) -> *) ((:!!$) a6989586621679729611) Source # 

Methods

suppressUnusedWarnings :: Proxy ((:!!$) a6989586621679729611) t -> () Source #

type Apply (NonEmpty a6989586621679729611) (TyFun Nat a6989586621679729611 -> Type) ((:!!$) a6989586621679729611) l Source # 
type Apply (NonEmpty a6989586621679729611) (TyFun Nat a6989586621679729611 -> Type) ((:!!$) a6989586621679729611) l = (:!!$$) a6989586621679729611 l

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

Instances

SuppressUnusedWarnings (NonEmpty a6989586621679729611 -> TyFun Nat a6989586621679729611 -> *) ((:!!$$) a6989586621679729611) Source # 

Methods

suppressUnusedWarnings :: Proxy ((:!!$$) a6989586621679729611) t -> () Source #

type Apply Nat a ((:!!$$) a l1) l2 Source # 
type Apply Nat a ((:!!$$) a l1) l2 = (:!!) a l1 l2

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

data ZipSym0 (l :: TyFun (NonEmpty a6989586621679729609) (TyFun (NonEmpty b6989586621679729610) (NonEmpty (a6989586621679729609, b6989586621679729610)) -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun (NonEmpty a6989586621679729609) (TyFun (NonEmpty b6989586621679729610) (NonEmpty (a6989586621679729609, b6989586621679729610)) -> Type) -> *) (ZipSym0 a6989586621679729609 b6989586621679729610) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipSym0 a6989586621679729609 b6989586621679729610) t -> () Source #

type Apply (NonEmpty a6989586621679729609) (TyFun (NonEmpty b6989586621679729610) (NonEmpty (a6989586621679729609, b6989586621679729610)) -> Type) (ZipSym0 a6989586621679729609 b6989586621679729610) l Source # 
type Apply (NonEmpty a6989586621679729609) (TyFun (NonEmpty b6989586621679729610) (NonEmpty (a6989586621679729609, b6989586621679729610)) -> Type) (ZipSym0 a6989586621679729609 b6989586621679729610) l = ZipSym1 a6989586621679729609 b6989586621679729610 l

data ZipSym1 (l :: NonEmpty a6989586621679729609) (l :: TyFun (NonEmpty b6989586621679729610) (NonEmpty (a6989586621679729609, b6989586621679729610))) Source #

Instances

SuppressUnusedWarnings (NonEmpty a6989586621679729609 -> TyFun (NonEmpty b6989586621679729610) (NonEmpty (a6989586621679729609, b6989586621679729610)) -> *) (ZipSym1 a6989586621679729609 b6989586621679729610) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipSym1 a6989586621679729609 b6989586621679729610) t -> () Source #

type Apply (NonEmpty b) (NonEmpty (a, b)) (ZipSym1 a b l1) l2 Source # 
type Apply (NonEmpty b) (NonEmpty (a, b)) (ZipSym1 a b l1) l2 = Zip a b l1 l2

type ZipSym2 (t :: NonEmpty a6989586621679729609) (t :: NonEmpty b6989586621679729610) = Zip t t Source #

data ZipWithSym0 (l :: TyFun (TyFun a6989586621679729606 (TyFun b6989586621679729607 c6989586621679729608 -> Type) -> Type) (TyFun (NonEmpty a6989586621679729606) (TyFun (NonEmpty b6989586621679729607) (NonEmpty c6989586621679729608) -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679729606 (TyFun b6989586621679729607 c6989586621679729608 -> Type) -> Type) (TyFun (NonEmpty a6989586621679729606) (TyFun (NonEmpty b6989586621679729607) (NonEmpty c6989586621679729608) -> Type) -> Type) -> *) (ZipWithSym0 a6989586621679729606 b6989586621679729607 c6989586621679729608) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWithSym0 a6989586621679729606 b6989586621679729607 c6989586621679729608) t -> () Source #

type Apply (TyFun a6989586621679729606 (TyFun b6989586621679729607 c6989586621679729608 -> Type) -> Type) (TyFun (NonEmpty a6989586621679729606) (TyFun (NonEmpty b6989586621679729607) (NonEmpty c6989586621679729608) -> Type) -> Type) (ZipWithSym0 a6989586621679729606 b6989586621679729607 c6989586621679729608) l Source # 
type Apply (TyFun a6989586621679729606 (TyFun b6989586621679729607 c6989586621679729608 -> Type) -> Type) (TyFun (NonEmpty a6989586621679729606) (TyFun (NonEmpty b6989586621679729607) (NonEmpty c6989586621679729608) -> Type) -> Type) (ZipWithSym0 a6989586621679729606 b6989586621679729607 c6989586621679729608) l = ZipWithSym1 a6989586621679729606 b6989586621679729607 c6989586621679729608 l

data ZipWithSym1 (l :: TyFun a6989586621679729606 (TyFun b6989586621679729607 c6989586621679729608 -> Type) -> Type) (l :: TyFun (NonEmpty a6989586621679729606) (TyFun (NonEmpty b6989586621679729607) (NonEmpty c6989586621679729608) -> Type)) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679729606 (TyFun b6989586621679729607 c6989586621679729608 -> Type) -> Type) -> TyFun (NonEmpty a6989586621679729606) (TyFun (NonEmpty b6989586621679729607) (NonEmpty c6989586621679729608) -> Type) -> *) (ZipWithSym1 a6989586621679729606 b6989586621679729607 c6989586621679729608) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWithSym1 a6989586621679729606 b6989586621679729607 c6989586621679729608) t -> () Source #

type Apply (NonEmpty a6989586621679729606) (TyFun (NonEmpty b6989586621679729607) (NonEmpty c6989586621679729608) -> Type) (ZipWithSym1 a6989586621679729606 b6989586621679729607 c6989586621679729608 l1) l2 Source # 
type Apply (NonEmpty a6989586621679729606) (TyFun (NonEmpty b6989586621679729607) (NonEmpty c6989586621679729608) -> Type) (ZipWithSym1 a6989586621679729606 b6989586621679729607 c6989586621679729608 l1) l2 = ZipWithSym2 a6989586621679729606 b6989586621679729607 c6989586621679729608 l1 l2

data ZipWithSym2 (l :: TyFun a6989586621679729606 (TyFun b6989586621679729607 c6989586621679729608 -> Type) -> Type) (l :: NonEmpty a6989586621679729606) (l :: TyFun (NonEmpty b6989586621679729607) (NonEmpty c6989586621679729608)) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679729606 (TyFun b6989586621679729607 c6989586621679729608 -> Type) -> Type) -> NonEmpty a6989586621679729606 -> TyFun (NonEmpty b6989586621679729607) (NonEmpty c6989586621679729608) -> *) (ZipWithSym2 a6989586621679729606 b6989586621679729607 c6989586621679729608) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWithSym2 a6989586621679729606 b6989586621679729607 c6989586621679729608) t -> () Source #

type Apply (NonEmpty b) (NonEmpty c) (ZipWithSym2 a b c l1 l2) l3 Source # 
type Apply (NonEmpty b) (NonEmpty c) (ZipWithSym2 a b c l1 l2) l3 = ZipWith a b c l1 l2 l3

type ZipWithSym3 (t :: TyFun a6989586621679729606 (TyFun b6989586621679729607 c6989586621679729608 -> Type) -> Type) (t :: NonEmpty a6989586621679729606) (t :: NonEmpty b6989586621679729607) = ZipWith t t t Source #

data UnzipSym0 (l :: TyFun (NonEmpty (a6989586621679729604, b6989586621679729605)) (NonEmpty a6989586621679729604, NonEmpty b6989586621679729605)) Source #

Instances

SuppressUnusedWarnings (TyFun (NonEmpty (a6989586621679729604, b6989586621679729605)) (NonEmpty a6989586621679729604, NonEmpty b6989586621679729605) -> *) (UnzipSym0 a6989586621679729604 b6989586621679729605) Source # 

Methods

suppressUnusedWarnings :: Proxy (UnzipSym0 a6989586621679729604 b6989586621679729605) t -> () Source #

type Apply (NonEmpty (a, b)) (NonEmpty a, NonEmpty b) (UnzipSym0 a b) l Source # 
type Apply (NonEmpty (a, b)) (NonEmpty a, NonEmpty b) (UnzipSym0 a b) l = Unzip a b l

type UnzipSym1 (t :: NonEmpty (a6989586621679729604, b6989586621679729605)) = Unzip t Source #

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

Instances

SuppressUnusedWarnings (TyFun [a6989586621679729650] (NonEmpty a6989586621679729650) -> *) (FromListSym0 a6989586621679729650) Source # 

Methods

suppressUnusedWarnings :: Proxy (FromListSym0 a6989586621679729650) t -> () Source #

type Apply [a] (NonEmpty a) (FromListSym0 a) l Source # 
type Apply [a] (NonEmpty a) (FromListSym0 a) l = FromList a l

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

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

Instances

SuppressUnusedWarnings (TyFun (NonEmpty a6989586621679729649) [a6989586621679729649] -> *) (ToListSym0 a6989586621679729649) Source # 

Methods

suppressUnusedWarnings :: Proxy (ToListSym0 a6989586621679729649) t -> () Source #

type Apply (NonEmpty a) [a] (ToListSym0 a) l Source # 
type Apply (NonEmpty a) [a] (ToListSym0 a) l = ToList a l

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

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

Instances

SuppressUnusedWarnings (TyFun [a6989586621679729661] (Maybe (NonEmpty a6989586621679729661)) -> *) (NonEmpty_Sym0 a6989586621679729661) Source # 

Methods

suppressUnusedWarnings :: Proxy (NonEmpty_Sym0 a6989586621679729661) t -> () Source #

type Apply [a] (Maybe (NonEmpty a)) (NonEmpty_Sym0 a) l Source # 
type Apply [a] (Maybe (NonEmpty a)) (NonEmpty_Sym0 a) l = NonEmpty_ a l

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

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