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

The singleton kind-indexed data family.

Instances

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

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 ... #

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

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

Equations

Intersperse a ((:|) b bs) = Apply (Apply (:|$) b) (Case_6989586621679609674 a b bs bs) 

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

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

Equations

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

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

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

Equations

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

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

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

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

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

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

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

Equations

Transpose a_6989586621679610181 = Apply (Apply (Apply (:.$) (Apply FmapSym0 FromListSym0)) (Apply (Apply (:.$) FromListSym0) (Apply (Apply (:.$) ListtransposeSym0) (Apply (Apply (:.$) ToListSym0) (Apply FmapSym0 ToListSym0))))) a_6989586621679610181 

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

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

Equations

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

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

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

Equations

SortWith a_6989586621679609857 a_6989586621679609859 = Apply (Apply (Apply (Apply (:.$) SortBySym0) ComparingSym0) a_6989586621679609857) a_6989586621679609859 

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

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

Equations

Length ((:|) _z_6989586621679610165 xs) = Apply (Apply (:+$) (FromInteger 1)) (Apply ListlengthSym0 xs) 

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

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

Equations

Head ((:|) a _z_6989586621679610035) = a 

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

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

Equations

Tail ((:|) _z_6989586621679610026 as) = as 

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

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

Equations

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

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

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

Equations

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

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

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

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

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

Equations

Cons a_6989586621679609995 a_6989586621679609997 = Apply (Apply (:<|$) a_6989586621679609995) a_6989586621679609997 

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

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

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

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

Equations

Unfoldr f a = Case_6989586621679610090 f a (Let6989586621679610082Scrutinee_6989586621679609213Sym2 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) #

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

Equations

Sort a_6989586621679609976 = Apply (Apply LiftSym0 ListsortSym0) a_6989586621679609976 

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

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

Equations

Reverse a_6989586621679609837 = Apply (Apply LiftSym0 ListreverseSym0) a_6989586621679609837 

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

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

Equations

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

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

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

Equations

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

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

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

Equations

Unfold f a = Case_6989586621679610126 f a (Let6989586621679610118Scrutinee_6989586621679609211Sym2 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) #

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

Equations

Insert a a_6989586621679609908 = Apply (Apply (Apply (:.$) FromListSym0) (Apply ListinsertSym0 a)) a_6989586621679609908 

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

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

Equations

Take n a_6989586621679609710 = Apply (Apply (Apply (:.$) (Apply ListtakeSym0 n)) ToListSym0) a_6989586621679609710 

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

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

Equations

Drop n a_6989586621679609723 = Apply (Apply (Apply (:.$) (Apply ListdropSym0 n)) ToListSym0) a_6989586621679609723 

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

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

Equations

SplitAt n a_6989586621679609736 = Apply (Apply (Apply (:.$) (Apply ListsplitAtSym0 n)) ToListSym0) a_6989586621679609736 

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

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

Equations

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

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

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

Equations

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

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

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

Equations

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

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

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

Equations

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

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

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

Equations

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

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

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

Equations

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

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

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

Equations

Group a_6989586621679609655 = Apply (Apply GroupBySym0 (:==$)) a_6989586621679609655 

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

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

Equations

GroupBy eq0 a_6989586621679609413 = Apply (Apply (Let6989586621679609417GoSym2 eq0 a_6989586621679609413) eq0) a_6989586621679609413 

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

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

Equations

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

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

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

Equations

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

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

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

Equations

Group1 a_6989586621679609635 = Apply (Apply GroupBy1Sym0 (:==$)) a_6989586621679609635 

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

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

Equations

GroupBy1 eq ((:|) x xs) = Apply (Apply (:|$) (Apply (Apply (:|$) x) (Let6989586621679609578YsSym3 eq x xs))) (Apply (Apply GroupBySym0 eq) (Let6989586621679609578ZsSym3 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)) #

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

Equations

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

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

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

Equations

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

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

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

Equations

IsPrefixOf '[] _z_6989586621679609397 = 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) #

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

Equations

Nub a_6989586621679609261 = Apply (Apply NubBySym0 (:==$)) a_6989586621679609261 

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

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

Equations

NubBy eq ((:|) a as) = Apply (Apply (:|$) a) (Apply (Apply ListnubBySym0 eq) (Apply (Apply ListfilterSym0 (Apply (Apply (Apply Lambda_6989586621679609239Sym0 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) #

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

Equations

arg_6989586621679609217 :!! arg_6989586621679609219 = Case_6989586621679609376 arg_6989586621679609217 arg_6989586621679609219 (Apply (Apply Tuple2Sym0 arg_6989586621679609217) arg_6989586621679609219) 

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

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

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

type family ZipWith (a :: TyFun a (TyFun b c -> Type) -> Type) (a :: NonEmpty a) (a :: NonEmpty b) :: NonEmpty c where ... #

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

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

Equations

Unzip ((:|) '(a, b) asbs) = Apply (Apply Tuple2Sym0 (Apply (Apply (:|$) a) (Let6989586621679609275AsSym3 a b asbs))) (Apply (Apply (:|$) b) (Let6989586621679609275BsSym3 a b asbs)) 

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

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

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

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

Equations

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

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

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

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

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

Equations

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

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

Defunctionalization symbols

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy ((:|$) a6989586621679073600) t -> () #

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy ((:|$$) a6989586621679073600) t -> () #

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

type (:|$$$) (t :: a6989586621679073600) (t :: [a6989586621679073600]) = (:|) t t #

data MapSym0 (l :: TyFun (TyFun a6989586621679609027 b6989586621679609028 -> Type) (TyFun (NonEmpty a6989586621679609027) (NonEmpty b6989586621679609028) -> Type)) #

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679609027 b6989586621679609028 -> Type) (TyFun (NonEmpty a6989586621679609027) (NonEmpty b6989586621679609028) -> Type) -> *) (MapSym0 a6989586621679609027 b6989586621679609028) # 

Methods

suppressUnusedWarnings :: Proxy (MapSym0 a6989586621679609027 b6989586621679609028) t -> () #

type Apply (TyFun a6989586621679609027 b6989586621679609028 -> Type) (TyFun (NonEmpty a6989586621679609027) (NonEmpty b6989586621679609028) -> Type) (MapSym0 a6989586621679609027 b6989586621679609028) l # 
type Apply (TyFun a6989586621679609027 b6989586621679609028 -> Type) (TyFun (NonEmpty a6989586621679609027) (NonEmpty b6989586621679609028) -> Type) (MapSym0 a6989586621679609027 b6989586621679609028) l = MapSym1 a6989586621679609027 b6989586621679609028 l

data MapSym1 (l :: TyFun a6989586621679609027 b6989586621679609028 -> Type) (l :: TyFun (NonEmpty a6989586621679609027) (NonEmpty b6989586621679609028)) #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679609027 b6989586621679609028 -> Type) -> TyFun (NonEmpty a6989586621679609027) (NonEmpty b6989586621679609028) -> *) (MapSym1 a6989586621679609027 b6989586621679609028) # 

Methods

suppressUnusedWarnings :: Proxy (MapSym1 a6989586621679609027 b6989586621679609028) t -> () #

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

type MapSym2 (t :: TyFun a6989586621679609027 b6989586621679609028 -> Type) (t :: NonEmpty a6989586621679609027) = Map t t #

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

Instances

SuppressUnusedWarnings (TyFun a6989586621679609017 (TyFun (NonEmpty a6989586621679609017) (NonEmpty a6989586621679609017) -> Type) -> *) (IntersperseSym0 a6989586621679609017) # 

Methods

suppressUnusedWarnings :: Proxy (IntersperseSym0 a6989586621679609017) t -> () #

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

data IntersperseSym1 (l :: a6989586621679609017) (l :: TyFun (NonEmpty a6989586621679609017) (NonEmpty a6989586621679609017)) #

Instances

SuppressUnusedWarnings (a6989586621679609017 -> TyFun (NonEmpty a6989586621679609017) (NonEmpty a6989586621679609017) -> *) (IntersperseSym1 a6989586621679609017) # 

Methods

suppressUnusedWarnings :: Proxy (IntersperseSym1 a6989586621679609017) t -> () #

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

type IntersperseSym2 (t :: a6989586621679609017) (t :: NonEmpty a6989586621679609017) = Intersperse t t #

data ScanlSym0 (l :: TyFun (TyFun b6989586621679609022 (TyFun a6989586621679609023 b6989586621679609022 -> Type) -> Type) (TyFun b6989586621679609022 (TyFun [a6989586621679609023] (NonEmpty b6989586621679609022) -> Type) -> Type)) #

Instances

SuppressUnusedWarnings (TyFun (TyFun b6989586621679609022 (TyFun a6989586621679609023 b6989586621679609022 -> Type) -> Type) (TyFun b6989586621679609022 (TyFun [a6989586621679609023] (NonEmpty b6989586621679609022) -> Type) -> Type) -> *) (ScanlSym0 a6989586621679609023 b6989586621679609022) # 

Methods

suppressUnusedWarnings :: Proxy (ScanlSym0 a6989586621679609023 b6989586621679609022) t -> () #

type Apply (TyFun b6989586621679609022 (TyFun a6989586621679609023 b6989586621679609022 -> Type) -> Type) (TyFun b6989586621679609022 (TyFun [a6989586621679609023] (NonEmpty b6989586621679609022) -> Type) -> Type) (ScanlSym0 a6989586621679609023 b6989586621679609022) l # 
type Apply (TyFun b6989586621679609022 (TyFun a6989586621679609023 b6989586621679609022 -> Type) -> Type) (TyFun b6989586621679609022 (TyFun [a6989586621679609023] (NonEmpty b6989586621679609022) -> Type) -> Type) (ScanlSym0 a6989586621679609023 b6989586621679609022) l = ScanlSym1 a6989586621679609023 b6989586621679609022 l

data ScanlSym1 (l :: TyFun b6989586621679609022 (TyFun a6989586621679609023 b6989586621679609022 -> Type) -> Type) (l :: TyFun b6989586621679609022 (TyFun [a6989586621679609023] (NonEmpty b6989586621679609022) -> Type)) #

Instances

SuppressUnusedWarnings ((TyFun b6989586621679609022 (TyFun a6989586621679609023 b6989586621679609022 -> Type) -> Type) -> TyFun b6989586621679609022 (TyFun [a6989586621679609023] (NonEmpty b6989586621679609022) -> Type) -> *) (ScanlSym1 a6989586621679609023 b6989586621679609022) # 

Methods

suppressUnusedWarnings :: Proxy (ScanlSym1 a6989586621679609023 b6989586621679609022) t -> () #

type Apply b6989586621679609022 (TyFun [a6989586621679609023] (NonEmpty b6989586621679609022) -> Type) (ScanlSym1 a6989586621679609023 b6989586621679609022 l1) l2 # 
type Apply b6989586621679609022 (TyFun [a6989586621679609023] (NonEmpty b6989586621679609022) -> Type) (ScanlSym1 a6989586621679609023 b6989586621679609022 l1) l2 = ScanlSym2 a6989586621679609023 b6989586621679609022 l1 l2

data ScanlSym2 (l :: TyFun b6989586621679609022 (TyFun a6989586621679609023 b6989586621679609022 -> Type) -> Type) (l :: b6989586621679609022) (l :: TyFun [a6989586621679609023] (NonEmpty b6989586621679609022)) #

Instances

SuppressUnusedWarnings ((TyFun b6989586621679609022 (TyFun a6989586621679609023 b6989586621679609022 -> Type) -> Type) -> b6989586621679609022 -> TyFun [a6989586621679609023] (NonEmpty b6989586621679609022) -> *) (ScanlSym2 a6989586621679609023 b6989586621679609022) # 

Methods

suppressUnusedWarnings :: Proxy (ScanlSym2 a6989586621679609023 b6989586621679609022) t -> () #

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

type ScanlSym3 (t :: TyFun b6989586621679609022 (TyFun a6989586621679609023 b6989586621679609022 -> Type) -> Type) (t :: b6989586621679609022) (t :: [a6989586621679609023]) = Scanl t t t #

data ScanrSym0 (l :: TyFun (TyFun a6989586621679609020 (TyFun b6989586621679609021 b6989586621679609021 -> Type) -> Type) (TyFun b6989586621679609021 (TyFun [a6989586621679609020] (NonEmpty b6989586621679609021) -> Type) -> Type)) #

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679609020 (TyFun b6989586621679609021 b6989586621679609021 -> Type) -> Type) (TyFun b6989586621679609021 (TyFun [a6989586621679609020] (NonEmpty b6989586621679609021) -> Type) -> Type) -> *) (ScanrSym0 a6989586621679609020 b6989586621679609021) # 

Methods

suppressUnusedWarnings :: Proxy (ScanrSym0 a6989586621679609020 b6989586621679609021) t -> () #

type Apply (TyFun a6989586621679609020 (TyFun b6989586621679609021 b6989586621679609021 -> Type) -> Type) (TyFun b6989586621679609021 (TyFun [a6989586621679609020] (NonEmpty b6989586621679609021) -> Type) -> Type) (ScanrSym0 a6989586621679609020 b6989586621679609021) l # 
type Apply (TyFun a6989586621679609020 (TyFun b6989586621679609021 b6989586621679609021 -> Type) -> Type) (TyFun b6989586621679609021 (TyFun [a6989586621679609020] (NonEmpty b6989586621679609021) -> Type) -> Type) (ScanrSym0 a6989586621679609020 b6989586621679609021) l = ScanrSym1 a6989586621679609020 b6989586621679609021 l

data ScanrSym1 (l :: TyFun a6989586621679609020 (TyFun b6989586621679609021 b6989586621679609021 -> Type) -> Type) (l :: TyFun b6989586621679609021 (TyFun [a6989586621679609020] (NonEmpty b6989586621679609021) -> Type)) #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679609020 (TyFun b6989586621679609021 b6989586621679609021 -> Type) -> Type) -> TyFun b6989586621679609021 (TyFun [a6989586621679609020] (NonEmpty b6989586621679609021) -> Type) -> *) (ScanrSym1 a6989586621679609020 b6989586621679609021) # 

Methods

suppressUnusedWarnings :: Proxy (ScanrSym1 a6989586621679609020 b6989586621679609021) t -> () #

type Apply b6989586621679609021 (TyFun [a6989586621679609020] (NonEmpty b6989586621679609021) -> Type) (ScanrSym1 a6989586621679609020 b6989586621679609021 l1) l2 # 
type Apply b6989586621679609021 (TyFun [a6989586621679609020] (NonEmpty b6989586621679609021) -> Type) (ScanrSym1 a6989586621679609020 b6989586621679609021 l1) l2 = ScanrSym2 a6989586621679609020 b6989586621679609021 l1 l2

data ScanrSym2 (l :: TyFun a6989586621679609020 (TyFun b6989586621679609021 b6989586621679609021 -> Type) -> Type) (l :: b6989586621679609021) (l :: TyFun [a6989586621679609020] (NonEmpty b6989586621679609021)) #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679609020 (TyFun b6989586621679609021 b6989586621679609021 -> Type) -> Type) -> b6989586621679609021 -> TyFun [a6989586621679609020] (NonEmpty b6989586621679609021) -> *) (ScanrSym2 a6989586621679609020 b6989586621679609021) # 

Methods

suppressUnusedWarnings :: Proxy (ScanrSym2 a6989586621679609020 b6989586621679609021) t -> () #

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

type ScanrSym3 (t :: TyFun a6989586621679609020 (TyFun b6989586621679609021 b6989586621679609021 -> Type) -> Type) (t :: b6989586621679609021) (t :: [a6989586621679609020]) = Scanr t t t #

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

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679609019 (TyFun a6989586621679609019 a6989586621679609019 -> Type) -> Type) (TyFun (NonEmpty a6989586621679609019) (NonEmpty a6989586621679609019) -> Type) -> *) (Scanl1Sym0 a6989586621679609019) # 

Methods

suppressUnusedWarnings :: Proxy (Scanl1Sym0 a6989586621679609019) t -> () #

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

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

Instances

SuppressUnusedWarnings ((TyFun a6989586621679609019 (TyFun a6989586621679609019 a6989586621679609019 -> Type) -> Type) -> TyFun (NonEmpty a6989586621679609019) (NonEmpty a6989586621679609019) -> *) (Scanl1Sym1 a6989586621679609019) # 

Methods

suppressUnusedWarnings :: Proxy (Scanl1Sym1 a6989586621679609019) t -> () #

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

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

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

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679609018 (TyFun a6989586621679609018 a6989586621679609018 -> Type) -> Type) (TyFun (NonEmpty a6989586621679609018) (NonEmpty a6989586621679609018) -> Type) -> *) (Scanr1Sym0 a6989586621679609018) # 

Methods

suppressUnusedWarnings :: Proxy (Scanr1Sym0 a6989586621679609018) t -> () #

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

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

Instances

SuppressUnusedWarnings ((TyFun a6989586621679609018 (TyFun a6989586621679609018 a6989586621679609018 -> Type) -> Type) -> TyFun (NonEmpty a6989586621679609018) (NonEmpty a6989586621679609018) -> *) (Scanr1Sym1 a6989586621679609018) # 

Methods

suppressUnusedWarnings :: Proxy (Scanr1Sym1 a6989586621679609018) t -> () #

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

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

data TransposeSym0 (l :: TyFun (NonEmpty (NonEmpty a6989586621679608983)) (NonEmpty (NonEmpty a6989586621679608983))) #

Instances

SuppressUnusedWarnings (TyFun (NonEmpty (NonEmpty a6989586621679608983)) (NonEmpty (NonEmpty a6989586621679608983)) -> *) (TransposeSym0 a6989586621679608983) # 

Methods

suppressUnusedWarnings :: Proxy (TransposeSym0 a6989586621679608983) t -> () #

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

type TransposeSym1 (t :: NonEmpty (NonEmpty a6989586621679608983)) = Transpose t #

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (SortBySym0 a6989586621679608982) t -> () #

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (SortBySym1 a6989586621679608982) t -> () #

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

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

data SortWithSym0 (l :: TyFun (TyFun a6989586621679608981 o6989586621679608980 -> Type) (TyFun (NonEmpty a6989586621679608981) (NonEmpty a6989586621679608981) -> Type)) #

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679608981 o6989586621679608980 -> Type) (TyFun (NonEmpty a6989586621679608981) (NonEmpty a6989586621679608981) -> Type) -> *) (SortWithSym0 o6989586621679608980 a6989586621679608981) # 

Methods

suppressUnusedWarnings :: Proxy (SortWithSym0 o6989586621679608980 a6989586621679608981) t -> () #

type Apply (TyFun a6989586621679608981 o6989586621679608980 -> Type) (TyFun (NonEmpty a6989586621679608981) (NonEmpty a6989586621679608981) -> Type) (SortWithSym0 o6989586621679608980 a6989586621679608981) l # 
type Apply (TyFun a6989586621679608981 o6989586621679608980 -> Type) (TyFun (NonEmpty a6989586621679608981) (NonEmpty a6989586621679608981) -> Type) (SortWithSym0 o6989586621679608980 a6989586621679608981) l = SortWithSym1 o6989586621679608980 a6989586621679608981 l

data SortWithSym1 (l :: TyFun a6989586621679608981 o6989586621679608980 -> Type) (l :: TyFun (NonEmpty a6989586621679608981) (NonEmpty a6989586621679608981)) #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679608981 o6989586621679608980 -> Type) -> TyFun (NonEmpty a6989586621679608981) (NonEmpty a6989586621679608981) -> *) (SortWithSym1 o6989586621679608980 a6989586621679608981) # 

Methods

suppressUnusedWarnings :: Proxy (SortWithSym1 o6989586621679608980 a6989586621679608981) t -> () #

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

type SortWithSym2 (t :: TyFun a6989586621679608981 o6989586621679608980 -> Type) (t :: NonEmpty a6989586621679608981) = SortWith t t #

data LengthSym0 (l :: TyFun (NonEmpty a6989586621679609046) Nat) #

Instances

SuppressUnusedWarnings (TyFun (NonEmpty a6989586621679609046) Nat -> *) (LengthSym0 a6989586621679609046) # 

Methods

suppressUnusedWarnings :: Proxy (LengthSym0 a6989586621679609046) t -> () #

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

type LengthSym1 (t :: NonEmpty a6989586621679609046) = Length t #

data HeadSym0 (l :: TyFun (NonEmpty a6989586621679609039) a6989586621679609039) #

Instances

SuppressUnusedWarnings (TyFun (NonEmpty a6989586621679609039) a6989586621679609039 -> *) (HeadSym0 a6989586621679609039) # 

Methods

suppressUnusedWarnings :: Proxy (HeadSym0 a6989586621679609039) t -> () #

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

type HeadSym1 (t :: NonEmpty a6989586621679609039) = Head t #

data TailSym0 (l :: TyFun (NonEmpty a6989586621679609038) [a6989586621679609038]) #

Instances

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

Methods

suppressUnusedWarnings :: Proxy (TailSym0 a6989586621679609038) t -> () #

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

type TailSym1 (t :: NonEmpty a6989586621679609038) = Tail t #

data LastSym0 (l :: TyFun (NonEmpty a6989586621679609037) a6989586621679609037) #

Instances

SuppressUnusedWarnings (TyFun (NonEmpty a6989586621679609037) a6989586621679609037 -> *) (LastSym0 a6989586621679609037) # 

Methods

suppressUnusedWarnings :: Proxy (LastSym0 a6989586621679609037) t -> () #

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

type LastSym1 (t :: NonEmpty a6989586621679609037) = Last t #

data InitSym0 (l :: TyFun (NonEmpty a6989586621679609036) [a6989586621679609036]) #

Instances

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

Methods

suppressUnusedWarnings :: Proxy (InitSym0 a6989586621679609036) t -> () #

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

type InitSym1 (t :: NonEmpty a6989586621679609036) = Init t #

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

Instances

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

Methods

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

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

data (l :: a6989586621679609035) :<|$$ (l :: TyFun (NonEmpty a6989586621679609035) (NonEmpty a6989586621679609035)) #

Instances

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

Methods

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

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

type (:<|$$$) (t :: a6989586621679609035) (t :: NonEmpty a6989586621679609035) = (:<|) t t #

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

Instances

SuppressUnusedWarnings (TyFun a6989586621679609034 (TyFun (NonEmpty a6989586621679609034) (NonEmpty a6989586621679609034) -> Type) -> *) (ConsSym0 a6989586621679609034) # 

Methods

suppressUnusedWarnings :: Proxy (ConsSym0 a6989586621679609034) t -> () #

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

data ConsSym1 (l :: a6989586621679609034) (l :: TyFun (NonEmpty a6989586621679609034) (NonEmpty a6989586621679609034)) #

Instances

SuppressUnusedWarnings (a6989586621679609034 -> TyFun (NonEmpty a6989586621679609034) (NonEmpty a6989586621679609034) -> *) (ConsSym1 a6989586621679609034) # 

Methods

suppressUnusedWarnings :: Proxy (ConsSym1 a6989586621679609034) t -> () #

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

type ConsSym2 (t :: a6989586621679609034) (t :: NonEmpty a6989586621679609034) = Cons t t #

data UnconsSym0 (l :: TyFun (NonEmpty a6989586621679609042) (a6989586621679609042, Maybe (NonEmpty a6989586621679609042))) #

Instances

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

Methods

suppressUnusedWarnings :: Proxy (UnconsSym0 a6989586621679609042) t -> () #

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

type UnconsSym1 (t :: NonEmpty a6989586621679609042) = Uncons t #

data UnfoldrSym0 (l :: TyFun (TyFun a6989586621679609040 (b6989586621679609041, Maybe a6989586621679609040) -> Type) (TyFun a6989586621679609040 (NonEmpty b6989586621679609041) -> Type)) #

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679609040 (b6989586621679609041, Maybe a6989586621679609040) -> Type) (TyFun a6989586621679609040 (NonEmpty b6989586621679609041) -> Type) -> *) (UnfoldrSym0 a6989586621679609040 b6989586621679609041) # 

Methods

suppressUnusedWarnings :: Proxy (UnfoldrSym0 a6989586621679609040 b6989586621679609041) t -> () #

type Apply (TyFun a6989586621679609040 (b6989586621679609041, Maybe a6989586621679609040) -> Type) (TyFun a6989586621679609040 (NonEmpty b6989586621679609041) -> Type) (UnfoldrSym0 a6989586621679609040 b6989586621679609041) l # 
type Apply (TyFun a6989586621679609040 (b6989586621679609041, Maybe a6989586621679609040) -> Type) (TyFun a6989586621679609040 (NonEmpty b6989586621679609041) -> Type) (UnfoldrSym0 a6989586621679609040 b6989586621679609041) l = UnfoldrSym1 a6989586621679609040 b6989586621679609041 l

data UnfoldrSym1 (l :: TyFun a6989586621679609040 (b6989586621679609041, Maybe a6989586621679609040) -> Type) (l :: TyFun a6989586621679609040 (NonEmpty b6989586621679609041)) #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679609040 (b6989586621679609041, Maybe a6989586621679609040) -> Type) -> TyFun a6989586621679609040 (NonEmpty b6989586621679609041) -> *) (UnfoldrSym1 a6989586621679609040 b6989586621679609041) # 

Methods

suppressUnusedWarnings :: Proxy (UnfoldrSym1 a6989586621679609040 b6989586621679609041) t -> () #

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

type UnfoldrSym2 (t :: TyFun a6989586621679609040 (b6989586621679609041, Maybe a6989586621679609040) -> Type) (t :: a6989586621679609040) = Unfoldr t t #

data SortSym0 (l :: TyFun (NonEmpty a6989586621679609033) (NonEmpty a6989586621679609033)) #

Instances

SuppressUnusedWarnings (TyFun (NonEmpty a6989586621679609033) (NonEmpty a6989586621679609033) -> *) (SortSym0 a6989586621679609033) # 

Methods

suppressUnusedWarnings :: Proxy (SortSym0 a6989586621679609033) t -> () #

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

type SortSym1 (t :: NonEmpty a6989586621679609033) = Sort t #

data ReverseSym0 (l :: TyFun (NonEmpty a6989586621679609016) (NonEmpty a6989586621679609016)) #

Instances

SuppressUnusedWarnings (TyFun (NonEmpty a6989586621679609016) (NonEmpty a6989586621679609016) -> *) (ReverseSym0 a6989586621679609016) # 

Methods

suppressUnusedWarnings :: Proxy (ReverseSym0 a6989586621679609016) t -> () #

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

type ReverseSym1 (t :: NonEmpty a6989586621679609016) = Reverse t #

data InitsSym0 (l :: TyFun [a6989586621679609026] (NonEmpty [a6989586621679609026])) #

Instances

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

Methods

suppressUnusedWarnings :: Proxy (InitsSym0 a6989586621679609026) t -> () #

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

type InitsSym1 (t :: [a6989586621679609026]) = Inits t #

data TailsSym0 (l :: TyFun [a6989586621679609025] (NonEmpty [a6989586621679609025])) #

Instances

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

Methods

suppressUnusedWarnings :: Proxy (TailsSym0 a6989586621679609025) t -> () #

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

type TailsSym1 (t :: [a6989586621679609025]) = Tails t #

data UnfoldSym0 (l :: TyFun (TyFun a6989586621679609044 (b6989586621679609045, Maybe a6989586621679609044) -> Type) (TyFun a6989586621679609044 (NonEmpty b6989586621679609045) -> Type)) #

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679609044 (b6989586621679609045, Maybe a6989586621679609044) -> Type) (TyFun a6989586621679609044 (NonEmpty b6989586621679609045) -> Type) -> *) (UnfoldSym0 a6989586621679609044 b6989586621679609045) # 

Methods

suppressUnusedWarnings :: Proxy (UnfoldSym0 a6989586621679609044 b6989586621679609045) t -> () #

type Apply (TyFun a6989586621679609044 (b6989586621679609045, Maybe a6989586621679609044) -> Type) (TyFun a6989586621679609044 (NonEmpty b6989586621679609045) -> Type) (UnfoldSym0 a6989586621679609044 b6989586621679609045) l # 
type Apply (TyFun a6989586621679609044 (b6989586621679609045, Maybe a6989586621679609044) -> Type) (TyFun a6989586621679609044 (NonEmpty b6989586621679609045) -> Type) (UnfoldSym0 a6989586621679609044 b6989586621679609045) l = UnfoldSym1 a6989586621679609044 b6989586621679609045 l

data UnfoldSym1 (l :: TyFun a6989586621679609044 (b6989586621679609045, Maybe a6989586621679609044) -> Type) (l :: TyFun a6989586621679609044 (NonEmpty b6989586621679609045)) #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679609044 (b6989586621679609045, Maybe a6989586621679609044) -> Type) -> TyFun a6989586621679609044 (NonEmpty b6989586621679609045) -> *) (UnfoldSym1 a6989586621679609044 b6989586621679609045) # 

Methods

suppressUnusedWarnings :: Proxy (UnfoldSym1 a6989586621679609044 b6989586621679609045) t -> () #

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (InsertSym0 a6989586621679609024) t -> () #

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

data InsertSym1 (l :: a6989586621679609024) (l :: TyFun [a6989586621679609024] (NonEmpty a6989586621679609024)) #

Instances

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

Methods

suppressUnusedWarnings :: Proxy (InsertSym1 a6989586621679609024) t -> () #

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

type InsertSym2 (t :: a6989586621679609024) (t :: [a6989586621679609024]) = Insert t t #

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (TakeSym0 a6989586621679609015) t -> () #

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (TakeSym1 a6989586621679609015) t -> () #

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

type TakeSym2 (t :: Nat) (t :: NonEmpty a6989586621679609015) = Take t t #

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (DropSym0 a6989586621679609014) t -> () #

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (DropSym1 a6989586621679609014) t -> () #

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

type DropSym2 (t :: Nat) (t :: NonEmpty a6989586621679609014) = Drop t t #

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (SplitAtSym0 a6989586621679609013) t -> () #

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (SplitAtSym1 a6989586621679609013) t -> () #

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

type SplitAtSym2 (t :: Nat) (t :: NonEmpty a6989586621679609013) = SplitAt t t #

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (TakeWhileSym0 a6989586621679609012) t -> () #

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (TakeWhileSym1 a6989586621679609012) t -> () #

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

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (DropWhileSym0 a6989586621679609011) t -> () #

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (DropWhileSym1 a6989586621679609011) t -> () #

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

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (SpanSym0 a6989586621679609010) t -> () #

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (SpanSym1 a6989586621679609010) t -> () #

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

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (BreakSym0 a6989586621679609009) t -> () #

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (BreakSym1 a6989586621679609009) t -> () #

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

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (FilterSym0 a6989586621679609008) t -> () #

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (FilterSym1 a6989586621679609008) t -> () #

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

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (PartitionSym0 a6989586621679609007) t -> () #

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (PartitionSym1 a6989586621679609007) t -> () #

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

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

data GroupSym0 (l :: TyFun [a6989586621679609006] [NonEmpty a6989586621679609006]) #

Instances

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

Methods

suppressUnusedWarnings :: Proxy (GroupSym0 a6989586621679609006) t -> () #

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

type GroupSym1 (t :: [a6989586621679609006]) = Group t #

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (GroupBySym0 a6989586621679609005) t -> () #

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (GroupBySym1 a6989586621679609005) t -> () #

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

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

data GroupWithSym0 (l :: TyFun (TyFun a6989586621679609004 b6989586621679609003 -> Type) (TyFun [a6989586621679609004] [NonEmpty a6989586621679609004] -> Type)) #

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679609004 b6989586621679609003 -> Type) (TyFun [a6989586621679609004] [NonEmpty a6989586621679609004] -> Type) -> *) (GroupWithSym0 b6989586621679609003 a6989586621679609004) # 

Methods

suppressUnusedWarnings :: Proxy (GroupWithSym0 b6989586621679609003 a6989586621679609004) t -> () #

type Apply (TyFun a6989586621679609004 b6989586621679609003 -> Type) (TyFun [a6989586621679609004] [NonEmpty a6989586621679609004] -> Type) (GroupWithSym0 b6989586621679609003 a6989586621679609004) l # 
type Apply (TyFun a6989586621679609004 b6989586621679609003 -> Type) (TyFun [a6989586621679609004] [NonEmpty a6989586621679609004] -> Type) (GroupWithSym0 b6989586621679609003 a6989586621679609004) l = GroupWithSym1 b6989586621679609003 a6989586621679609004 l

data GroupWithSym1 (l :: TyFun a6989586621679609004 b6989586621679609003 -> Type) (l :: TyFun [a6989586621679609004] [NonEmpty a6989586621679609004]) #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679609004 b6989586621679609003 -> Type) -> TyFun [a6989586621679609004] [NonEmpty a6989586621679609004] -> *) (GroupWithSym1 b6989586621679609003 a6989586621679609004) # 

Methods

suppressUnusedWarnings :: Proxy (GroupWithSym1 b6989586621679609003 a6989586621679609004) t -> () #

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

type GroupWithSym2 (t :: TyFun a6989586621679609004 b6989586621679609003 -> Type) (t :: [a6989586621679609004]) = GroupWith t t #

data GroupAllWithSym0 (l :: TyFun (TyFun a6989586621679609002 b6989586621679609001 -> Type) (TyFun [a6989586621679609002] [NonEmpty a6989586621679609002] -> Type)) #

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679609002 b6989586621679609001 -> Type) (TyFun [a6989586621679609002] [NonEmpty a6989586621679609002] -> Type) -> *) (GroupAllWithSym0 b6989586621679609001 a6989586621679609002) # 

Methods

suppressUnusedWarnings :: Proxy (GroupAllWithSym0 b6989586621679609001 a6989586621679609002) t -> () #

type Apply (TyFun a6989586621679609002 b6989586621679609001 -> Type) (TyFun [a6989586621679609002] [NonEmpty a6989586621679609002] -> Type) (GroupAllWithSym0 b6989586621679609001 a6989586621679609002) l # 
type Apply (TyFun a6989586621679609002 b6989586621679609001 -> Type) (TyFun [a6989586621679609002] [NonEmpty a6989586621679609002] -> Type) (GroupAllWithSym0 b6989586621679609001 a6989586621679609002) l = GroupAllWithSym1 b6989586621679609001 a6989586621679609002 l

data GroupAllWithSym1 (l :: TyFun a6989586621679609002 b6989586621679609001 -> Type) (l :: TyFun [a6989586621679609002] [NonEmpty a6989586621679609002]) #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679609002 b6989586621679609001 -> Type) -> TyFun [a6989586621679609002] [NonEmpty a6989586621679609002] -> *) (GroupAllWithSym1 b6989586621679609001 a6989586621679609002) # 

Methods

suppressUnusedWarnings :: Proxy (GroupAllWithSym1 b6989586621679609001 a6989586621679609002) t -> () #

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

type GroupAllWithSym2 (t :: TyFun a6989586621679609002 b6989586621679609001 -> Type) (t :: [a6989586621679609002]) = GroupAllWith t t #

data Group1Sym0 (l :: TyFun (NonEmpty a6989586621679609000) (NonEmpty (NonEmpty a6989586621679609000))) #

Instances

SuppressUnusedWarnings (TyFun (NonEmpty a6989586621679609000) (NonEmpty (NonEmpty a6989586621679609000)) -> *) (Group1Sym0 a6989586621679609000) # 

Methods

suppressUnusedWarnings :: Proxy (Group1Sym0 a6989586621679609000) t -> () #

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

type Group1Sym1 (t :: NonEmpty a6989586621679609000) = Group1 t #

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (GroupBy1Sym0 a6989586621679608999) t -> () #

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (GroupBy1Sym1 a6989586621679608999) t -> () #

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

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

data GroupWith1Sym0 (l :: TyFun (TyFun a6989586621679608998 b6989586621679608997 -> Type) (TyFun (NonEmpty a6989586621679608998) (NonEmpty (NonEmpty a6989586621679608998)) -> Type)) #

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679608998 b6989586621679608997 -> Type) (TyFun (NonEmpty a6989586621679608998) (NonEmpty (NonEmpty a6989586621679608998)) -> Type) -> *) (GroupWith1Sym0 b6989586621679608997 a6989586621679608998) # 

Methods

suppressUnusedWarnings :: Proxy (GroupWith1Sym0 b6989586621679608997 a6989586621679608998) t -> () #

type Apply (TyFun a6989586621679608998 b6989586621679608997 -> Type) (TyFun (NonEmpty a6989586621679608998) (NonEmpty (NonEmpty a6989586621679608998)) -> Type) (GroupWith1Sym0 b6989586621679608997 a6989586621679608998) l # 
type Apply (TyFun a6989586621679608998 b6989586621679608997 -> Type) (TyFun (NonEmpty a6989586621679608998) (NonEmpty (NonEmpty a6989586621679608998)) -> Type) (GroupWith1Sym0 b6989586621679608997 a6989586621679608998) l = GroupWith1Sym1 b6989586621679608997 a6989586621679608998 l

data GroupWith1Sym1 (l :: TyFun a6989586621679608998 b6989586621679608997 -> Type) (l :: TyFun (NonEmpty a6989586621679608998) (NonEmpty (NonEmpty a6989586621679608998))) #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679608998 b6989586621679608997 -> Type) -> TyFun (NonEmpty a6989586621679608998) (NonEmpty (NonEmpty a6989586621679608998)) -> *) (GroupWith1Sym1 b6989586621679608997 a6989586621679608998) # 

Methods

suppressUnusedWarnings :: Proxy (GroupWith1Sym1 b6989586621679608997 a6989586621679608998) t -> () #

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

type GroupWith1Sym2 (t :: TyFun a6989586621679608998 b6989586621679608997 -> Type) (t :: NonEmpty a6989586621679608998) = GroupWith1 t t #

data GroupAllWith1Sym0 (l :: TyFun (TyFun a6989586621679608996 b6989586621679608995 -> Type) (TyFun (NonEmpty a6989586621679608996) (NonEmpty (NonEmpty a6989586621679608996)) -> Type)) #

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679608996 b6989586621679608995 -> Type) (TyFun (NonEmpty a6989586621679608996) (NonEmpty (NonEmpty a6989586621679608996)) -> Type) -> *) (GroupAllWith1Sym0 b6989586621679608995 a6989586621679608996) # 

Methods

suppressUnusedWarnings :: Proxy (GroupAllWith1Sym0 b6989586621679608995 a6989586621679608996) t -> () #

type Apply (TyFun a6989586621679608996 b6989586621679608995 -> Type) (TyFun (NonEmpty a6989586621679608996) (NonEmpty (NonEmpty a6989586621679608996)) -> Type) (GroupAllWith1Sym0 b6989586621679608995 a6989586621679608996) l # 
type Apply (TyFun a6989586621679608996 b6989586621679608995 -> Type) (TyFun (NonEmpty a6989586621679608996) (NonEmpty (NonEmpty a6989586621679608996)) -> Type) (GroupAllWith1Sym0 b6989586621679608995 a6989586621679608996) l = GroupAllWith1Sym1 b6989586621679608995 a6989586621679608996 l

data GroupAllWith1Sym1 (l :: TyFun a6989586621679608996 b6989586621679608995 -> Type) (l :: TyFun (NonEmpty a6989586621679608996) (NonEmpty (NonEmpty a6989586621679608996))) #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679608996 b6989586621679608995 -> Type) -> TyFun (NonEmpty a6989586621679608996) (NonEmpty (NonEmpty a6989586621679608996)) -> *) (GroupAllWith1Sym1 b6989586621679608995 a6989586621679608996) # 

Methods

suppressUnusedWarnings :: Proxy (GroupAllWith1Sym1 b6989586621679608995 a6989586621679608996) t -> () #

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

type GroupAllWith1Sym2 (t :: TyFun a6989586621679608996 b6989586621679608995 -> Type) (t :: NonEmpty a6989586621679608996) = GroupAllWith1 t t #

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (IsPrefixOfSym0 a6989586621679608994) t -> () #

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (IsPrefixOfSym1 a6989586621679608994) t -> () #

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

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

data NubSym0 (l :: TyFun (NonEmpty a6989586621679608985) (NonEmpty a6989586621679608985)) #

Instances

SuppressUnusedWarnings (TyFun (NonEmpty a6989586621679608985) (NonEmpty a6989586621679608985) -> *) (NubSym0 a6989586621679608985) # 

Methods

suppressUnusedWarnings :: Proxy (NubSym0 a6989586621679608985) t -> () #

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

type NubSym1 (t :: NonEmpty a6989586621679608985) = Nub t #

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (NubBySym0 a6989586621679608984) t -> () #

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (NubBySym1 a6989586621679608984) t -> () #

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

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

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy ((:!!$) a6989586621679608993) t -> () #

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

data (l :: NonEmpty a6989586621679608993) :!!$$ (l :: TyFun Nat a6989586621679608993) #

Instances

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

Methods

suppressUnusedWarnings :: Proxy ((:!!$$) a6989586621679608993) t -> () #

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

type (:!!$$$) (t :: NonEmpty a6989586621679608993) (t :: Nat) = (:!!) t t #

data ZipSym0 (l :: TyFun (NonEmpty a6989586621679608991) (TyFun (NonEmpty b6989586621679608992) (NonEmpty (a6989586621679608991, b6989586621679608992)) -> Type)) #

Instances

SuppressUnusedWarnings (TyFun (NonEmpty a6989586621679608991) (TyFun (NonEmpty b6989586621679608992) (NonEmpty (a6989586621679608991, b6989586621679608992)) -> Type) -> *) (ZipSym0 a6989586621679608991 b6989586621679608992) # 

Methods

suppressUnusedWarnings :: Proxy (ZipSym0 a6989586621679608991 b6989586621679608992) t -> () #

type Apply (NonEmpty a6989586621679608991) (TyFun (NonEmpty b6989586621679608992) (NonEmpty (a6989586621679608991, b6989586621679608992)) -> Type) (ZipSym0 a6989586621679608991 b6989586621679608992) l # 
type Apply (NonEmpty a6989586621679608991) (TyFun (NonEmpty b6989586621679608992) (NonEmpty (a6989586621679608991, b6989586621679608992)) -> Type) (ZipSym0 a6989586621679608991 b6989586621679608992) l = ZipSym1 a6989586621679608991 b6989586621679608992 l

data ZipSym1 (l :: NonEmpty a6989586621679608991) (l :: TyFun (NonEmpty b6989586621679608992) (NonEmpty (a6989586621679608991, b6989586621679608992))) #

Instances

SuppressUnusedWarnings (NonEmpty a6989586621679608991 -> TyFun (NonEmpty b6989586621679608992) (NonEmpty (a6989586621679608991, b6989586621679608992)) -> *) (ZipSym1 a6989586621679608991 b6989586621679608992) # 

Methods

suppressUnusedWarnings :: Proxy (ZipSym1 a6989586621679608991 b6989586621679608992) t -> () #

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

type ZipSym2 (t :: NonEmpty a6989586621679608991) (t :: NonEmpty b6989586621679608992) = Zip t t #

data ZipWithSym0 (l :: TyFun (TyFun a6989586621679608988 (TyFun b6989586621679608989 c6989586621679608990 -> Type) -> Type) (TyFun (NonEmpty a6989586621679608988) (TyFun (NonEmpty b6989586621679608989) (NonEmpty c6989586621679608990) -> Type) -> Type)) #

Instances

SuppressUnusedWarnings (TyFun (TyFun a6989586621679608988 (TyFun b6989586621679608989 c6989586621679608990 -> Type) -> Type) (TyFun (NonEmpty a6989586621679608988) (TyFun (NonEmpty b6989586621679608989) (NonEmpty c6989586621679608990) -> Type) -> Type) -> *) (ZipWithSym0 a6989586621679608988 b6989586621679608989 c6989586621679608990) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWithSym0 a6989586621679608988 b6989586621679608989 c6989586621679608990) t -> () #

type Apply (TyFun a6989586621679608988 (TyFun b6989586621679608989 c6989586621679608990 -> Type) -> Type) (TyFun (NonEmpty a6989586621679608988) (TyFun (NonEmpty b6989586621679608989) (NonEmpty c6989586621679608990) -> Type) -> Type) (ZipWithSym0 a6989586621679608988 b6989586621679608989 c6989586621679608990) l # 
type Apply (TyFun a6989586621679608988 (TyFun b6989586621679608989 c6989586621679608990 -> Type) -> Type) (TyFun (NonEmpty a6989586621679608988) (TyFun (NonEmpty b6989586621679608989) (NonEmpty c6989586621679608990) -> Type) -> Type) (ZipWithSym0 a6989586621679608988 b6989586621679608989 c6989586621679608990) l = ZipWithSym1 a6989586621679608988 b6989586621679608989 c6989586621679608990 l

data ZipWithSym1 (l :: TyFun a6989586621679608988 (TyFun b6989586621679608989 c6989586621679608990 -> Type) -> Type) (l :: TyFun (NonEmpty a6989586621679608988) (TyFun (NonEmpty b6989586621679608989) (NonEmpty c6989586621679608990) -> Type)) #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679608988 (TyFun b6989586621679608989 c6989586621679608990 -> Type) -> Type) -> TyFun (NonEmpty a6989586621679608988) (TyFun (NonEmpty b6989586621679608989) (NonEmpty c6989586621679608990) -> Type) -> *) (ZipWithSym1 a6989586621679608988 b6989586621679608989 c6989586621679608990) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWithSym1 a6989586621679608988 b6989586621679608989 c6989586621679608990) t -> () #

type Apply (NonEmpty a6989586621679608988) (TyFun (NonEmpty b6989586621679608989) (NonEmpty c6989586621679608990) -> Type) (ZipWithSym1 a6989586621679608988 b6989586621679608989 c6989586621679608990 l1) l2 # 
type Apply (NonEmpty a6989586621679608988) (TyFun (NonEmpty b6989586621679608989) (NonEmpty c6989586621679608990) -> Type) (ZipWithSym1 a6989586621679608988 b6989586621679608989 c6989586621679608990 l1) l2 = ZipWithSym2 a6989586621679608988 b6989586621679608989 c6989586621679608990 l1 l2

data ZipWithSym2 (l :: TyFun a6989586621679608988 (TyFun b6989586621679608989 c6989586621679608990 -> Type) -> Type) (l :: NonEmpty a6989586621679608988) (l :: TyFun (NonEmpty b6989586621679608989) (NonEmpty c6989586621679608990)) #

Instances

SuppressUnusedWarnings ((TyFun a6989586621679608988 (TyFun b6989586621679608989 c6989586621679608990 -> Type) -> Type) -> NonEmpty a6989586621679608988 -> TyFun (NonEmpty b6989586621679608989) (NonEmpty c6989586621679608990) -> *) (ZipWithSym2 a6989586621679608988 b6989586621679608989 c6989586621679608990) # 

Methods

suppressUnusedWarnings :: Proxy (ZipWithSym2 a6989586621679608988 b6989586621679608989 c6989586621679608990) t -> () #

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

type ZipWithSym3 (t :: TyFun a6989586621679608988 (TyFun b6989586621679608989 c6989586621679608990 -> Type) -> Type) (t :: NonEmpty a6989586621679608988) (t :: NonEmpty b6989586621679608989) = ZipWith t t t #

data UnzipSym0 (l :: TyFun (NonEmpty (a6989586621679608986, b6989586621679608987)) (NonEmpty a6989586621679608986, NonEmpty b6989586621679608987)) #

Instances

SuppressUnusedWarnings (TyFun (NonEmpty (a6989586621679608986, b6989586621679608987)) (NonEmpty a6989586621679608986, NonEmpty b6989586621679608987) -> *) (UnzipSym0 a6989586621679608986 b6989586621679608987) # 

Methods

suppressUnusedWarnings :: Proxy (UnzipSym0 a6989586621679608986 b6989586621679608987) t -> () #

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

type UnzipSym1 (t :: NonEmpty (a6989586621679608986, b6989586621679608987)) = Unzip t #

data FromListSym0 (l :: TyFun [a6989586621679609032] (NonEmpty a6989586621679609032)) #

Instances

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

Methods

suppressUnusedWarnings :: Proxy (FromListSym0 a6989586621679609032) t -> () #

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

type FromListSym1 (t :: [a6989586621679609032]) = FromList t #

data ToListSym0 (l :: TyFun (NonEmpty a6989586621679609031) [a6989586621679609031]) #

Instances

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

Methods

suppressUnusedWarnings :: Proxy (ToListSym0 a6989586621679609031) t -> () #

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

type ToListSym1 (t :: NonEmpty a6989586621679609031) = ToList t #

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

Instances

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

Methods

suppressUnusedWarnings :: Proxy (NonEmpty_Sym0 a6989586621679609043) t -> () #

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

type NonEmpty_Sym1 (t :: [a6989586621679609043]) = NonEmpty_ t #

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