singletons-base-3.0: A promoted and singled version of the base library
Copyright(C) 2016 Richard Eisenberg
LicenseBSD-style (see LICENSE)
MaintainerRyan Scott
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.List.NonEmpty.Singletons

Description

Defines functions and datatypes relating to the singleton for NonEmpty, including singled versions of all the definitions in Data.List.NonEmpty.

Because many of these definitions are produced by Template Haskell, it is not possible to create proper Haddock documentation. Please look up the corresponding operation in Data.List.NonEmpty. Also, please excuse the apparent repeated variable names. This is due to an interaction between Template Haskell and Haddock.

Synopsis

The NonEmpty singleton

type family Sing :: k -> Type #

The singleton kind-indexed type family.

Instances

Instances details
type Sing Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Sing = SBool
type Sing Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Sing Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type Sing = SNat
type Sing Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type Sing = SSymbol
type Sing Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Sing = STuple0
type Sing Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Sing = SVoid
type Sing Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal

type Sing = SAll
type Sing Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal

type Sing = SAny
type Sing Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

type Sing Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Sing = SList :: [a] -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Sing = SMaybe :: Maybe a -> Type
type Sing Source #

A choice of singleton for the kind TYPE rep (for some RuntimeRep rep), an instantiation of which is the famous kind Type.

Conceivably, one could generalize this instance to `Sing @k` for any kind k, and remove all other Sing instances. We don't adopt this design, however, since it is far more convenient in practice to work with explicit singleton values than TypeReps (for instance, TypeReps are more difficult to pattern match on, and require extra runtime checks).

We cannot produce explicit singleton values for everything in TYPE rep, however, since it is an open kind, so we reach for TypeRep in this one particular case.

Instance details

Defined in Data.Singletons.Base.TypeRepTYPE

type Sing = TypeRep :: TYPE rep -> Type
type Sing Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal

type Sing = SMin :: Min a -> Type
type Sing Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal

type Sing = SMax :: Max a -> Type
type Sing Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal

type Sing = SFirst :: First a -> Type
type Sing Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal

type Sing = SLast :: Last a -> Type
type Sing Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal

type Sing Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Sing = SIdentity :: Identity a -> Type
type Sing Source # 
Instance details

Defined in Data.Monoid.Singletons

type Sing = SFirst :: First a -> Type
type Sing Source # 
Instance details

Defined in Data.Monoid.Singletons

type Sing = SLast :: Last a -> Type
type Sing Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal

type Sing = SDual :: Dual a -> Type
type Sing Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal

type Sing = SSum :: Sum a -> Type
type Sing Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal

type Sing = SProduct :: Product a -> Type
type Sing Source # 
Instance details

Defined in Data.Ord.Singletons

type Sing = SDown :: Down a -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Sing = SNonEmpty :: NonEmpty a -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Sing = SEither :: Either a b -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Sing = STuple2 :: (a, b) -> Type
type Sing Source # 
Instance details

Defined in Data.Semigroup.Singletons

type Sing = SArg :: Arg a b -> Type
type Sing Source # 
Instance details

Defined in Data.Proxy.Singletons

type Sing = SProxy :: Proxy t -> Type
type Sing 
Instance details

Defined in Data.Singletons

type Sing 
Instance details

Defined in Data.Singletons

type Sing = SLambda :: (k1 ~> k2) -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Sing = STuple3 :: (a, b, c) -> Type
type Sing Source # 
Instance details

Defined in Data.Functor.Const.Singletons

type Sing = SConst :: Const a b -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Sing = STuple4 :: (a, b, c, d) -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Sing = STuple5 :: (a, b, c, d, e) -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Sing = STuple6 :: (a, b, c, d, e, f) -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Sing = STuple7 :: (a, b, c, d, e, f, g) -> Type

data SNonEmpty :: forall (a :: Type). NonEmpty a -> Type where Source #

Constructors

(:%|) :: forall (a :: Type) (n :: a) (n :: [a]). (Sing n) -> (Sing n) -> SNonEmpty ('(:|) n n :: NonEmpty (a :: Type)) infixr 5 

Instances

Instances details
(SDecide a, SDecide [a]) => TestCoercion (SNonEmpty :: NonEmpty a -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

testCoercion :: forall (a0 :: k) (b :: k). SNonEmpty a0 -> SNonEmpty b -> Maybe (Coercion a0 b) #

(SDecide a, SDecide [a]) => TestEquality (SNonEmpty :: NonEmpty a -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

testEquality :: forall (a0 :: k) (b :: k). SNonEmpty a0 -> SNonEmpty b -> Maybe (a0 :~: b) #

(ShowSing a, ShowSing [a]) => Show (SNonEmpty z) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Non-empty stream transformations

type family Map (a :: (~>) a b) (a :: NonEmpty a) :: NonEmpty b where ... Source #

Equations

Map f ('(:|) a as) = Apply (Apply (:|@#@$) (Apply f a)) (Apply (Apply ListmapSym0 f) as) 

sMap :: forall a b (t :: (~>) a b) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply MapSym0 t) t :: NonEmpty b) Source #

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

Equations

Intersperse a ('(:|) b bs) = Apply (Apply (:|@#@$) b) (Case_6989586621681120646 a b bs bs) 

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

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

Equations

Scanl f z a_6989586621681120677 = Apply (Apply (Apply (.@#@$) FromListSym0) (Apply (Apply ListscanlSym0 f) z)) a_6989586621681120677 

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

Equations

Scanr f z a_6989586621681120665 = Apply (Apply (Apply (.@#@$) FromListSym0) (Apply (Apply ListscanrSym0 f) z)) a_6989586621681120665 

sScanr :: forall a b (t :: (~>) a ((~>) b b)) (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 :: (~>) a ((~>) a a)) (a :: NonEmpty a) :: NonEmpty a where ... Source #

Equations

Scanl1 f ('(:|) a as) = Apply FromListSym0 (Apply (Apply (Apply ListscanlSym0 f) a) as) 

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

type family Scanr1 (a :: (~>) a ((~>) a a)) (a :: NonEmpty a) :: NonEmpty a where ... Source #

Equations

Scanr1 f ('(:|) a as) = Apply FromListSym0 (Apply (Apply Listscanr1Sym0 f) (Apply (Apply (:@#@$) a) as)) 

sScanr1 :: forall a (t :: (~>) a ((~>) a a)) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply Scanr1Sym0 t) t :: NonEmpty a) Source #

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

Equations

Transpose a_6989586621681120346 = Apply (Apply (Apply (.@#@$) (Apply FmapSym0 FromListSym0)) (Apply (Apply (.@#@$) FromListSym0) (Apply (Apply (.@#@$) ListtransposeSym0) (Apply (Apply (.@#@$) ToListSym0) (Apply FmapSym0 ToListSym0))))) a_6989586621681120346 

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

type family SortBy (a :: (~>) a ((~>) a Ordering)) (a :: NonEmpty a) :: NonEmpty a where ... Source #

Equations

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

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

type family SortWith (a :: (~>) a o) (a :: NonEmpty a) :: NonEmpty a where ... Source #

Equations

SortWith a_6989586621681120326 a_6989586621681120328 = Apply (Apply (Apply (Apply (.@#@$) SortBySym0) ComparingSym0) a_6989586621681120326) a_6989586621681120328 

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

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

Equations

Length ('(:|) _ xs) = Apply (Apply (+@#@$) (FromInteger 1)) (Apply ListlengthSym0 xs) 

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

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

Equations

Head ('(:|) a _) = a 

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

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

Equations

Tail ('(:|) _ as) = as 

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

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

Equations

Last ('(:|) a as) = Apply ListlastSym0 (Apply (Apply (:@#@$) a) as) 

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

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

Equations

Init ('(:|) a as) = Apply ListinitSym0 (Apply (Apply (:@#@$) a) as) 

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

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

Equations

a <| ('(:|) b bs) = Apply (Apply (:|@#@$) a) (Apply (Apply (:@#@$) b) bs) 

(%<|) :: forall a (t :: a) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply (<|@#@$) t) t :: NonEmpty a) Source #

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

Equations

Cons a_6989586621681120743 a_6989586621681120745 = Apply (Apply (<|@#@$) a_6989586621681120743) a_6989586621681120745 

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

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

Equations

Uncons ('(:|) a as) = Apply (Apply Tuple2Sym0 a) (Apply NonEmpty_Sym0 as) 

sUncons :: forall a (t :: NonEmpty a). Sing t -> Sing (Apply UnconsSym0 t :: (a, Maybe (NonEmpty a))) Source #

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

Equations

Unfoldr f a = Case_6989586621681120800 f a (Let6989586621681120798Scrutinee_6989586621681119224Sym2 f a) 

sUnfoldr :: forall a b (t :: (~>) a (b, Maybe a)) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply UnfoldrSym0 t) t :: NonEmpty b) Source #

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

Equations

Sort a_6989586621681120737 = Apply (Apply LiftSym0 ListsortSym0) a_6989586621681120737 

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

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

Equations

Reverse a_6989586621681120632 = Apply (Apply LiftSym0 ListreverseSym0) a_6989586621681120632 

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

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

Equations

Inits a_6989586621681120704 = Apply (Apply (Apply (.@#@$) FromListSym0) ListinitsSym0) a_6989586621681120704 

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

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

Equations

Tails a_6989586621681120698 = Apply (Apply (Apply (.@#@$) FromListSym0) ListtailsSym0) a_6989586621681120698 

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

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

Equations

Unfold f a = Case_6989586621681120824 f a (Let6989586621681120822Scrutinee_6989586621681119214Sym2 f a) 

sUnfold :: forall a b (t :: (~>) a (b, Maybe a)) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply UnfoldSym0 t) t :: NonEmpty b) Source #

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

Equations

Insert a a_6989586621681120689 = Apply (Apply (Apply (.@#@$) FromListSym0) (Apply ListinsertSym0 a)) a_6989586621681120689 

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

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

Equations

Take n a_6989586621681120623 = Apply (Apply (Apply (.@#@$) (Apply ListtakeSym0 n)) ToListSym0) a_6989586621681120623 

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

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

Equations

Drop n a_6989586621681120614 = Apply (Apply (Apply (.@#@$) (Apply ListdropSym0 n)) ToListSym0) a_6989586621681120614 

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

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

Equations

SplitAt n a_6989586621681120605 = Apply (Apply (Apply (.@#@$) (Apply ListsplitAtSym0 n)) ToListSym0) a_6989586621681120605 

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

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

Equations

TakeWhile p a_6989586621681120596 = Apply (Apply (Apply (.@#@$) (Apply ListtakeWhileSym0 p)) ToListSym0) a_6989586621681120596 

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

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

Equations

DropWhile p a_6989586621681120587 = Apply (Apply (Apply (.@#@$) (Apply ListdropWhileSym0 p)) ToListSym0) a_6989586621681120587 

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

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

Equations

Span p a_6989586621681120578 = Apply (Apply (Apply (.@#@$) (Apply ListspanSym0 p)) ToListSym0) a_6989586621681120578 

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

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

Equations

Break p a_6989586621681120569 = Apply (Apply SpanSym0 (Apply (Apply (.@#@$) NotSym0) p)) a_6989586621681120569 

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

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

Equations

Filter p a_6989586621681120560 = Apply (Apply (Apply (.@#@$) (Apply ListfilterSym0 p)) ToListSym0) a_6989586621681120560 

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

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

Equations

Partition p a_6989586621681120551 = Apply (Apply (Apply (.@#@$) (Apply ListpartitionSym0 p)) ToListSym0) a_6989586621681120551 

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

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

Equations

Group a_6989586621681120545 = Apply (Apply GroupBySym0 (==@#@$)) a_6989586621681120545 

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

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

Equations

GroupBy eq0 a_6989586621681120511 = Apply (Apply (Let6989586621681120520GoSym2 eq0 a_6989586621681120511) eq0) a_6989586621681120511 

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

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

Equations

GroupWith f a_6989586621681120502 = Apply (Apply GroupBySym0 (Apply (Apply OnSym0 (==@#@$)) f)) a_6989586621681120502 

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

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

Equations

GroupAllWith f a_6989586621681120493 = Apply (Apply (Apply (.@#@$) (Apply GroupWithSym0 f)) (Apply ListsortBySym0 (Apply (Apply OnSym0 CompareSym0) f))) a_6989586621681120493 

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

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

Equations

Group1 a_6989586621681120487 = Apply (Apply GroupBy1Sym0 (==@#@$)) a_6989586621681120487 

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

type family GroupBy1 (a :: (~>) a ((~>) a Bool)) (a :: NonEmpty a) :: NonEmpty (NonEmpty a) where ... Source #

Equations

GroupBy1 eq ('(:|) x xs) = Apply (Apply (:|@#@$) (Apply (Apply (:|@#@$) x) (Let6989586621681120469YsSym3 eq x xs))) (Apply (Apply GroupBySym0 eq) (Let6989586621681120469ZsSym3 eq x xs)) 

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

type family GroupWith1 (a :: (~>) a b) (a :: NonEmpty a) :: NonEmpty (NonEmpty a) where ... Source #

Equations

GroupWith1 f a_6989586621681120452 = Apply (Apply GroupBy1Sym0 (Apply (Apply OnSym0 (==@#@$)) f)) a_6989586621681120452 

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

type family GroupAllWith1 (a :: (~>) a b) (a :: NonEmpty a) :: NonEmpty (NonEmpty a) where ... Source #

Equations

GroupAllWith1 f a_6989586621681120443 = Apply (Apply (Apply (.@#@$) (Apply GroupWith1Sym0 f)) (Apply SortWithSym0 f)) a_6989586621681120443 

sGroupAllWith1 :: forall a b (t :: (~>) a b) (t :: NonEmpty a). SOrd b => Sing t -> Sing t -> Sing (Apply (Apply GroupAllWith1Sym0 t) t :: NonEmpty (NonEmpty a)) Source #

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

Equations

IsPrefixOf '[] _ = TrueSym0 
IsPrefixOf ('(:) y ys) ('(:|) x xs) = Apply (Apply (&&@#@$) (Apply (Apply (==@#@$) y) x)) (Apply (Apply ListisPrefixOfSym0 ys) xs) 

sIsPrefixOf :: forall a (t :: [a]) (t :: NonEmpty a). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IsPrefixOfSym0 t) t :: Bool) Source #

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

Equations

Nub a_6989586621681120364 = Apply (Apply NubBySym0 (==@#@$)) a_6989586621681120364 

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

type family NubBy (a :: (~>) a ((~>) a Bool)) (a :: NonEmpty a) :: NonEmpty a where ... Source #

Equations

NubBy eq ('(:|) a as) = Apply (Apply (:|@#@$) a) (Apply (Apply ListnubBySym0 eq) (Apply (Apply ListfilterSym0 (Apply (Apply (Apply Lambda_6989586621681120360Sym0 eq) a) as)) as)) 

sNubBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply NubBySym0 t) t :: NonEmpty a) Source #

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

Equations

arg_6989586621681119236 !! arg_6989586621681119238 = Case_6989586621681120422 arg_6989586621681119236 arg_6989586621681119238 (Apply (Apply Tuple2Sym0 arg_6989586621681119236) arg_6989586621681119238) 

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

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

Equations

Zip ('(:|) x xs) ('(:|) y ys) = Apply (Apply (:|@#@$) (Apply (Apply Tuple2Sym0 x) y)) (Apply (Apply ListzipSym0 xs) ys) 

sZip :: forall a b (t :: NonEmpty a) (t :: NonEmpty b). Sing t -> Sing t -> Sing (Apply (Apply ZipSym0 t) t :: NonEmpty (a, b)) Source #

type family ZipWith (a :: (~>) a ((~>) b c)) (a :: NonEmpty a) (a :: NonEmpty b) :: NonEmpty c where ... Source #

Equations

ZipWith f ('(:|) x xs) ('(:|) y ys) = Apply (Apply (:|@#@$) (Apply (Apply f x) y)) (Apply (Apply (Apply ListzipWithSym0 f) xs) ys) 

sZipWith :: forall a b c (t :: (~>) a ((~>) b c)) (t :: NonEmpty a) (t :: NonEmpty b). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ZipWithSym0 t) t) t :: NonEmpty c) Source #

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

Equations

Unzip ('(:|) '(a, b) asbs) = Apply (Apply Tuple2Sym0 (Apply (Apply (:|@#@$) a) (Let6989586621681120376AsSym3 a b asbs))) (Apply (Apply (:|@#@$) b) (Let6989586621681120376BsSym3 a b asbs)) 

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

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

Equations

FromList ('(:) a as) = Apply (Apply (:|@#@$) a) as 
FromList '[] = Apply ErrorSym0 "NonEmpty.fromList: empty list" 

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

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

Equations

ToList ('(:|) a as) = Apply (Apply (:@#@$) a) as 

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

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

Equations

NonEmpty_ '[] = NothingSym0 
NonEmpty_ ('(:) a as) = Apply JustSym0 (Apply (Apply (:|@#@$) a) as) 

sNonEmpty_ :: forall a (t :: [a]). Sing t -> Sing (Apply NonEmpty_Sym0 t :: Maybe (NonEmpty a)) Source #

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

Equations

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

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

Defunctionalization symbols

data (:|@#@$) :: (~>) a ((~>) [a] (NonEmpty (a :: Type))) infixr 5 Source #

Instances

Instances details
SingI ((:|@#@$) :: TyFun a ([a] ~> NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (:|@#@$) #

SuppressUnusedWarnings ((:|@#@$) :: TyFun a ([a] ~> NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply ((:|@#@$) :: TyFun a ([a] ~> NonEmpty a) -> Type) (a6989586621679041897 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply ((:|@#@$) :: TyFun a ([a] ~> NonEmpty a) -> Type) (a6989586621679041897 :: a) = (:|@#@$$) a6989586621679041897

data (:|@#@$$) (a6989586621679041897 :: a) :: (~>) [a] (NonEmpty (a :: Type)) infixr 5 Source #

Instances

Instances details
SingI d => SingI ((:|@#@$$) d :: TyFun [a] (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing ((:|@#@$$) d) #

SuppressUnusedWarnings ((:|@#@$$) a6989586621679041897 :: TyFun [a] (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply ((:|@#@$$) a6989586621679041897 :: TyFun [a] (NonEmpty a) -> Type) (a6989586621679041898 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply ((:|@#@$$) a6989586621679041897 :: TyFun [a] (NonEmpty a) -> Type) (a6989586621679041898 :: [a]) = a6989586621679041897 :| a6989586621679041898

type family (a6989586621679041897 :: a) :|@#@$$$ (a6989586621679041898 :: [a]) :: NonEmpty (a :: Type) where ... infixr 5 Source #

Equations

a6989586621679041897 :|@#@$$$ a6989586621679041898 = '(:|) a6989586621679041897 a6989586621679041898 

data MapSym0 :: (~>) ((~>) a b) ((~>) (NonEmpty a) (NonEmpty b)) Source #

Instances

Instances details
SingI (MapSym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing MapSym0 #

SuppressUnusedWarnings (MapSym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (MapSym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty b) -> Type) (a6989586621681120713 :: a ~> b) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (MapSym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty b) -> Type) (a6989586621681120713 :: a ~> b) = MapSym1 a6989586621681120713

data MapSym1 (a6989586621681120713 :: (~>) a b) :: (~>) (NonEmpty a) (NonEmpty b) Source #

Instances

Instances details
SingI d => SingI (MapSym1 d :: TyFun (NonEmpty a) (NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (MapSym1 d) #

SuppressUnusedWarnings (MapSym1 a6989586621681120713 :: TyFun (NonEmpty a) (NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (MapSym1 a6989586621681120713 :: TyFun (NonEmpty a) (NonEmpty b) -> Type) (a6989586621681120714 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (MapSym1 a6989586621681120713 :: TyFun (NonEmpty a) (NonEmpty b) -> Type) (a6989586621681120714 :: NonEmpty a) = Map a6989586621681120713 a6989586621681120714

type family MapSym2 (a6989586621681120713 :: (~>) a b) (a6989586621681120714 :: NonEmpty a) :: NonEmpty b where ... Source #

Equations

MapSym2 a6989586621681120713 a6989586621681120714 = Map a6989586621681120713 a6989586621681120714 

data IntersperseSym0 :: (~>) a ((~>) (NonEmpty a) (NonEmpty a)) Source #

Instances

Instances details
SingI (IntersperseSym0 :: TyFun a (NonEmpty a ~> NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (IntersperseSym0 :: TyFun a (NonEmpty a ~> NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (IntersperseSym0 :: TyFun a (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621681120641 :: a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (IntersperseSym0 :: TyFun a (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621681120641 :: a) = IntersperseSym1 a6989586621681120641

data IntersperseSym1 (a6989586621681120641 :: a) :: (~>) (NonEmpty a) (NonEmpty a) Source #

Instances

Instances details
SingI d => SingI (IntersperseSym1 d :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (IntersperseSym1 d) #

SuppressUnusedWarnings (IntersperseSym1 a6989586621681120641 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (IntersperseSym1 a6989586621681120641 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681120642 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (IntersperseSym1 a6989586621681120641 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681120642 :: NonEmpty a) = Intersperse a6989586621681120641 a6989586621681120642

type family IntersperseSym2 (a6989586621681120641 :: a) (a6989586621681120642 :: NonEmpty a) :: NonEmpty a where ... Source #

Equations

IntersperseSym2 a6989586621681120641 a6989586621681120642 = Intersperse a6989586621681120641 a6989586621681120642 

data ScanlSym0 :: (~>) ((~>) b ((~>) a b)) ((~>) b ((~>) [a] (NonEmpty b))) Source #

Instances

Instances details
SingI (ScanlSym0 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> NonEmpty b)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing ScanlSym0 #

SuppressUnusedWarnings (ScanlSym0 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> NonEmpty b)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ScanlSym0 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> NonEmpty b)) -> Type) (a6989586621681120683 :: b ~> (a ~> b)) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ScanlSym0 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> NonEmpty b)) -> Type) (a6989586621681120683 :: b ~> (a ~> b)) = ScanlSym1 a6989586621681120683

data ScanlSym1 (a6989586621681120683 :: (~>) b ((~>) a b)) :: (~>) b ((~>) [a] (NonEmpty b)) Source #

Instances

Instances details
SingI d => SingI (ScanlSym1 d :: TyFun b ([a] ~> NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (ScanlSym1 d) #

SuppressUnusedWarnings (ScanlSym1 a6989586621681120683 :: TyFun b ([a] ~> NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ScanlSym1 a6989586621681120683 :: TyFun b ([a] ~> NonEmpty b) -> Type) (a6989586621681120684 :: b) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ScanlSym1 a6989586621681120683 :: TyFun b ([a] ~> NonEmpty b) -> Type) (a6989586621681120684 :: b) = ScanlSym2 a6989586621681120683 a6989586621681120684

data ScanlSym2 (a6989586621681120683 :: (~>) b ((~>) a b)) (a6989586621681120684 :: b) :: (~>) [a] (NonEmpty b) Source #

Instances

Instances details
(SingI d1, SingI d2) => SingI (ScanlSym2 d1 d2 :: TyFun [a] (NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (ScanlSym2 d1 d2) #

SuppressUnusedWarnings (ScanlSym2 a6989586621681120683 a6989586621681120684 :: TyFun [a] (NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ScanlSym2 a6989586621681120683 a6989586621681120684 :: TyFun [a] (NonEmpty b) -> Type) (a6989586621681120685 :: [a]) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ScanlSym2 a6989586621681120683 a6989586621681120684 :: TyFun [a] (NonEmpty b) -> Type) (a6989586621681120685 :: [a]) = Scanl a6989586621681120683 a6989586621681120684 a6989586621681120685

type family ScanlSym3 (a6989586621681120683 :: (~>) b ((~>) a b)) (a6989586621681120684 :: b) (a6989586621681120685 :: [a]) :: NonEmpty b where ... Source #

Equations

ScanlSym3 a6989586621681120683 a6989586621681120684 a6989586621681120685 = Scanl a6989586621681120683 a6989586621681120684 a6989586621681120685 

data ScanrSym0 :: (~>) ((~>) a ((~>) b b)) ((~>) b ((~>) [a] (NonEmpty b))) Source #

Instances

Instances details
SingI (ScanrSym0 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> NonEmpty b)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing ScanrSym0 #

SuppressUnusedWarnings (ScanrSym0 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> NonEmpty b)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ScanrSym0 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> NonEmpty b)) -> Type) (a6989586621681120671 :: a ~> (b ~> b)) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ScanrSym0 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> NonEmpty b)) -> Type) (a6989586621681120671 :: a ~> (b ~> b)) = ScanrSym1 a6989586621681120671

data ScanrSym1 (a6989586621681120671 :: (~>) a ((~>) b b)) :: (~>) b ((~>) [a] (NonEmpty b)) Source #

Instances

Instances details
SingI d => SingI (ScanrSym1 d :: TyFun b ([a] ~> NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (ScanrSym1 d) #

SuppressUnusedWarnings (ScanrSym1 a6989586621681120671 :: TyFun b ([a] ~> NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ScanrSym1 a6989586621681120671 :: TyFun b ([a] ~> NonEmpty b) -> Type) (a6989586621681120672 :: b) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ScanrSym1 a6989586621681120671 :: TyFun b ([a] ~> NonEmpty b) -> Type) (a6989586621681120672 :: b) = ScanrSym2 a6989586621681120671 a6989586621681120672

data ScanrSym2 (a6989586621681120671 :: (~>) a ((~>) b b)) (a6989586621681120672 :: b) :: (~>) [a] (NonEmpty b) Source #

Instances

Instances details
(SingI d1, SingI d2) => SingI (ScanrSym2 d1 d2 :: TyFun [a] (NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (ScanrSym2 d1 d2) #

SuppressUnusedWarnings (ScanrSym2 a6989586621681120671 a6989586621681120672 :: TyFun [a] (NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ScanrSym2 a6989586621681120671 a6989586621681120672 :: TyFun [a] (NonEmpty b) -> Type) (a6989586621681120673 :: [a]) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ScanrSym2 a6989586621681120671 a6989586621681120672 :: TyFun [a] (NonEmpty b) -> Type) (a6989586621681120673 :: [a]) = Scanr a6989586621681120671 a6989586621681120672 a6989586621681120673

type family ScanrSym3 (a6989586621681120671 :: (~>) a ((~>) b b)) (a6989586621681120672 :: b) (a6989586621681120673 :: [a]) :: NonEmpty b where ... Source #

Equations

ScanrSym3 a6989586621681120671 a6989586621681120672 a6989586621681120673 = Scanr a6989586621681120671 a6989586621681120672 a6989586621681120673 

data Scanl1Sym0 :: (~>) ((~>) a ((~>) a a)) ((~>) (NonEmpty a) (NonEmpty a)) Source #

Instances

Instances details
SingI (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) (NonEmpty a ~> NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing Scanl1Sym0 #

SuppressUnusedWarnings (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) (NonEmpty a ~> NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621681120660 :: a ~> (a ~> a)) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621681120660 :: a ~> (a ~> a)) = Scanl1Sym1 a6989586621681120660

data Scanl1Sym1 (a6989586621681120660 :: (~>) a ((~>) a a)) :: (~>) (NonEmpty a) (NonEmpty a) Source #

Instances

Instances details
SingI d => SingI (Scanl1Sym1 d :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (Scanl1Sym1 d) #

SuppressUnusedWarnings (Scanl1Sym1 a6989586621681120660 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (Scanl1Sym1 a6989586621681120660 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681120661 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (Scanl1Sym1 a6989586621681120660 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681120661 :: NonEmpty a) = Scanl1 a6989586621681120660 a6989586621681120661

type family Scanl1Sym2 (a6989586621681120660 :: (~>) a ((~>) a a)) (a6989586621681120661 :: NonEmpty a) :: NonEmpty a where ... Source #

Equations

Scanl1Sym2 a6989586621681120660 a6989586621681120661 = Scanl1 a6989586621681120660 a6989586621681120661 

data Scanr1Sym0 :: (~>) ((~>) a ((~>) a a)) ((~>) (NonEmpty a) (NonEmpty a)) Source #

Instances

Instances details
SingI (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) (NonEmpty a ~> NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing Scanr1Sym0 #

SuppressUnusedWarnings (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) (NonEmpty a ~> NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621681120652 :: a ~> (a ~> a)) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621681120652 :: a ~> (a ~> a)) = Scanr1Sym1 a6989586621681120652

data Scanr1Sym1 (a6989586621681120652 :: (~>) a ((~>) a a)) :: (~>) (NonEmpty a) (NonEmpty a) Source #

Instances

Instances details
SingI d => SingI (Scanr1Sym1 d :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (Scanr1Sym1 d) #

SuppressUnusedWarnings (Scanr1Sym1 a6989586621681120652 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (Scanr1Sym1 a6989586621681120652 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681120653 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (Scanr1Sym1 a6989586621681120652 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681120653 :: NonEmpty a) = Scanr1 a6989586621681120652 a6989586621681120653

type family Scanr1Sym2 (a6989586621681120652 :: (~>) a ((~>) a a)) (a6989586621681120653 :: NonEmpty a) :: NonEmpty a where ... Source #

Equations

Scanr1Sym2 a6989586621681120652 a6989586621681120653 = Scanr1 a6989586621681120652 a6989586621681120653 

data TransposeSym0 :: (~>) (NonEmpty (NonEmpty a)) (NonEmpty (NonEmpty a)) Source #

Instances

Instances details
SingI (TransposeSym0 :: TyFun (NonEmpty (NonEmpty a)) (NonEmpty (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (TransposeSym0 :: TyFun (NonEmpty (NonEmpty a)) (NonEmpty (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (TransposeSym0 :: TyFun (NonEmpty (NonEmpty a)) (NonEmpty (NonEmpty a)) -> Type) (a6989586621681120350 :: NonEmpty (NonEmpty a)) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (TransposeSym0 :: TyFun (NonEmpty (NonEmpty a)) (NonEmpty (NonEmpty a)) -> Type) (a6989586621681120350 :: NonEmpty (NonEmpty a)) = Transpose a6989586621681120350

type family TransposeSym1 (a6989586621681120350 :: NonEmpty (NonEmpty a)) :: NonEmpty (NonEmpty a) where ... Source #

Equations

TransposeSym1 a6989586621681120350 = Transpose a6989586621681120350 

data SortBySym0 :: (~>) ((~>) a ((~>) a Ordering)) ((~>) (NonEmpty a) (NonEmpty a)) Source #

Instances

Instances details
SingI (SortBySym0 :: TyFun (a ~> (a ~> Ordering)) (NonEmpty a ~> NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing SortBySym0 #

SuppressUnusedWarnings (SortBySym0 :: TyFun (a ~> (a ~> Ordering)) (NonEmpty a ~> NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (SortBySym0 :: TyFun (a ~> (a ~> Ordering)) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621681120342 :: a ~> (a ~> Ordering)) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (SortBySym0 :: TyFun (a ~> (a ~> Ordering)) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621681120342 :: a ~> (a ~> Ordering)) = SortBySym1 a6989586621681120342

data SortBySym1 (a6989586621681120342 :: (~>) a ((~>) a Ordering)) :: (~>) (NonEmpty a) (NonEmpty a) Source #

Instances

Instances details
SingI d => SingI (SortBySym1 d :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (SortBySym1 d) #

SuppressUnusedWarnings (SortBySym1 a6989586621681120342 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (SortBySym1 a6989586621681120342 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681120343 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (SortBySym1 a6989586621681120342 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681120343 :: NonEmpty a) = SortBy a6989586621681120342 a6989586621681120343

type family SortBySym2 (a6989586621681120342 :: (~>) a ((~>) a Ordering)) (a6989586621681120343 :: NonEmpty a) :: NonEmpty a where ... Source #

Equations

SortBySym2 a6989586621681120342 a6989586621681120343 = SortBy a6989586621681120342 a6989586621681120343 

data SortWithSym0 :: (~>) ((~>) a o) ((~>) (NonEmpty a) (NonEmpty a)) Source #

Instances

Instances details
SOrd o => SingI (SortWithSym0 :: TyFun (a ~> o) (NonEmpty a ~> NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (SortWithSym0 :: TyFun (a ~> o) (NonEmpty a ~> NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (SortWithSym0 :: TyFun (a ~> o) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621681120333 :: a ~> o) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (SortWithSym0 :: TyFun (a ~> o) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621681120333 :: a ~> o) = SortWithSym1 a6989586621681120333

data SortWithSym1 (a6989586621681120333 :: (~>) a o) :: (~>) (NonEmpty a) (NonEmpty a) Source #

Instances

Instances details
(SOrd o, SingI d) => SingI (SortWithSym1 d :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (SortWithSym1 d) #

SuppressUnusedWarnings (SortWithSym1 a6989586621681120333 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (SortWithSym1 a6989586621681120333 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681120334 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (SortWithSym1 a6989586621681120333 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681120334 :: NonEmpty a) = SortWith a6989586621681120333 a6989586621681120334

type family SortWithSym2 (a6989586621681120333 :: (~>) a o) (a6989586621681120334 :: NonEmpty a) :: NonEmpty a where ... Source #

Equations

SortWithSym2 a6989586621681120333 a6989586621681120334 = SortWith a6989586621681120333 a6989586621681120334 

data LengthSym0 :: (~>) (NonEmpty a) Nat Source #

Instances

Instances details
SingI (LengthSym0 :: TyFun (NonEmpty a) Nat -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing LengthSym0 #

SuppressUnusedWarnings (LengthSym0 :: TyFun (NonEmpty a) Nat -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (LengthSym0 :: TyFun (NonEmpty a) Nat -> Type) (a6989586621681120843 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (LengthSym0 :: TyFun (NonEmpty a) Nat -> Type) (a6989586621681120843 :: NonEmpty a) = Length a6989586621681120843

type family LengthSym1 (a6989586621681120843 :: NonEmpty a) :: Nat where ... Source #

Equations

LengthSym1 a6989586621681120843 = Length a6989586621681120843 

data HeadSym0 :: (~>) (NonEmpty a) a Source #

Instances

Instances details
SingI (HeadSym0 :: TyFun (NonEmpty a) a -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing HeadSym0 #

SuppressUnusedWarnings (HeadSym0 :: TyFun (NonEmpty a) a -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (HeadSym0 :: TyFun (NonEmpty a) a -> Type) (a6989586621681120778 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (HeadSym0 :: TyFun (NonEmpty a) a -> Type) (a6989586621681120778 :: NonEmpty a) = Head a6989586621681120778

type family HeadSym1 (a6989586621681120778 :: NonEmpty a) :: a where ... Source #

Equations

HeadSym1 a6989586621681120778 = Head a6989586621681120778 

data TailSym0 :: (~>) (NonEmpty a) [a] Source #

Instances

Instances details
SingI (TailSym0 :: TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing TailSym0 #

SuppressUnusedWarnings (TailSym0 :: TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (TailSym0 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681120774 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (TailSym0 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681120774 :: NonEmpty a) = Tail a6989586621681120774

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

Equations

TailSym1 a6989586621681120774 = Tail a6989586621681120774 

data LastSym0 :: (~>) (NonEmpty a) a Source #

Instances

Instances details
SingI (LastSym0 :: TyFun (NonEmpty a) a -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing LastSym0 #

SuppressUnusedWarnings (LastSym0 :: TyFun (NonEmpty a) a -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (LastSym0 :: TyFun (NonEmpty a) a -> Type) (a6989586621681120769 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (LastSym0 :: TyFun (NonEmpty a) a -> Type) (a6989586621681120769 :: NonEmpty a) = Last a6989586621681120769

type family LastSym1 (a6989586621681120769 :: NonEmpty a) :: a where ... Source #

Equations

LastSym1 a6989586621681120769 = Last a6989586621681120769 

data InitSym0 :: (~>) (NonEmpty a) [a] Source #

Instances

Instances details
SingI (InitSym0 :: TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing InitSym0 #

SuppressUnusedWarnings (InitSym0 :: TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (InitSym0 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681120764 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (InitSym0 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681120764 :: NonEmpty a) = Init a6989586621681120764

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

Equations

InitSym1 a6989586621681120764 = Init a6989586621681120764 

data (<|@#@$) :: (~>) a ((~>) (NonEmpty a) (NonEmpty a)) Source #

Instances

Instances details
SingI ((<|@#@$) :: TyFun a (NonEmpty a ~> NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (<|@#@$) #

SuppressUnusedWarnings ((<|@#@$) :: TyFun a (NonEmpty a ~> NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply ((<|@#@$) :: TyFun a (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621681120757 :: a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply ((<|@#@$) :: TyFun a (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621681120757 :: a) = (<|@#@$$) a6989586621681120757

data (<|@#@$$) (a6989586621681120757 :: a) :: (~>) (NonEmpty a) (NonEmpty a) Source #

Instances

Instances details
SingI d => SingI ((<|@#@$$) d :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing ((<|@#@$$) d) #

SuppressUnusedWarnings ((<|@#@$$) a6989586621681120757 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply ((<|@#@$$) a6989586621681120757 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681120758 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply ((<|@#@$$) a6989586621681120757 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681120758 :: NonEmpty a) = a6989586621681120757 <| a6989586621681120758

type family (a6989586621681120757 :: a) <|@#@$$$ (a6989586621681120758 :: NonEmpty a) :: NonEmpty a where ... Source #

Equations

a6989586621681120757 <|@#@$$$ a6989586621681120758 = (<|) a6989586621681120757 a6989586621681120758 

data ConsSym0 :: (~>) a ((~>) (NonEmpty a) (NonEmpty a)) Source #

Instances

Instances details
SingI (ConsSym0 :: TyFun a (NonEmpty a ~> NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing ConsSym0 #

SuppressUnusedWarnings (ConsSym0 :: TyFun a (NonEmpty a ~> NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ConsSym0 :: TyFun a (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621681120750 :: a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ConsSym0 :: TyFun a (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621681120750 :: a) = ConsSym1 a6989586621681120750

data ConsSym1 (a6989586621681120750 :: a) :: (~>) (NonEmpty a) (NonEmpty a) Source #

Instances

Instances details
SingI d => SingI (ConsSym1 d :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (ConsSym1 d) #

SuppressUnusedWarnings (ConsSym1 a6989586621681120750 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ConsSym1 a6989586621681120750 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681120751 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ConsSym1 a6989586621681120750 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681120751 :: NonEmpty a) = Cons a6989586621681120750 a6989586621681120751

type family ConsSym2 (a6989586621681120750 :: a) (a6989586621681120751 :: NonEmpty a) :: NonEmpty a where ... Source #

Equations

ConsSym2 a6989586621681120750 a6989586621681120751 = Cons a6989586621681120750 a6989586621681120751 

data UnconsSym0 :: (~>) (NonEmpty a) (a, Maybe (NonEmpty a)) Source #

Instances

Instances details
SingI (UnconsSym0 :: TyFun (NonEmpty a) (a, Maybe (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing UnconsSym0 #

SuppressUnusedWarnings (UnconsSym0 :: TyFun (NonEmpty a) (a, Maybe (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (UnconsSym0 :: TyFun (NonEmpty a) (a, Maybe (NonEmpty a)) -> Type) (a6989586621681120807 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (UnconsSym0 :: TyFun (NonEmpty a) (a, Maybe (NonEmpty a)) -> Type) (a6989586621681120807 :: NonEmpty a) = Uncons a6989586621681120807

type family UnconsSym1 (a6989586621681120807 :: NonEmpty a) :: (a, Maybe (NonEmpty a)) where ... Source #

Equations

UnconsSym1 a6989586621681120807 = Uncons a6989586621681120807 

data UnfoldrSym0 :: (~>) ((~>) a (b, Maybe a)) ((~>) a (NonEmpty b)) Source #

Instances

Instances details
SingI (UnfoldrSym0 :: TyFun (a ~> (b, Maybe a)) (a ~> NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (UnfoldrSym0 :: TyFun (a ~> (b, Maybe a)) (a ~> NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (UnfoldrSym0 :: TyFun (a ~> (b, Maybe a)) (a ~> NonEmpty b) -> Type) (a6989586621681120783 :: a ~> (b, Maybe a)) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (UnfoldrSym0 :: TyFun (a ~> (b, Maybe a)) (a ~> NonEmpty b) -> Type) (a6989586621681120783 :: a ~> (b, Maybe a)) = UnfoldrSym1 a6989586621681120783

data UnfoldrSym1 (a6989586621681120783 :: (~>) a (b, Maybe a)) :: (~>) a (NonEmpty b) Source #

Instances

Instances details
SingI d => SingI (UnfoldrSym1 d :: TyFun a (NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (UnfoldrSym1 d) #

SuppressUnusedWarnings (UnfoldrSym1 a6989586621681120783 :: TyFun a (NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (UnfoldrSym1 a6989586621681120783 :: TyFun a (NonEmpty b) -> Type) (a6989586621681120784 :: a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (UnfoldrSym1 a6989586621681120783 :: TyFun a (NonEmpty b) -> Type) (a6989586621681120784 :: a) = Unfoldr a6989586621681120783 a6989586621681120784

type family UnfoldrSym2 (a6989586621681120783 :: (~>) a (b, Maybe a)) (a6989586621681120784 :: a) :: NonEmpty b where ... Source #

Equations

UnfoldrSym2 a6989586621681120783 a6989586621681120784 = Unfoldr a6989586621681120783 a6989586621681120784 

data SortSym0 :: (~>) (NonEmpty a) (NonEmpty a) Source #

Instances

Instances details
SOrd a => SingI (SortSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing SortSym0 #

SuppressUnusedWarnings (SortSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (SortSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681120741 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (SortSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681120741 :: NonEmpty a) = Sort a6989586621681120741

type family SortSym1 (a6989586621681120741 :: NonEmpty a) :: NonEmpty a where ... Source #

Equations

SortSym1 a6989586621681120741 = Sort a6989586621681120741 

data ReverseSym0 :: (~>) (NonEmpty a) (NonEmpty a) Source #

Instances

Instances details
SingI (ReverseSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (ReverseSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ReverseSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681120636 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ReverseSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681120636 :: NonEmpty a) = Reverse a6989586621681120636

type family ReverseSym1 (a6989586621681120636 :: NonEmpty a) :: NonEmpty a where ... Source #

Equations

ReverseSym1 a6989586621681120636 = Reverse a6989586621681120636 

data InitsSym0 :: (~>) [a] (NonEmpty [a]) Source #

Instances

Instances details
SingI (InitsSym0 :: TyFun [a] (NonEmpty [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing InitsSym0 #

SuppressUnusedWarnings (InitsSym0 :: TyFun [a] (NonEmpty [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (InitsSym0 :: TyFun [a] (NonEmpty [a]) -> Type) (a6989586621681120708 :: [a]) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (InitsSym0 :: TyFun [a] (NonEmpty [a]) -> Type) (a6989586621681120708 :: [a]) = Inits a6989586621681120708

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

Equations

InitsSym1 a6989586621681120708 = Inits a6989586621681120708 

data TailsSym0 :: (~>) [a] (NonEmpty [a]) Source #

Instances

Instances details
SingI (TailsSym0 :: TyFun [a] (NonEmpty [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing TailsSym0 #

SuppressUnusedWarnings (TailsSym0 :: TyFun [a] (NonEmpty [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (TailsSym0 :: TyFun [a] (NonEmpty [a]) -> Type) (a6989586621681120702 :: [a]) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (TailsSym0 :: TyFun [a] (NonEmpty [a]) -> Type) (a6989586621681120702 :: [a]) = Tails a6989586621681120702

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

Equations

TailsSym1 a6989586621681120702 = Tails a6989586621681120702 

data UnfoldSym0 :: (~>) ((~>) a (b, Maybe a)) ((~>) a (NonEmpty b)) Source #

Instances

Instances details
SingI (UnfoldSym0 :: TyFun (a ~> (b, Maybe a)) (a ~> NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing UnfoldSym0 #

SuppressUnusedWarnings (UnfoldSym0 :: TyFun (a ~> (b, Maybe a)) (a ~> NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (UnfoldSym0 :: TyFun (a ~> (b, Maybe a)) (a ~> NonEmpty b) -> Type) (a6989586621681120818 :: a ~> (b, Maybe a)) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (UnfoldSym0 :: TyFun (a ~> (b, Maybe a)) (a ~> NonEmpty b) -> Type) (a6989586621681120818 :: a ~> (b, Maybe a)) = UnfoldSym1 a6989586621681120818

data UnfoldSym1 (a6989586621681120818 :: (~>) a (b, Maybe a)) :: (~>) a (NonEmpty b) Source #

Instances

Instances details
SingI d => SingI (UnfoldSym1 d :: TyFun a (NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (UnfoldSym1 d) #

SuppressUnusedWarnings (UnfoldSym1 a6989586621681120818 :: TyFun a (NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (UnfoldSym1 a6989586621681120818 :: TyFun a (NonEmpty b) -> Type) (a6989586621681120819 :: a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (UnfoldSym1 a6989586621681120818 :: TyFun a (NonEmpty b) -> Type) (a6989586621681120819 :: a) = Unfold a6989586621681120818 a6989586621681120819

data InsertSym0 :: (~>) a ((~>) [a] (NonEmpty a)) Source #

Instances

Instances details
SOrd a => SingI (InsertSym0 :: TyFun a ([a] ~> NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing InsertSym0 #

SuppressUnusedWarnings (InsertSym0 :: TyFun a ([a] ~> NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (InsertSym0 :: TyFun a ([a] ~> NonEmpty a) -> Type) (a6989586621681120694 :: a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (InsertSym0 :: TyFun a ([a] ~> NonEmpty a) -> Type) (a6989586621681120694 :: a) = InsertSym1 a6989586621681120694

data InsertSym1 (a6989586621681120694 :: a) :: (~>) [a] (NonEmpty a) Source #

Instances

Instances details
(SOrd a, SingI d) => SingI (InsertSym1 d :: TyFun [a] (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (InsertSym1 d) #

SuppressUnusedWarnings (InsertSym1 a6989586621681120694 :: TyFun [a] (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (InsertSym1 a6989586621681120694 :: TyFun [a] (NonEmpty a) -> Type) (a6989586621681120695 :: [a]) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (InsertSym1 a6989586621681120694 :: TyFun [a] (NonEmpty a) -> Type) (a6989586621681120695 :: [a]) = Insert a6989586621681120694 a6989586621681120695

type family InsertSym2 (a6989586621681120694 :: a) (a6989586621681120695 :: [a]) :: NonEmpty a where ... Source #

Equations

InsertSym2 a6989586621681120694 a6989586621681120695 = Insert a6989586621681120694 a6989586621681120695 

data TakeSym0 :: (~>) Nat ((~>) (NonEmpty a) [a]) Source #

Instances

Instances details
SingI (TakeSym0 :: TyFun Nat (NonEmpty a ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing TakeSym0 #

SuppressUnusedWarnings (TakeSym0 :: TyFun Nat (NonEmpty a ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (TakeSym0 :: TyFun Nat (NonEmpty a ~> [a]) -> Type) (a6989586621681120628 :: Nat) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (TakeSym0 :: TyFun Nat (NonEmpty a ~> [a]) -> Type) (a6989586621681120628 :: Nat) = TakeSym1 a6989586621681120628 :: TyFun (NonEmpty a) [a] -> Type

data TakeSym1 (a6989586621681120628 :: Nat) :: (~>) (NonEmpty a) [a] Source #

Instances

Instances details
SingI d => SingI (TakeSym1 d :: TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (TakeSym1 d) #

SuppressUnusedWarnings (TakeSym1 a6989586621681120628 :: TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (TakeSym1 a6989586621681120628 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681120629 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (TakeSym1 a6989586621681120628 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681120629 :: NonEmpty a) = Take a6989586621681120628 a6989586621681120629

type family TakeSym2 (a6989586621681120628 :: Nat) (a6989586621681120629 :: NonEmpty a) :: [a] where ... Source #

Equations

TakeSym2 a6989586621681120628 a6989586621681120629 = Take a6989586621681120628 a6989586621681120629 

data DropSym0 :: (~>) Nat ((~>) (NonEmpty a) [a]) Source #

Instances

Instances details
SingI (DropSym0 :: TyFun Nat (NonEmpty a ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing DropSym0 #

SuppressUnusedWarnings (DropSym0 :: TyFun Nat (NonEmpty a ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (DropSym0 :: TyFun Nat (NonEmpty a ~> [a]) -> Type) (a6989586621681120619 :: Nat) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (DropSym0 :: TyFun Nat (NonEmpty a ~> [a]) -> Type) (a6989586621681120619 :: Nat) = DropSym1 a6989586621681120619 :: TyFun (NonEmpty a) [a] -> Type

data DropSym1 (a6989586621681120619 :: Nat) :: (~>) (NonEmpty a) [a] Source #

Instances

Instances details
SingI d => SingI (DropSym1 d :: TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (DropSym1 d) #

SuppressUnusedWarnings (DropSym1 a6989586621681120619 :: TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (DropSym1 a6989586621681120619 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681120620 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (DropSym1 a6989586621681120619 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681120620 :: NonEmpty a) = Drop a6989586621681120619 a6989586621681120620

type family DropSym2 (a6989586621681120619 :: Nat) (a6989586621681120620 :: NonEmpty a) :: [a] where ... Source #

Equations

DropSym2 a6989586621681120619 a6989586621681120620 = Drop a6989586621681120619 a6989586621681120620 

data SplitAtSym0 :: (~>) Nat ((~>) (NonEmpty a) ([a], [a])) Source #

Instances

Instances details
SingI (SplitAtSym0 :: TyFun Nat (NonEmpty a ~> ([a], [a])) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (SplitAtSym0 :: TyFun Nat (NonEmpty a ~> ([a], [a])) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (SplitAtSym0 :: TyFun Nat (NonEmpty a ~> ([a], [a])) -> Type) (a6989586621681120610 :: Nat) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (SplitAtSym0 :: TyFun Nat (NonEmpty a ~> ([a], [a])) -> Type) (a6989586621681120610 :: Nat) = SplitAtSym1 a6989586621681120610 :: TyFun (NonEmpty a) ([a], [a]) -> Type

data SplitAtSym1 (a6989586621681120610 :: Nat) :: (~>) (NonEmpty a) ([a], [a]) Source #

Instances

Instances details
SingI d => SingI (SplitAtSym1 d :: TyFun (NonEmpty a) ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (SplitAtSym1 d) #

SuppressUnusedWarnings (SplitAtSym1 a6989586621681120610 :: TyFun (NonEmpty a) ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (SplitAtSym1 a6989586621681120610 :: TyFun (NonEmpty a) ([a], [a]) -> Type) (a6989586621681120611 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (SplitAtSym1 a6989586621681120610 :: TyFun (NonEmpty a) ([a], [a]) -> Type) (a6989586621681120611 :: NonEmpty a) = SplitAt a6989586621681120610 a6989586621681120611

type family SplitAtSym2 (a6989586621681120610 :: Nat) (a6989586621681120611 :: NonEmpty a) :: ([a], [a]) where ... Source #

Equations

SplitAtSym2 a6989586621681120610 a6989586621681120611 = SplitAt a6989586621681120610 a6989586621681120611 

data TakeWhileSym0 :: (~>) ((~>) a Bool) ((~>) (NonEmpty a) [a]) Source #

Instances

Instances details
SingI (TakeWhileSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (TakeWhileSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (TakeWhileSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) (a6989586621681120601 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (TakeWhileSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) (a6989586621681120601 :: a ~> Bool) = TakeWhileSym1 a6989586621681120601

data TakeWhileSym1 (a6989586621681120601 :: (~>) a Bool) :: (~>) (NonEmpty a) [a] Source #

Instances

Instances details
SingI d => SingI (TakeWhileSym1 d :: TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (TakeWhileSym1 d) #

SuppressUnusedWarnings (TakeWhileSym1 a6989586621681120601 :: TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (TakeWhileSym1 a6989586621681120601 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681120602 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (TakeWhileSym1 a6989586621681120601 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681120602 :: NonEmpty a) = TakeWhile a6989586621681120601 a6989586621681120602

type family TakeWhileSym2 (a6989586621681120601 :: (~>) a Bool) (a6989586621681120602 :: NonEmpty a) :: [a] where ... Source #

Equations

TakeWhileSym2 a6989586621681120601 a6989586621681120602 = TakeWhile a6989586621681120601 a6989586621681120602 

data DropWhileSym0 :: (~>) ((~>) a Bool) ((~>) (NonEmpty a) [a]) Source #

Instances

Instances details
SingI (DropWhileSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (DropWhileSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (DropWhileSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) (a6989586621681120592 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (DropWhileSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) (a6989586621681120592 :: a ~> Bool) = DropWhileSym1 a6989586621681120592

data DropWhileSym1 (a6989586621681120592 :: (~>) a Bool) :: (~>) (NonEmpty a) [a] Source #

Instances

Instances details
SingI d => SingI (DropWhileSym1 d :: TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (DropWhileSym1 d) #

SuppressUnusedWarnings (DropWhileSym1 a6989586621681120592 :: TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (DropWhileSym1 a6989586621681120592 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681120593 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (DropWhileSym1 a6989586621681120592 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681120593 :: NonEmpty a) = DropWhile a6989586621681120592 a6989586621681120593

type family DropWhileSym2 (a6989586621681120592 :: (~>) a Bool) (a6989586621681120593 :: NonEmpty a) :: [a] where ... Source #

Equations

DropWhileSym2 a6989586621681120592 a6989586621681120593 = DropWhile a6989586621681120592 a6989586621681120593 

data SpanSym0 :: (~>) ((~>) a Bool) ((~>) (NonEmpty a) ([a], [a])) Source #

Instances

Instances details
SingI (SpanSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing SpanSym0 #

SuppressUnusedWarnings (SpanSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (SpanSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) (a6989586621681120583 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (SpanSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) (a6989586621681120583 :: a ~> Bool) = SpanSym1 a6989586621681120583

data SpanSym1 (a6989586621681120583 :: (~>) a Bool) :: (~>) (NonEmpty a) ([a], [a]) Source #

Instances

Instances details
SingI d => SingI (SpanSym1 d :: TyFun (NonEmpty a) ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (SpanSym1 d) #

SuppressUnusedWarnings (SpanSym1 a6989586621681120583 :: TyFun (NonEmpty a) ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (SpanSym1 a6989586621681120583 :: TyFun (NonEmpty a) ([a], [a]) -> Type) (a6989586621681120584 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (SpanSym1 a6989586621681120583 :: TyFun (NonEmpty a) ([a], [a]) -> Type) (a6989586621681120584 :: NonEmpty a) = Span a6989586621681120583 a6989586621681120584

type family SpanSym2 (a6989586621681120583 :: (~>) a Bool) (a6989586621681120584 :: NonEmpty a) :: ([a], [a]) where ... Source #

Equations

SpanSym2 a6989586621681120583 a6989586621681120584 = Span a6989586621681120583 a6989586621681120584 

data BreakSym0 :: (~>) ((~>) a Bool) ((~>) (NonEmpty a) ([a], [a])) Source #

Instances

Instances details
SingI (BreakSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing BreakSym0 #

SuppressUnusedWarnings (BreakSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (BreakSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) (a6989586621681120574 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (BreakSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) (a6989586621681120574 :: a ~> Bool) = BreakSym1 a6989586621681120574

data BreakSym1 (a6989586621681120574 :: (~>) a Bool) :: (~>) (NonEmpty a) ([a], [a]) Source #

Instances

Instances details
SingI d => SingI (BreakSym1 d :: TyFun (NonEmpty a) ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (BreakSym1 d) #

SuppressUnusedWarnings (BreakSym1 a6989586621681120574 :: TyFun (NonEmpty a) ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (BreakSym1 a6989586621681120574 :: TyFun (NonEmpty a) ([a], [a]) -> Type) (a6989586621681120575 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (BreakSym1 a6989586621681120574 :: TyFun (NonEmpty a) ([a], [a]) -> Type) (a6989586621681120575 :: NonEmpty a) = Break a6989586621681120574 a6989586621681120575

type family BreakSym2 (a6989586621681120574 :: (~>) a Bool) (a6989586621681120575 :: NonEmpty a) :: ([a], [a]) where ... Source #

Equations

BreakSym2 a6989586621681120574 a6989586621681120575 = Break a6989586621681120574 a6989586621681120575 

data FilterSym0 :: (~>) ((~>) a Bool) ((~>) (NonEmpty a) [a]) Source #

Instances

Instances details
SingI (FilterSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing FilterSym0 #

SuppressUnusedWarnings (FilterSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (FilterSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) (a6989586621681120565 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (FilterSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) (a6989586621681120565 :: a ~> Bool) = FilterSym1 a6989586621681120565

data FilterSym1 (a6989586621681120565 :: (~>) a Bool) :: (~>) (NonEmpty a) [a] Source #

Instances

Instances details
SingI d => SingI (FilterSym1 d :: TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (FilterSym1 d) #

SuppressUnusedWarnings (FilterSym1 a6989586621681120565 :: TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (FilterSym1 a6989586621681120565 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681120566 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (FilterSym1 a6989586621681120565 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681120566 :: NonEmpty a) = Filter a6989586621681120565 a6989586621681120566

type family FilterSym2 (a6989586621681120565 :: (~>) a Bool) (a6989586621681120566 :: NonEmpty a) :: [a] where ... Source #

Equations

FilterSym2 a6989586621681120565 a6989586621681120566 = Filter a6989586621681120565 a6989586621681120566 

data PartitionSym0 :: (~>) ((~>) a Bool) ((~>) (NonEmpty a) ([a], [a])) Source #

Instances

Instances details
SingI (PartitionSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (PartitionSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (PartitionSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) (a6989586621681120556 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (PartitionSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) (a6989586621681120556 :: a ~> Bool) = PartitionSym1 a6989586621681120556

data PartitionSym1 (a6989586621681120556 :: (~>) a Bool) :: (~>) (NonEmpty a) ([a], [a]) Source #

Instances

Instances details
SingI d => SingI (PartitionSym1 d :: TyFun (NonEmpty a) ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (PartitionSym1 d) #

SuppressUnusedWarnings (PartitionSym1 a6989586621681120556 :: TyFun (NonEmpty a) ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (PartitionSym1 a6989586621681120556 :: TyFun (NonEmpty a) ([a], [a]) -> Type) (a6989586621681120557 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (PartitionSym1 a6989586621681120556 :: TyFun (NonEmpty a) ([a], [a]) -> Type) (a6989586621681120557 :: NonEmpty a) = Partition a6989586621681120556 a6989586621681120557

type family PartitionSym2 (a6989586621681120556 :: (~>) a Bool) (a6989586621681120557 :: NonEmpty a) :: ([a], [a]) where ... Source #

Equations

PartitionSym2 a6989586621681120556 a6989586621681120557 = Partition a6989586621681120556 a6989586621681120557 

data GroupSym0 :: (~>) [a] [NonEmpty a] Source #

Instances

Instances details
SEq a => SingI (GroupSym0 :: TyFun [a] [NonEmpty a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing GroupSym0 #

SuppressUnusedWarnings (GroupSym0 :: TyFun [a] [NonEmpty a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (GroupSym0 :: TyFun [a] [NonEmpty a] -> Type) (a6989586621681120549 :: [a]) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (GroupSym0 :: TyFun [a] [NonEmpty a] -> Type) (a6989586621681120549 :: [a]) = Group a6989586621681120549

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

Equations

GroupSym1 a6989586621681120549 = Group a6989586621681120549 

data GroupBySym0 :: (~>) ((~>) a ((~>) a Bool)) ((~>) [a] [NonEmpty a]) Source #

Instances

Instances details
SingI (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [NonEmpty a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [NonEmpty a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [NonEmpty a]) -> Type) (a6989586621681120516 :: a ~> (a ~> Bool)) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [NonEmpty a]) -> Type) (a6989586621681120516 :: a ~> (a ~> Bool)) = GroupBySym1 a6989586621681120516

data GroupBySym1 (a6989586621681120516 :: (~>) a ((~>) a Bool)) :: (~>) [a] [NonEmpty a] Source #

Instances

Instances details
SingI d => SingI (GroupBySym1 d :: TyFun [a] [NonEmpty a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (GroupBySym1 d) #

SuppressUnusedWarnings (GroupBySym1 a6989586621681120516 :: TyFun [a] [NonEmpty a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (GroupBySym1 a6989586621681120516 :: TyFun [a] [NonEmpty a] -> Type) (a6989586621681120517 :: [a]) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (GroupBySym1 a6989586621681120516 :: TyFun [a] [NonEmpty a] -> Type) (a6989586621681120517 :: [a]) = GroupBy a6989586621681120516 a6989586621681120517

type family GroupBySym2 (a6989586621681120516 :: (~>) a ((~>) a Bool)) (a6989586621681120517 :: [a]) :: [NonEmpty a] where ... Source #

Equations

GroupBySym2 a6989586621681120516 a6989586621681120517 = GroupBy a6989586621681120516 a6989586621681120517 

data GroupWithSym0 :: (~>) ((~>) a b) ((~>) [a] [NonEmpty a]) Source #

Instances

Instances details
SEq b => SingI (GroupWithSym0 :: TyFun (a ~> b) ([a] ~> [NonEmpty a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (GroupWithSym0 :: TyFun (a ~> b) ([a] ~> [NonEmpty a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (GroupWithSym0 :: TyFun (a ~> b) ([a] ~> [NonEmpty a]) -> Type) (a6989586621681120507 :: a ~> b) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (GroupWithSym0 :: TyFun (a ~> b) ([a] ~> [NonEmpty a]) -> Type) (a6989586621681120507 :: a ~> b) = GroupWithSym1 a6989586621681120507

data GroupWithSym1 (a6989586621681120507 :: (~>) a b) :: (~>) [a] [NonEmpty a] Source #

Instances

Instances details
(SEq b, SingI d) => SingI (GroupWithSym1 d :: TyFun [a] [NonEmpty a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (GroupWithSym1 d) #

SuppressUnusedWarnings (GroupWithSym1 a6989586621681120507 :: TyFun [a] [NonEmpty a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (GroupWithSym1 a6989586621681120507 :: TyFun [a] [NonEmpty a] -> Type) (a6989586621681120508 :: [a]) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (GroupWithSym1 a6989586621681120507 :: TyFun [a] [NonEmpty a] -> Type) (a6989586621681120508 :: [a]) = GroupWith a6989586621681120507 a6989586621681120508

type family GroupWithSym2 (a6989586621681120507 :: (~>) a b) (a6989586621681120508 :: [a]) :: [NonEmpty a] where ... Source #

Equations

GroupWithSym2 a6989586621681120507 a6989586621681120508 = GroupWith a6989586621681120507 a6989586621681120508 

data GroupAllWithSym0 :: (~>) ((~>) a b) ((~>) [a] [NonEmpty a]) Source #

Instances

Instances details
SOrd b => SingI (GroupAllWithSym0 :: TyFun (a ~> b) ([a] ~> [NonEmpty a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (GroupAllWithSym0 :: TyFun (a ~> b) ([a] ~> [NonEmpty a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (GroupAllWithSym0 :: TyFun (a ~> b) ([a] ~> [NonEmpty a]) -> Type) (a6989586621681120498 :: a ~> b) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (GroupAllWithSym0 :: TyFun (a ~> b) ([a] ~> [NonEmpty a]) -> Type) (a6989586621681120498 :: a ~> b) = GroupAllWithSym1 a6989586621681120498

data GroupAllWithSym1 (a6989586621681120498 :: (~>) a b) :: (~>) [a] [NonEmpty a] Source #

Instances

Instances details
(SOrd b, SingI d) => SingI (GroupAllWithSym1 d :: TyFun [a] [NonEmpty a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (GroupAllWithSym1 d) #

SuppressUnusedWarnings (GroupAllWithSym1 a6989586621681120498 :: TyFun [a] [NonEmpty a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (GroupAllWithSym1 a6989586621681120498 :: TyFun [a] [NonEmpty a] -> Type) (a6989586621681120499 :: [a]) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (GroupAllWithSym1 a6989586621681120498 :: TyFun [a] [NonEmpty a] -> Type) (a6989586621681120499 :: [a]) = GroupAllWith a6989586621681120498 a6989586621681120499

type family GroupAllWithSym2 (a6989586621681120498 :: (~>) a b) (a6989586621681120499 :: [a]) :: [NonEmpty a] where ... Source #

Equations

GroupAllWithSym2 a6989586621681120498 a6989586621681120499 = GroupAllWith a6989586621681120498 a6989586621681120499 

data Group1Sym0 :: (~>) (NonEmpty a) (NonEmpty (NonEmpty a)) Source #

Instances

Instances details
SEq a => SingI (Group1Sym0 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing Group1Sym0 #

SuppressUnusedWarnings (Group1Sym0 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (Group1Sym0 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621681120491 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (Group1Sym0 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621681120491 :: NonEmpty a) = Group1 a6989586621681120491

type family Group1Sym1 (a6989586621681120491 :: NonEmpty a) :: NonEmpty (NonEmpty a) where ... Source #

Equations

Group1Sym1 a6989586621681120491 = Group1 a6989586621681120491 

data GroupBy1Sym0 :: (~>) ((~>) a ((~>) a Bool)) ((~>) (NonEmpty a) (NonEmpty (NonEmpty a))) Source #

Instances

Instances details
SingI (GroupBy1Sym0 :: TyFun (a ~> (a ~> Bool)) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (GroupBy1Sym0 :: TyFun (a ~> (a ~> Bool)) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (GroupBy1Sym0 :: TyFun (a ~> (a ~> Bool)) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) (a6989586621681120464 :: a ~> (a ~> Bool)) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (GroupBy1Sym0 :: TyFun (a ~> (a ~> Bool)) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) (a6989586621681120464 :: a ~> (a ~> Bool)) = GroupBy1Sym1 a6989586621681120464

data GroupBy1Sym1 (a6989586621681120464 :: (~>) a ((~>) a Bool)) :: (~>) (NonEmpty a) (NonEmpty (NonEmpty a)) Source #

Instances

Instances details
SingI d => SingI (GroupBy1Sym1 d :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (GroupBy1Sym1 d) #

SuppressUnusedWarnings (GroupBy1Sym1 a6989586621681120464 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (GroupBy1Sym1 a6989586621681120464 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621681120465 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (GroupBy1Sym1 a6989586621681120464 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621681120465 :: NonEmpty a) = GroupBy1 a6989586621681120464 a6989586621681120465

type family GroupBy1Sym2 (a6989586621681120464 :: (~>) a ((~>) a Bool)) (a6989586621681120465 :: NonEmpty a) :: NonEmpty (NonEmpty a) where ... Source #

Equations

GroupBy1Sym2 a6989586621681120464 a6989586621681120465 = GroupBy1 a6989586621681120464 a6989586621681120465 

data GroupWith1Sym0 :: (~>) ((~>) a b) ((~>) (NonEmpty a) (NonEmpty (NonEmpty a))) Source #

Instances

Instances details
SEq b => SingI (GroupWith1Sym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (GroupWith1Sym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (GroupWith1Sym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) (a6989586621681120457 :: a ~> b) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (GroupWith1Sym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) (a6989586621681120457 :: a ~> b) = GroupWith1Sym1 a6989586621681120457

data GroupWith1Sym1 (a6989586621681120457 :: (~>) a b) :: (~>) (NonEmpty a) (NonEmpty (NonEmpty a)) Source #

Instances

Instances details
(SEq b, SingI d) => SingI (GroupWith1Sym1 d :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (GroupWith1Sym1 d) #

SuppressUnusedWarnings (GroupWith1Sym1 a6989586621681120457 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (GroupWith1Sym1 a6989586621681120457 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621681120458 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (GroupWith1Sym1 a6989586621681120457 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621681120458 :: NonEmpty a) = GroupWith1 a6989586621681120457 a6989586621681120458

type family GroupWith1Sym2 (a6989586621681120457 :: (~>) a b) (a6989586621681120458 :: NonEmpty a) :: NonEmpty (NonEmpty a) where ... Source #

Equations

GroupWith1Sym2 a6989586621681120457 a6989586621681120458 = GroupWith1 a6989586621681120457 a6989586621681120458 

data GroupAllWith1Sym0 :: (~>) ((~>) a b) ((~>) (NonEmpty a) (NonEmpty (NonEmpty a))) Source #

Instances

Instances details
SOrd b => SingI (GroupAllWith1Sym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (GroupAllWith1Sym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (GroupAllWith1Sym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) (a6989586621681120448 :: a ~> b) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (GroupAllWith1Sym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) (a6989586621681120448 :: a ~> b) = GroupAllWith1Sym1 a6989586621681120448

data GroupAllWith1Sym1 (a6989586621681120448 :: (~>) a b) :: (~>) (NonEmpty a) (NonEmpty (NonEmpty a)) Source #

Instances

Instances details
(SOrd b, SingI d) => SingI (GroupAllWith1Sym1 d :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (GroupAllWith1Sym1 a6989586621681120448 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (GroupAllWith1Sym1 a6989586621681120448 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621681120449 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (GroupAllWith1Sym1 a6989586621681120448 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621681120449 :: NonEmpty a) = GroupAllWith1 a6989586621681120448 a6989586621681120449

type family GroupAllWith1Sym2 (a6989586621681120448 :: (~>) a b) (a6989586621681120449 :: NonEmpty a) :: NonEmpty (NonEmpty a) where ... Source #

Equations

GroupAllWith1Sym2 a6989586621681120448 a6989586621681120449 = GroupAllWith1 a6989586621681120448 a6989586621681120449 

data IsPrefixOfSym0 :: (~>) [a] ((~>) (NonEmpty a) Bool) Source #

Instances

Instances details
SEq a => SingI (IsPrefixOfSym0 :: TyFun [a] (NonEmpty a ~> Bool) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (IsPrefixOfSym0 :: TyFun [a] (NonEmpty a ~> Bool) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (IsPrefixOfSym0 :: TyFun [a] (NonEmpty a ~> Bool) -> Type) (a6989586621681120437 :: [a]) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (IsPrefixOfSym0 :: TyFun [a] (NonEmpty a ~> Bool) -> Type) (a6989586621681120437 :: [a]) = IsPrefixOfSym1 a6989586621681120437

data IsPrefixOfSym1 (a6989586621681120437 :: [a]) :: (~>) (NonEmpty a) Bool Source #

Instances

Instances details
(SEq a, SingI d) => SingI (IsPrefixOfSym1 d :: TyFun (NonEmpty a) Bool -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (IsPrefixOfSym1 d) #

SuppressUnusedWarnings (IsPrefixOfSym1 a6989586621681120437 :: TyFun (NonEmpty a) Bool -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (IsPrefixOfSym1 a6989586621681120437 :: TyFun (NonEmpty a) Bool -> Type) (a6989586621681120438 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (IsPrefixOfSym1 a6989586621681120437 :: TyFun (NonEmpty a) Bool -> Type) (a6989586621681120438 :: NonEmpty a) = IsPrefixOf a6989586621681120437 a6989586621681120438

type family IsPrefixOfSym2 (a6989586621681120437 :: [a]) (a6989586621681120438 :: NonEmpty a) :: Bool where ... Source #

Equations

IsPrefixOfSym2 a6989586621681120437 a6989586621681120438 = IsPrefixOf a6989586621681120437 a6989586621681120438 

data NubSym0 :: (~>) (NonEmpty a) (NonEmpty a) Source #

Instances

Instances details
SEq a => SingI (NubSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing NubSym0 #

SuppressUnusedWarnings (NubSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (NubSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681120368 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (NubSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681120368 :: NonEmpty a) = Nub a6989586621681120368

type family NubSym1 (a6989586621681120368 :: NonEmpty a) :: NonEmpty a where ... Source #

Equations

NubSym1 a6989586621681120368 = Nub a6989586621681120368 

data NubBySym0 :: (~>) ((~>) a ((~>) a Bool)) ((~>) (NonEmpty a) (NonEmpty a)) Source #

Instances

Instances details
SingI (NubBySym0 :: TyFun (a ~> (a ~> Bool)) (NonEmpty a ~> NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing NubBySym0 #

SuppressUnusedWarnings (NubBySym0 :: TyFun (a ~> (a ~> Bool)) (NonEmpty a ~> NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (NubBySym0 :: TyFun (a ~> (a ~> Bool)) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621681120355 :: a ~> (a ~> Bool)) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (NubBySym0 :: TyFun (a ~> (a ~> Bool)) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621681120355 :: a ~> (a ~> Bool)) = NubBySym1 a6989586621681120355

data NubBySym1 (a6989586621681120355 :: (~>) a ((~>) a Bool)) :: (~>) (NonEmpty a) (NonEmpty a) Source #

Instances

Instances details
SingI d => SingI (NubBySym1 d :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (NubBySym1 d) #

SuppressUnusedWarnings (NubBySym1 a6989586621681120355 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (NubBySym1 a6989586621681120355 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681120356 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (NubBySym1 a6989586621681120355 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681120356 :: NonEmpty a) = NubBy a6989586621681120355 a6989586621681120356

type family NubBySym2 (a6989586621681120355 :: (~>) a ((~>) a Bool)) (a6989586621681120356 :: NonEmpty a) :: NonEmpty a where ... Source #

Equations

NubBySym2 a6989586621681120355 a6989586621681120356 = NubBy a6989586621681120355 a6989586621681120356 

data (!!@#@$) :: (~>) (NonEmpty a) ((~>) Nat a) Source #

Instances

Instances details
SingI ((!!@#@$) :: TyFun (NonEmpty a) (Nat ~> a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (!!@#@$) #

SuppressUnusedWarnings ((!!@#@$) :: TyFun (NonEmpty a) (Nat ~> a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply ((!!@#@$) :: TyFun (NonEmpty a) (Nat ~> a) -> Type) (a6989586621681120418 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply ((!!@#@$) :: TyFun (NonEmpty a) (Nat ~> a) -> Type) (a6989586621681120418 :: NonEmpty a) = (!!@#@$$) a6989586621681120418

data (!!@#@$$) (a6989586621681120418 :: NonEmpty a) :: (~>) Nat a Source #

Instances

Instances details
SingI d => SingI ((!!@#@$$) d :: TyFun Nat a -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing ((!!@#@$$) d) #

SuppressUnusedWarnings ((!!@#@$$) a6989586621681120418 :: TyFun Nat a -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply ((!!@#@$$) a6989586621681120418 :: TyFun Nat a -> Type) (a6989586621681120419 :: Nat) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply ((!!@#@$$) a6989586621681120418 :: TyFun Nat a -> Type) (a6989586621681120419 :: Nat) = a6989586621681120418 !! a6989586621681120419

type family (a6989586621681120418 :: NonEmpty a) !!@#@$$$ (a6989586621681120419 :: Nat) :: a where ... Source #

Equations

a6989586621681120418 !!@#@$$$ a6989586621681120419 = (!!) a6989586621681120418 a6989586621681120419 

data ZipSym0 :: (~>) (NonEmpty a) ((~>) (NonEmpty b) (NonEmpty (a, b))) Source #

Instances

Instances details
SingI (ZipSym0 :: TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty (a, b)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing ZipSym0 #

SuppressUnusedWarnings (ZipSym0 :: TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty (a, b)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ZipSym0 :: TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty (a, b)) -> Type) (a6989586621681120409 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ZipSym0 :: TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty (a, b)) -> Type) (a6989586621681120409 :: NonEmpty a) = ZipSym1 a6989586621681120409 :: TyFun (NonEmpty b) (NonEmpty (a, b)) -> Type

data ZipSym1 (a6989586621681120409 :: NonEmpty a) :: (~>) (NonEmpty b) (NonEmpty (a, b)) Source #

Instances

Instances details
SingI d => SingI (ZipSym1 d :: TyFun (NonEmpty b) (NonEmpty (a, b)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (ZipSym1 d) #

SuppressUnusedWarnings (ZipSym1 a6989586621681120409 :: TyFun (NonEmpty b) (NonEmpty (a, b)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ZipSym1 a6989586621681120409 :: TyFun (NonEmpty b) (NonEmpty (a, b)) -> Type) (a6989586621681120410 :: NonEmpty b) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ZipSym1 a6989586621681120409 :: TyFun (NonEmpty b) (NonEmpty (a, b)) -> Type) (a6989586621681120410 :: NonEmpty b) = Zip a6989586621681120409 a6989586621681120410

type family ZipSym2 (a6989586621681120409 :: NonEmpty a) (a6989586621681120410 :: NonEmpty b) :: NonEmpty (a, b) where ... Source #

Equations

ZipSym2 a6989586621681120409 a6989586621681120410 = Zip a6989586621681120409 a6989586621681120410 

data ZipWithSym0 :: (~>) ((~>) a ((~>) b c)) ((~>) (NonEmpty a) ((~>) (NonEmpty b) (NonEmpty c))) Source #

Instances

Instances details
SingI (ZipWithSym0 :: TyFun (a ~> (b ~> c)) (NonEmpty a ~> (NonEmpty b ~> NonEmpty c)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (ZipWithSym0 :: TyFun (a ~> (b ~> c)) (NonEmpty a ~> (NonEmpty b ~> NonEmpty c)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ZipWithSym0 :: TyFun (a ~> (b ~> c)) (NonEmpty a ~> (NonEmpty b ~> NonEmpty c)) -> Type) (a6989586621681120398 :: a ~> (b ~> c)) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ZipWithSym0 :: TyFun (a ~> (b ~> c)) (NonEmpty a ~> (NonEmpty b ~> NonEmpty c)) -> Type) (a6989586621681120398 :: a ~> (b ~> c)) = ZipWithSym1 a6989586621681120398

data ZipWithSym1 (a6989586621681120398 :: (~>) a ((~>) b c)) :: (~>) (NonEmpty a) ((~>) (NonEmpty b) (NonEmpty c)) Source #

Instances

Instances details
SingI d => SingI (ZipWithSym1 d :: TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty c) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (ZipWithSym1 d) #

SuppressUnusedWarnings (ZipWithSym1 a6989586621681120398 :: TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty c) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ZipWithSym1 a6989586621681120398 :: TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty c) -> Type) (a6989586621681120399 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ZipWithSym1 a6989586621681120398 :: TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty c) -> Type) (a6989586621681120399 :: NonEmpty a) = ZipWithSym2 a6989586621681120398 a6989586621681120399

data ZipWithSym2 (a6989586621681120398 :: (~>) a ((~>) b c)) (a6989586621681120399 :: NonEmpty a) :: (~>) (NonEmpty b) (NonEmpty c) Source #

Instances

Instances details
(SingI d1, SingI d2) => SingI (ZipWithSym2 d1 d2 :: TyFun (NonEmpty b) (NonEmpty c) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (ZipWithSym2 d1 d2) #

SuppressUnusedWarnings (ZipWithSym2 a6989586621681120398 a6989586621681120399 :: TyFun (NonEmpty b) (NonEmpty c) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ZipWithSym2 a6989586621681120398 a6989586621681120399 :: TyFun (NonEmpty b) (NonEmpty c) -> Type) (a6989586621681120400 :: NonEmpty b) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ZipWithSym2 a6989586621681120398 a6989586621681120399 :: TyFun (NonEmpty b) (NonEmpty c) -> Type) (a6989586621681120400 :: NonEmpty b) = ZipWith a6989586621681120398 a6989586621681120399 a6989586621681120400

type family ZipWithSym3 (a6989586621681120398 :: (~>) a ((~>) b c)) (a6989586621681120399 :: NonEmpty a) (a6989586621681120400 :: NonEmpty b) :: NonEmpty c where ... Source #

Equations

ZipWithSym3 a6989586621681120398 a6989586621681120399 a6989586621681120400 = ZipWith a6989586621681120398 a6989586621681120399 a6989586621681120400 

data UnzipSym0 :: (~>) (NonEmpty (a, b)) (NonEmpty a, NonEmpty b) Source #

Instances

Instances details
SingI (UnzipSym0 :: TyFun (NonEmpty (a, b)) (NonEmpty a, NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing UnzipSym0 #

SuppressUnusedWarnings (UnzipSym0 :: TyFun (NonEmpty (a, b)) (NonEmpty a, NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (UnzipSym0 :: TyFun (NonEmpty (a, b)) (NonEmpty a, NonEmpty b) -> Type) (a6989586621681120372 :: NonEmpty (a, b)) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (UnzipSym0 :: TyFun (NonEmpty (a, b)) (NonEmpty a, NonEmpty b) -> Type) (a6989586621681120372 :: NonEmpty (a, b)) = Unzip a6989586621681120372

type family UnzipSym1 (a6989586621681120372 :: NonEmpty (a, b)) :: (NonEmpty a, NonEmpty b) where ... Source #

Equations

UnzipSym1 a6989586621681120372 = Unzip a6989586621681120372 

data FromListSym0 :: (~>) [a] (NonEmpty a) Source #

Instances

Instances details
SingI (FromListSym0 :: TyFun [a] (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (FromListSym0 :: TyFun [a] (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (FromListSym0 :: TyFun [a] (NonEmpty a) -> Type) (a6989586621681120734 :: [a]) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (FromListSym0 :: TyFun [a] (NonEmpty a) -> Type) (a6989586621681120734 :: [a]) = FromList a6989586621681120734

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

Equations

FromListSym1 a6989586621681120734 = FromList a6989586621681120734 

data ToListSym0 :: (~>) (NonEmpty a) [a] Source #

Instances

Instances details
SingI (ToListSym0 :: TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing ToListSym0 #

SuppressUnusedWarnings (ToListSym0 :: TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ToListSym0 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681120729 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ToListSym0 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681120729 :: NonEmpty a) = ToList a6989586621681120729

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

Equations

ToListSym1 a6989586621681120729 = ToList a6989586621681120729 

data NonEmpty_Sym0 :: (~>) [a] (Maybe (NonEmpty a)) Source #

Instances

Instances details
SingI (NonEmpty_Sym0 :: TyFun [a] (Maybe (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (NonEmpty_Sym0 :: TyFun [a] (Maybe (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (NonEmpty_Sym0 :: TyFun [a] (Maybe (NonEmpty a)) -> Type) (a6989586621681120812 :: [a]) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (NonEmpty_Sym0 :: TyFun [a] (Maybe (NonEmpty a)) -> Type) (a6989586621681120812 :: [a]) = NonEmpty_ a6989586621681120812

type family NonEmpty_Sym1 (a6989586621681120812 :: [a]) :: Maybe (NonEmpty a) where ... Source #

Equations

NonEmpty_Sym1 a6989586621681120812 = NonEmpty_ a6989586621681120812 

data XorSym0 :: (~>) (NonEmpty Bool) Bool Source #

Instances

Instances details
SingI XorSym0 Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing XorSym0 #

SuppressUnusedWarnings XorSym0 Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply XorSym0 (a6989586621681120832 :: NonEmpty Bool) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply XorSym0 (a6989586621681120832 :: NonEmpty Bool) = Xor a6989586621681120832

type family XorSym1 (a6989586621681120832 :: NonEmpty Bool) :: Bool where ... Source #

Equations

XorSym1 a6989586621681120832 = Xor a6989586621681120832 

Orphan instances

SMonadZip NonEmpty Source # 
Instance details

Methods

sMzip :: forall a b (t :: NonEmpty a) (t :: NonEmpty b). Sing t -> Sing t -> Sing (Apply (Apply MzipSym0 t) t) Source #

sMzipWith :: forall a b c (t :: a ~> (b ~> c)) (t :: NonEmpty a) (t :: NonEmpty b). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply MzipWithSym0 t) t) t) Source #

sMunzip :: forall a b (t :: NonEmpty (a, b)). Sing t -> Sing (Apply MunzipSym0 t) Source #

PMonadZip NonEmpty Source # 
Instance details

Associated Types

type Mzip arg arg :: m (a, b) Source #

type MzipWith arg arg arg :: m c Source #

type Munzip arg :: (m a, m b) Source #