Copyright | (C) 2016 Richard Eisenberg |
---|---|
License | BSD-style (see LICENSE) |
Maintainer | Richard Eisenberg (rae@cs.brynmawr.edu) |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
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.
- data family Sing (a :: k)
- type SNonEmpty = (Sing :: NonEmpty a -> Type)
- type family Map (a :: TyFun a b -> Type) (a :: NonEmpty a) :: NonEmpty b where ...
- 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 ...
- 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 ...
- 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 ...
- 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 ...
- 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 ...
- 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 ...
- 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 ...
- 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 ...
- 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 ...
- sLength :: forall (t :: NonEmpty a). Sing t -> Sing (Apply LengthSym0 t :: Nat)
- type family Head (a :: NonEmpty a) :: a where ...
- sHead :: forall (t :: NonEmpty a). Sing t -> Sing (Apply HeadSym0 t :: a)
- type family Tail (a :: NonEmpty a) :: [a] where ...
- sTail :: forall (t :: NonEmpty a). Sing t -> Sing (Apply TailSym0 t :: [a])
- type family Last (a :: NonEmpty a) :: a where ...
- sLast :: forall (t :: NonEmpty a). Sing t -> Sing (Apply LastSym0 t :: a)
- type family Init (a :: NonEmpty a) :: [a] where ...
- sInit :: forall (t :: NonEmpty a). Sing t -> Sing (Apply InitSym0 t :: [a])
- type family (a :: a) :<| (a :: NonEmpty a) :: NonEmpty a where ...
- (%:<|) :: 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 ...
- 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 ...
- 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 ...
- 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 ...
- sSort :: forall (t :: NonEmpty a). SOrd a => Sing t -> Sing (Apply SortSym0 t :: NonEmpty a)
- type family Reverse (a :: NonEmpty a) :: NonEmpty a where ...
- sReverse :: forall (t :: NonEmpty a). Sing t -> Sing (Apply ReverseSym0 t :: NonEmpty a)
- type family Inits (a :: [a]) :: NonEmpty [a] where ...
- sInits :: forall (t :: [a]). Sing t -> Sing (Apply InitsSym0 t :: NonEmpty [a])
- type family Tails (a :: [a]) :: NonEmpty [a] where ...
- 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 ...
- 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 ...
- 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 ...
- 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 ...
- 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 ...
- 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 ...
- 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 ...
- 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 ...
- 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 ...
- 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 ...
- 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 ...
- 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 ...
- 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 ...
- 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 ...
- 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 ...
- 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 ...
- 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 ...
- 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 ...
- 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 ...
- 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 ...
- 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 ...
- 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 ...
- 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 ...
- (%:!!) :: 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 ...
- 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 ...
- 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 ...
- sUnzip :: forall (t :: NonEmpty (a, b)). Sing t -> Sing (Apply UnzipSym0 t :: (NonEmpty a, NonEmpty b))
- type family FromList (a :: [a]) :: NonEmpty a where ...
- sFromList :: forall (t :: [a]). Sing t -> Sing (Apply FromListSym0 t :: NonEmpty a)
- type family ToList (a :: NonEmpty a) :: [a] where ...
- sToList :: forall (t :: NonEmpty a). Sing t -> Sing (Apply ToListSym0 t :: [a])
- type family NonEmpty_ (a :: [a]) :: Maybe (NonEmpty a) where ...
- sNonEmpty_ :: forall (t :: [a]). Sing t -> Sing (Apply NonEmpty_Sym0 t :: Maybe (NonEmpty a))
- type family Xor (a :: NonEmpty Bool) :: Bool where ...
- sXor :: forall (t :: NonEmpty Bool). Sing t -> Sing (Apply XorSym0 t :: Bool)
- data (:|$) (l :: TyFun a6989586621679075408 (TyFun [a6989586621679075408] (NonEmpty a6989586621679075408) -> Type))
- data (l :: a6989586621679075408) :|$$ (l :: TyFun [a6989586621679075408] (NonEmpty a6989586621679075408))
- type (:|$$$) (t :: a6989586621679075408) (t :: [a6989586621679075408]) = (:|) t t
- data MapSym0 (l :: TyFun (TyFun a6989586621679729645 b6989586621679729646 -> Type) (TyFun (NonEmpty a6989586621679729645) (NonEmpty b6989586621679729646) -> Type))
- data MapSym1 (l :: TyFun a6989586621679729645 b6989586621679729646 -> Type) (l :: TyFun (NonEmpty a6989586621679729645) (NonEmpty b6989586621679729646))
- type MapSym2 (t :: TyFun a6989586621679729645 b6989586621679729646 -> Type) (t :: NonEmpty a6989586621679729645) = Map t t
- data IntersperseSym0 (l :: TyFun a6989586621679729635 (TyFun (NonEmpty a6989586621679729635) (NonEmpty a6989586621679729635) -> Type))
- data IntersperseSym1 (l :: a6989586621679729635) (l :: TyFun (NonEmpty a6989586621679729635) (NonEmpty a6989586621679729635))
- type IntersperseSym2 (t :: a6989586621679729635) (t :: NonEmpty a6989586621679729635) = Intersperse t t
- data ScanlSym0 (l :: TyFun (TyFun b6989586621679729640 (TyFun a6989586621679729641 b6989586621679729640 -> Type) -> Type) (TyFun b6989586621679729640 (TyFun [a6989586621679729641] (NonEmpty b6989586621679729640) -> Type) -> Type))
- data ScanlSym1 (l :: TyFun b6989586621679729640 (TyFun a6989586621679729641 b6989586621679729640 -> Type) -> Type) (l :: TyFun b6989586621679729640 (TyFun [a6989586621679729641] (NonEmpty b6989586621679729640) -> Type))
- data ScanlSym2 (l :: TyFun b6989586621679729640 (TyFun a6989586621679729641 b6989586621679729640 -> Type) -> Type) (l :: b6989586621679729640) (l :: TyFun [a6989586621679729641] (NonEmpty b6989586621679729640))
- type ScanlSym3 (t :: TyFun b6989586621679729640 (TyFun a6989586621679729641 b6989586621679729640 -> Type) -> Type) (t :: b6989586621679729640) (t :: [a6989586621679729641]) = Scanl t t t
- data ScanrSym0 (l :: TyFun (TyFun a6989586621679729638 (TyFun b6989586621679729639 b6989586621679729639 -> Type) -> Type) (TyFun b6989586621679729639 (TyFun [a6989586621679729638] (NonEmpty b6989586621679729639) -> Type) -> Type))
- data ScanrSym1 (l :: TyFun a6989586621679729638 (TyFun b6989586621679729639 b6989586621679729639 -> Type) -> Type) (l :: TyFun b6989586621679729639 (TyFun [a6989586621679729638] (NonEmpty b6989586621679729639) -> Type))
- data ScanrSym2 (l :: TyFun a6989586621679729638 (TyFun b6989586621679729639 b6989586621679729639 -> Type) -> Type) (l :: b6989586621679729639) (l :: TyFun [a6989586621679729638] (NonEmpty b6989586621679729639))
- type ScanrSym3 (t :: TyFun a6989586621679729638 (TyFun b6989586621679729639 b6989586621679729639 -> Type) -> Type) (t :: b6989586621679729639) (t :: [a6989586621679729638]) = Scanr t t t
- data Scanl1Sym0 (l :: TyFun (TyFun a6989586621679729637 (TyFun a6989586621679729637 a6989586621679729637 -> Type) -> Type) (TyFun (NonEmpty a6989586621679729637) (NonEmpty a6989586621679729637) -> Type))
- data Scanl1Sym1 (l :: TyFun a6989586621679729637 (TyFun a6989586621679729637 a6989586621679729637 -> Type) -> Type) (l :: TyFun (NonEmpty a6989586621679729637) (NonEmpty a6989586621679729637))
- type Scanl1Sym2 (t :: TyFun a6989586621679729637 (TyFun a6989586621679729637 a6989586621679729637 -> Type) -> Type) (t :: NonEmpty a6989586621679729637) = Scanl1 t t
- data Scanr1Sym0 (l :: TyFun (TyFun a6989586621679729636 (TyFun a6989586621679729636 a6989586621679729636 -> Type) -> Type) (TyFun (NonEmpty a6989586621679729636) (NonEmpty a6989586621679729636) -> Type))
- data Scanr1Sym1 (l :: TyFun a6989586621679729636 (TyFun a6989586621679729636 a6989586621679729636 -> Type) -> Type) (l :: TyFun (NonEmpty a6989586621679729636) (NonEmpty a6989586621679729636))
- type Scanr1Sym2 (t :: TyFun a6989586621679729636 (TyFun a6989586621679729636 a6989586621679729636 -> Type) -> Type) (t :: NonEmpty a6989586621679729636) = Scanr1 t t
- data TransposeSym0 (l :: TyFun (NonEmpty (NonEmpty a6989586621679729601)) (NonEmpty (NonEmpty a6989586621679729601)))
- type TransposeSym1 (t :: NonEmpty (NonEmpty a6989586621679729601)) = Transpose t
- data SortBySym0 (l :: TyFun (TyFun a6989586621679729600 (TyFun a6989586621679729600 Ordering -> Type) -> Type) (TyFun (NonEmpty a6989586621679729600) (NonEmpty a6989586621679729600) -> Type))
- data SortBySym1 (l :: TyFun a6989586621679729600 (TyFun a6989586621679729600 Ordering -> Type) -> Type) (l :: TyFun (NonEmpty a6989586621679729600) (NonEmpty a6989586621679729600))
- type SortBySym2 (t :: TyFun a6989586621679729600 (TyFun a6989586621679729600 Ordering -> Type) -> Type) (t :: NonEmpty a6989586621679729600) = SortBy t t
- data SortWithSym0 (l :: TyFun (TyFun a6989586621679729599 o6989586621679729598 -> Type) (TyFun (NonEmpty a6989586621679729599) (NonEmpty a6989586621679729599) -> Type))
- data SortWithSym1 (l :: TyFun a6989586621679729599 o6989586621679729598 -> Type) (l :: TyFun (NonEmpty a6989586621679729599) (NonEmpty a6989586621679729599))
- type SortWithSym2 (t :: TyFun a6989586621679729599 o6989586621679729598 -> Type) (t :: NonEmpty a6989586621679729599) = SortWith t t
- data LengthSym0 (l :: TyFun (NonEmpty a6989586621679729664) Nat)
- type LengthSym1 (t :: NonEmpty a6989586621679729664) = Length t
- data HeadSym0 (l :: TyFun (NonEmpty a6989586621679729657) a6989586621679729657)
- type HeadSym1 (t :: NonEmpty a6989586621679729657) = Head t
- data TailSym0 (l :: TyFun (NonEmpty a6989586621679729656) [a6989586621679729656])
- type TailSym1 (t :: NonEmpty a6989586621679729656) = Tail t
- data LastSym0 (l :: TyFun (NonEmpty a6989586621679729655) a6989586621679729655)
- type LastSym1 (t :: NonEmpty a6989586621679729655) = Last t
- data InitSym0 (l :: TyFun (NonEmpty a6989586621679729654) [a6989586621679729654])
- type InitSym1 (t :: NonEmpty a6989586621679729654) = Init t
- data (:<|$) (l :: TyFun a6989586621679729653 (TyFun (NonEmpty a6989586621679729653) (NonEmpty a6989586621679729653) -> Type))
- data (l :: a6989586621679729653) :<|$$ (l :: TyFun (NonEmpty a6989586621679729653) (NonEmpty a6989586621679729653))
- type (:<|$$$) (t :: a6989586621679729653) (t :: NonEmpty a6989586621679729653) = (:<|) t t
- data ConsSym0 (l :: TyFun a6989586621679729652 (TyFun (NonEmpty a6989586621679729652) (NonEmpty a6989586621679729652) -> Type))
- data ConsSym1 (l :: a6989586621679729652) (l :: TyFun (NonEmpty a6989586621679729652) (NonEmpty a6989586621679729652))
- type ConsSym2 (t :: a6989586621679729652) (t :: NonEmpty a6989586621679729652) = Cons t t
- data UnconsSym0 (l :: TyFun (NonEmpty a6989586621679729660) (a6989586621679729660, Maybe (NonEmpty a6989586621679729660)))
- type UnconsSym1 (t :: NonEmpty a6989586621679729660) = Uncons t
- data UnfoldrSym0 (l :: TyFun (TyFun a6989586621679729658 (b6989586621679729659, Maybe a6989586621679729658) -> Type) (TyFun a6989586621679729658 (NonEmpty b6989586621679729659) -> Type))
- data UnfoldrSym1 (l :: TyFun a6989586621679729658 (b6989586621679729659, Maybe a6989586621679729658) -> Type) (l :: TyFun a6989586621679729658 (NonEmpty b6989586621679729659))
- type UnfoldrSym2 (t :: TyFun a6989586621679729658 (b6989586621679729659, Maybe a6989586621679729658) -> Type) (t :: a6989586621679729658) = Unfoldr t t
- data SortSym0 (l :: TyFun (NonEmpty a6989586621679729651) (NonEmpty a6989586621679729651))
- type SortSym1 (t :: NonEmpty a6989586621679729651) = Sort t
- data ReverseSym0 (l :: TyFun (NonEmpty a6989586621679729634) (NonEmpty a6989586621679729634))
- type ReverseSym1 (t :: NonEmpty a6989586621679729634) = Reverse t
- data InitsSym0 (l :: TyFun [a6989586621679729644] (NonEmpty [a6989586621679729644]))
- type InitsSym1 (t :: [a6989586621679729644]) = Inits t
- data TailsSym0 (l :: TyFun [a6989586621679729643] (NonEmpty [a6989586621679729643]))
- type TailsSym1 (t :: [a6989586621679729643]) = Tails t
- data UnfoldSym0 (l :: TyFun (TyFun a6989586621679729662 (b6989586621679729663, Maybe a6989586621679729662) -> Type) (TyFun a6989586621679729662 (NonEmpty b6989586621679729663) -> Type))
- data UnfoldSym1 (l :: TyFun a6989586621679729662 (b6989586621679729663, Maybe a6989586621679729662) -> Type) (l :: TyFun a6989586621679729662 (NonEmpty b6989586621679729663))
- data InsertSym0 (l :: TyFun a6989586621679729642 (TyFun [a6989586621679729642] (NonEmpty a6989586621679729642) -> Type))
- data InsertSym1 (l :: a6989586621679729642) (l :: TyFun [a6989586621679729642] (NonEmpty a6989586621679729642))
- type InsertSym2 (t :: a6989586621679729642) (t :: [a6989586621679729642]) = Insert t t
- data TakeSym0 (l :: TyFun Nat (TyFun (NonEmpty a6989586621679729633) [a6989586621679729633] -> Type))
- data TakeSym1 (l :: Nat) (l :: TyFun (NonEmpty a6989586621679729633) [a6989586621679729633])
- type TakeSym2 (t :: Nat) (t :: NonEmpty a6989586621679729633) = Take t t
- data DropSym0 (l :: TyFun Nat (TyFun (NonEmpty a6989586621679729632) [a6989586621679729632] -> Type))
- data DropSym1 (l :: Nat) (l :: TyFun (NonEmpty a6989586621679729632) [a6989586621679729632])
- type DropSym2 (t :: Nat) (t :: NonEmpty a6989586621679729632) = Drop t t
- data SplitAtSym0 (l :: TyFun Nat (TyFun (NonEmpty a6989586621679729631) ([a6989586621679729631], [a6989586621679729631]) -> Type))
- data SplitAtSym1 (l :: Nat) (l :: TyFun (NonEmpty a6989586621679729631) ([a6989586621679729631], [a6989586621679729631]))
- type SplitAtSym2 (t :: Nat) (t :: NonEmpty a6989586621679729631) = SplitAt t t
- data TakeWhileSym0 (l :: TyFun (TyFun a6989586621679729630 Bool -> Type) (TyFun (NonEmpty a6989586621679729630) [a6989586621679729630] -> Type))
- data TakeWhileSym1 (l :: TyFun a6989586621679729630 Bool -> Type) (l :: TyFun (NonEmpty a6989586621679729630) [a6989586621679729630])
- type TakeWhileSym2 (t :: TyFun a6989586621679729630 Bool -> Type) (t :: NonEmpty a6989586621679729630) = TakeWhile t t
- data DropWhileSym0 (l :: TyFun (TyFun a6989586621679729629 Bool -> Type) (TyFun (NonEmpty a6989586621679729629) [a6989586621679729629] -> Type))
- data DropWhileSym1 (l :: TyFun a6989586621679729629 Bool -> Type) (l :: TyFun (NonEmpty a6989586621679729629) [a6989586621679729629])
- type DropWhileSym2 (t :: TyFun a6989586621679729629 Bool -> Type) (t :: NonEmpty a6989586621679729629) = DropWhile t t
- data SpanSym0 (l :: TyFun (TyFun a6989586621679729628 Bool -> Type) (TyFun (NonEmpty a6989586621679729628) ([a6989586621679729628], [a6989586621679729628]) -> Type))
- data SpanSym1 (l :: TyFun a6989586621679729628 Bool -> Type) (l :: TyFun (NonEmpty a6989586621679729628) ([a6989586621679729628], [a6989586621679729628]))
- type SpanSym2 (t :: TyFun a6989586621679729628 Bool -> Type) (t :: NonEmpty a6989586621679729628) = Span t t
- data BreakSym0 (l :: TyFun (TyFun a6989586621679729627 Bool -> Type) (TyFun (NonEmpty a6989586621679729627) ([a6989586621679729627], [a6989586621679729627]) -> Type))
- data BreakSym1 (l :: TyFun a6989586621679729627 Bool -> Type) (l :: TyFun (NonEmpty a6989586621679729627) ([a6989586621679729627], [a6989586621679729627]))
- type BreakSym2 (t :: TyFun a6989586621679729627 Bool -> Type) (t :: NonEmpty a6989586621679729627) = Break t t
- data FilterSym0 (l :: TyFun (TyFun a6989586621679729626 Bool -> Type) (TyFun (NonEmpty a6989586621679729626) [a6989586621679729626] -> Type))
- data FilterSym1 (l :: TyFun a6989586621679729626 Bool -> Type) (l :: TyFun (NonEmpty a6989586621679729626) [a6989586621679729626])
- type FilterSym2 (t :: TyFun a6989586621679729626 Bool -> Type) (t :: NonEmpty a6989586621679729626) = Filter t t
- data PartitionSym0 (l :: TyFun (TyFun a6989586621679729625 Bool -> Type) (TyFun (NonEmpty a6989586621679729625) ([a6989586621679729625], [a6989586621679729625]) -> Type))
- data PartitionSym1 (l :: TyFun a6989586621679729625 Bool -> Type) (l :: TyFun (NonEmpty a6989586621679729625) ([a6989586621679729625], [a6989586621679729625]))
- type PartitionSym2 (t :: TyFun a6989586621679729625 Bool -> Type) (t :: NonEmpty a6989586621679729625) = Partition t t
- data GroupSym0 (l :: TyFun [a6989586621679729624] [NonEmpty a6989586621679729624])
- type GroupSym1 (t :: [a6989586621679729624]) = Group t
- data GroupBySym0 (l :: TyFun (TyFun a6989586621679729623 (TyFun a6989586621679729623 Bool -> Type) -> Type) (TyFun [a6989586621679729623] [NonEmpty a6989586621679729623] -> Type))
- data GroupBySym1 (l :: TyFun a6989586621679729623 (TyFun a6989586621679729623 Bool -> Type) -> Type) (l :: TyFun [a6989586621679729623] [NonEmpty a6989586621679729623])
- type GroupBySym2 (t :: TyFun a6989586621679729623 (TyFun a6989586621679729623 Bool -> Type) -> Type) (t :: [a6989586621679729623]) = GroupBy t t
- data GroupWithSym0 (l :: TyFun (TyFun a6989586621679729622 b6989586621679729621 -> Type) (TyFun [a6989586621679729622] [NonEmpty a6989586621679729622] -> Type))
- data GroupWithSym1 (l :: TyFun a6989586621679729622 b6989586621679729621 -> Type) (l :: TyFun [a6989586621679729622] [NonEmpty a6989586621679729622])
- type GroupWithSym2 (t :: TyFun a6989586621679729622 b6989586621679729621 -> Type) (t :: [a6989586621679729622]) = GroupWith t t
- data GroupAllWithSym0 (l :: TyFun (TyFun a6989586621679729620 b6989586621679729619 -> Type) (TyFun [a6989586621679729620] [NonEmpty a6989586621679729620] -> Type))
- data GroupAllWithSym1 (l :: TyFun a6989586621679729620 b6989586621679729619 -> Type) (l :: TyFun [a6989586621679729620] [NonEmpty a6989586621679729620])
- type GroupAllWithSym2 (t :: TyFun a6989586621679729620 b6989586621679729619 -> Type) (t :: [a6989586621679729620]) = GroupAllWith t t
- data Group1Sym0 (l :: TyFun (NonEmpty a6989586621679729618) (NonEmpty (NonEmpty a6989586621679729618)))
- type Group1Sym1 (t :: NonEmpty a6989586621679729618) = Group1 t
- data GroupBy1Sym0 (l :: TyFun (TyFun a6989586621679729617 (TyFun a6989586621679729617 Bool -> Type) -> Type) (TyFun (NonEmpty a6989586621679729617) (NonEmpty (NonEmpty a6989586621679729617)) -> Type))
- data GroupBy1Sym1 (l :: TyFun a6989586621679729617 (TyFun a6989586621679729617 Bool -> Type) -> Type) (l :: TyFun (NonEmpty a6989586621679729617) (NonEmpty (NonEmpty a6989586621679729617)))
- type GroupBy1Sym2 (t :: TyFun a6989586621679729617 (TyFun a6989586621679729617 Bool -> Type) -> Type) (t :: NonEmpty a6989586621679729617) = GroupBy1 t t
- data GroupWith1Sym0 (l :: TyFun (TyFun a6989586621679729616 b6989586621679729615 -> Type) (TyFun (NonEmpty a6989586621679729616) (NonEmpty (NonEmpty a6989586621679729616)) -> Type))
- data GroupWith1Sym1 (l :: TyFun a6989586621679729616 b6989586621679729615 -> Type) (l :: TyFun (NonEmpty a6989586621679729616) (NonEmpty (NonEmpty a6989586621679729616)))
- type GroupWith1Sym2 (t :: TyFun a6989586621679729616 b6989586621679729615 -> Type) (t :: NonEmpty a6989586621679729616) = GroupWith1 t t
- data GroupAllWith1Sym0 (l :: TyFun (TyFun a6989586621679729614 b6989586621679729613 -> Type) (TyFun (NonEmpty a6989586621679729614) (NonEmpty (NonEmpty a6989586621679729614)) -> Type))
- data GroupAllWith1Sym1 (l :: TyFun a6989586621679729614 b6989586621679729613 -> Type) (l :: TyFun (NonEmpty a6989586621679729614) (NonEmpty (NonEmpty a6989586621679729614)))
- type GroupAllWith1Sym2 (t :: TyFun a6989586621679729614 b6989586621679729613 -> Type) (t :: NonEmpty a6989586621679729614) = GroupAllWith1 t t
- data IsPrefixOfSym0 (l :: TyFun [a6989586621679729612] (TyFun (NonEmpty a6989586621679729612) Bool -> Type))
- data IsPrefixOfSym1 (l :: [a6989586621679729612]) (l :: TyFun (NonEmpty a6989586621679729612) Bool)
- type IsPrefixOfSym2 (t :: [a6989586621679729612]) (t :: NonEmpty a6989586621679729612) = IsPrefixOf t t
- data NubSym0 (l :: TyFun (NonEmpty a6989586621679729603) (NonEmpty a6989586621679729603))
- type NubSym1 (t :: NonEmpty a6989586621679729603) = Nub t
- data NubBySym0 (l :: TyFun (TyFun a6989586621679729602 (TyFun a6989586621679729602 Bool -> Type) -> Type) (TyFun (NonEmpty a6989586621679729602) (NonEmpty a6989586621679729602) -> Type))
- data NubBySym1 (l :: TyFun a6989586621679729602 (TyFun a6989586621679729602 Bool -> Type) -> Type) (l :: TyFun (NonEmpty a6989586621679729602) (NonEmpty a6989586621679729602))
- type NubBySym2 (t :: TyFun a6989586621679729602 (TyFun a6989586621679729602 Bool -> Type) -> Type) (t :: NonEmpty a6989586621679729602) = NubBy t t
- data (:!!$) (l :: TyFun (NonEmpty a6989586621679729611) (TyFun Nat a6989586621679729611 -> Type))
- data (l :: NonEmpty a6989586621679729611) :!!$$ (l :: TyFun Nat a6989586621679729611)
- type (:!!$$$) (t :: NonEmpty a6989586621679729611) (t :: Nat) = (:!!) t t
- data ZipSym0 (l :: TyFun (NonEmpty a6989586621679729609) (TyFun (NonEmpty b6989586621679729610) (NonEmpty (a6989586621679729609, b6989586621679729610)) -> Type))
- data ZipSym1 (l :: NonEmpty a6989586621679729609) (l :: TyFun (NonEmpty b6989586621679729610) (NonEmpty (a6989586621679729609, b6989586621679729610)))
- type ZipSym2 (t :: NonEmpty a6989586621679729609) (t :: NonEmpty b6989586621679729610) = Zip t t
- data ZipWithSym0 (l :: TyFun (TyFun a6989586621679729606 (TyFun b6989586621679729607 c6989586621679729608 -> Type) -> Type) (TyFun (NonEmpty a6989586621679729606) (TyFun (NonEmpty b6989586621679729607) (NonEmpty c6989586621679729608) -> Type) -> Type))
- data ZipWithSym1 (l :: TyFun a6989586621679729606 (TyFun b6989586621679729607 c6989586621679729608 -> Type) -> Type) (l :: TyFun (NonEmpty a6989586621679729606) (TyFun (NonEmpty b6989586621679729607) (NonEmpty c6989586621679729608) -> Type))
- data ZipWithSym2 (l :: TyFun a6989586621679729606 (TyFun b6989586621679729607 c6989586621679729608 -> Type) -> Type) (l :: NonEmpty a6989586621679729606) (l :: TyFun (NonEmpty b6989586621679729607) (NonEmpty c6989586621679729608))
- type ZipWithSym3 (t :: TyFun a6989586621679729606 (TyFun b6989586621679729607 c6989586621679729608 -> Type) -> Type) (t :: NonEmpty a6989586621679729606) (t :: NonEmpty b6989586621679729607) = ZipWith t t t
- data UnzipSym0 (l :: TyFun (NonEmpty (a6989586621679729604, b6989586621679729605)) (NonEmpty a6989586621679729604, NonEmpty b6989586621679729605))
- type UnzipSym1 (t :: NonEmpty (a6989586621679729604, b6989586621679729605)) = Unzip t
- data FromListSym0 (l :: TyFun [a6989586621679729650] (NonEmpty a6989586621679729650))
- type FromListSym1 (t :: [a6989586621679729650]) = FromList t
- data ToListSym0 (l :: TyFun (NonEmpty a6989586621679729649) [a6989586621679729649])
- type ToListSym1 (t :: NonEmpty a6989586621679729649) = ToList t
- data NonEmpty_Sym0 (l :: TyFun [a6989586621679729661] (Maybe (NonEmpty a6989586621679729661)))
- type NonEmpty_Sym1 (t :: [a6989586621679729661]) = NonEmpty_ t
- data XorSym0 (l :: TyFun (NonEmpty Bool) Bool)
- type XorSym1 (t :: NonEmpty Bool) = Xor t
The NonEmpty
singleton
data family Sing (a :: k) Source #
The singleton kind-indexed data family.
data Sing Bool Source # | |
data Sing Ordering Source # | |
data Sing * Source # | |
data Sing Nat Source # | |
data Sing Symbol Source # | |
data Sing () Source # | |
data Sing [a] Source # | |
data Sing (Maybe a) Source # | |
data Sing (NonEmpty a) Source # | |
data Sing (Either a b) Source # | |
data Sing (a, b) Source # | |
data Sing ((~>) k1 k2) Source # | |
data Sing (a, b, c) Source # | |
data Sing (a, b, c, d) Source # | |
data Sing (a, b, c, d, e) Source # | |
data Sing (a, b, c, d, e, f) Source # | |
data Sing (a, b, c, d, e, f, g) Source # | |
Though Haddock doesn't show it, the Sing
instance above declares
constructor
(:%|) :: Sing h -> Sing t -> Sing (h :| t)
Non-empty stream transformations
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 #
Intersperse a ((:|) b bs) = Apply (Apply (:|$) b) (Case_6989586621679730292 a b bs bs) |
sIntersperse :: forall (t :: a) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply IntersperseSym0 t) t :: NonEmpty a) Source #
type family Scanl (a :: TyFun b (TyFun a b -> Type) -> Type) (a :: b) (a :: [a]) :: NonEmpty b where ... Source #
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 #
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 #
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 #
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 #
Transpose a_6989586621679730799 = Apply (Apply (Apply (:.$) (Apply FmapSym0 FromListSym0)) (Apply (Apply (:.$) FromListSym0) (Apply (Apply (:.$) ListtransposeSym0) (Apply (Apply (:.$) ToListSym0) (Apply FmapSym0 ToListSym0))))) a_6989586621679730799 |
sTranspose :: forall (t :: NonEmpty (NonEmpty a)). Sing t -> Sing (Apply TransposeSym0 t :: NonEmpty (NonEmpty a)) Source #
type family SortBy (a :: TyFun a (TyFun a Ordering -> Type) -> Type) (a :: NonEmpty a) :: NonEmpty a where ... Source #
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 #
SortWith a_6989586621679730475 a_6989586621679730477 = Apply (Apply (Apply (Apply (:.$) SortBySym0) ComparingSym0) a_6989586621679730475) a_6989586621679730477 |
sSortWith :: forall (t :: TyFun a o -> Type) (t :: NonEmpty a). SOrd o => Sing t -> Sing t -> Sing (Apply (Apply SortWithSym0 t) t :: NonEmpty a) Source #
(%:<|) :: forall (t :: a) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply (:<|$) t) t :: NonEmpty a) Source #
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 #
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 #
Unfoldr f a = Case_6989586621679730708 f a (Let6989586621679730700Scrutinee_6989586621679729831Sym2 f a) |
sUnfoldr :: forall (t :: TyFun a (b, Maybe a) -> Type) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply UnfoldrSym0 t) t :: NonEmpty b) Source #
sSort :: forall (t :: NonEmpty a). SOrd a => Sing t -> Sing (Apply SortSym0 t :: NonEmpty a) Source #
type family Unfold (a :: TyFun a (b, Maybe a) -> Type) (a :: a) :: NonEmpty b where ... Source #
Unfold f a = Case_6989586621679730744 f a (Let6989586621679730736Scrutinee_6989586621679729829Sym2 f a) |
sUnfold :: forall (t :: TyFun a (b, Maybe a) -> Type) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply UnfoldSym0 t) t :: NonEmpty b) Source #
sInsert :: forall (t :: a) (t :: [a]). SOrd a => Sing t -> Sing t -> Sing (Apply (Apply InsertSym0 t) t :: NonEmpty a) Source #
sTake :: forall (t :: Nat) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply TakeSym0 t) t :: [a]) Source #
sDrop :: forall (t :: Nat) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply DropSym0 t) t :: [a]) Source #
sSplitAt :: forall (t :: Nat) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply SplitAtSym0 t) t :: ([a], [a])) Source #
sTakeWhile :: forall (t :: TyFun a Bool -> Type) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply TakeWhileSym0 t) t :: [a]) Source #
sDropWhile :: forall (t :: TyFun a Bool -> Type) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply DropWhileSym0 t) t :: [a]) Source #
sSpan :: forall (t :: TyFun a Bool -> Type) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply SpanSym0 t) t :: ([a], [a])) Source #
sBreak :: forall (t :: TyFun a Bool -> Type) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply BreakSym0 t) t :: ([a], [a])) Source #
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 #
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 #
Group a_6989586621679730273 = Apply (Apply GroupBySym0 (:==$)) a_6989586621679730273 |
type family GroupBy (a :: TyFun a (TyFun a Bool -> Type) -> Type) (a :: [a]) :: [NonEmpty a] where ... Source #
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 #
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 #
GroupAllWith f a_6989586621679730180 = Apply (Apply (Apply (:.$) (Apply GroupWithSym0 f)) (Apply ListsortBySym0 (Apply (Apply OnSym0 CompareSym0) f))) a_6989586621679730180 |
sGroupAllWith :: forall (t :: TyFun a b -> Type) (t :: [a]). SOrd b => Sing t -> Sing t -> Sing (Apply (Apply GroupAllWithSym0 t) t :: [NonEmpty a]) Source #
type family Group1 (a :: NonEmpty a) :: NonEmpty (NonEmpty a) where ... Source #
Group1 a_6989586621679730253 = Apply (Apply GroupBy1Sym0 (:==$)) a_6989586621679730253 |
sGroup1 :: forall (t :: NonEmpty a). SEq a => Sing t -> Sing (Apply Group1Sym0 t :: NonEmpty (NonEmpty a)) Source #
type family GroupBy1 (a :: TyFun a (TyFun a Bool -> Type) -> Type) (a :: NonEmpty a) :: NonEmpty (NonEmpty a) where ... Source #
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 #
GroupWith1 f a_6989586621679730269 = Apply (Apply GroupBy1Sym0 (Apply (Apply OnSym0 (:==$)) f)) a_6989586621679730269 |
sGroupWith1 :: forall (t :: TyFun a b -> Type) (t :: NonEmpty a). SEq b => Sing t -> Sing t -> Sing (Apply (Apply GroupWith1Sym0 t) t :: NonEmpty (NonEmpty a)) Source #
type family GroupAllWith1 (a :: TyFun a b -> Type) (a :: NonEmpty a) :: NonEmpty (NonEmpty a) where ... Source #
GroupAllWith1 f a_6989586621679730499 = Apply (Apply (Apply (:.$) (Apply GroupWith1Sym0 f)) (Apply SortWithSym0 f)) a_6989586621679730499 |
sGroupAllWith1 :: forall (t :: TyFun a b -> Type) (t :: NonEmpty a). SOrd b => Sing t -> Sing t -> Sing (Apply (Apply GroupAllWith1Sym0 t) t :: NonEmpty (NonEmpty a)) Source #
type family IsPrefixOf (a :: [a]) (a :: NonEmpty a) :: Bool where ... Source #
sIsPrefixOf :: forall (t :: [a]) (t :: NonEmpty a). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IsPrefixOfSym0 t) t :: Bool) Source #
type family NubBy (a :: TyFun a (TyFun a Bool -> Type) -> Type) (a :: NonEmpty a) :: NonEmpty a where ... Source #
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 #
arg_6989586621679729835 :!! arg_6989586621679729837 = Case_6989586621679729994 arg_6989586621679729835 arg_6989586621679729837 (Apply (Apply Tuple2Sym0 arg_6989586621679729835) arg_6989586621679729837) |
(%:!!) :: forall (t :: NonEmpty a) (t :: Nat). Sing t -> Sing t -> Sing (Apply (Apply (:!!$) t) t :: a) Source #
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 #
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 #
sUnzip :: forall (t :: NonEmpty (a, b)). Sing t -> Sing (Apply UnzipSym0 t :: (NonEmpty a, NonEmpty b)) Source #
sNonEmpty_ :: forall (t :: [a]). Sing t -> Sing (Apply NonEmpty_Sym0 t :: Maybe (NonEmpty a)) Source #
Defunctionalization symbols
data (:|$) (l :: TyFun a6989586621679075408 (TyFun [a6989586621679075408] (NonEmpty a6989586621679075408) -> Type)) Source #
SuppressUnusedWarnings (TyFun a6989586621679075408 (TyFun [a6989586621679075408] (NonEmpty a6989586621679075408) -> Type) -> *) ((:|$) a6989586621679075408) Source # | |
type Apply a6989586621679075408 (TyFun [a6989586621679075408] (NonEmpty a6989586621679075408) -> Type) ((:|$) a6989586621679075408) l Source # | |
data (l :: a6989586621679075408) :|$$ (l :: TyFun [a6989586621679075408] (NonEmpty a6989586621679075408)) Source #
data MapSym0 (l :: TyFun (TyFun a6989586621679729645 b6989586621679729646 -> Type) (TyFun (NonEmpty a6989586621679729645) (NonEmpty b6989586621679729646) -> Type)) Source #
SuppressUnusedWarnings (TyFun (TyFun a6989586621679729645 b6989586621679729646 -> Type) (TyFun (NonEmpty a6989586621679729645) (NonEmpty b6989586621679729646) -> Type) -> *) (MapSym0 a6989586621679729645 b6989586621679729646) Source # | |
type Apply (TyFun a6989586621679729645 b6989586621679729646 -> Type) (TyFun (NonEmpty a6989586621679729645) (NonEmpty b6989586621679729646) -> Type) (MapSym0 a6989586621679729645 b6989586621679729646) l Source # | |
data MapSym1 (l :: TyFun a6989586621679729645 b6989586621679729646 -> Type) (l :: TyFun (NonEmpty a6989586621679729645) (NonEmpty b6989586621679729646)) Source #
type MapSym2 (t :: TyFun a6989586621679729645 b6989586621679729646 -> Type) (t :: NonEmpty a6989586621679729645) = Map t t Source #
data IntersperseSym0 (l :: TyFun a6989586621679729635 (TyFun (NonEmpty a6989586621679729635) (NonEmpty a6989586621679729635) -> Type)) Source #
SuppressUnusedWarnings (TyFun a6989586621679729635 (TyFun (NonEmpty a6989586621679729635) (NonEmpty a6989586621679729635) -> Type) -> *) (IntersperseSym0 a6989586621679729635) Source # | |
type Apply a6989586621679729635 (TyFun (NonEmpty a6989586621679729635) (NonEmpty a6989586621679729635) -> Type) (IntersperseSym0 a6989586621679729635) l Source # | |
data IntersperseSym1 (l :: a6989586621679729635) (l :: TyFun (NonEmpty a6989586621679729635) (NonEmpty a6989586621679729635)) Source #
SuppressUnusedWarnings (a6989586621679729635 -> TyFun (NonEmpty a6989586621679729635) (NonEmpty a6989586621679729635) -> *) (IntersperseSym1 a6989586621679729635) Source # | |
type Apply (NonEmpty a) (NonEmpty a) (IntersperseSym1 a l1) l2 Source # | |
type IntersperseSym2 (t :: a6989586621679729635) (t :: NonEmpty a6989586621679729635) = Intersperse t t Source #
data ScanlSym0 (l :: TyFun (TyFun b6989586621679729640 (TyFun a6989586621679729641 b6989586621679729640 -> Type) -> Type) (TyFun b6989586621679729640 (TyFun [a6989586621679729641] (NonEmpty b6989586621679729640) -> Type) -> Type)) Source #
SuppressUnusedWarnings (TyFun (TyFun b6989586621679729640 (TyFun a6989586621679729641 b6989586621679729640 -> Type) -> Type) (TyFun b6989586621679729640 (TyFun [a6989586621679729641] (NonEmpty b6989586621679729640) -> Type) -> Type) -> *) (ScanlSym0 a6989586621679729641 b6989586621679729640) Source # | |
type Apply (TyFun b6989586621679729640 (TyFun a6989586621679729641 b6989586621679729640 -> Type) -> Type) (TyFun b6989586621679729640 (TyFun [a6989586621679729641] (NonEmpty b6989586621679729640) -> Type) -> Type) (ScanlSym0 a6989586621679729641 b6989586621679729640) l Source # | |
data ScanlSym1 (l :: TyFun b6989586621679729640 (TyFun a6989586621679729641 b6989586621679729640 -> Type) -> Type) (l :: TyFun b6989586621679729640 (TyFun [a6989586621679729641] (NonEmpty b6989586621679729640) -> Type)) Source #
SuppressUnusedWarnings ((TyFun b6989586621679729640 (TyFun a6989586621679729641 b6989586621679729640 -> Type) -> Type) -> TyFun b6989586621679729640 (TyFun [a6989586621679729641] (NonEmpty b6989586621679729640) -> Type) -> *) (ScanlSym1 a6989586621679729641 b6989586621679729640) Source # | |
type Apply b6989586621679729640 (TyFun [a6989586621679729641] (NonEmpty b6989586621679729640) -> Type) (ScanlSym1 a6989586621679729641 b6989586621679729640 l1) l2 Source # | |
data ScanlSym2 (l :: TyFun b6989586621679729640 (TyFun a6989586621679729641 b6989586621679729640 -> Type) -> Type) (l :: b6989586621679729640) (l :: TyFun [a6989586621679729641] (NonEmpty b6989586621679729640)) Source #
SuppressUnusedWarnings ((TyFun b6989586621679729640 (TyFun a6989586621679729641 b6989586621679729640 -> Type) -> Type) -> b6989586621679729640 -> TyFun [a6989586621679729641] (NonEmpty b6989586621679729640) -> *) (ScanlSym2 a6989586621679729641 b6989586621679729640) Source # | |
type Apply [a] (NonEmpty b) (ScanlSym2 a b l1 l2) l3 Source # | |
type ScanlSym3 (t :: TyFun b6989586621679729640 (TyFun a6989586621679729641 b6989586621679729640 -> Type) -> Type) (t :: b6989586621679729640) (t :: [a6989586621679729641]) = Scanl t t t Source #
data ScanrSym0 (l :: TyFun (TyFun a6989586621679729638 (TyFun b6989586621679729639 b6989586621679729639 -> Type) -> Type) (TyFun b6989586621679729639 (TyFun [a6989586621679729638] (NonEmpty b6989586621679729639) -> Type) -> Type)) Source #
SuppressUnusedWarnings (TyFun (TyFun a6989586621679729638 (TyFun b6989586621679729639 b6989586621679729639 -> Type) -> Type) (TyFun b6989586621679729639 (TyFun [a6989586621679729638] (NonEmpty b6989586621679729639) -> Type) -> Type) -> *) (ScanrSym0 a6989586621679729638 b6989586621679729639) Source # | |
type Apply (TyFun a6989586621679729638 (TyFun b6989586621679729639 b6989586621679729639 -> Type) -> Type) (TyFun b6989586621679729639 (TyFun [a6989586621679729638] (NonEmpty b6989586621679729639) -> Type) -> Type) (ScanrSym0 a6989586621679729638 b6989586621679729639) l Source # | |
data ScanrSym1 (l :: TyFun a6989586621679729638 (TyFun b6989586621679729639 b6989586621679729639 -> Type) -> Type) (l :: TyFun b6989586621679729639 (TyFun [a6989586621679729638] (NonEmpty b6989586621679729639) -> Type)) Source #
SuppressUnusedWarnings ((TyFun a6989586621679729638 (TyFun b6989586621679729639 b6989586621679729639 -> Type) -> Type) -> TyFun b6989586621679729639 (TyFun [a6989586621679729638] (NonEmpty b6989586621679729639) -> Type) -> *) (ScanrSym1 a6989586621679729638 b6989586621679729639) Source # | |
type Apply b6989586621679729639 (TyFun [a6989586621679729638] (NonEmpty b6989586621679729639) -> Type) (ScanrSym1 a6989586621679729638 b6989586621679729639 l1) l2 Source # | |
data ScanrSym2 (l :: TyFun a6989586621679729638 (TyFun b6989586621679729639 b6989586621679729639 -> Type) -> Type) (l :: b6989586621679729639) (l :: TyFun [a6989586621679729638] (NonEmpty b6989586621679729639)) Source #
SuppressUnusedWarnings ((TyFun a6989586621679729638 (TyFun b6989586621679729639 b6989586621679729639 -> Type) -> Type) -> b6989586621679729639 -> TyFun [a6989586621679729638] (NonEmpty b6989586621679729639) -> *) (ScanrSym2 a6989586621679729638 b6989586621679729639) Source # | |
type Apply [a] (NonEmpty b) (ScanrSym2 a b l1 l2) l3 Source # | |
type ScanrSym3 (t :: TyFun a6989586621679729638 (TyFun b6989586621679729639 b6989586621679729639 -> Type) -> Type) (t :: b6989586621679729639) (t :: [a6989586621679729638]) = Scanr t t t Source #
data Scanl1Sym0 (l :: TyFun (TyFun a6989586621679729637 (TyFun a6989586621679729637 a6989586621679729637 -> Type) -> Type) (TyFun (NonEmpty a6989586621679729637) (NonEmpty a6989586621679729637) -> Type)) Source #
SuppressUnusedWarnings (TyFun (TyFun a6989586621679729637 (TyFun a6989586621679729637 a6989586621679729637 -> Type) -> Type) (TyFun (NonEmpty a6989586621679729637) (NonEmpty a6989586621679729637) -> Type) -> *) (Scanl1Sym0 a6989586621679729637) Source # | |
type Apply (TyFun a6989586621679729637 (TyFun a6989586621679729637 a6989586621679729637 -> Type) -> Type) (TyFun (NonEmpty a6989586621679729637) (NonEmpty a6989586621679729637) -> Type) (Scanl1Sym0 a6989586621679729637) l Source # | |
data Scanl1Sym1 (l :: TyFun a6989586621679729637 (TyFun a6989586621679729637 a6989586621679729637 -> Type) -> Type) (l :: TyFun (NonEmpty a6989586621679729637) (NonEmpty a6989586621679729637)) Source #
SuppressUnusedWarnings ((TyFun a6989586621679729637 (TyFun a6989586621679729637 a6989586621679729637 -> Type) -> Type) -> TyFun (NonEmpty a6989586621679729637) (NonEmpty a6989586621679729637) -> *) (Scanl1Sym1 a6989586621679729637) Source # | |
type Apply (NonEmpty a) (NonEmpty a) (Scanl1Sym1 a l1) l2 Source # | |
type Scanl1Sym2 (t :: TyFun a6989586621679729637 (TyFun a6989586621679729637 a6989586621679729637 -> Type) -> Type) (t :: NonEmpty a6989586621679729637) = Scanl1 t t Source #
data Scanr1Sym0 (l :: TyFun (TyFun a6989586621679729636 (TyFun a6989586621679729636 a6989586621679729636 -> Type) -> Type) (TyFun (NonEmpty a6989586621679729636) (NonEmpty a6989586621679729636) -> Type)) Source #
SuppressUnusedWarnings (TyFun (TyFun a6989586621679729636 (TyFun a6989586621679729636 a6989586621679729636 -> Type) -> Type) (TyFun (NonEmpty a6989586621679729636) (NonEmpty a6989586621679729636) -> Type) -> *) (Scanr1Sym0 a6989586621679729636) Source # | |
type Apply (TyFun a6989586621679729636 (TyFun a6989586621679729636 a6989586621679729636 -> Type) -> Type) (TyFun (NonEmpty a6989586621679729636) (NonEmpty a6989586621679729636) -> Type) (Scanr1Sym0 a6989586621679729636) l Source # | |
data Scanr1Sym1 (l :: TyFun a6989586621679729636 (TyFun a6989586621679729636 a6989586621679729636 -> Type) -> Type) (l :: TyFun (NonEmpty a6989586621679729636) (NonEmpty a6989586621679729636)) Source #
SuppressUnusedWarnings ((TyFun a6989586621679729636 (TyFun a6989586621679729636 a6989586621679729636 -> Type) -> Type) -> TyFun (NonEmpty a6989586621679729636) (NonEmpty a6989586621679729636) -> *) (Scanr1Sym1 a6989586621679729636) Source # | |
type Apply (NonEmpty a) (NonEmpty a) (Scanr1Sym1 a l1) l2 Source # | |
type Scanr1Sym2 (t :: TyFun a6989586621679729636 (TyFun a6989586621679729636 a6989586621679729636 -> Type) -> Type) (t :: NonEmpty a6989586621679729636) = Scanr1 t t Source #
data TransposeSym0 (l :: TyFun (NonEmpty (NonEmpty a6989586621679729601)) (NonEmpty (NonEmpty a6989586621679729601))) Source #
data SortBySym0 (l :: TyFun (TyFun a6989586621679729600 (TyFun a6989586621679729600 Ordering -> Type) -> Type) (TyFun (NonEmpty a6989586621679729600) (NonEmpty a6989586621679729600) -> Type)) Source #
SuppressUnusedWarnings (TyFun (TyFun a6989586621679729600 (TyFun a6989586621679729600 Ordering -> Type) -> Type) (TyFun (NonEmpty a6989586621679729600) (NonEmpty a6989586621679729600) -> Type) -> *) (SortBySym0 a6989586621679729600) Source # | |
type Apply (TyFun a6989586621679729600 (TyFun a6989586621679729600 Ordering -> Type) -> Type) (TyFun (NonEmpty a6989586621679729600) (NonEmpty a6989586621679729600) -> Type) (SortBySym0 a6989586621679729600) l Source # | |
data SortBySym1 (l :: TyFun a6989586621679729600 (TyFun a6989586621679729600 Ordering -> Type) -> Type) (l :: TyFun (NonEmpty a6989586621679729600) (NonEmpty a6989586621679729600)) Source #
type SortBySym2 (t :: TyFun a6989586621679729600 (TyFun a6989586621679729600 Ordering -> Type) -> Type) (t :: NonEmpty a6989586621679729600) = SortBy t t Source #
data SortWithSym0 (l :: TyFun (TyFun a6989586621679729599 o6989586621679729598 -> Type) (TyFun (NonEmpty a6989586621679729599) (NonEmpty a6989586621679729599) -> Type)) Source #
SuppressUnusedWarnings (TyFun (TyFun a6989586621679729599 o6989586621679729598 -> Type) (TyFun (NonEmpty a6989586621679729599) (NonEmpty a6989586621679729599) -> Type) -> *) (SortWithSym0 o6989586621679729598 a6989586621679729599) Source # | |
type Apply (TyFun a6989586621679729599 o6989586621679729598 -> Type) (TyFun (NonEmpty a6989586621679729599) (NonEmpty a6989586621679729599) -> Type) (SortWithSym0 o6989586621679729598 a6989586621679729599) l Source # | |
data SortWithSym1 (l :: TyFun a6989586621679729599 o6989586621679729598 -> Type) (l :: TyFun (NonEmpty a6989586621679729599) (NonEmpty a6989586621679729599)) Source #
type SortWithSym2 (t :: TyFun a6989586621679729599 o6989586621679729598 -> Type) (t :: NonEmpty a6989586621679729599) = SortWith t t Source #
data LengthSym0 (l :: TyFun (NonEmpty a6989586621679729664) Nat) Source #
SuppressUnusedWarnings (TyFun (NonEmpty a6989586621679729664) Nat -> *) (LengthSym0 a6989586621679729664) Source # | |
type Apply (NonEmpty a) Nat (LengthSym0 a) l Source # | |
type LengthSym1 (t :: NonEmpty a6989586621679729664) = Length t Source #
data (:<|$) (l :: TyFun a6989586621679729653 (TyFun (NonEmpty a6989586621679729653) (NonEmpty a6989586621679729653) -> Type)) Source #
SuppressUnusedWarnings (TyFun a6989586621679729653 (TyFun (NonEmpty a6989586621679729653) (NonEmpty a6989586621679729653) -> Type) -> *) ((:<|$) a6989586621679729653) Source # | |
type Apply a6989586621679729653 (TyFun (NonEmpty a6989586621679729653) (NonEmpty a6989586621679729653) -> Type) ((:<|$) a6989586621679729653) l Source # | |
data (l :: a6989586621679729653) :<|$$ (l :: TyFun (NonEmpty a6989586621679729653) (NonEmpty a6989586621679729653)) Source #
data ConsSym0 (l :: TyFun a6989586621679729652 (TyFun (NonEmpty a6989586621679729652) (NonEmpty a6989586621679729652) -> Type)) Source #
SuppressUnusedWarnings (TyFun a6989586621679729652 (TyFun (NonEmpty a6989586621679729652) (NonEmpty a6989586621679729652) -> Type) -> *) (ConsSym0 a6989586621679729652) Source # | |
type Apply a6989586621679729652 (TyFun (NonEmpty a6989586621679729652) (NonEmpty a6989586621679729652) -> Type) (ConsSym0 a6989586621679729652) l Source # | |
data ConsSym1 (l :: a6989586621679729652) (l :: TyFun (NonEmpty a6989586621679729652) (NonEmpty a6989586621679729652)) Source #
data UnconsSym0 (l :: TyFun (NonEmpty a6989586621679729660) (a6989586621679729660, Maybe (NonEmpty a6989586621679729660))) Source #
type UnconsSym1 (t :: NonEmpty a6989586621679729660) = Uncons t Source #
data UnfoldrSym0 (l :: TyFun (TyFun a6989586621679729658 (b6989586621679729659, Maybe a6989586621679729658) -> Type) (TyFun a6989586621679729658 (NonEmpty b6989586621679729659) -> Type)) Source #
SuppressUnusedWarnings (TyFun (TyFun a6989586621679729658 (b6989586621679729659, Maybe a6989586621679729658) -> Type) (TyFun a6989586621679729658 (NonEmpty b6989586621679729659) -> Type) -> *) (UnfoldrSym0 a6989586621679729658 b6989586621679729659) Source # | |
type Apply (TyFun a6989586621679729658 (b6989586621679729659, Maybe a6989586621679729658) -> Type) (TyFun a6989586621679729658 (NonEmpty b6989586621679729659) -> Type) (UnfoldrSym0 a6989586621679729658 b6989586621679729659) l Source # | |
data UnfoldrSym1 (l :: TyFun a6989586621679729658 (b6989586621679729659, Maybe a6989586621679729658) -> Type) (l :: TyFun a6989586621679729658 (NonEmpty b6989586621679729659)) Source #
SuppressUnusedWarnings ((TyFun a6989586621679729658 (b6989586621679729659, Maybe a6989586621679729658) -> Type) -> TyFun a6989586621679729658 (NonEmpty b6989586621679729659) -> *) (UnfoldrSym1 a6989586621679729658 b6989586621679729659) Source # | |
type Apply a (NonEmpty b) (UnfoldrSym1 a b l1) l2 Source # | |
type UnfoldrSym2 (t :: TyFun a6989586621679729658 (b6989586621679729659, Maybe a6989586621679729658) -> Type) (t :: a6989586621679729658) = Unfoldr t t Source #
data ReverseSym0 (l :: TyFun (NonEmpty a6989586621679729634) (NonEmpty a6989586621679729634)) Source #
SuppressUnusedWarnings (TyFun (NonEmpty a6989586621679729634) (NonEmpty a6989586621679729634) -> *) (ReverseSym0 a6989586621679729634) Source # | |
type Apply (NonEmpty a) (NonEmpty a) (ReverseSym0 a) l Source # | |
type ReverseSym1 (t :: NonEmpty a6989586621679729634) = Reverse t Source #
data UnfoldSym0 (l :: TyFun (TyFun a6989586621679729662 (b6989586621679729663, Maybe a6989586621679729662) -> Type) (TyFun a6989586621679729662 (NonEmpty b6989586621679729663) -> Type)) Source #
SuppressUnusedWarnings (TyFun (TyFun a6989586621679729662 (b6989586621679729663, Maybe a6989586621679729662) -> Type) (TyFun a6989586621679729662 (NonEmpty b6989586621679729663) -> Type) -> *) (UnfoldSym0 a6989586621679729662 b6989586621679729663) Source # | |
type Apply (TyFun a6989586621679729662 (b6989586621679729663, Maybe a6989586621679729662) -> Type) (TyFun a6989586621679729662 (NonEmpty b6989586621679729663) -> Type) (UnfoldSym0 a6989586621679729662 b6989586621679729663) l Source # | |
data UnfoldSym1 (l :: TyFun a6989586621679729662 (b6989586621679729663, Maybe a6989586621679729662) -> Type) (l :: TyFun a6989586621679729662 (NonEmpty b6989586621679729663)) Source #
SuppressUnusedWarnings ((TyFun a6989586621679729662 (b6989586621679729663, Maybe a6989586621679729662) -> Type) -> TyFun a6989586621679729662 (NonEmpty b6989586621679729663) -> *) (UnfoldSym1 a6989586621679729662 b6989586621679729663) Source # | |
type Apply a (NonEmpty b) (UnfoldSym1 a b l1) l2 Source # | |
data InsertSym0 (l :: TyFun a6989586621679729642 (TyFun [a6989586621679729642] (NonEmpty a6989586621679729642) -> Type)) Source #
SuppressUnusedWarnings (TyFun a6989586621679729642 (TyFun [a6989586621679729642] (NonEmpty a6989586621679729642) -> Type) -> *) (InsertSym0 a6989586621679729642) Source # | |
type Apply a6989586621679729642 (TyFun [a6989586621679729642] (NonEmpty a6989586621679729642) -> Type) (InsertSym0 a6989586621679729642) l Source # | |
data InsertSym1 (l :: a6989586621679729642) (l :: TyFun [a6989586621679729642] (NonEmpty a6989586621679729642)) Source #
SuppressUnusedWarnings (a6989586621679729642 -> TyFun [a6989586621679729642] (NonEmpty a6989586621679729642) -> *) (InsertSym1 a6989586621679729642) Source # | |
type Apply [a] (NonEmpty a) (InsertSym1 a l1) l2 Source # | |
type InsertSym2 (t :: a6989586621679729642) (t :: [a6989586621679729642]) = Insert t t Source #
data TakeSym0 (l :: TyFun Nat (TyFun (NonEmpty a6989586621679729633) [a6989586621679729633] -> Type)) Source #
data TakeSym1 (l :: Nat) (l :: TyFun (NonEmpty a6989586621679729633) [a6989586621679729633]) Source #
data DropSym0 (l :: TyFun Nat (TyFun (NonEmpty a6989586621679729632) [a6989586621679729632] -> Type)) Source #
data DropSym1 (l :: Nat) (l :: TyFun (NonEmpty a6989586621679729632) [a6989586621679729632]) Source #
data SplitAtSym0 (l :: TyFun Nat (TyFun (NonEmpty a6989586621679729631) ([a6989586621679729631], [a6989586621679729631]) -> Type)) Source #
SuppressUnusedWarnings (TyFun Nat (TyFun (NonEmpty a6989586621679729631) ([a6989586621679729631], [a6989586621679729631]) -> Type) -> *) (SplitAtSym0 a6989586621679729631) Source # | |
type Apply Nat (TyFun (NonEmpty a6989586621679729631) ([a6989586621679729631], [a6989586621679729631]) -> Type) (SplitAtSym0 a6989586621679729631) l Source # | |
data SplitAtSym1 (l :: Nat) (l :: TyFun (NonEmpty a6989586621679729631) ([a6989586621679729631], [a6989586621679729631])) Source #
SuppressUnusedWarnings (Nat -> TyFun (NonEmpty a6989586621679729631) ([a6989586621679729631], [a6989586621679729631]) -> *) (SplitAtSym1 a6989586621679729631) Source # | |
type Apply (NonEmpty a) ([a], [a]) (SplitAtSym1 a l1) l2 Source # | |
data TakeWhileSym0 (l :: TyFun (TyFun a6989586621679729630 Bool -> Type) (TyFun (NonEmpty a6989586621679729630) [a6989586621679729630] -> Type)) Source #
SuppressUnusedWarnings (TyFun (TyFun a6989586621679729630 Bool -> Type) (TyFun (NonEmpty a6989586621679729630) [a6989586621679729630] -> Type) -> *) (TakeWhileSym0 a6989586621679729630) Source # | |
type Apply (TyFun a6989586621679729630 Bool -> Type) (TyFun (NonEmpty a6989586621679729630) [a6989586621679729630] -> Type) (TakeWhileSym0 a6989586621679729630) l Source # | |
data TakeWhileSym1 (l :: TyFun a6989586621679729630 Bool -> Type) (l :: TyFun (NonEmpty a6989586621679729630) [a6989586621679729630]) Source #
SuppressUnusedWarnings ((TyFun a6989586621679729630 Bool -> Type) -> TyFun (NonEmpty a6989586621679729630) [a6989586621679729630] -> *) (TakeWhileSym1 a6989586621679729630) Source # | |
type Apply (NonEmpty a) [a] (TakeWhileSym1 a l1) l2 Source # | |
type TakeWhileSym2 (t :: TyFun a6989586621679729630 Bool -> Type) (t :: NonEmpty a6989586621679729630) = TakeWhile t t Source #
data DropWhileSym0 (l :: TyFun (TyFun a6989586621679729629 Bool -> Type) (TyFun (NonEmpty a6989586621679729629) [a6989586621679729629] -> Type)) Source #
SuppressUnusedWarnings (TyFun (TyFun a6989586621679729629 Bool -> Type) (TyFun (NonEmpty a6989586621679729629) [a6989586621679729629] -> Type) -> *) (DropWhileSym0 a6989586621679729629) Source # | |
type Apply (TyFun a6989586621679729629 Bool -> Type) (TyFun (NonEmpty a6989586621679729629) [a6989586621679729629] -> Type) (DropWhileSym0 a6989586621679729629) l Source # | |
data DropWhileSym1 (l :: TyFun a6989586621679729629 Bool -> Type) (l :: TyFun (NonEmpty a6989586621679729629) [a6989586621679729629]) Source #
SuppressUnusedWarnings ((TyFun a6989586621679729629 Bool -> Type) -> TyFun (NonEmpty a6989586621679729629) [a6989586621679729629] -> *) (DropWhileSym1 a6989586621679729629) Source # | |
type Apply (NonEmpty a) [a] (DropWhileSym1 a l1) l2 Source # | |
type DropWhileSym2 (t :: TyFun a6989586621679729629 Bool -> Type) (t :: NonEmpty a6989586621679729629) = DropWhile t t Source #
data SpanSym0 (l :: TyFun (TyFun a6989586621679729628 Bool -> Type) (TyFun (NonEmpty a6989586621679729628) ([a6989586621679729628], [a6989586621679729628]) -> Type)) Source #
SuppressUnusedWarnings (TyFun (TyFun a6989586621679729628 Bool -> Type) (TyFun (NonEmpty a6989586621679729628) ([a6989586621679729628], [a6989586621679729628]) -> Type) -> *) (SpanSym0 a6989586621679729628) Source # | |
type Apply (TyFun a6989586621679729628 Bool -> Type) (TyFun (NonEmpty a6989586621679729628) ([a6989586621679729628], [a6989586621679729628]) -> Type) (SpanSym0 a6989586621679729628) l Source # | |
data SpanSym1 (l :: TyFun a6989586621679729628 Bool -> Type) (l :: TyFun (NonEmpty a6989586621679729628) ([a6989586621679729628], [a6989586621679729628])) Source #
type SpanSym2 (t :: TyFun a6989586621679729628 Bool -> Type) (t :: NonEmpty a6989586621679729628) = Span t t Source #
data BreakSym0 (l :: TyFun (TyFun a6989586621679729627 Bool -> Type) (TyFun (NonEmpty a6989586621679729627) ([a6989586621679729627], [a6989586621679729627]) -> Type)) Source #
SuppressUnusedWarnings (TyFun (TyFun a6989586621679729627 Bool -> Type) (TyFun (NonEmpty a6989586621679729627) ([a6989586621679729627], [a6989586621679729627]) -> Type) -> *) (BreakSym0 a6989586621679729627) Source # | |
type Apply (TyFun a6989586621679729627 Bool -> Type) (TyFun (NonEmpty a6989586621679729627) ([a6989586621679729627], [a6989586621679729627]) -> Type) (BreakSym0 a6989586621679729627) l Source # | |
data BreakSym1 (l :: TyFun a6989586621679729627 Bool -> Type) (l :: TyFun (NonEmpty a6989586621679729627) ([a6989586621679729627], [a6989586621679729627])) Source #
type BreakSym2 (t :: TyFun a6989586621679729627 Bool -> Type) (t :: NonEmpty a6989586621679729627) = Break t t Source #
data FilterSym0 (l :: TyFun (TyFun a6989586621679729626 Bool -> Type) (TyFun (NonEmpty a6989586621679729626) [a6989586621679729626] -> Type)) Source #
SuppressUnusedWarnings (TyFun (TyFun a6989586621679729626 Bool -> Type) (TyFun (NonEmpty a6989586621679729626) [a6989586621679729626] -> Type) -> *) (FilterSym0 a6989586621679729626) Source # | |
type Apply (TyFun a6989586621679729626 Bool -> Type) (TyFun (NonEmpty a6989586621679729626) [a6989586621679729626] -> Type) (FilterSym0 a6989586621679729626) l Source # | |
data FilterSym1 (l :: TyFun a6989586621679729626 Bool -> Type) (l :: TyFun (NonEmpty a6989586621679729626) [a6989586621679729626]) Source #
SuppressUnusedWarnings ((TyFun a6989586621679729626 Bool -> Type) -> TyFun (NonEmpty a6989586621679729626) [a6989586621679729626] -> *) (FilterSym1 a6989586621679729626) Source # | |
type Apply (NonEmpty a) [a] (FilterSym1 a l1) l2 Source # | |
type FilterSym2 (t :: TyFun a6989586621679729626 Bool -> Type) (t :: NonEmpty a6989586621679729626) = Filter t t Source #
data PartitionSym0 (l :: TyFun (TyFun a6989586621679729625 Bool -> Type) (TyFun (NonEmpty a6989586621679729625) ([a6989586621679729625], [a6989586621679729625]) -> Type)) Source #
SuppressUnusedWarnings (TyFun (TyFun a6989586621679729625 Bool -> Type) (TyFun (NonEmpty a6989586621679729625) ([a6989586621679729625], [a6989586621679729625]) -> Type) -> *) (PartitionSym0 a6989586621679729625) Source # | |
type Apply (TyFun a6989586621679729625 Bool -> Type) (TyFun (NonEmpty a6989586621679729625) ([a6989586621679729625], [a6989586621679729625]) -> Type) (PartitionSym0 a6989586621679729625) l Source # | |
data PartitionSym1 (l :: TyFun a6989586621679729625 Bool -> Type) (l :: TyFun (NonEmpty a6989586621679729625) ([a6989586621679729625], [a6989586621679729625])) Source #
SuppressUnusedWarnings ((TyFun a6989586621679729625 Bool -> Type) -> TyFun (NonEmpty a6989586621679729625) ([a6989586621679729625], [a6989586621679729625]) -> *) (PartitionSym1 a6989586621679729625) Source # | |
type Apply (NonEmpty a) ([a], [a]) (PartitionSym1 a l1) l2 Source # | |
type PartitionSym2 (t :: TyFun a6989586621679729625 Bool -> Type) (t :: NonEmpty a6989586621679729625) = Partition t t Source #
data GroupBySym0 (l :: TyFun (TyFun a6989586621679729623 (TyFun a6989586621679729623 Bool -> Type) -> Type) (TyFun [a6989586621679729623] [NonEmpty a6989586621679729623] -> Type)) Source #
SuppressUnusedWarnings (TyFun (TyFun a6989586621679729623 (TyFun a6989586621679729623 Bool -> Type) -> Type) (TyFun [a6989586621679729623] [NonEmpty a6989586621679729623] -> Type) -> *) (GroupBySym0 a6989586621679729623) Source # | |
type Apply (TyFun a6989586621679729623 (TyFun a6989586621679729623 Bool -> Type) -> Type) (TyFun [a6989586621679729623] [NonEmpty a6989586621679729623] -> Type) (GroupBySym0 a6989586621679729623) l Source # | |
data GroupBySym1 (l :: TyFun a6989586621679729623 (TyFun a6989586621679729623 Bool -> Type) -> Type) (l :: TyFun [a6989586621679729623] [NonEmpty a6989586621679729623]) Source #
type GroupBySym2 (t :: TyFun a6989586621679729623 (TyFun a6989586621679729623 Bool -> Type) -> Type) (t :: [a6989586621679729623]) = GroupBy t t Source #
data GroupWithSym0 (l :: TyFun (TyFun a6989586621679729622 b6989586621679729621 -> Type) (TyFun [a6989586621679729622] [NonEmpty a6989586621679729622] -> Type)) Source #
SuppressUnusedWarnings (TyFun (TyFun a6989586621679729622 b6989586621679729621 -> Type) (TyFun [a6989586621679729622] [NonEmpty a6989586621679729622] -> Type) -> *) (GroupWithSym0 b6989586621679729621 a6989586621679729622) Source # | |
type Apply (TyFun a6989586621679729622 b6989586621679729621 -> Type) (TyFun [a6989586621679729622] [NonEmpty a6989586621679729622] -> Type) (GroupWithSym0 b6989586621679729621 a6989586621679729622) l Source # | |
data GroupWithSym1 (l :: TyFun a6989586621679729622 b6989586621679729621 -> Type) (l :: TyFun [a6989586621679729622] [NonEmpty a6989586621679729622]) Source #
SuppressUnusedWarnings ((TyFun a6989586621679729622 b6989586621679729621 -> Type) -> TyFun [a6989586621679729622] [NonEmpty a6989586621679729622] -> *) (GroupWithSym1 b6989586621679729621 a6989586621679729622) Source # | |
type Apply [a] [NonEmpty a] (GroupWithSym1 b a l1) l2 Source # | |
type GroupWithSym2 (t :: TyFun a6989586621679729622 b6989586621679729621 -> Type) (t :: [a6989586621679729622]) = GroupWith t t Source #
data GroupAllWithSym0 (l :: TyFun (TyFun a6989586621679729620 b6989586621679729619 -> Type) (TyFun [a6989586621679729620] [NonEmpty a6989586621679729620] -> Type)) Source #
SuppressUnusedWarnings (TyFun (TyFun a6989586621679729620 b6989586621679729619 -> Type) (TyFun [a6989586621679729620] [NonEmpty a6989586621679729620] -> Type) -> *) (GroupAllWithSym0 b6989586621679729619 a6989586621679729620) Source # | |
type Apply (TyFun a6989586621679729620 b6989586621679729619 -> Type) (TyFun [a6989586621679729620] [NonEmpty a6989586621679729620] -> Type) (GroupAllWithSym0 b6989586621679729619 a6989586621679729620) l Source # | |
data GroupAllWithSym1 (l :: TyFun a6989586621679729620 b6989586621679729619 -> Type) (l :: TyFun [a6989586621679729620] [NonEmpty a6989586621679729620]) Source #
SuppressUnusedWarnings ((TyFun a6989586621679729620 b6989586621679729619 -> Type) -> TyFun [a6989586621679729620] [NonEmpty a6989586621679729620] -> *) (GroupAllWithSym1 b6989586621679729619 a6989586621679729620) Source # | |
type Apply [a] [NonEmpty a] (GroupAllWithSym1 b a l1) l2 Source # | |
type GroupAllWithSym2 (t :: TyFun a6989586621679729620 b6989586621679729619 -> Type) (t :: [a6989586621679729620]) = GroupAllWith t t Source #
data Group1Sym0 (l :: TyFun (NonEmpty a6989586621679729618) (NonEmpty (NonEmpty a6989586621679729618))) Source #
type Group1Sym1 (t :: NonEmpty a6989586621679729618) = Group1 t Source #
data GroupBy1Sym0 (l :: TyFun (TyFun a6989586621679729617 (TyFun a6989586621679729617 Bool -> Type) -> Type) (TyFun (NonEmpty a6989586621679729617) (NonEmpty (NonEmpty a6989586621679729617)) -> Type)) Source #
SuppressUnusedWarnings (TyFun (TyFun a6989586621679729617 (TyFun a6989586621679729617 Bool -> Type) -> Type) (TyFun (NonEmpty a6989586621679729617) (NonEmpty (NonEmpty a6989586621679729617)) -> Type) -> *) (GroupBy1Sym0 a6989586621679729617) Source # | |
type Apply (TyFun a6989586621679729617 (TyFun a6989586621679729617 Bool -> Type) -> Type) (TyFun (NonEmpty a6989586621679729617) (NonEmpty (NonEmpty a6989586621679729617)) -> Type) (GroupBy1Sym0 a6989586621679729617) l Source # | |
data GroupBy1Sym1 (l :: TyFun a6989586621679729617 (TyFun a6989586621679729617 Bool -> Type) -> Type) (l :: TyFun (NonEmpty a6989586621679729617) (NonEmpty (NonEmpty a6989586621679729617))) Source #
SuppressUnusedWarnings ((TyFun a6989586621679729617 (TyFun a6989586621679729617 Bool -> Type) -> Type) -> TyFun (NonEmpty a6989586621679729617) (NonEmpty (NonEmpty a6989586621679729617)) -> *) (GroupBy1Sym1 a6989586621679729617) Source # | |
type Apply (NonEmpty a) (NonEmpty (NonEmpty a)) (GroupBy1Sym1 a l1) l2 Source # | |
type GroupBy1Sym2 (t :: TyFun a6989586621679729617 (TyFun a6989586621679729617 Bool -> Type) -> Type) (t :: NonEmpty a6989586621679729617) = GroupBy1 t t Source #
data GroupWith1Sym0 (l :: TyFun (TyFun a6989586621679729616 b6989586621679729615 -> Type) (TyFun (NonEmpty a6989586621679729616) (NonEmpty (NonEmpty a6989586621679729616)) -> Type)) Source #
SuppressUnusedWarnings (TyFun (TyFun a6989586621679729616 b6989586621679729615 -> Type) (TyFun (NonEmpty a6989586621679729616) (NonEmpty (NonEmpty a6989586621679729616)) -> Type) -> *) (GroupWith1Sym0 b6989586621679729615 a6989586621679729616) Source # | |
type Apply (TyFun a6989586621679729616 b6989586621679729615 -> Type) (TyFun (NonEmpty a6989586621679729616) (NonEmpty (NonEmpty a6989586621679729616)) -> Type) (GroupWith1Sym0 b6989586621679729615 a6989586621679729616) l Source # | |
data GroupWith1Sym1 (l :: TyFun a6989586621679729616 b6989586621679729615 -> Type) (l :: TyFun (NonEmpty a6989586621679729616) (NonEmpty (NonEmpty a6989586621679729616))) Source #
SuppressUnusedWarnings ((TyFun a6989586621679729616 b6989586621679729615 -> Type) -> TyFun (NonEmpty a6989586621679729616) (NonEmpty (NonEmpty a6989586621679729616)) -> *) (GroupWith1Sym1 b6989586621679729615 a6989586621679729616) Source # | |
type Apply (NonEmpty a) (NonEmpty (NonEmpty a)) (GroupWith1Sym1 b a l1) l2 Source # | |
type GroupWith1Sym2 (t :: TyFun a6989586621679729616 b6989586621679729615 -> Type) (t :: NonEmpty a6989586621679729616) = GroupWith1 t t Source #
data GroupAllWith1Sym0 (l :: TyFun (TyFun a6989586621679729614 b6989586621679729613 -> Type) (TyFun (NonEmpty a6989586621679729614) (NonEmpty (NonEmpty a6989586621679729614)) -> Type)) Source #
SuppressUnusedWarnings (TyFun (TyFun a6989586621679729614 b6989586621679729613 -> Type) (TyFun (NonEmpty a6989586621679729614) (NonEmpty (NonEmpty a6989586621679729614)) -> Type) -> *) (GroupAllWith1Sym0 b6989586621679729613 a6989586621679729614) Source # | |
type Apply (TyFun a6989586621679729614 b6989586621679729613 -> Type) (TyFun (NonEmpty a6989586621679729614) (NonEmpty (NonEmpty a6989586621679729614)) -> Type) (GroupAllWith1Sym0 b6989586621679729613 a6989586621679729614) l Source # | |
data GroupAllWith1Sym1 (l :: TyFun a6989586621679729614 b6989586621679729613 -> Type) (l :: TyFun (NonEmpty a6989586621679729614) (NonEmpty (NonEmpty a6989586621679729614))) Source #
SuppressUnusedWarnings ((TyFun a6989586621679729614 b6989586621679729613 -> Type) -> TyFun (NonEmpty a6989586621679729614) (NonEmpty (NonEmpty a6989586621679729614)) -> *) (GroupAllWith1Sym1 b6989586621679729613 a6989586621679729614) Source # | |
type Apply (NonEmpty a) (NonEmpty (NonEmpty a)) (GroupAllWith1Sym1 b a l1) l2 Source # | |
type GroupAllWith1Sym2 (t :: TyFun a6989586621679729614 b6989586621679729613 -> Type) (t :: NonEmpty a6989586621679729614) = GroupAllWith1 t t Source #
data IsPrefixOfSym0 (l :: TyFun [a6989586621679729612] (TyFun (NonEmpty a6989586621679729612) Bool -> Type)) Source #
data IsPrefixOfSym1 (l :: [a6989586621679729612]) (l :: TyFun (NonEmpty a6989586621679729612) Bool) Source #
SuppressUnusedWarnings ([a6989586621679729612] -> TyFun (NonEmpty a6989586621679729612) Bool -> *) (IsPrefixOfSym1 a6989586621679729612) Source # | |
type Apply (NonEmpty a) Bool (IsPrefixOfSym1 a l1) l2 Source # | |
type IsPrefixOfSym2 (t :: [a6989586621679729612]) (t :: NonEmpty a6989586621679729612) = IsPrefixOf t t Source #
data NubBySym0 (l :: TyFun (TyFun a6989586621679729602 (TyFun a6989586621679729602 Bool -> Type) -> Type) (TyFun (NonEmpty a6989586621679729602) (NonEmpty a6989586621679729602) -> Type)) Source #
SuppressUnusedWarnings (TyFun (TyFun a6989586621679729602 (TyFun a6989586621679729602 Bool -> Type) -> Type) (TyFun (NonEmpty a6989586621679729602) (NonEmpty a6989586621679729602) -> Type) -> *) (NubBySym0 a6989586621679729602) Source # | |
type Apply (TyFun a6989586621679729602 (TyFun a6989586621679729602 Bool -> Type) -> Type) (TyFun (NonEmpty a6989586621679729602) (NonEmpty a6989586621679729602) -> Type) (NubBySym0 a6989586621679729602) l Source # | |
data NubBySym1 (l :: TyFun a6989586621679729602 (TyFun a6989586621679729602 Bool -> Type) -> Type) (l :: TyFun (NonEmpty a6989586621679729602) (NonEmpty a6989586621679729602)) Source #
type NubBySym2 (t :: TyFun a6989586621679729602 (TyFun a6989586621679729602 Bool -> Type) -> Type) (t :: NonEmpty a6989586621679729602) = NubBy t t Source #
data (:!!$) (l :: TyFun (NonEmpty a6989586621679729611) (TyFun Nat a6989586621679729611 -> Type)) Source #
data ZipSym0 (l :: TyFun (NonEmpty a6989586621679729609) (TyFun (NonEmpty b6989586621679729610) (NonEmpty (a6989586621679729609, b6989586621679729610)) -> Type)) Source #
SuppressUnusedWarnings (TyFun (NonEmpty a6989586621679729609) (TyFun (NonEmpty b6989586621679729610) (NonEmpty (a6989586621679729609, b6989586621679729610)) -> Type) -> *) (ZipSym0 a6989586621679729609 b6989586621679729610) Source # | |
type Apply (NonEmpty a6989586621679729609) (TyFun (NonEmpty b6989586621679729610) (NonEmpty (a6989586621679729609, b6989586621679729610)) -> Type) (ZipSym0 a6989586621679729609 b6989586621679729610) l Source # | |
data ZipSym1 (l :: NonEmpty a6989586621679729609) (l :: TyFun (NonEmpty b6989586621679729610) (NonEmpty (a6989586621679729609, b6989586621679729610))) Source #
type ZipSym2 (t :: NonEmpty a6989586621679729609) (t :: NonEmpty b6989586621679729610) = Zip t t Source #
data ZipWithSym0 (l :: TyFun (TyFun a6989586621679729606 (TyFun b6989586621679729607 c6989586621679729608 -> Type) -> Type) (TyFun (NonEmpty a6989586621679729606) (TyFun (NonEmpty b6989586621679729607) (NonEmpty c6989586621679729608) -> Type) -> Type)) Source #
SuppressUnusedWarnings (TyFun (TyFun a6989586621679729606 (TyFun b6989586621679729607 c6989586621679729608 -> Type) -> Type) (TyFun (NonEmpty a6989586621679729606) (TyFun (NonEmpty b6989586621679729607) (NonEmpty c6989586621679729608) -> Type) -> Type) -> *) (ZipWithSym0 a6989586621679729606 b6989586621679729607 c6989586621679729608) Source # | |
type Apply (TyFun a6989586621679729606 (TyFun b6989586621679729607 c6989586621679729608 -> Type) -> Type) (TyFun (NonEmpty a6989586621679729606) (TyFun (NonEmpty b6989586621679729607) (NonEmpty c6989586621679729608) -> Type) -> Type) (ZipWithSym0 a6989586621679729606 b6989586621679729607 c6989586621679729608) l Source # | |
data ZipWithSym1 (l :: TyFun a6989586621679729606 (TyFun b6989586621679729607 c6989586621679729608 -> Type) -> Type) (l :: TyFun (NonEmpty a6989586621679729606) (TyFun (NonEmpty b6989586621679729607) (NonEmpty c6989586621679729608) -> Type)) Source #
SuppressUnusedWarnings ((TyFun a6989586621679729606 (TyFun b6989586621679729607 c6989586621679729608 -> Type) -> Type) -> TyFun (NonEmpty a6989586621679729606) (TyFun (NonEmpty b6989586621679729607) (NonEmpty c6989586621679729608) -> Type) -> *) (ZipWithSym1 a6989586621679729606 b6989586621679729607 c6989586621679729608) Source # | |
type Apply (NonEmpty a6989586621679729606) (TyFun (NonEmpty b6989586621679729607) (NonEmpty c6989586621679729608) -> Type) (ZipWithSym1 a6989586621679729606 b6989586621679729607 c6989586621679729608 l1) l2 Source # | |
data ZipWithSym2 (l :: TyFun a6989586621679729606 (TyFun b6989586621679729607 c6989586621679729608 -> Type) -> Type) (l :: NonEmpty a6989586621679729606) (l :: TyFun (NonEmpty b6989586621679729607) (NonEmpty c6989586621679729608)) Source #
SuppressUnusedWarnings ((TyFun a6989586621679729606 (TyFun b6989586621679729607 c6989586621679729608 -> Type) -> Type) -> NonEmpty a6989586621679729606 -> TyFun (NonEmpty b6989586621679729607) (NonEmpty c6989586621679729608) -> *) (ZipWithSym2 a6989586621679729606 b6989586621679729607 c6989586621679729608) Source # | |
type Apply (NonEmpty b) (NonEmpty c) (ZipWithSym2 a b c l1 l2) l3 Source # | |
type ZipWithSym3 (t :: TyFun a6989586621679729606 (TyFun b6989586621679729607 c6989586621679729608 -> Type) -> Type) (t :: NonEmpty a6989586621679729606) (t :: NonEmpty b6989586621679729607) = ZipWith t t t Source #
data UnzipSym0 (l :: TyFun (NonEmpty (a6989586621679729604, b6989586621679729605)) (NonEmpty a6989586621679729604, NonEmpty b6989586621679729605)) Source #
data FromListSym0 (l :: TyFun [a6989586621679729650] (NonEmpty a6989586621679729650)) Source #
SuppressUnusedWarnings (TyFun [a6989586621679729650] (NonEmpty a6989586621679729650) -> *) (FromListSym0 a6989586621679729650) Source # | |
type Apply [a] (NonEmpty a) (FromListSym0 a) l Source # | |
type FromListSym1 (t :: [a6989586621679729650]) = FromList t Source #
data ToListSym0 (l :: TyFun (NonEmpty a6989586621679729649) [a6989586621679729649]) Source #
SuppressUnusedWarnings (TyFun (NonEmpty a6989586621679729649) [a6989586621679729649] -> *) (ToListSym0 a6989586621679729649) Source # | |
type Apply (NonEmpty a) [a] (ToListSym0 a) l Source # | |
type ToListSym1 (t :: NonEmpty a6989586621679729649) = ToList t Source #
data NonEmpty_Sym0 (l :: TyFun [a6989586621679729661] (Maybe (NonEmpty a6989586621679729661))) Source #
SuppressUnusedWarnings (TyFun [a6989586621679729661] (Maybe (NonEmpty a6989586621679729661)) -> *) (NonEmpty_Sym0 a6989586621679729661) Source # | |
type Apply [a] (Maybe (NonEmpty a)) (NonEmpty_Sym0 a) l Source # | |
type NonEmpty_Sym1 (t :: [a6989586621679729661]) = NonEmpty_ t Source #