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 |
Data.Singletons.Prelude.List.NonEmpty
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.
- 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 a6989586621679073600 (TyFun [a6989586621679073600] (NonEmpty a6989586621679073600) -> Type))
- data (l :: a6989586621679073600) :|$$ (l :: TyFun [a6989586621679073600] (NonEmpty a6989586621679073600))
- type (:|$$$) (t :: a6989586621679073600) (t :: [a6989586621679073600]) = (:|) t t
- data MapSym0 (l :: TyFun (TyFun a6989586621679609027 b6989586621679609028 -> Type) (TyFun (NonEmpty a6989586621679609027) (NonEmpty b6989586621679609028) -> Type))
- data MapSym1 (l :: TyFun a6989586621679609027 b6989586621679609028 -> Type) (l :: TyFun (NonEmpty a6989586621679609027) (NonEmpty b6989586621679609028))
- type MapSym2 (t :: TyFun a6989586621679609027 b6989586621679609028 -> Type) (t :: NonEmpty a6989586621679609027) = Map t t
- data IntersperseSym0 (l :: TyFun a6989586621679609017 (TyFun (NonEmpty a6989586621679609017) (NonEmpty a6989586621679609017) -> Type))
- data IntersperseSym1 (l :: a6989586621679609017) (l :: TyFun (NonEmpty a6989586621679609017) (NonEmpty a6989586621679609017))
- 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))
- data ScanlSym1 (l :: TyFun b6989586621679609022 (TyFun a6989586621679609023 b6989586621679609022 -> Type) -> Type) (l :: TyFun b6989586621679609022 (TyFun [a6989586621679609023] (NonEmpty b6989586621679609022) -> Type))
- data ScanlSym2 (l :: TyFun b6989586621679609022 (TyFun a6989586621679609023 b6989586621679609022 -> Type) -> Type) (l :: b6989586621679609022) (l :: TyFun [a6989586621679609023] (NonEmpty b6989586621679609022))
- 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))
- data ScanrSym1 (l :: TyFun a6989586621679609020 (TyFun b6989586621679609021 b6989586621679609021 -> Type) -> Type) (l :: TyFun b6989586621679609021 (TyFun [a6989586621679609020] (NonEmpty b6989586621679609021) -> Type))
- data ScanrSym2 (l :: TyFun a6989586621679609020 (TyFun b6989586621679609021 b6989586621679609021 -> Type) -> Type) (l :: b6989586621679609021) (l :: TyFun [a6989586621679609020] (NonEmpty b6989586621679609021))
- 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))
- data Scanl1Sym1 (l :: TyFun a6989586621679609019 (TyFun a6989586621679609019 a6989586621679609019 -> Type) -> Type) (l :: TyFun (NonEmpty a6989586621679609019) (NonEmpty a6989586621679609019))
- 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))
- data Scanr1Sym1 (l :: TyFun a6989586621679609018 (TyFun a6989586621679609018 a6989586621679609018 -> Type) -> Type) (l :: TyFun (NonEmpty a6989586621679609018) (NonEmpty a6989586621679609018))
- 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)))
- 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))
- data SortBySym1 (l :: TyFun a6989586621679608982 (TyFun a6989586621679608982 Ordering -> Type) -> Type) (l :: TyFun (NonEmpty a6989586621679608982) (NonEmpty a6989586621679608982))
- 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))
- data SortWithSym1 (l :: TyFun a6989586621679608981 o6989586621679608980 -> Type) (l :: TyFun (NonEmpty a6989586621679608981) (NonEmpty a6989586621679608981))
- type SortWithSym2 (t :: TyFun a6989586621679608981 o6989586621679608980 -> Type) (t :: NonEmpty a6989586621679608981) = SortWith t t
- data LengthSym0 (l :: TyFun (NonEmpty a6989586621679609046) Nat)
- type LengthSym1 (t :: NonEmpty a6989586621679609046) = Length t
- data HeadSym0 (l :: TyFun (NonEmpty a6989586621679609039) a6989586621679609039)
- type HeadSym1 (t :: NonEmpty a6989586621679609039) = Head t
- data TailSym0 (l :: TyFun (NonEmpty a6989586621679609038) [a6989586621679609038])
- type TailSym1 (t :: NonEmpty a6989586621679609038) = Tail t
- data LastSym0 (l :: TyFun (NonEmpty a6989586621679609037) a6989586621679609037)
- type LastSym1 (t :: NonEmpty a6989586621679609037) = Last t
- data InitSym0 (l :: TyFun (NonEmpty a6989586621679609036) [a6989586621679609036])
- type InitSym1 (t :: NonEmpty a6989586621679609036) = Init t
- data (:<|$) (l :: TyFun a6989586621679609035 (TyFun (NonEmpty a6989586621679609035) (NonEmpty a6989586621679609035) -> Type))
- data (l :: a6989586621679609035) :<|$$ (l :: TyFun (NonEmpty a6989586621679609035) (NonEmpty a6989586621679609035))
- type (:<|$$$) (t :: a6989586621679609035) (t :: NonEmpty a6989586621679609035) = (:<|) t t
- data ConsSym0 (l :: TyFun a6989586621679609034 (TyFun (NonEmpty a6989586621679609034) (NonEmpty a6989586621679609034) -> Type))
- data ConsSym1 (l :: a6989586621679609034) (l :: TyFun (NonEmpty a6989586621679609034) (NonEmpty a6989586621679609034))
- type ConsSym2 (t :: a6989586621679609034) (t :: NonEmpty a6989586621679609034) = Cons t t
- data UnconsSym0 (l :: TyFun (NonEmpty a6989586621679609042) (a6989586621679609042, Maybe (NonEmpty a6989586621679609042)))
- type UnconsSym1 (t :: NonEmpty a6989586621679609042) = Uncons t
- data UnfoldrSym0 (l :: TyFun (TyFun a6989586621679609040 (b6989586621679609041, Maybe a6989586621679609040) -> Type) (TyFun a6989586621679609040 (NonEmpty b6989586621679609041) -> Type))
- data UnfoldrSym1 (l :: TyFun a6989586621679609040 (b6989586621679609041, Maybe a6989586621679609040) -> Type) (l :: TyFun a6989586621679609040 (NonEmpty b6989586621679609041))
- type UnfoldrSym2 (t :: TyFun a6989586621679609040 (b6989586621679609041, Maybe a6989586621679609040) -> Type) (t :: a6989586621679609040) = Unfoldr t t
- data SortSym0 (l :: TyFun (NonEmpty a6989586621679609033) (NonEmpty a6989586621679609033))
- type SortSym1 (t :: NonEmpty a6989586621679609033) = Sort t
- data ReverseSym0 (l :: TyFun (NonEmpty a6989586621679609016) (NonEmpty a6989586621679609016))
- type ReverseSym1 (t :: NonEmpty a6989586621679609016) = Reverse t
- data InitsSym0 (l :: TyFun [a6989586621679609026] (NonEmpty [a6989586621679609026]))
- type InitsSym1 (t :: [a6989586621679609026]) = Inits t
- data TailsSym0 (l :: TyFun [a6989586621679609025] (NonEmpty [a6989586621679609025]))
- type TailsSym1 (t :: [a6989586621679609025]) = Tails t
- data UnfoldSym0 (l :: TyFun (TyFun a6989586621679609044 (b6989586621679609045, Maybe a6989586621679609044) -> Type) (TyFun a6989586621679609044 (NonEmpty b6989586621679609045) -> Type))
- data UnfoldSym1 (l :: TyFun a6989586621679609044 (b6989586621679609045, Maybe a6989586621679609044) -> Type) (l :: TyFun a6989586621679609044 (NonEmpty b6989586621679609045))
- data InsertSym0 (l :: TyFun a6989586621679609024 (TyFun [a6989586621679609024] (NonEmpty a6989586621679609024) -> Type))
- data InsertSym1 (l :: a6989586621679609024) (l :: TyFun [a6989586621679609024] (NonEmpty a6989586621679609024))
- type InsertSym2 (t :: a6989586621679609024) (t :: [a6989586621679609024]) = Insert t t
- data TakeSym0 (l :: TyFun Nat (TyFun (NonEmpty a6989586621679609015) [a6989586621679609015] -> Type))
- data TakeSym1 (l :: Nat) (l :: TyFun (NonEmpty a6989586621679609015) [a6989586621679609015])
- type TakeSym2 (t :: Nat) (t :: NonEmpty a6989586621679609015) = Take t t
- data DropSym0 (l :: TyFun Nat (TyFun (NonEmpty a6989586621679609014) [a6989586621679609014] -> Type))
- data DropSym1 (l :: Nat) (l :: TyFun (NonEmpty a6989586621679609014) [a6989586621679609014])
- type DropSym2 (t :: Nat) (t :: NonEmpty a6989586621679609014) = Drop t t
- data SplitAtSym0 (l :: TyFun Nat (TyFun (NonEmpty a6989586621679609013) ([a6989586621679609013], [a6989586621679609013]) -> Type))
- data SplitAtSym1 (l :: Nat) (l :: TyFun (NonEmpty a6989586621679609013) ([a6989586621679609013], [a6989586621679609013]))
- type SplitAtSym2 (t :: Nat) (t :: NonEmpty a6989586621679609013) = SplitAt t t
- data TakeWhileSym0 (l :: TyFun (TyFun a6989586621679609012 Bool -> Type) (TyFun (NonEmpty a6989586621679609012) [a6989586621679609012] -> Type))
- data TakeWhileSym1 (l :: TyFun a6989586621679609012 Bool -> Type) (l :: TyFun (NonEmpty a6989586621679609012) [a6989586621679609012])
- 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))
- data DropWhileSym1 (l :: TyFun a6989586621679609011 Bool -> Type) (l :: TyFun (NonEmpty a6989586621679609011) [a6989586621679609011])
- 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))
- data SpanSym1 (l :: TyFun a6989586621679609010 Bool -> Type) (l :: TyFun (NonEmpty a6989586621679609010) ([a6989586621679609010], [a6989586621679609010]))
- 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))
- data BreakSym1 (l :: TyFun a6989586621679609009 Bool -> Type) (l :: TyFun (NonEmpty a6989586621679609009) ([a6989586621679609009], [a6989586621679609009]))
- 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))
- data FilterSym1 (l :: TyFun a6989586621679609008 Bool -> Type) (l :: TyFun (NonEmpty a6989586621679609008) [a6989586621679609008])
- 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))
- data PartitionSym1 (l :: TyFun a6989586621679609007 Bool -> Type) (l :: TyFun (NonEmpty a6989586621679609007) ([a6989586621679609007], [a6989586621679609007]))
- type PartitionSym2 (t :: TyFun a6989586621679609007 Bool -> Type) (t :: NonEmpty a6989586621679609007) = Partition t t
- data GroupSym0 (l :: TyFun [a6989586621679609006] [NonEmpty a6989586621679609006])
- type GroupSym1 (t :: [a6989586621679609006]) = Group t
- data GroupBySym0 (l :: TyFun (TyFun a6989586621679609005 (TyFun a6989586621679609005 Bool -> Type) -> Type) (TyFun [a6989586621679609005] [NonEmpty a6989586621679609005] -> Type))
- data GroupBySym1 (l :: TyFun a6989586621679609005 (TyFun a6989586621679609005 Bool -> Type) -> Type) (l :: TyFun [a6989586621679609005] [NonEmpty a6989586621679609005])
- 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))
- data GroupWithSym1 (l :: TyFun a6989586621679609004 b6989586621679609003 -> Type) (l :: TyFun [a6989586621679609004] [NonEmpty a6989586621679609004])
- 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))
- data GroupAllWithSym1 (l :: TyFun a6989586621679609002 b6989586621679609001 -> Type) (l :: TyFun [a6989586621679609002] [NonEmpty a6989586621679609002])
- type GroupAllWithSym2 (t :: TyFun a6989586621679609002 b6989586621679609001 -> Type) (t :: [a6989586621679609002]) = GroupAllWith t t
- data Group1Sym0 (l :: TyFun (NonEmpty a6989586621679609000) (NonEmpty (NonEmpty a6989586621679609000)))
- 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))
- data GroupBy1Sym1 (l :: TyFun a6989586621679608999 (TyFun a6989586621679608999 Bool -> Type) -> Type) (l :: TyFun (NonEmpty a6989586621679608999) (NonEmpty (NonEmpty a6989586621679608999)))
- 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))
- data GroupWith1Sym1 (l :: TyFun a6989586621679608998 b6989586621679608997 -> Type) (l :: TyFun (NonEmpty a6989586621679608998) (NonEmpty (NonEmpty a6989586621679608998)))
- 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))
- data GroupAllWith1Sym1 (l :: TyFun a6989586621679608996 b6989586621679608995 -> Type) (l :: TyFun (NonEmpty a6989586621679608996) (NonEmpty (NonEmpty a6989586621679608996)))
- type GroupAllWith1Sym2 (t :: TyFun a6989586621679608996 b6989586621679608995 -> Type) (t :: NonEmpty a6989586621679608996) = GroupAllWith1 t t
- data IsPrefixOfSym0 (l :: TyFun [a6989586621679608994] (TyFun (NonEmpty a6989586621679608994) Bool -> Type))
- data IsPrefixOfSym1 (l :: [a6989586621679608994]) (l :: TyFun (NonEmpty a6989586621679608994) Bool)
- type IsPrefixOfSym2 (t :: [a6989586621679608994]) (t :: NonEmpty a6989586621679608994) = IsPrefixOf t t
- data NubSym0 (l :: TyFun (NonEmpty a6989586621679608985) (NonEmpty a6989586621679608985))
- type NubSym1 (t :: NonEmpty a6989586621679608985) = Nub t
- data NubBySym0 (l :: TyFun (TyFun a6989586621679608984 (TyFun a6989586621679608984 Bool -> Type) -> Type) (TyFun (NonEmpty a6989586621679608984) (NonEmpty a6989586621679608984) -> Type))
- data NubBySym1 (l :: TyFun a6989586621679608984 (TyFun a6989586621679608984 Bool -> Type) -> Type) (l :: TyFun (NonEmpty a6989586621679608984) (NonEmpty a6989586621679608984))
- 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))
- data (l :: NonEmpty a6989586621679608993) :!!$$ (l :: TyFun Nat a6989586621679608993)
- type (:!!$$$) (t :: NonEmpty a6989586621679608993) (t :: Nat) = (:!!) t t
- data ZipSym0 (l :: TyFun (NonEmpty a6989586621679608991) (TyFun (NonEmpty b6989586621679608992) (NonEmpty (a6989586621679608991, b6989586621679608992)) -> Type))
- data ZipSym1 (l :: NonEmpty a6989586621679608991) (l :: TyFun (NonEmpty b6989586621679608992) (NonEmpty (a6989586621679608991, b6989586621679608992)))
- 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))
- data ZipWithSym1 (l :: TyFun a6989586621679608988 (TyFun b6989586621679608989 c6989586621679608990 -> Type) -> Type) (l :: TyFun (NonEmpty a6989586621679608988) (TyFun (NonEmpty b6989586621679608989) (NonEmpty c6989586621679608990) -> Type))
- data ZipWithSym2 (l :: TyFun a6989586621679608988 (TyFun b6989586621679608989 c6989586621679608990 -> Type) -> Type) (l :: NonEmpty a6989586621679608988) (l :: TyFun (NonEmpty b6989586621679608989) (NonEmpty c6989586621679608990))
- 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))
- type UnzipSym1 (t :: NonEmpty (a6989586621679608986, b6989586621679608987)) = Unzip t
- data FromListSym0 (l :: TyFun [a6989586621679609032] (NonEmpty a6989586621679609032))
- type FromListSym1 (t :: [a6989586621679609032]) = FromList t
- data ToListSym0 (l :: TyFun (NonEmpty a6989586621679609031) [a6989586621679609031])
- type ToListSym1 (t :: NonEmpty a6989586621679609031) = ToList t
- data NonEmpty_Sym0 (l :: TyFun [a6989586621679609043] (Maybe (NonEmpty a6989586621679609043)))
- type NonEmpty_Sym1 (t :: [a6989586621679609043]) = NonEmpty_ t
- data XorSym0 (l :: TyFun (NonEmpty Bool) Bool)
- type XorSym1 (t :: NonEmpty Bool) = Xor t
The NonEmpty
singleton
The singleton kind-indexed data family.
Instances
data Sing Bool # | |
data Sing Ordering # | |
data Sing * # | |
data Sing Nat # | |
data Sing Symbol # | |
data Sing () # | |
data Sing [a] # | |
data Sing (Maybe a) # | |
data Sing (NonEmpty a) # | |
data Sing (Either a b) # | |
data Sing (a, b) # | |
data Sing ((~>) k1 k2) # | |
data Sing (a, b, c) # | |
data Sing (a, b, c, d) # | |
data Sing (a, b, c, d, e) # | |
data Sing (a, b, c, d, e, f) # | |
data Sing (a, b, c, d, e, f, g) # | |
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) #
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 ... #
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 ... #
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 ... #
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) #
(%:<|) :: forall (t :: a) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply (:<|$) t) t :: NonEmpty a) #
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 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) #
sInsert :: forall (t :: a) (t :: [a]). SOrd a => Sing t -> Sing t -> Sing (Apply (Apply InsertSym0 t) t :: NonEmpty a) #
sTake :: forall (t :: Nat) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply TakeSym0 t) t :: [a]) #
sDrop :: forall (t :: Nat) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply DropSym0 t) t :: [a]) #
sSplitAt :: forall (t :: Nat) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply SplitAtSym0 t) t :: ([a], [a])) #
sTakeWhile :: forall (t :: TyFun a Bool -> Type) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply TakeWhileSym0 t) t :: [a]) #
sDropWhile :: forall (t :: TyFun a Bool -> Type) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply DropWhileSym0 t) t :: [a]) #
sSpan :: forall (t :: TyFun a Bool -> Type) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply SpanSym0 t) t :: ([a], [a])) #
sBreak :: forall (t :: TyFun a Bool -> Type) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply BreakSym0 t) t :: ([a], [a])) #
sFilter :: forall (t :: TyFun a Bool -> Type) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply FilterSym0 t) t :: [a]) #
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 |
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]) #
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 ... #
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 ... #
sIsPrefixOf :: forall (t :: [a]) (t :: NonEmpty a). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IsPrefixOfSym0 t) t :: Bool) #
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 ... #
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) #
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) #
sUnzip :: forall (t :: NonEmpty (a, b)). Sing t -> Sing (Apply UnzipSym0 t :: (NonEmpty a, NonEmpty b)) #
sNonEmpty_ :: forall (t :: [a]). Sing t -> Sing (Apply NonEmpty_Sym0 t :: Maybe (NonEmpty a)) #
Defunctionalization symbols
data (:|$) (l :: TyFun a6989586621679073600 (TyFun [a6989586621679073600] (NonEmpty a6989586621679073600) -> Type)) #
Instances
data (l :: a6989586621679073600) :|$$ (l :: TyFun [a6989586621679073600] (NonEmpty a6989586621679073600)) #
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) # | |
type Apply (TyFun a6989586621679609027 b6989586621679609028 -> Type) (TyFun (NonEmpty a6989586621679609027) (NonEmpty b6989586621679609028) -> Type) (MapSym0 a6989586621679609027 b6989586621679609028) l # | |
data MapSym1 (l :: TyFun a6989586621679609027 b6989586621679609028 -> Type) (l :: TyFun (NonEmpty a6989586621679609027) (NonEmpty b6989586621679609028)) #
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) # | |
type Apply a6989586621679609017 (TyFun (NonEmpty a6989586621679609017) (NonEmpty a6989586621679609017) -> Type) (IntersperseSym0 a6989586621679609017) l # | |
data IntersperseSym1 (l :: a6989586621679609017) (l :: TyFun (NonEmpty a6989586621679609017) (NonEmpty a6989586621679609017)) #
Instances
SuppressUnusedWarnings (a6989586621679609017 -> TyFun (NonEmpty a6989586621679609017) (NonEmpty a6989586621679609017) -> *) (IntersperseSym1 a6989586621679609017) # | |
type Apply (NonEmpty a) (NonEmpty a) (IntersperseSym1 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) # | |
type Apply (TyFun b6989586621679609022 (TyFun a6989586621679609023 b6989586621679609022 -> Type) -> Type) (TyFun b6989586621679609022 (TyFun [a6989586621679609023] (NonEmpty b6989586621679609022) -> Type) -> Type) (ScanlSym0 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) # | |
type Apply b6989586621679609022 (TyFun [a6989586621679609023] (NonEmpty b6989586621679609022) -> Type) (ScanlSym1 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) # | |
type Apply [a] (NonEmpty b) (ScanlSym2 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) # | |
type Apply (TyFun a6989586621679609020 (TyFun b6989586621679609021 b6989586621679609021 -> Type) -> Type) (TyFun b6989586621679609021 (TyFun [a6989586621679609020] (NonEmpty b6989586621679609021) -> Type) -> Type) (ScanrSym0 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) # | |
type Apply b6989586621679609021 (TyFun [a6989586621679609020] (NonEmpty b6989586621679609021) -> Type) (ScanrSym1 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) # | |
type Apply [a] (NonEmpty b) (ScanrSym2 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) # | |
type Apply (TyFun a6989586621679609019 (TyFun a6989586621679609019 a6989586621679609019 -> Type) -> Type) (TyFun (NonEmpty a6989586621679609019) (NonEmpty a6989586621679609019) -> Type) (Scanl1Sym0 a6989586621679609019) l # | |
data Scanl1Sym1 (l :: TyFun a6989586621679609019 (TyFun a6989586621679609019 a6989586621679609019 -> Type) -> Type) (l :: TyFun (NonEmpty a6989586621679609019) (NonEmpty a6989586621679609019)) #
Instances
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) # | |
type Apply (TyFun a6989586621679609018 (TyFun a6989586621679609018 a6989586621679609018 -> Type) -> Type) (TyFun (NonEmpty a6989586621679609018) (NonEmpty a6989586621679609018) -> Type) (Scanr1Sym0 a6989586621679609018) l # | |
data Scanr1Sym1 (l :: TyFun a6989586621679609018 (TyFun a6989586621679609018 a6989586621679609018 -> Type) -> Type) (l :: TyFun (NonEmpty a6989586621679609018) (NonEmpty a6989586621679609018)) #
Instances
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))) #
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) # | |
type Apply (TyFun a6989586621679608982 (TyFun a6989586621679608982 Ordering -> Type) -> Type) (TyFun (NonEmpty a6989586621679608982) (NonEmpty a6989586621679608982) -> Type) (SortBySym0 a6989586621679608982) l # | |
data SortBySym1 (l :: TyFun a6989586621679608982 (TyFun a6989586621679608982 Ordering -> Type) -> Type) (l :: TyFun (NonEmpty a6989586621679608982) (NonEmpty a6989586621679608982)) #
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) # | |
type Apply (TyFun a6989586621679608981 o6989586621679608980 -> Type) (TyFun (NonEmpty a6989586621679608981) (NonEmpty a6989586621679608981) -> Type) (SortWithSym0 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) # | |
type Apply (NonEmpty a) (NonEmpty a) (SortWithSym1 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) # | |
type Apply (NonEmpty a) Nat (LengthSym0 a) l # | |
type LengthSym1 (t :: NonEmpty a6989586621679609046) = Length t #
data (:<|$) (l :: TyFun a6989586621679609035 (TyFun (NonEmpty a6989586621679609035) (NonEmpty a6989586621679609035) -> Type)) #
Instances
SuppressUnusedWarnings (TyFun a6989586621679609035 (TyFun (NonEmpty a6989586621679609035) (NonEmpty a6989586621679609035) -> Type) -> *) ((:<|$) a6989586621679609035) # | |
type Apply a6989586621679609035 (TyFun (NonEmpty a6989586621679609035) (NonEmpty a6989586621679609035) -> Type) ((:<|$) a6989586621679609035) l # | |
data (l :: a6989586621679609035) :<|$$ (l :: TyFun (NonEmpty a6989586621679609035) (NonEmpty a6989586621679609035)) #
data ConsSym0 (l :: TyFun a6989586621679609034 (TyFun (NonEmpty a6989586621679609034) (NonEmpty a6989586621679609034) -> Type)) #
Instances
SuppressUnusedWarnings (TyFun a6989586621679609034 (TyFun (NonEmpty a6989586621679609034) (NonEmpty a6989586621679609034) -> Type) -> *) (ConsSym0 a6989586621679609034) # | |
type Apply a6989586621679609034 (TyFun (NonEmpty a6989586621679609034) (NonEmpty a6989586621679609034) -> Type) (ConsSym0 a6989586621679609034) l # | |
data ConsSym1 (l :: a6989586621679609034) (l :: TyFun (NonEmpty a6989586621679609034) (NonEmpty a6989586621679609034)) #
data UnconsSym0 (l :: TyFun (NonEmpty a6989586621679609042) (a6989586621679609042, Maybe (NonEmpty a6989586621679609042))) #
Instances
SuppressUnusedWarnings (TyFun (NonEmpty a6989586621679609042) (a6989586621679609042, Maybe (NonEmpty a6989586621679609042)) -> *) (UnconsSym0 a6989586621679609042) # | |
type Apply (NonEmpty a) (a, Maybe (NonEmpty a)) (UnconsSym0 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) # | |
type Apply (TyFun a6989586621679609040 (b6989586621679609041, Maybe a6989586621679609040) -> Type) (TyFun a6989586621679609040 (NonEmpty b6989586621679609041) -> Type) (UnfoldrSym0 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) # | |
type Apply a (NonEmpty b) (UnfoldrSym1 a b l1) l2 # | |
type UnfoldrSym2 (t :: TyFun a6989586621679609040 (b6989586621679609041, Maybe a6989586621679609040) -> Type) (t :: a6989586621679609040) = Unfoldr t t #
data ReverseSym0 (l :: TyFun (NonEmpty a6989586621679609016) (NonEmpty a6989586621679609016)) #
Instances
SuppressUnusedWarnings (TyFun (NonEmpty a6989586621679609016) (NonEmpty a6989586621679609016) -> *) (ReverseSym0 a6989586621679609016) # | |
type Apply (NonEmpty a) (NonEmpty a) (ReverseSym0 a) l # | |
type ReverseSym1 (t :: NonEmpty a6989586621679609016) = Reverse 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) # | |
type Apply (TyFun a6989586621679609044 (b6989586621679609045, Maybe a6989586621679609044) -> Type) (TyFun a6989586621679609044 (NonEmpty b6989586621679609045) -> Type) (UnfoldSym0 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) # | |
type Apply a (NonEmpty b) (UnfoldSym1 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) # | |
type Apply a6989586621679609024 (TyFun [a6989586621679609024] (NonEmpty a6989586621679609024) -> Type) (InsertSym0 a6989586621679609024) l # | |
data InsertSym1 (l :: a6989586621679609024) (l :: TyFun [a6989586621679609024] (NonEmpty a6989586621679609024)) #
Instances
SuppressUnusedWarnings (a6989586621679609024 -> TyFun [a6989586621679609024] (NonEmpty a6989586621679609024) -> *) (InsertSym1 a6989586621679609024) # | |
type Apply [a] (NonEmpty a) (InsertSym1 a l1) l2 # | |
type InsertSym2 (t :: a6989586621679609024) (t :: [a6989586621679609024]) = Insert t t #
data TakeSym0 (l :: TyFun Nat (TyFun (NonEmpty a6989586621679609015) [a6989586621679609015] -> Type)) #
data DropSym0 (l :: TyFun Nat (TyFun (NonEmpty a6989586621679609014) [a6989586621679609014] -> Type)) #
data SplitAtSym0 (l :: TyFun Nat (TyFun (NonEmpty a6989586621679609013) ([a6989586621679609013], [a6989586621679609013]) -> Type)) #
Instances
SuppressUnusedWarnings (TyFun Nat (TyFun (NonEmpty a6989586621679609013) ([a6989586621679609013], [a6989586621679609013]) -> Type) -> *) (SplitAtSym0 a6989586621679609013) # | |
type Apply Nat (TyFun (NonEmpty a6989586621679609013) ([a6989586621679609013], [a6989586621679609013]) -> Type) (SplitAtSym0 a6989586621679609013) l # | |
data SplitAtSym1 (l :: Nat) (l :: TyFun (NonEmpty a6989586621679609013) ([a6989586621679609013], [a6989586621679609013])) #
Instances
SuppressUnusedWarnings (Nat -> TyFun (NonEmpty a6989586621679609013) ([a6989586621679609013], [a6989586621679609013]) -> *) (SplitAtSym1 a6989586621679609013) # | |
type Apply (NonEmpty a) ([a], [a]) (SplitAtSym1 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) # | |
type Apply (TyFun a6989586621679609012 Bool -> Type) (TyFun (NonEmpty a6989586621679609012) [a6989586621679609012] -> Type) (TakeWhileSym0 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) # | |
type Apply (NonEmpty a) [a] (TakeWhileSym1 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) # | |
type Apply (TyFun a6989586621679609011 Bool -> Type) (TyFun (NonEmpty a6989586621679609011) [a6989586621679609011] -> Type) (DropWhileSym0 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) # | |
type Apply (NonEmpty a) [a] (DropWhileSym1 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) # | |
type Apply (TyFun a6989586621679609010 Bool -> Type) (TyFun (NonEmpty a6989586621679609010) ([a6989586621679609010], [a6989586621679609010]) -> Type) (SpanSym0 a6989586621679609010) l # | |
data SpanSym1 (l :: TyFun a6989586621679609010 Bool -> Type) (l :: TyFun (NonEmpty a6989586621679609010) ([a6989586621679609010], [a6989586621679609010])) #
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) # | |
type Apply (TyFun a6989586621679609009 Bool -> Type) (TyFun (NonEmpty a6989586621679609009) ([a6989586621679609009], [a6989586621679609009]) -> Type) (BreakSym0 a6989586621679609009) l # | |
data BreakSym1 (l :: TyFun a6989586621679609009 Bool -> Type) (l :: TyFun (NonEmpty a6989586621679609009) ([a6989586621679609009], [a6989586621679609009])) #
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) # | |
type Apply (TyFun a6989586621679609008 Bool -> Type) (TyFun (NonEmpty a6989586621679609008) [a6989586621679609008] -> Type) (FilterSym0 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) # | |
type Apply (NonEmpty a) [a] (FilterSym1 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) # | |
type Apply (TyFun a6989586621679609007 Bool -> Type) (TyFun (NonEmpty a6989586621679609007) ([a6989586621679609007], [a6989586621679609007]) -> Type) (PartitionSym0 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) # | |
type Apply (NonEmpty a) ([a], [a]) (PartitionSym1 a l1) l2 # | |
type PartitionSym2 (t :: TyFun a6989586621679609007 Bool -> Type) (t :: NonEmpty a6989586621679609007) = Partition t 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) # | |
type Apply (TyFun a6989586621679609005 (TyFun a6989586621679609005 Bool -> Type) -> Type) (TyFun [a6989586621679609005] [NonEmpty a6989586621679609005] -> Type) (GroupBySym0 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) # | |
type Apply [a] [NonEmpty a] (GroupBySym1 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) # | |
type Apply (TyFun a6989586621679609004 b6989586621679609003 -> Type) (TyFun [a6989586621679609004] [NonEmpty a6989586621679609004] -> Type) (GroupWithSym0 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) # | |
type Apply [a] [NonEmpty a] (GroupWithSym1 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) # | |
type Apply (TyFun a6989586621679609002 b6989586621679609001 -> Type) (TyFun [a6989586621679609002] [NonEmpty a6989586621679609002] -> Type) (GroupAllWithSym0 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) # | |
type Apply [a] [NonEmpty a] (GroupAllWithSym1 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) # | |
type Apply (NonEmpty a) (NonEmpty (NonEmpty a)) (Group1Sym0 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) # | |
type Apply (TyFun a6989586621679608999 (TyFun a6989586621679608999 Bool -> Type) -> Type) (TyFun (NonEmpty a6989586621679608999) (NonEmpty (NonEmpty a6989586621679608999)) -> Type) (GroupBy1Sym0 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) # | |
type Apply (NonEmpty a) (NonEmpty (NonEmpty a)) (GroupBy1Sym1 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) # | |
type Apply (TyFun a6989586621679608998 b6989586621679608997 -> Type) (TyFun (NonEmpty a6989586621679608998) (NonEmpty (NonEmpty a6989586621679608998)) -> Type) (GroupWith1Sym0 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) # | |
type Apply (NonEmpty a) (NonEmpty (NonEmpty a)) (GroupWith1Sym1 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) # | |
type Apply (TyFun a6989586621679608996 b6989586621679608995 -> Type) (TyFun (NonEmpty a6989586621679608996) (NonEmpty (NonEmpty a6989586621679608996)) -> Type) (GroupAllWith1Sym0 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) # | |
type Apply (NonEmpty a) (NonEmpty (NonEmpty a)) (GroupAllWith1Sym1 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)) #
data IsPrefixOfSym1 (l :: [a6989586621679608994]) (l :: TyFun (NonEmpty a6989586621679608994) Bool) #
Instances
SuppressUnusedWarnings ([a6989586621679608994] -> TyFun (NonEmpty a6989586621679608994) Bool -> *) (IsPrefixOfSym1 a6989586621679608994) # | |
type Apply (NonEmpty a) Bool (IsPrefixOfSym1 a l1) l2 # | |
type IsPrefixOfSym2 (t :: [a6989586621679608994]) (t :: NonEmpty a6989586621679608994) = IsPrefixOf t 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) # | |
type Apply (TyFun a6989586621679608984 (TyFun a6989586621679608984 Bool -> Type) -> Type) (TyFun (NonEmpty a6989586621679608984) (NonEmpty a6989586621679608984) -> Type) (NubBySym0 a6989586621679608984) l # | |
data NubBySym1 (l :: TyFun a6989586621679608984 (TyFun a6989586621679608984 Bool -> Type) -> Type) (l :: TyFun (NonEmpty a6989586621679608984) (NonEmpty a6989586621679608984)) #
type NubBySym2 (t :: TyFun a6989586621679608984 (TyFun a6989586621679608984 Bool -> Type) -> Type) (t :: NonEmpty a6989586621679608984) = NubBy 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) # | |
type Apply (NonEmpty a6989586621679608991) (TyFun (NonEmpty b6989586621679608992) (NonEmpty (a6989586621679608991, b6989586621679608992)) -> Type) (ZipSym0 a6989586621679608991 b6989586621679608992) l # | |
data ZipSym1 (l :: NonEmpty a6989586621679608991) (l :: TyFun (NonEmpty b6989586621679608992) (NonEmpty (a6989586621679608991, b6989586621679608992))) #
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) # | |
type Apply (TyFun a6989586621679608988 (TyFun b6989586621679608989 c6989586621679608990 -> Type) -> Type) (TyFun (NonEmpty a6989586621679608988) (TyFun (NonEmpty b6989586621679608989) (NonEmpty c6989586621679608990) -> Type) -> Type) (ZipWithSym0 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) # | |
type Apply (NonEmpty a6989586621679608988) (TyFun (NonEmpty b6989586621679608989) (NonEmpty c6989586621679608990) -> Type) (ZipWithSym1 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) # | |
type Apply (NonEmpty b) (NonEmpty c) (ZipWithSym2 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)) #
data FromListSym0 (l :: TyFun [a6989586621679609032] (NonEmpty a6989586621679609032)) #
Instances
SuppressUnusedWarnings (TyFun [a6989586621679609032] (NonEmpty a6989586621679609032) -> *) (FromListSym0 a6989586621679609032) # | |
type Apply [a] (NonEmpty a) (FromListSym0 a) l # | |
type FromListSym1 (t :: [a6989586621679609032]) = FromList t #
data ToListSym0 (l :: TyFun (NonEmpty a6989586621679609031) [a6989586621679609031]) #
Instances
SuppressUnusedWarnings (TyFun (NonEmpty a6989586621679609031) [a6989586621679609031] -> *) (ToListSym0 a6989586621679609031) # | |
type Apply (NonEmpty a) [a] (ToListSym0 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) # | |
type Apply [a] (Maybe (NonEmpty a)) (NonEmpty_Sym0 a) l # | |
type NonEmpty_Sym1 (t :: [a6989586621679609043]) = NonEmpty_ t #