singletons-2.3: 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_6989586621679727059 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_6989586621679727312 = Apply (Apply (Apply (:.$) FromListSym0) (Apply (Apply ListscanlSym0 f) z)) a_6989586621679727312 

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_6989586621679727332 = Apply (Apply (Apply (:.$) FromListSym0) (Apply (Apply ListscanrSym0 f) z)) a_6989586621679727332 

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_6989586621679727566 = Apply (Apply (Apply (:.$) (Apply FmapSym0 FromListSym0)) (Apply (Apply (:.$) FromListSym0) (Apply (Apply (:.$) ListtransposeSym0) (Apply (Apply (:.$) ToListSym0) (Apply FmapSym0 ToListSym0))))) a_6989586621679727566 

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

Equations

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

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_6989586621679727242 a_6989586621679727244 = Apply (Apply (Apply (Apply (:.$) SortBySym0) ComparingSym0) a_6989586621679727242) a_6989586621679727244 

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_6989586621679727550 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_6989586621679727420) = 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_6989586621679727411 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_6989586621679727380 a_6989586621679727382 = Apply (Apply (:<|$) a_6989586621679727380) a_6989586621679727382 

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_6989586621679727475 f a (Let6989586621679727467Scrutinee_6989586621679726598Sym2 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_6989586621679727361 = Apply (Apply LiftSym0 ListsortSym0) a_6989586621679727361 

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_6989586621679727222 = Apply (Apply LiftSym0 ListreverseSym0) a_6989586621679727222 

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_6989586621679727270 = Apply (Apply (Apply (:.$) FromListSym0) ListinitsSym0) a_6989586621679727270 

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_6989586621679727277 = Apply (Apply (Apply (:.$) FromListSym0) ListtailsSym0) a_6989586621679727277 

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_6989586621679727511 f a (Let6989586621679727503Scrutinee_6989586621679726596Sym2 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_6989586621679727293 = Apply (Apply (Apply (:.$) FromListSym0) (Apply ListinsertSym0 a)) a_6989586621679727293 

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_6989586621679727095 = Apply (Apply (Apply (:.$) (Apply ListtakeSym0 n)) ToListSym0) a_6989586621679727095 

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_6989586621679727108 = Apply (Apply (Apply (:.$) (Apply ListdropSym0 n)) ToListSym0) a_6989586621679727108 

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_6989586621679727121 = Apply (Apply (Apply (:.$) (Apply ListsplitAtSym0 n)) ToListSym0) a_6989586621679727121 

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_6989586621679727134 = Apply (Apply (Apply (:.$) (Apply ListtakeWhileSym0 p)) ToListSym0) a_6989586621679727134 

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_6989586621679727147 = Apply (Apply (Apply (:.$) (Apply ListdropWhileSym0 p)) ToListSym0) a_6989586621679727147 

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_6989586621679727160 = Apply (Apply (Apply (:.$) (Apply ListspanSym0 p)) ToListSym0) a_6989586621679727160 

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_6989586621679727173 = Apply (Apply SpanSym0 (Apply (Apply (:.$) NotSym0) p)) a_6989586621679727173 

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_6989586621679727186 = Apply (Apply (Apply (:.$) (Apply ListfilterSym0 p)) ToListSym0) a_6989586621679727186 

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_6989586621679727199 = Apply (Apply (Apply (:.$) (Apply ListpartitionSym0 p)) ToListSym0) a_6989586621679727199 

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_6989586621679727040 = Apply (Apply GroupBySym0 (:==$)) a_6989586621679727040 

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_6989586621679726798 = Apply (Apply (Let6989586621679726802GoSym2 eq0 a_6989586621679726798) eq0) a_6989586621679726798 

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_6989586621679726934 = Apply (Apply GroupBySym0 (Apply (Apply OnSym0 (:==$)) f)) a_6989586621679726934 

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_6989586621679726947 = Apply (Apply (Apply (:.$) (Apply GroupWithSym0 f)) (Apply ListsortBySym0 (Apply (Apply OnSym0 CompareSym0) f))) a_6989586621679726947 

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_6989586621679727020 = Apply (Apply GroupBy1Sym0 (:==$)) a_6989586621679727020 

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) (Let6989586621679726963YsSym3 eq x xs))) (Apply (Apply GroupBySym0 eq) (Let6989586621679726963ZsSym3 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_6989586621679727036 = Apply (Apply GroupBy1Sym0 (Apply (Apply OnSym0 (:==$)) f)) a_6989586621679727036 

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_6989586621679727266 = Apply (Apply (Apply (:.$) (Apply GroupWith1Sym0 f)) (Apply SortWithSym0 f)) a_6989586621679727266 

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_6989586621679726782 = 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_6989586621679726646 = Apply (Apply NubBySym0 (:==$)) a_6989586621679726646 

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_6989586621679726624Sym0 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_6989586621679726602 :!! arg_6989586621679726604 = Case_6989586621679726761 arg_6989586621679726602 arg_6989586621679726604 (Apply (Apply Tuple2Sym0 arg_6989586621679726602) arg_6989586621679726604) 

(%:!!) :: 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) (Let6989586621679726660AsSym3 a b asbs))) (Apply (Apply (:|$) b) (Let6989586621679726660BsSym3 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 (Let6989586621679727523Xor'Sym2 x xs)) x) xs 

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

Defunctionalization symbols

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

Instances

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

Methods

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

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

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

Instances

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

Methods

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

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

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

data MapSym0 (l :: TyFun (TyFun a6989586621679726412 b6989586621679726413 -> Type) (TyFun (NonEmpty a6989586621679726412) (NonEmpty b6989586621679726413) -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679726412 b6989586621679726413 -> Type) (TyFun (NonEmpty a6989586621679726412) (NonEmpty b6989586621679726413) -> Type) -> *) (MapSym0 a6989586621679726412 b6989586621679726413) Source # 

Methods

suppressUnusedWarnings :: Proxy (MapSym0 a6989586621679726412 b6989586621679726413) t -> () Source #

type Apply (TyFun a6989586621679726412 b6989586621679726413 -> Type) (TyFun (NonEmpty a6989586621679726412) (NonEmpty b6989586621679726413) -> Type) (MapSym0 a6989586621679726412 b6989586621679726413) l Source # 
type Apply (TyFun a6989586621679726412 b6989586621679726413 -> Type) (TyFun (NonEmpty a6989586621679726412) (NonEmpty b6989586621679726413) -> Type) (MapSym0 a6989586621679726412 b6989586621679726413) l = MapSym1 a6989586621679726412 b6989586621679726413 l

data MapSym1 (l :: TyFun a6989586621679726412 b6989586621679726413 -> Type) (l :: TyFun (NonEmpty a6989586621679726412) (NonEmpty b6989586621679726413)) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679726412 b6989586621679726413 -> Type) -> TyFun (NonEmpty a6989586621679726412) (NonEmpty b6989586621679726413) -> *) (MapSym1 a6989586621679726412 b6989586621679726413) Source # 

Methods

suppressUnusedWarnings :: Proxy (MapSym1 a6989586621679726412 b6989586621679726413) 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 a6989586621679726412 b6989586621679726413 -> Type) (t :: NonEmpty a6989586621679726412) = Map t t Source #

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

Instances

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

Methods

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

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (IntersperseSym1 a6989586621679726402) 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 :: a6989586621679726402) (t :: NonEmpty a6989586621679726402) = Intersperse t t Source #

data ScanlSym0 (l :: TyFun (TyFun b6989586621679726407 (TyFun a6989586621679726408 b6989586621679726407 -> Type) -> Type) (TyFun b6989586621679726407 (TyFun [a6989586621679726408] (NonEmpty b6989586621679726407) -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun (TyFun b6989586621679726407 (TyFun a6989586621679726408 b6989586621679726407 -> Type) -> Type) (TyFun b6989586621679726407 (TyFun [a6989586621679726408] (NonEmpty b6989586621679726407) -> Type) -> Type) -> *) (ScanlSym0 a6989586621679726408 b6989586621679726407) Source # 

Methods

suppressUnusedWarnings :: Proxy (ScanlSym0 a6989586621679726408 b6989586621679726407) t -> () Source #

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

data ScanlSym1 (l :: TyFun b6989586621679726407 (TyFun a6989586621679726408 b6989586621679726407 -> Type) -> Type) (l :: TyFun b6989586621679726407 (TyFun [a6989586621679726408] (NonEmpty b6989586621679726407) -> Type)) Source #

Instances

SuppressUnusedWarnings ((TyFun b6989586621679726407 (TyFun a6989586621679726408 b6989586621679726407 -> Type) -> Type) -> TyFun b6989586621679726407 (TyFun [a6989586621679726408] (NonEmpty b6989586621679726407) -> Type) -> *) (ScanlSym1 a6989586621679726408 b6989586621679726407) Source # 

Methods

suppressUnusedWarnings :: Proxy (ScanlSym1 a6989586621679726408 b6989586621679726407) t -> () Source #

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

data ScanlSym2 (l :: TyFun b6989586621679726407 (TyFun a6989586621679726408 b6989586621679726407 -> Type) -> Type) (l :: b6989586621679726407) (l :: TyFun [a6989586621679726408] (NonEmpty b6989586621679726407)) Source #

Instances

SuppressUnusedWarnings ((TyFun b6989586621679726407 (TyFun a6989586621679726408 b6989586621679726407 -> Type) -> Type) -> b6989586621679726407 -> TyFun [a6989586621679726408] (NonEmpty b6989586621679726407) -> *) (ScanlSym2 a6989586621679726408 b6989586621679726407) Source # 

Methods

suppressUnusedWarnings :: Proxy (ScanlSym2 a6989586621679726408 b6989586621679726407) 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 b6989586621679726407 (TyFun a6989586621679726408 b6989586621679726407 -> Type) -> Type) (t :: b6989586621679726407) (t :: [a6989586621679726408]) = Scanl t t t Source #

data ScanrSym0 (l :: TyFun (TyFun a6989586621679726405 (TyFun b6989586621679726406 b6989586621679726406 -> Type) -> Type) (TyFun b6989586621679726406 (TyFun [a6989586621679726405] (NonEmpty b6989586621679726406) -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679726405 (TyFun b6989586621679726406 b6989586621679726406 -> Type) -> Type) (TyFun b6989586621679726406 (TyFun [a6989586621679726405] (NonEmpty b6989586621679726406) -> Type) -> Type) -> *) (ScanrSym0 a6989586621679726405 b6989586621679726406) Source # 

Methods

suppressUnusedWarnings :: Proxy (ScanrSym0 a6989586621679726405 b6989586621679726406) t -> () Source #

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

data ScanrSym1 (l :: TyFun a6989586621679726405 (TyFun b6989586621679726406 b6989586621679726406 -> Type) -> Type) (l :: TyFun b6989586621679726406 (TyFun [a6989586621679726405] (NonEmpty b6989586621679726406) -> Type)) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679726405 (TyFun b6989586621679726406 b6989586621679726406 -> Type) -> Type) -> TyFun b6989586621679726406 (TyFun [a6989586621679726405] (NonEmpty b6989586621679726406) -> Type) -> *) (ScanrSym1 a6989586621679726405 b6989586621679726406) Source # 

Methods

suppressUnusedWarnings :: Proxy (ScanrSym1 a6989586621679726405 b6989586621679726406) t -> () Source #

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

data ScanrSym2 (l :: TyFun a6989586621679726405 (TyFun b6989586621679726406 b6989586621679726406 -> Type) -> Type) (l :: b6989586621679726406) (l :: TyFun [a6989586621679726405] (NonEmpty b6989586621679726406)) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679726405 (TyFun b6989586621679726406 b6989586621679726406 -> Type) -> Type) -> b6989586621679726406 -> TyFun [a6989586621679726405] (NonEmpty b6989586621679726406) -> *) (ScanrSym2 a6989586621679726405 b6989586621679726406) Source # 

Methods

suppressUnusedWarnings :: Proxy (ScanrSym2 a6989586621679726405 b6989586621679726406) 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 a6989586621679726405 (TyFun b6989586621679726406 b6989586621679726406 -> Type) -> Type) (t :: b6989586621679726406) (t :: [a6989586621679726405]) = Scanr t t t Source #

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

Instances

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

Methods

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

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (Scanl1Sym1 a6989586621679726404) 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 a6989586621679726404 (TyFun a6989586621679726404 a6989586621679726404 -> Type) -> Type) (t :: NonEmpty a6989586621679726404) = Scanl1 t t Source #

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

Instances

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

Methods

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

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (Scanr1Sym1 a6989586621679726403) 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 a6989586621679726403 (TyFun a6989586621679726403 a6989586621679726403 -> Type) -> Type) (t :: NonEmpty a6989586621679726403) = Scanr1 t t Source #

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

Instances

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

Methods

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

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

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

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

Instances

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

Methods

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

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (SortBySym1 a6989586621679726367) 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 a6989586621679726367 (TyFun a6989586621679726367 Ordering -> Type) -> Type) (t :: NonEmpty a6989586621679726367) = SortBy t t Source #

data SortWithSym0 (l :: TyFun (TyFun a6989586621679726366 o6989586621679726365 -> Type) (TyFun (NonEmpty a6989586621679726366) (NonEmpty a6989586621679726366) -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679726366 o6989586621679726365 -> Type) (TyFun (NonEmpty a6989586621679726366) (NonEmpty a6989586621679726366) -> Type) -> *) (SortWithSym0 o6989586621679726365 a6989586621679726366) Source # 

Methods

suppressUnusedWarnings :: Proxy (SortWithSym0 o6989586621679726365 a6989586621679726366) t -> () Source #

type Apply (TyFun a6989586621679726366 o6989586621679726365 -> Type) (TyFun (NonEmpty a6989586621679726366) (NonEmpty a6989586621679726366) -> Type) (SortWithSym0 o6989586621679726365 a6989586621679726366) l Source # 
type Apply (TyFun a6989586621679726366 o6989586621679726365 -> Type) (TyFun (NonEmpty a6989586621679726366) (NonEmpty a6989586621679726366) -> Type) (SortWithSym0 o6989586621679726365 a6989586621679726366) l = SortWithSym1 o6989586621679726365 a6989586621679726366 l

data SortWithSym1 (l :: TyFun a6989586621679726366 o6989586621679726365 -> Type) (l :: TyFun (NonEmpty a6989586621679726366) (NonEmpty a6989586621679726366)) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679726366 o6989586621679726365 -> Type) -> TyFun (NonEmpty a6989586621679726366) (NonEmpty a6989586621679726366) -> *) (SortWithSym1 o6989586621679726365 a6989586621679726366) Source # 

Methods

suppressUnusedWarnings :: Proxy (SortWithSym1 o6989586621679726365 a6989586621679726366) 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 a6989586621679726366 o6989586621679726365 -> Type) (t :: NonEmpty a6989586621679726366) = SortWith t t Source #

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (LengthSym0 a6989586621679726431) 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 a6989586621679726431) = Length t Source #

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (HeadSym0 a6989586621679726424) 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 a6989586621679726424) = Head t Source #

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (TailSym0 a6989586621679726423) 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 a6989586621679726423) = Tail t Source #

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (LastSym0 a6989586621679726422) 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 a6989586621679726422) = Last t Source #

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (InitSym0 a6989586621679726421) 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 a6989586621679726421) = Init t Source #

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

Instances

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

Methods

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

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy ((:<|$$) a6989586621679726420) 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 :: a6989586621679726420) (t :: NonEmpty a6989586621679726420) = (:<|) t t Source #

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

Instances

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

Methods

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

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (ConsSym1 a6989586621679726419) 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 :: a6989586621679726419) (t :: NonEmpty a6989586621679726419) = Cons t t Source #

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (UnconsSym0 a6989586621679726427) 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 a6989586621679726427) = Uncons t Source #

data UnfoldrSym0 (l :: TyFun (TyFun a6989586621679726425 (b6989586621679726426, Maybe a6989586621679726425) -> Type) (TyFun a6989586621679726425 (NonEmpty b6989586621679726426) -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679726425 (b6989586621679726426, Maybe a6989586621679726425) -> Type) (TyFun a6989586621679726425 (NonEmpty b6989586621679726426) -> Type) -> *) (UnfoldrSym0 a6989586621679726425 b6989586621679726426) Source # 

Methods

suppressUnusedWarnings :: Proxy (UnfoldrSym0 a6989586621679726425 b6989586621679726426) t -> () Source #

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

data UnfoldrSym1 (l :: TyFun a6989586621679726425 (b6989586621679726426, Maybe a6989586621679726425) -> Type) (l :: TyFun a6989586621679726425 (NonEmpty b6989586621679726426)) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679726425 (b6989586621679726426, Maybe a6989586621679726425) -> Type) -> TyFun a6989586621679726425 (NonEmpty b6989586621679726426) -> *) (UnfoldrSym1 a6989586621679726425 b6989586621679726426) Source # 

Methods

suppressUnusedWarnings :: Proxy (UnfoldrSym1 a6989586621679726425 b6989586621679726426) 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 a6989586621679726425 (b6989586621679726426, Maybe a6989586621679726425) -> Type) (t :: a6989586621679726425) = Unfoldr t t Source #

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (SortSym0 a6989586621679726418) 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 a6989586621679726418) = Sort t Source #

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (ReverseSym0 a6989586621679726401) 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 a6989586621679726401) = Reverse t Source #

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (InitsSym0 a6989586621679726411) 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 :: [a6989586621679726411]) = Inits t Source #

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (TailsSym0 a6989586621679726410) 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 :: [a6989586621679726410]) = Tails t Source #

data UnfoldSym0 (l :: TyFun (TyFun a6989586621679726429 (b6989586621679726430, Maybe a6989586621679726429) -> Type) (TyFun a6989586621679726429 (NonEmpty b6989586621679726430) -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679726429 (b6989586621679726430, Maybe a6989586621679726429) -> Type) (TyFun a6989586621679726429 (NonEmpty b6989586621679726430) -> Type) -> *) (UnfoldSym0 a6989586621679726429 b6989586621679726430) Source # 

Methods

suppressUnusedWarnings :: Proxy (UnfoldSym0 a6989586621679726429 b6989586621679726430) t -> () Source #

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

data UnfoldSym1 (l :: TyFun a6989586621679726429 (b6989586621679726430, Maybe a6989586621679726429) -> Type) (l :: TyFun a6989586621679726429 (NonEmpty b6989586621679726430)) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679726429 (b6989586621679726430, Maybe a6989586621679726429) -> Type) -> TyFun a6989586621679726429 (NonEmpty b6989586621679726430) -> *) (UnfoldSym1 a6989586621679726429 b6989586621679726430) Source # 

Methods

suppressUnusedWarnings :: Proxy (UnfoldSym1 a6989586621679726429 b6989586621679726430) 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 a6989586621679726409 (TyFun [a6989586621679726409] (NonEmpty a6989586621679726409) -> Type)) Source #

Instances

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

Methods

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

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (InsertSym1 a6989586621679726409) 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 :: a6989586621679726409) (t :: [a6989586621679726409]) = Insert t t Source #

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

Instances

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

Methods

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

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (TakeSym1 a6989586621679726400) 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 a6989586621679726400) = Take t t Source #

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

Instances

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

Methods

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

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (DropSym1 a6989586621679726399) 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 a6989586621679726399) = Drop t t Source #

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

Instances

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

Methods

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

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (SplitAtSym1 a6989586621679726398) 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 a6989586621679726398) = SplitAt t t Source #

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

Instances

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

Methods

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

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (TakeWhileSym1 a6989586621679726397) 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 a6989586621679726397 Bool -> Type) (t :: NonEmpty a6989586621679726397) = TakeWhile t t Source #

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

Instances

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

Methods

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

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (DropWhileSym1 a6989586621679726396) 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 a6989586621679726396 Bool -> Type) (t :: NonEmpty a6989586621679726396) = DropWhile t t Source #

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

Instances

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

Methods

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

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (SpanSym1 a6989586621679726395) 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 a6989586621679726395 Bool -> Type) (t :: NonEmpty a6989586621679726395) = Span t t Source #

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

Instances

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

Methods

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

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (BreakSym1 a6989586621679726394) 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 a6989586621679726394 Bool -> Type) (t :: NonEmpty a6989586621679726394) = Break t t Source #

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

Instances

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

Methods

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

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (FilterSym1 a6989586621679726393) 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 a6989586621679726393 Bool -> Type) (t :: NonEmpty a6989586621679726393) = Filter t t Source #

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

Instances

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

Methods

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

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (PartitionSym1 a6989586621679726392) 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 a6989586621679726392 Bool -> Type) (t :: NonEmpty a6989586621679726392) = Partition t t Source #

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (GroupSym0 a6989586621679726391) 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 :: [a6989586621679726391]) = Group t Source #

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

Instances

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

Methods

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

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (GroupBySym1 a6989586621679726390) 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 a6989586621679726390 (TyFun a6989586621679726390 Bool -> Type) -> Type) (t :: [a6989586621679726390]) = GroupBy t t Source #

data GroupWithSym0 (l :: TyFun (TyFun a6989586621679726389 b6989586621679726388 -> Type) (TyFun [a6989586621679726389] [NonEmpty a6989586621679726389] -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679726389 b6989586621679726388 -> Type) (TyFun [a6989586621679726389] [NonEmpty a6989586621679726389] -> Type) -> *) (GroupWithSym0 b6989586621679726388 a6989586621679726389) Source # 

Methods

suppressUnusedWarnings :: Proxy (GroupWithSym0 b6989586621679726388 a6989586621679726389) t -> () Source #

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

data GroupWithSym1 (l :: TyFun a6989586621679726389 b6989586621679726388 -> Type) (l :: TyFun [a6989586621679726389] [NonEmpty a6989586621679726389]) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679726389 b6989586621679726388 -> Type) -> TyFun [a6989586621679726389] [NonEmpty a6989586621679726389] -> *) (GroupWithSym1 b6989586621679726388 a6989586621679726389) Source # 

Methods

suppressUnusedWarnings :: Proxy (GroupWithSym1 b6989586621679726388 a6989586621679726389) 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 a6989586621679726389 b6989586621679726388 -> Type) (t :: [a6989586621679726389]) = GroupWith t t Source #

data GroupAllWithSym0 (l :: TyFun (TyFun a6989586621679726387 b6989586621679726386 -> Type) (TyFun [a6989586621679726387] [NonEmpty a6989586621679726387] -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679726387 b6989586621679726386 -> Type) (TyFun [a6989586621679726387] [NonEmpty a6989586621679726387] -> Type) -> *) (GroupAllWithSym0 b6989586621679726386 a6989586621679726387) Source # 

Methods

suppressUnusedWarnings :: Proxy (GroupAllWithSym0 b6989586621679726386 a6989586621679726387) t -> () Source #

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

data GroupAllWithSym1 (l :: TyFun a6989586621679726387 b6989586621679726386 -> Type) (l :: TyFun [a6989586621679726387] [NonEmpty a6989586621679726387]) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679726387 b6989586621679726386 -> Type) -> TyFun [a6989586621679726387] [NonEmpty a6989586621679726387] -> *) (GroupAllWithSym1 b6989586621679726386 a6989586621679726387) Source # 

Methods

suppressUnusedWarnings :: Proxy (GroupAllWithSym1 b6989586621679726386 a6989586621679726387) 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 a6989586621679726387 b6989586621679726386 -> Type) (t :: [a6989586621679726387]) = GroupAllWith t t Source #

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (Group1Sym0 a6989586621679726385) 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 a6989586621679726385) = Group1 t Source #

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

Instances

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

Methods

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

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (GroupBy1Sym1 a6989586621679726384) 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 a6989586621679726384 (TyFun a6989586621679726384 Bool -> Type) -> Type) (t :: NonEmpty a6989586621679726384) = GroupBy1 t t Source #

data GroupWith1Sym0 (l :: TyFun (TyFun a6989586621679726383 b6989586621679726382 -> Type) (TyFun (NonEmpty a6989586621679726383) (NonEmpty (NonEmpty a6989586621679726383)) -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679726383 b6989586621679726382 -> Type) (TyFun (NonEmpty a6989586621679726383) (NonEmpty (NonEmpty a6989586621679726383)) -> Type) -> *) (GroupWith1Sym0 b6989586621679726382 a6989586621679726383) Source # 

Methods

suppressUnusedWarnings :: Proxy (GroupWith1Sym0 b6989586621679726382 a6989586621679726383) t -> () Source #

type Apply (TyFun a6989586621679726383 b6989586621679726382 -> Type) (TyFun (NonEmpty a6989586621679726383) (NonEmpty (NonEmpty a6989586621679726383)) -> Type) (GroupWith1Sym0 b6989586621679726382 a6989586621679726383) l Source # 
type Apply (TyFun a6989586621679726383 b6989586621679726382 -> Type) (TyFun (NonEmpty a6989586621679726383) (NonEmpty (NonEmpty a6989586621679726383)) -> Type) (GroupWith1Sym0 b6989586621679726382 a6989586621679726383) l = GroupWith1Sym1 b6989586621679726382 a6989586621679726383 l

data GroupWith1Sym1 (l :: TyFun a6989586621679726383 b6989586621679726382 -> Type) (l :: TyFun (NonEmpty a6989586621679726383) (NonEmpty (NonEmpty a6989586621679726383))) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679726383 b6989586621679726382 -> Type) -> TyFun (NonEmpty a6989586621679726383) (NonEmpty (NonEmpty a6989586621679726383)) -> *) (GroupWith1Sym1 b6989586621679726382 a6989586621679726383) Source # 

Methods

suppressUnusedWarnings :: Proxy (GroupWith1Sym1 b6989586621679726382 a6989586621679726383) 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 a6989586621679726383 b6989586621679726382 -> Type) (t :: NonEmpty a6989586621679726383) = GroupWith1 t t Source #

data GroupAllWith1Sym0 (l :: TyFun (TyFun a6989586621679726381 b6989586621679726380 -> Type) (TyFun (NonEmpty a6989586621679726381) (NonEmpty (NonEmpty a6989586621679726381)) -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679726381 b6989586621679726380 -> Type) (TyFun (NonEmpty a6989586621679726381) (NonEmpty (NonEmpty a6989586621679726381)) -> Type) -> *) (GroupAllWith1Sym0 b6989586621679726380 a6989586621679726381) Source # 

Methods

suppressUnusedWarnings :: Proxy (GroupAllWith1Sym0 b6989586621679726380 a6989586621679726381) t -> () Source #

type Apply (TyFun a6989586621679726381 b6989586621679726380 -> Type) (TyFun (NonEmpty a6989586621679726381) (NonEmpty (NonEmpty a6989586621679726381)) -> Type) (GroupAllWith1Sym0 b6989586621679726380 a6989586621679726381) l Source # 
type Apply (TyFun a6989586621679726381 b6989586621679726380 -> Type) (TyFun (NonEmpty a6989586621679726381) (NonEmpty (NonEmpty a6989586621679726381)) -> Type) (GroupAllWith1Sym0 b6989586621679726380 a6989586621679726381) l = GroupAllWith1Sym1 b6989586621679726380 a6989586621679726381 l

data GroupAllWith1Sym1 (l :: TyFun a6989586621679726381 b6989586621679726380 -> Type) (l :: TyFun (NonEmpty a6989586621679726381) (NonEmpty (NonEmpty a6989586621679726381))) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679726381 b6989586621679726380 -> Type) -> TyFun (NonEmpty a6989586621679726381) (NonEmpty (NonEmpty a6989586621679726381)) -> *) (GroupAllWith1Sym1 b6989586621679726380 a6989586621679726381) Source # 

Methods

suppressUnusedWarnings :: Proxy (GroupAllWith1Sym1 b6989586621679726380 a6989586621679726381) 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 a6989586621679726381 b6989586621679726380 -> Type) (t :: NonEmpty a6989586621679726381) = GroupAllWith1 t t Source #

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

Instances

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

Methods

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

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (IsPrefixOfSym1 a6989586621679726379) 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 :: [a6989586621679726379]) (t :: NonEmpty a6989586621679726379) = IsPrefixOf t t Source #

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (NubSym0 a6989586621679726370) 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 a6989586621679726370) = Nub t Source #

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

Instances

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

Methods

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

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (NubBySym1 a6989586621679726369) 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 a6989586621679726369 (TyFun a6989586621679726369 Bool -> Type) -> Type) (t :: NonEmpty a6989586621679726369) = NubBy t t Source #

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

Instances

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

Methods

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

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

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

Instances

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

Methods

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

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

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

data ZipSym0 (l :: TyFun (NonEmpty a6989586621679726376) (TyFun (NonEmpty b6989586621679726377) (NonEmpty (a6989586621679726376, b6989586621679726377)) -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun (NonEmpty a6989586621679726376) (TyFun (NonEmpty b6989586621679726377) (NonEmpty (a6989586621679726376, b6989586621679726377)) -> Type) -> *) (ZipSym0 a6989586621679726376 b6989586621679726377) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipSym0 a6989586621679726376 b6989586621679726377) t -> () Source #

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

data ZipSym1 (l :: NonEmpty a6989586621679726376) (l :: TyFun (NonEmpty b6989586621679726377) (NonEmpty (a6989586621679726376, b6989586621679726377))) Source #

Instances

SuppressUnusedWarnings (NonEmpty a6989586621679726376 -> TyFun (NonEmpty b6989586621679726377) (NonEmpty (a6989586621679726376, b6989586621679726377)) -> *) (ZipSym1 a6989586621679726376 b6989586621679726377) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipSym1 a6989586621679726376 b6989586621679726377) 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 a6989586621679726376) (t :: NonEmpty b6989586621679726377) = Zip t t Source #

data ZipWithSym0 (l :: TyFun (TyFun a6989586621679726373 (TyFun b6989586621679726374 c6989586621679726375 -> Type) -> Type) (TyFun (NonEmpty a6989586621679726373) (TyFun (NonEmpty b6989586621679726374) (NonEmpty c6989586621679726375) -> Type) -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679726373 (TyFun b6989586621679726374 c6989586621679726375 -> Type) -> Type) (TyFun (NonEmpty a6989586621679726373) (TyFun (NonEmpty b6989586621679726374) (NonEmpty c6989586621679726375) -> Type) -> Type) -> *) (ZipWithSym0 a6989586621679726373 b6989586621679726374 c6989586621679726375) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWithSym0 a6989586621679726373 b6989586621679726374 c6989586621679726375) t -> () Source #

type Apply (TyFun a6989586621679726373 (TyFun b6989586621679726374 c6989586621679726375 -> Type) -> Type) (TyFun (NonEmpty a6989586621679726373) (TyFun (NonEmpty b6989586621679726374) (NonEmpty c6989586621679726375) -> Type) -> Type) (ZipWithSym0 a6989586621679726373 b6989586621679726374 c6989586621679726375) l Source # 
type Apply (TyFun a6989586621679726373 (TyFun b6989586621679726374 c6989586621679726375 -> Type) -> Type) (TyFun (NonEmpty a6989586621679726373) (TyFun (NonEmpty b6989586621679726374) (NonEmpty c6989586621679726375) -> Type) -> Type) (ZipWithSym0 a6989586621679726373 b6989586621679726374 c6989586621679726375) l = ZipWithSym1 a6989586621679726373 b6989586621679726374 c6989586621679726375 l

data ZipWithSym1 (l :: TyFun a6989586621679726373 (TyFun b6989586621679726374 c6989586621679726375 -> Type) -> Type) (l :: TyFun (NonEmpty a6989586621679726373) (TyFun (NonEmpty b6989586621679726374) (NonEmpty c6989586621679726375) -> Type)) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679726373 (TyFun b6989586621679726374 c6989586621679726375 -> Type) -> Type) -> TyFun (NonEmpty a6989586621679726373) (TyFun (NonEmpty b6989586621679726374) (NonEmpty c6989586621679726375) -> Type) -> *) (ZipWithSym1 a6989586621679726373 b6989586621679726374 c6989586621679726375) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWithSym1 a6989586621679726373 b6989586621679726374 c6989586621679726375) t -> () Source #

type Apply (NonEmpty a6989586621679726373) (TyFun (NonEmpty b6989586621679726374) (NonEmpty c6989586621679726375) -> Type) (ZipWithSym1 a6989586621679726373 b6989586621679726374 c6989586621679726375 l1) l2 Source # 
type Apply (NonEmpty a6989586621679726373) (TyFun (NonEmpty b6989586621679726374) (NonEmpty c6989586621679726375) -> Type) (ZipWithSym1 a6989586621679726373 b6989586621679726374 c6989586621679726375 l1) l2 = ZipWithSym2 a6989586621679726373 b6989586621679726374 c6989586621679726375 l1 l2

data ZipWithSym2 (l :: TyFun a6989586621679726373 (TyFun b6989586621679726374 c6989586621679726375 -> Type) -> Type) (l :: NonEmpty a6989586621679726373) (l :: TyFun (NonEmpty b6989586621679726374) (NonEmpty c6989586621679726375)) Source #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679726373 (TyFun b6989586621679726374 c6989586621679726375 -> Type) -> Type) -> NonEmpty a6989586621679726373 -> TyFun (NonEmpty b6989586621679726374) (NonEmpty c6989586621679726375) -> *) (ZipWithSym2 a6989586621679726373 b6989586621679726374 c6989586621679726375) Source # 

Methods

suppressUnusedWarnings :: Proxy (ZipWithSym2 a6989586621679726373 b6989586621679726374 c6989586621679726375) 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 a6989586621679726373 (TyFun b6989586621679726374 c6989586621679726375 -> Type) -> Type) (t :: NonEmpty a6989586621679726373) (t :: NonEmpty b6989586621679726374) = ZipWith t t t Source #

data UnzipSym0 (l :: TyFun (NonEmpty (a6989586621679726371, b6989586621679726372)) (NonEmpty a6989586621679726371, NonEmpty b6989586621679726372)) Source #

Instances

SuppressUnusedWarnings (TyFun (NonEmpty (a6989586621679726371, b6989586621679726372)) (NonEmpty a6989586621679726371, NonEmpty b6989586621679726372) -> *) (UnzipSym0 a6989586621679726371 b6989586621679726372) Source # 

Methods

suppressUnusedWarnings :: Proxy (UnzipSym0 a6989586621679726371 b6989586621679726372) 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 (a6989586621679726371, b6989586621679726372)) = Unzip t Source #

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (FromListSym0 a6989586621679726417) 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 :: [a6989586621679726417]) = FromList t Source #

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (ToListSym0 a6989586621679726416) 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 a6989586621679726416) = ToList t Source #

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (NonEmpty_Sym0 a6989586621679726428) 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 :: [a6989586621679726428]) = NonEmpty_ t Source #

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