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

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.Semigroup.Singletons.Internal.Wrappers

type Sing = SAll
type Sing Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Sing = SAny
type Sing Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Sing = SVoid
type Sing Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type Sing = SNat
type Sing Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Sing Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

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 = SBool
type Sing Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type Sing = SChar
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 = 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.Ord.Singletons

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

Defined in Data.Semigroup.Singletons.Internal.Wrappers

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

Defined in Data.Semigroup.Singletons.Internal.Wrappers

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

Defined in Data.Semigroup.Singletons.Internal.Wrappers

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

Defined in Data.Semigroup.Singletons.Internal.Wrappers

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

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Sing = SWrappedMonoid :: WrappedMonoid m -> Type
type Sing Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

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

Defined in Data.Semigroup.Singletons.Internal.Wrappers

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

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Sing = SSum :: Sum 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 = 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.Singletons.Base.Instances

type Sing = SList :: [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.Proxy.Singletons

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

Defined in Data.Semigroup.Singletons

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

Defined in Data.Singletons

type Sing = SWrappedSing :: WrappedSing a -> Type
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 = STuple2 :: (a, b) -> 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 = STuple3 :: (a, b, c) -> Type
type Sing Source # 
Instance details

Defined in Data.Functor.Product.Singletons

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

Defined in Data.Functor.Sum.Singletons

type Sing = SSum :: Sum f g a -> 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.Functor.Compose.Singletons

type Sing = SCompose :: Compose f g a -> 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

Methods

showsPrec :: Int -> SNonEmpty z -> ShowS

show :: SNonEmpty z -> String

showList :: [SNonEmpty z] -> ShowS

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 (t :: (~>) a b) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply MapSym0 t) t :: NonEmpty b) :: Type Source #

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

Equations

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

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

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

Equations

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

sScanl :: forall (t :: (~>) b ((~>) a b)) (t :: b) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ScanlSym0 t) t) t :: NonEmpty b) :: Type Source #

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

Equations

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

sScanr :: forall (t :: (~>) a ((~>) b b)) (t :: b) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ScanrSym0 t) t) t :: NonEmpty b) :: Type 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 (t :: (~>) a ((~>) a a)) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply Scanl1Sym0 t) t :: NonEmpty a) :: Type 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 (t :: (~>) a ((~>) a a)) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply Scanr1Sym0 t) t :: NonEmpty a) :: Type Source #

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

Equations

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

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

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

Equations

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

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

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

Equations

SortWith a_6989586621680609716 a_6989586621680609718 = Apply (Apply (Apply (Apply (.@#@$) SortBySym0) ComparingSym0) a_6989586621680609716) a_6989586621680609718 

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

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

Equations

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

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

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

Equations

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

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

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

Equations

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

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

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

Equations

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

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

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

Equations

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

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

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

Equations

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

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

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

Equations

Cons a_6989586621680610133 a_6989586621680610135 = Apply (Apply (<|@#@$) a_6989586621680610133) a_6989586621680610135 

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

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

Equations

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

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

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

Equations

Unfoldr f a = Case_6989586621680610190 f a (Let6989586621680610188Scrutinee_6989586621680608752Sym2 f a) 

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

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

Equations

Sort a_6989586621680610127 = Apply (Apply LiftSym0 ListsortSym0) a_6989586621680610127 

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

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

Equations

Reverse a_6989586621680610022 = Apply (Apply LiftSym0 ListreverseSym0) a_6989586621680610022 

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

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

Equations

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

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

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

Equations

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

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

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

Equations

Unfold f a = Case_6989586621680610214 f a (Let6989586621680610212Scrutinee_6989586621680608742Sym2 f a) 

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

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

Equations

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

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

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

Equations

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

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

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

Equations

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

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

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

Equations

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

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

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

Equations

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

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

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

Equations

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

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

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

Equations

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

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

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

Equations

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

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

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

Equations

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

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

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

Equations

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

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

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

Equations

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

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

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

Equations

GroupBy eq0 a_6989586621680609901 = Apply (Apply (Let6989586621680609910GoSym2 eq0 a_6989586621680609901) eq0) a_6989586621680609901 

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

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

Equations

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

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

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

Equations

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

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

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

Equations

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

sGroup1 :: forall (t :: NonEmpty a). SEq a => Sing t -> Sing (Apply Group1Sym0 t :: NonEmpty (NonEmpty a)) :: Type 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) (Let6989586621680609859YsSym3 eq x xs))) (Apply (Apply GroupBySym0 eq) (Let6989586621680609859ZsSym3 eq x xs)) 

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

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

Equations

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

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

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

Equations

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

sGroupAllWith1 :: forall (t :: (~>) a b) (t :: NonEmpty a). SOrd b => Sing t -> Sing t -> Sing (Apply (Apply GroupAllWith1Sym0 t) t :: NonEmpty (NonEmpty a)) :: Type 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 (t :: [a]) (t :: NonEmpty a). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IsPrefixOfSym0 t) t :: Bool) :: Type Source #

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

Equations

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

sNub :: forall (t :: NonEmpty a). SEq a => Sing t -> Sing (Apply NubSym0 t :: NonEmpty a) :: Type 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_6989586621680609750Sym0 eq) a) as)) as)) 

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

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

Equations

arg_6989586621680608764 !! arg_6989586621680608766 = Case_6989586621680609812 arg_6989586621680608764 arg_6989586621680608766 (Apply (Apply Tuple2Sym0 arg_6989586621680608764) arg_6989586621680608766) 

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

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

Equations

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

sZip :: forall (t :: NonEmpty a) (t :: NonEmpty b). Sing t -> Sing t -> Sing (Apply (Apply ZipSym0 t) t :: NonEmpty (a, b)) :: Type 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 (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) :: Type 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) (Let6989586621680609766AsSym3 a b asbs))) (Apply (Apply (:|@#@$) b) (Let6989586621680609766BsSym3 a b asbs)) 

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

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

Equations

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

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

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

Equations

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

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

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

Equations

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

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

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

Equations

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

sXor :: forall (t :: NonEmpty Bool). Sing t -> Sing (Apply XorSym0 t :: Bool) :: Type 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) (a6989586621679037625 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

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

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

Instances

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

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: k1). Sing x -> Sing ((:|@#@$$) x) #

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

Defined in Data.Singletons.Base.Instances

Methods

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

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

Defined in Data.Singletons.Base.Instances

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

Defined in Data.Singletons.Base.Instances

type Apply ((:|@#@$$) a6989586621679037625 :: TyFun [a] (NonEmpty a) -> Type) (a6989586621679037626 :: [a]) = a6989586621679037625 ':| a6989586621679037626

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

Equations

a6989586621679037625 :|@#@$$$ a6989586621679037626 = '(:|) a6989586621679037625 a6989586621679037626 

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) (a6989586621680610103 :: a ~> b) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

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

Instances

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

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: k1). Sing x -> Sing (MapSym1 x) #

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 a6989586621680610103 :: TyFun (NonEmpty a) (NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.List.NonEmpty.Singletons

type Apply (MapSym1 a6989586621680610103 :: TyFun (NonEmpty a) (NonEmpty b) -> Type) (a6989586621680610104 :: NonEmpty a) = Map a6989586621680610103 a6989586621680610104

type family MapSym2 (a6989586621680610103 :: (~>) a b) (a6989586621680610104 :: NonEmpty a) :: NonEmpty b where ... Source #

Equations

MapSym2 a6989586621680610103 a6989586621680610104 = Map a6989586621680610103 a6989586621680610104 

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) (a6989586621680610031 :: a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

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

Instances

Instances details
SingI1 (IntersperseSym1 :: a -> TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: k1). Sing x -> Sing (IntersperseSym1 x) #

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 a6989586621680610031 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.List.NonEmpty.Singletons

type Apply (IntersperseSym1 a6989586621680610031 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621680610032 :: NonEmpty a) = Intersperse a6989586621680610031 a6989586621680610032

type family IntersperseSym2 (a6989586621680610031 :: a) (a6989586621680610032 :: NonEmpty a) :: NonEmpty a where ... Source #

Equations

IntersperseSym2 a6989586621680610031 a6989586621680610032 = Intersperse a6989586621680610031 a6989586621680610032 

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) (a6989586621680610073 :: b ~> (a ~> b)) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

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

Instances

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

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: k1). Sing x -> Sing (ScanlSym1 x) #

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 a6989586621680610073 :: TyFun b ([a] ~> NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.List.NonEmpty.Singletons

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

data ScanlSym2 (a6989586621680610073 :: (~>) b ((~>) a b)) (a6989586621680610074 :: b) :: (~>) [a] (NonEmpty b) Source #

Instances

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

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: k1). Sing x -> Sing (ScanlSym2 d x) #

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

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing2 :: forall (x :: k1) (y :: k2). Sing x -> Sing y -> Sing (ScanlSym2 x y) #

(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 a6989586621680610073 a6989586621680610074 :: TyFun [a] (NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ScanlSym2 a6989586621680610073 a6989586621680610074 :: TyFun [a] (NonEmpty b) -> Type) (a6989586621680610075 :: [a]) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ScanlSym2 a6989586621680610073 a6989586621680610074 :: TyFun [a] (NonEmpty b) -> Type) (a6989586621680610075 :: [a]) = Scanl a6989586621680610073 a6989586621680610074 a6989586621680610075

type family ScanlSym3 (a6989586621680610073 :: (~>) b ((~>) a b)) (a6989586621680610074 :: b) (a6989586621680610075 :: [a]) :: NonEmpty b where ... Source #

Equations

ScanlSym3 a6989586621680610073 a6989586621680610074 a6989586621680610075 = Scanl a6989586621680610073 a6989586621680610074 a6989586621680610075 

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) (a6989586621680610061 :: a ~> (b ~> b)) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

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

Instances

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

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: k1). Sing x -> Sing (ScanrSym1 x) #

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 a6989586621680610061 :: TyFun b ([a] ~> NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.List.NonEmpty.Singletons

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

data ScanrSym2 (a6989586621680610061 :: (~>) a ((~>) b b)) (a6989586621680610062 :: b) :: (~>) [a] (NonEmpty b) Source #

Instances

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

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: k1). Sing x -> Sing (ScanrSym2 d x) #

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

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing2 :: forall (x :: k1) (y :: k2). Sing x -> Sing y -> Sing (ScanrSym2 x y) #

(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 a6989586621680610061 a6989586621680610062 :: TyFun [a] (NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ScanrSym2 a6989586621680610061 a6989586621680610062 :: TyFun [a] (NonEmpty b) -> Type) (a6989586621680610063 :: [a]) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ScanrSym2 a6989586621680610061 a6989586621680610062 :: TyFun [a] (NonEmpty b) -> Type) (a6989586621680610063 :: [a]) = Scanr a6989586621680610061 a6989586621680610062 a6989586621680610063

type family ScanrSym3 (a6989586621680610061 :: (~>) a ((~>) b b)) (a6989586621680610062 :: b) (a6989586621680610063 :: [a]) :: NonEmpty b where ... Source #

Equations

ScanrSym3 a6989586621680610061 a6989586621680610062 a6989586621680610063 = Scanr a6989586621680610061 a6989586621680610062 a6989586621680610063 

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) (a6989586621680610050 :: a ~> (a ~> a)) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

data Scanl1Sym1 (a6989586621680610050 :: (~>) 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 a6989586621680610050 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SingI1 (Scanl1Sym1 :: (a ~> (a ~> a)) -> TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: k1). Sing x -> Sing (Scanl1Sym1 x) #

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

Defined in Data.List.NonEmpty.Singletons

type Apply (Scanl1Sym1 a6989586621680610050 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621680610051 :: NonEmpty a) = Scanl1 a6989586621680610050 a6989586621680610051

type family Scanl1Sym2 (a6989586621680610050 :: (~>) a ((~>) a a)) (a6989586621680610051 :: NonEmpty a) :: NonEmpty a where ... Source #

Equations

Scanl1Sym2 a6989586621680610050 a6989586621680610051 = Scanl1 a6989586621680610050 a6989586621680610051 

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) (a6989586621680610042 :: a ~> (a ~> a)) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

data Scanr1Sym1 (a6989586621680610042 :: (~>) 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 a6989586621680610042 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SingI1 (Scanr1Sym1 :: (a ~> (a ~> a)) -> TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: k1). Sing x -> Sing (Scanr1Sym1 x) #

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

Defined in Data.List.NonEmpty.Singletons

type Apply (Scanr1Sym1 a6989586621680610042 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621680610043 :: NonEmpty a) = Scanr1 a6989586621680610042 a6989586621680610043

type family Scanr1Sym2 (a6989586621680610042 :: (~>) a ((~>) a a)) (a6989586621680610043 :: NonEmpty a) :: NonEmpty a where ... Source #

Equations

Scanr1Sym2 a6989586621680610042 a6989586621680610043 = Scanr1 a6989586621680610042 a6989586621680610043 

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) (a6989586621680609740 :: NonEmpty (NonEmpty a)) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

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

Equations

TransposeSym1 a6989586621680609740 = Transpose a6989586621680609740 

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) (a6989586621680609732 :: a ~> (a ~> Ordering)) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

data SortBySym1 (a6989586621680609732 :: (~>) 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 a6989586621680609732 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SingI1 (SortBySym1 :: (a ~> (a ~> Ordering)) -> TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: k1). Sing x -> Sing (SortBySym1 x) #

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

Defined in Data.List.NonEmpty.Singletons

type Apply (SortBySym1 a6989586621680609732 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621680609733 :: NonEmpty a) = SortBy a6989586621680609732 a6989586621680609733

type family SortBySym2 (a6989586621680609732 :: (~>) a ((~>) a Ordering)) (a6989586621680609733 :: NonEmpty a) :: NonEmpty a where ... Source #

Equations

SortBySym2 a6989586621680609732 a6989586621680609733 = SortBy a6989586621680609732 a6989586621680609733 

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) (a6989586621680609723 :: a ~> o) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

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

Instances

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

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: k1). Sing x -> Sing (SortWithSym1 x) #

(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 a6989586621680609723 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.List.NonEmpty.Singletons

type Apply (SortWithSym1 a6989586621680609723 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621680609724 :: NonEmpty a) = SortWith a6989586621680609723 a6989586621680609724

type family SortWithSym2 (a6989586621680609723 :: (~>) a o) (a6989586621680609724 :: NonEmpty a) :: NonEmpty a where ... Source #

Equations

SortWithSym2 a6989586621680609723 a6989586621680609724 = SortWith a6989586621680609723 a6989586621680609724 

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

Instances

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

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing LengthSym0 #

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

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.List.NonEmpty.Singletons

type Apply (LengthSym0 :: TyFun (NonEmpty a) Natural -> Type) (a6989586621680610233 :: NonEmpty a) = Length a6989586621680610233

type family LengthSym1 (a6989586621680610233 :: NonEmpty a) :: Natural where ... Source #

Equations

LengthSym1 a6989586621680610233 = Length a6989586621680610233 

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) (a6989586621680610168 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

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

Equations

HeadSym1 a6989586621680610168 = Head a6989586621680610168 

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) (a6989586621680610164 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

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

Equations

TailSym1 a6989586621680610164 = Tail a6989586621680610164 

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) (a6989586621680610159 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

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

Equations

LastSym1 a6989586621680610159 = Last a6989586621680610159 

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) (a6989586621680610154 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

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

Equations

InitSym1 a6989586621680610154 = Init a6989586621680610154 

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) (a6989586621680610147 :: a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

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

Instances

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

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: k1). Sing x -> Sing ((<|@#@$$) x) #

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

Defined in Data.List.NonEmpty.Singletons

Methods

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

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

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.List.NonEmpty.Singletons

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

type family (a6989586621680610147 :: a) <|@#@$$$ (a6989586621680610148 :: NonEmpty a) :: NonEmpty a where ... Source #

Equations

a6989586621680610147 <|@#@$$$ a6989586621680610148 = (<|) a6989586621680610147 a6989586621680610148 

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) (a6989586621680610140 :: a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

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

Instances

Instances details
SingI1 (ConsSym1 :: a -> TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: k1). Sing x -> Sing (ConsSym1 x) #

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 a6989586621680610140 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.List.NonEmpty.Singletons

type Apply (ConsSym1 a6989586621680610140 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621680610141 :: NonEmpty a) = Cons a6989586621680610140 a6989586621680610141

type family ConsSym2 (a6989586621680610140 :: a) (a6989586621680610141 :: NonEmpty a) :: NonEmpty a where ... Source #

Equations

ConsSym2 a6989586621680610140 a6989586621680610141 = Cons a6989586621680610140 a6989586621680610141 

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) (a6989586621680610197 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

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

Equations

UnconsSym1 a6989586621680610197 = Uncons a6989586621680610197 

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) (a6989586621680610173 :: 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) (a6989586621680610173 :: a ~> (b, Maybe a)) = UnfoldrSym1 a6989586621680610173

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

Instances

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

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: k1). Sing x -> Sing (UnfoldrSym1 x) #

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 a6989586621680610173 :: TyFun a (NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.List.NonEmpty.Singletons

type Apply (UnfoldrSym1 a6989586621680610173 :: TyFun a (NonEmpty b) -> Type) (a6989586621680610174 :: a) = Unfoldr a6989586621680610173 a6989586621680610174

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

Equations

UnfoldrSym2 a6989586621680610173 a6989586621680610174 = Unfoldr a6989586621680610173 a6989586621680610174 

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) (a6989586621680610131 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

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

Equations

SortSym1 a6989586621680610131 = Sort a6989586621680610131 

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) (a6989586621680610026 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

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

Equations

ReverseSym1 a6989586621680610026 = Reverse a6989586621680610026 

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) (a6989586621680610098 :: [a]) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

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

Equations

InitsSym1 a6989586621680610098 = Inits a6989586621680610098 

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) (a6989586621680610092 :: [a]) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

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

Equations

TailsSym1 a6989586621680610092 = Tails a6989586621680610092 

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) (a6989586621680610208 :: 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) (a6989586621680610208 :: a ~> (b, Maybe a)) = UnfoldSym1 a6989586621680610208

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

Instances

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

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: k1). Sing x -> Sing (UnfoldSym1 x) #

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 a6989586621680610208 :: TyFun a (NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.List.NonEmpty.Singletons

type Apply (UnfoldSym1 a6989586621680610208 :: TyFun a (NonEmpty b) -> Type) (a6989586621680610209 :: a) = Unfold a6989586621680610208 a6989586621680610209

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) (a6989586621680610084 :: a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

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

Instances

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

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: k1). Sing x -> Sing (InsertSym1 x) #

(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 a6989586621680610084 :: TyFun [a] (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.List.NonEmpty.Singletons

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

type family InsertSym2 (a6989586621680610084 :: a) (a6989586621680610085 :: [a]) :: NonEmpty a where ... Source #

Equations

InsertSym2 a6989586621680610084 a6989586621680610085 = Insert a6989586621680610084 a6989586621680610085 

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

Instances

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

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing TakeSym0 #

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

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.List.NonEmpty.Singletons

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

data TakeSym1 (a6989586621680610018 :: Natural) :: (~>) (NonEmpty a) [a] Source #

Instances

Instances details
SingI1 (TakeSym1 :: Natural -> TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: k1). Sing x -> Sing (TakeSym1 x) #

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 a6989586621680610018 :: TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.List.NonEmpty.Singletons

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

type family TakeSym2 (a6989586621680610018 :: Natural) (a6989586621680610019 :: NonEmpty a) :: [a] where ... Source #

Equations

TakeSym2 a6989586621680610018 a6989586621680610019 = Take a6989586621680610018 a6989586621680610019 

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

Instances

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

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing DropSym0 #

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

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.List.NonEmpty.Singletons

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

data DropSym1 (a6989586621680610009 :: Natural) :: (~>) (NonEmpty a) [a] Source #

Instances

Instances details
SingI1 (DropSym1 :: Natural -> TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: k1). Sing x -> Sing (DropSym1 x) #

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 a6989586621680610009 :: TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.List.NonEmpty.Singletons

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

type family DropSym2 (a6989586621680610009 :: Natural) (a6989586621680610010 :: NonEmpty a) :: [a] where ... Source #

Equations

DropSym2 a6989586621680610009 a6989586621680610010 = Drop a6989586621680610009 a6989586621680610010 

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

Instances

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

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.List.NonEmpty.Singletons

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

data SplitAtSym1 (a6989586621680610000 :: Natural) :: (~>) (NonEmpty a) ([a], [a]) Source #

Instances

Instances details
SingI1 (SplitAtSym1 :: Natural -> TyFun (NonEmpty a) ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: k1). Sing x -> Sing (SplitAtSym1 x) #

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 a6989586621680610000 :: TyFun (NonEmpty a) ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.List.NonEmpty.Singletons

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

type family SplitAtSym2 (a6989586621680610000 :: Natural) (a6989586621680610001 :: NonEmpty a) :: ([a], [a]) where ... Source #

Equations

SplitAtSym2 a6989586621680610000 a6989586621680610001 = SplitAt a6989586621680610000 a6989586621680610001 

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) (a6989586621680609991 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

data TakeWhileSym1 (a6989586621680609991 :: (~>) 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 a6989586621680609991 :: TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: k1). Sing x -> Sing (TakeWhileSym1 x) #

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

Defined in Data.List.NonEmpty.Singletons

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

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

Equations

TakeWhileSym2 a6989586621680609991 a6989586621680609992 = TakeWhile a6989586621680609991 a6989586621680609992 

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) (a6989586621680609982 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

data DropWhileSym1 (a6989586621680609982 :: (~>) 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 a6989586621680609982 :: TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: k1). Sing x -> Sing (DropWhileSym1 x) #

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

Defined in Data.List.NonEmpty.Singletons

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

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

Equations

DropWhileSym2 a6989586621680609982 a6989586621680609983 = DropWhile a6989586621680609982 a6989586621680609983 

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) (a6989586621680609973 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

data SpanSym1 (a6989586621680609973 :: (~>) 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 a6989586621680609973 :: TyFun (NonEmpty a) ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: k1). Sing x -> Sing (SpanSym1 x) #

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

Defined in Data.List.NonEmpty.Singletons

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

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

Equations

SpanSym2 a6989586621680609973 a6989586621680609974 = Span a6989586621680609973 a6989586621680609974 

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) (a6989586621680609964 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

data BreakSym1 (a6989586621680609964 :: (~>) 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 a6989586621680609964 :: TyFun (NonEmpty a) ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: k1). Sing x -> Sing (BreakSym1 x) #

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

Defined in Data.List.NonEmpty.Singletons

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

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

Equations

BreakSym2 a6989586621680609964 a6989586621680609965 = Break a6989586621680609964 a6989586621680609965 

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) (a6989586621680609955 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

data FilterSym1 (a6989586621680609955 :: (~>) 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 a6989586621680609955 :: TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: k1). Sing x -> Sing (FilterSym1 x) #

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

Defined in Data.List.NonEmpty.Singletons

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

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

Equations

FilterSym2 a6989586621680609955 a6989586621680609956 = Filter a6989586621680609955 a6989586621680609956 

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) (a6989586621680609946 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

data PartitionSym1 (a6989586621680609946 :: (~>) 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 a6989586621680609946 :: TyFun (NonEmpty a) ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: k1). Sing x -> Sing (PartitionSym1 x) #

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

Defined in Data.List.NonEmpty.Singletons

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

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

Equations

PartitionSym2 a6989586621680609946 a6989586621680609947 = Partition a6989586621680609946 a6989586621680609947 

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) (a6989586621680609939 :: [a]) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

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

Equations

GroupSym1 a6989586621680609939 = Group a6989586621680609939 

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) (a6989586621680609906 :: a ~> (a ~> Bool)) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

data GroupBySym1 (a6989586621680609906 :: (~>) 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 a6989586621680609906 :: TyFun [a] [NonEmpty a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: k1). Sing x -> Sing (GroupBySym1 x) #

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

Defined in Data.List.NonEmpty.Singletons

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

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

Equations

GroupBySym2 a6989586621680609906 a6989586621680609907 = GroupBy a6989586621680609906 a6989586621680609907 

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) (a6989586621680609897 :: a ~> b) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

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

Instances

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

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: k1). Sing x -> Sing (GroupWithSym1 x) #

(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 a6989586621680609897 :: TyFun [a] [NonEmpty a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.List.NonEmpty.Singletons

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

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

Equations

GroupWithSym2 a6989586621680609897 a6989586621680609898 = GroupWith a6989586621680609897 a6989586621680609898 

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) (a6989586621680609888 :: a ~> b) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

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

Instances

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

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: k1). Sing x -> Sing (GroupAllWithSym1 x) #

(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 a6989586621680609888 :: TyFun [a] [NonEmpty a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.List.NonEmpty.Singletons

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

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

Equations

GroupAllWithSym2 a6989586621680609888 a6989586621680609889 = GroupAllWith a6989586621680609888 a6989586621680609889 

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) (a6989586621680609881 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

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

Equations

Group1Sym1 a6989586621680609881 = Group1 a6989586621680609881 

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) (a6989586621680609854 :: 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) (a6989586621680609854 :: a ~> (a ~> Bool)) = GroupBy1Sym1 a6989586621680609854

data GroupBy1Sym1 (a6989586621680609854 :: (~>) 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 a6989586621680609854 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SingI1 (GroupBy1Sym1 :: (a ~> (a ~> Bool)) -> TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: k1). Sing x -> Sing (GroupBy1Sym1 x) #

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

Defined in Data.List.NonEmpty.Singletons

type Apply (GroupBy1Sym1 a6989586621680609854 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621680609855 :: NonEmpty a) = GroupBy1 a6989586621680609854 a6989586621680609855

type family GroupBy1Sym2 (a6989586621680609854 :: (~>) a ((~>) a Bool)) (a6989586621680609855 :: NonEmpty a) :: NonEmpty (NonEmpty a) where ... Source #

Equations

GroupBy1Sym2 a6989586621680609854 a6989586621680609855 = GroupBy1 a6989586621680609854 a6989586621680609855 

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) (a6989586621680609847 :: a ~> b) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

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

Instances

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

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: k1). Sing x -> Sing (GroupWith1Sym1 x) #

(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 a6989586621680609847 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.List.NonEmpty.Singletons

type Apply (GroupWith1Sym1 a6989586621680609847 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621680609848 :: NonEmpty a) = GroupWith1 a6989586621680609847 a6989586621680609848

type family GroupWith1Sym2 (a6989586621680609847 :: (~>) a b) (a6989586621680609848 :: NonEmpty a) :: NonEmpty (NonEmpty a) where ... Source #

Equations

GroupWith1Sym2 a6989586621680609847 a6989586621680609848 = GroupWith1 a6989586621680609847 a6989586621680609848 

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) (a6989586621680609838 :: a ~> b) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

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

Instances

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

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: k1). Sing x -> Sing (GroupAllWith1Sym1 x) #

(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 a6989586621680609838 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.List.NonEmpty.Singletons

type Apply (GroupAllWith1Sym1 a6989586621680609838 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621680609839 :: NonEmpty a) = GroupAllWith1 a6989586621680609838 a6989586621680609839

type family GroupAllWith1Sym2 (a6989586621680609838 :: (~>) a b) (a6989586621680609839 :: NonEmpty a) :: NonEmpty (NonEmpty a) where ... Source #

Equations

GroupAllWith1Sym2 a6989586621680609838 a6989586621680609839 = GroupAllWith1 a6989586621680609838 a6989586621680609839 

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) (a6989586621680609827 :: [a]) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

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

Instances

Instances details
SEq a => SingI1 (IsPrefixOfSym1 :: [a] -> TyFun (NonEmpty a) Bool -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: k1). Sing x -> Sing (IsPrefixOfSym1 x) #

(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 a6989586621680609827 :: TyFun (NonEmpty a) Bool -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.List.NonEmpty.Singletons

type Apply (IsPrefixOfSym1 a6989586621680609827 :: TyFun (NonEmpty a) Bool -> Type) (a6989586621680609828 :: NonEmpty a) = IsPrefixOf a6989586621680609827 a6989586621680609828

type family IsPrefixOfSym2 (a6989586621680609827 :: [a]) (a6989586621680609828 :: NonEmpty a) :: Bool where ... Source #

Equations

IsPrefixOfSym2 a6989586621680609827 a6989586621680609828 = IsPrefixOf a6989586621680609827 a6989586621680609828 

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) (a6989586621680609758 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

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

Equations

NubSym1 a6989586621680609758 = Nub a6989586621680609758 

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) (a6989586621680609745 :: a ~> (a ~> Bool)) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

data NubBySym1 (a6989586621680609745 :: (~>) 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 a6989586621680609745 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SingI1 (NubBySym1 :: (a ~> (a ~> Bool)) -> TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: k1). Sing x -> Sing (NubBySym1 x) #

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

Defined in Data.List.NonEmpty.Singletons

type Apply (NubBySym1 a6989586621680609745 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621680609746 :: NonEmpty a) = NubBy a6989586621680609745 a6989586621680609746

type family NubBySym2 (a6989586621680609745 :: (~>) a ((~>) a Bool)) (a6989586621680609746 :: NonEmpty a) :: NonEmpty a where ... Source #

Equations

NubBySym2 a6989586621680609745 a6989586621680609746 = NubBy a6989586621680609745 a6989586621680609746 

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

Instances

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

Defined in Data.List.NonEmpty.Singletons

Methods

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

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

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.List.NonEmpty.Singletons

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

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

Instances

Instances details
SingI1 ((!!@#@$$) :: NonEmpty a -> TyFun Natural a -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: k1). Sing x -> Sing ((!!@#@$$) x) #

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

Defined in Data.List.NonEmpty.Singletons

Methods

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

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

Defined in Data.List.NonEmpty.Singletons

type Apply ((!!@#@$$) a6989586621680609808 :: TyFun Natural a -> Type) (a6989586621680609809 :: Natural) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply ((!!@#@$$) a6989586621680609808 :: TyFun Natural a -> Type) (a6989586621680609809 :: Natural) = a6989586621680609808 !! a6989586621680609809

type family (a6989586621680609808 :: NonEmpty a) !!@#@$$$ (a6989586621680609809 :: Natural) :: a where ... Source #

Equations

a6989586621680609808 !!@#@$$$ a6989586621680609809 = (!!) a6989586621680609808 a6989586621680609809 

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) (a6989586621680609799 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

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

Instances

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

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: k1). Sing x -> Sing (ZipSym1 x) #

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 a6989586621680609799 :: TyFun (NonEmpty b) (NonEmpty (a, b)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.List.NonEmpty.Singletons

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

type family ZipSym2 (a6989586621680609799 :: NonEmpty a) (a6989586621680609800 :: NonEmpty b) :: NonEmpty (a, b) where ... Source #

Equations

ZipSym2 a6989586621680609799 a6989586621680609800 = Zip a6989586621680609799 a6989586621680609800 

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) (a6989586621680609788 :: 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) (a6989586621680609788 :: a ~> (b ~> c)) = ZipWithSym1 a6989586621680609788

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

Instances

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

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: k1). Sing x -> Sing (ZipWithSym1 x) #

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 a6989586621680609788 :: TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty c) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.List.NonEmpty.Singletons

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

data ZipWithSym2 (a6989586621680609788 :: (~>) a ((~>) b c)) (a6989586621680609789 :: NonEmpty a) :: (~>) (NonEmpty b) (NonEmpty c) Source #

Instances

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

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: k1). Sing x -> Sing (ZipWithSym2 d x) #

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

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing2 :: forall (x :: k1) (y :: k2). Sing x -> Sing y -> Sing (ZipWithSym2 x y) #

(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 a6989586621680609788 a6989586621680609789 :: TyFun (NonEmpty b) (NonEmpty c) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ZipWithSym2 a6989586621680609788 a6989586621680609789 :: TyFun (NonEmpty b) (NonEmpty c) -> Type) (a6989586621680609790 :: NonEmpty b) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ZipWithSym2 a6989586621680609788 a6989586621680609789 :: TyFun (NonEmpty b) (NonEmpty c) -> Type) (a6989586621680609790 :: NonEmpty b) = ZipWith a6989586621680609788 a6989586621680609789 a6989586621680609790

type family ZipWithSym3 (a6989586621680609788 :: (~>) a ((~>) b c)) (a6989586621680609789 :: NonEmpty a) (a6989586621680609790 :: NonEmpty b) :: NonEmpty c where ... Source #

Equations

ZipWithSym3 a6989586621680609788 a6989586621680609789 a6989586621680609790 = ZipWith a6989586621680609788 a6989586621680609789 a6989586621680609790 

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) (a6989586621680609762 :: NonEmpty (a, b)) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

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

Equations

UnzipSym1 a6989586621680609762 = Unzip a6989586621680609762 

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) (a6989586621680610124 :: [a]) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

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

Equations

FromListSym1 a6989586621680610124 = FromList a6989586621680610124 

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) (a6989586621680610119 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

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

Equations

ToListSym1 a6989586621680610119 = ToList a6989586621680610119 

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) (a6989586621680610202 :: [a]) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

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

Equations

NonEmpty_Sym1 a6989586621680610202 = NonEmpty_ a6989586621680610202 

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 (a6989586621680610222 :: NonEmpty Bool) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

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

Equations

XorSym1 a6989586621680610222 = Xor a6989586621680610222 

Orphan instances

PMonadZip NonEmpty Source # 
Instance details

Associated Types

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

type MzipWith arg arg1 arg2 :: m c Source #

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

SMonadZip NonEmpty Source # 
Instance details

Methods

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

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

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