singletons-2.7: A framework for generating singleton types
Copyright(C) 2016 Richard Eisenberg
LicenseBSD-style (see LICENSE)
MaintainerRyan Scott
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Singletons.Prelude.List.NonEmpty

Description

Defines functions and datatypes relating to the singleton for NonEmpty, including a singletons version of all the definitions in Data.List.NonEmpty.

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

Synopsis

The NonEmpty singleton

type family Sing Source #

The singleton kind-indexed type family.

Instances

Instances details
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Sing = SBool
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Sing Source # 
Instance details

Defined in Data.Singletons.TypeLits.Internal

type Sing = SNat
type Sing Source # 
Instance details

Defined in Data.Singletons.TypeLits.Internal

type Sing = SSymbol
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Sing = STuple0
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Sing = SVoid
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Sing = SAll
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Sing = SAny
type Sing Source # 
Instance details

Defined in Data.Singletons.TypeError

type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.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.TypeRepTYPE

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Sing = SOption :: Option a -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Monoid

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

Defined in Data.Singletons.Prelude.Monoid

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Proxy

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

Defined in Data.Singletons.Internal

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

Defined in Data.Singletons.Internal

type Sing Source # 
Instance details

Defined in Data.Singletons.Sigma

type Sing = SSigma :: Sigma s t -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Const

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

data SNonEmpty z 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.Prelude.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.Prelude.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.ShowSing

Non-empty stream transformations

type family Map a a where ... Source #

Equations

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

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

type family Intersperse a a where ... Source #

Equations

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

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

type family Scanl a a a where ... Source #

Equations

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

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

type family Scanr a a a where ... Source #

Equations

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

sScanr :: forall a b (t :: (~>) a ((~>) b b)) (t :: b) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ScanrSym0 t) t) t :: NonEmpty b) Source #

type family Scanl1 a a where ... Source #

Equations

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

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

type family Scanr1 a a where ... Source #

Equations

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

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

type family Transpose a where ... Source #

Equations

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

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

type family SortBy a a where ... Source #

Equations

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

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

type family SortWith a a where ... Source #

Equations

SortWith a_6989586621681185765 a_6989586621681185767 = Apply (Apply (Apply (Apply (.@#@$) SortBySym0) ComparingSym0) a_6989586621681185765) a_6989586621681185767 

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

type family Length a where ... Source #

Equations

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

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

type family Head a where ... Source #

Equations

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

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

type family Tail a where ... Source #

Equations

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

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

type family Last a where ... Source #

Equations

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

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

type family Init a where ... Source #

Equations

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

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

type family a <| a where ... Source #

Equations

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

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

type family Cons a a where ... Source #

Equations

Cons a_6989586621681186182 a_6989586621681186184 = Apply (Apply (<|@#@$) a_6989586621681186182) a_6989586621681186184 

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

type family Uncons a where ... Source #

Equations

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

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

type family Unfoldr a a where ... Source #

Equations

Unfoldr f a = Case_6989586621681186239 f a (Let6989586621681186237Scrutinee_6989586621681184652Sym2 f a) 

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

type family Sort a where ... Source #

Equations

Sort a_6989586621681186176 = Apply (Apply LiftSym0 ListsortSym0) a_6989586621681186176 

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

type family Reverse a where ... Source #

Equations

Reverse a_6989586621681186071 = Apply (Apply LiftSym0 ListreverseSym0) a_6989586621681186071 

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

type family Inits a where ... Source #

Equations

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

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

type family Tails a where ... Source #

Equations

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

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

type family Unfold a a where ... Source #

Equations

Unfold f a = Case_6989586621681186263 f a (Let6989586621681186261Scrutinee_6989586621681184642Sym2 f a) 

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

type family Insert a a where ... Source #

Equations

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

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

type family Take a a where ... Source #

Equations

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

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

type family Drop a a where ... Source #

Equations

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

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

type family SplitAt a a where ... Source #

Equations

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

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

type family TakeWhile a a where ... Source #

Equations

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

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

type family DropWhile a a where ... Source #

Equations

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

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

type family Span a a where ... Source #

Equations

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

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

type family Break a a where ... Source #

Equations

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

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

type family Filter a a where ... Source #

Equations

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

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

type family Partition a a where ... Source #

Equations

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

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

type family Group a where ... Source #

Equations

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

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

type family GroupBy a a where ... Source #

Equations

GroupBy eq0 a_6989586621681185950 = Apply (Apply (Let6989586621681185959GoSym2 eq0 a_6989586621681185950) eq0) a_6989586621681185950 

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

type family GroupWith a a where ... Source #

Equations

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

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

type family GroupAllWith a a where ... Source #

Equations

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

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

type family Group1 a where ... Source #

Equations

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

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

type family GroupBy1 a a where ... Source #

Equations

GroupBy1 eq ('(:|) x xs) = Apply (Apply (:|@#@$) (Apply (Apply (:|@#@$) x) (Let6989586621681185908YsSym3 eq x xs))) (Apply (Apply GroupBySym0 eq) (Let6989586621681185908ZsSym3 eq x xs)) 

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

type family GroupWith1 a a where ... Source #

Equations

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

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

type family GroupAllWith1 a a where ... Source #

Equations

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

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

type family IsPrefixOf a a where ... Source #

Equations

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

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

type family Nub a where ... Source #

Equations

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

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

type family NubBy a a where ... Source #

Equations

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

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

type family a !! a where ... Source #

Equations

arg_6989586621681184664 !! arg_6989586621681184666 = Case_6989586621681185861 arg_6989586621681184664 arg_6989586621681184666 (Apply (Apply Tuple2Sym0 arg_6989586621681184664) arg_6989586621681184666) 

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

type family Zip a a where ... Source #

Equations

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

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

type family ZipWith a a a where ... Source #

Equations

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

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

type family Unzip a where ... Source #

Equations

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

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

type family FromList a where ... Source #

Equations

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

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

type family ToList a where ... Source #

Equations

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

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

type family NonEmpty_ a where ... Source #

Equations

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

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

type family Xor a where ... Source #

Equations

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

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

Defunctionalization symbols

data (:|@#@$) a6989586621679304206 infixr 5 Source #

Instances

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

data a6989586621679304206 :|@#@$$ a6989586621679304207 infixr 5 Source #

Instances

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

Defined in Data.Singletons.Prelude.Instances

Methods

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

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

type (:|@#@$$$) (a6989586621679304206 :: a) (a6989586621679304207 :: [a]) = '(:|) a6989586621679304206 a6989586621679304207 :: NonEmpty (a :: Type) infixr 5 Source #

data MapSym0 a6989586621681186152 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

data MapSym1 a6989586621681186152 a6989586621681186153 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

Methods

sing :: Sing (MapSym1 d) Source #

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (MapSym1 a6989586621681186152 :: TyFun (NonEmpty a) (NonEmpty b) -> Type) (a6989586621681186153 :: NonEmpty a) = MapSym2 a6989586621681186152 a6989586621681186153

type MapSym2 (a6989586621681186152 :: (~>) a b) (a6989586621681186153 :: NonEmpty a) = Map a6989586621681186152 a6989586621681186153 :: NonEmpty b Source #

data IntersperseSym0 a6989586621681186080 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

data IntersperseSym1 a6989586621681186080 a6989586621681186081 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (IntersperseSym1 a6989586621681186080 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681186081 :: NonEmpty a) = IntersperseSym2 a6989586621681186080 a6989586621681186081

type IntersperseSym2 (a6989586621681186080 :: a) (a6989586621681186081 :: NonEmpty a) = Intersperse a6989586621681186080 a6989586621681186081 :: NonEmpty a Source #

data ScanlSym0 a6989586621681186122 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

data ScanlSym1 a6989586621681186122 a6989586621681186123 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

Methods

sing :: Sing (ScanlSym1 d) Source #

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

data ScanlSym2 a6989586621681186122 a6989586621681186123 a6989586621681186124 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

Methods

sing :: Sing (ScanlSym2 d1 d2) Source #

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ScanlSym2 a6989586621681186122 a6989586621681186123 :: TyFun [a] (NonEmpty b) -> Type) (a6989586621681186124 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ScanlSym2 a6989586621681186122 a6989586621681186123 :: TyFun [a] (NonEmpty b) -> Type) (a6989586621681186124 :: [a]) = ScanlSym3 a6989586621681186122 a6989586621681186123 a6989586621681186124

type ScanlSym3 (a6989586621681186122 :: (~>) b ((~>) a b)) (a6989586621681186123 :: b) (a6989586621681186124 :: [a]) = Scanl a6989586621681186122 a6989586621681186123 a6989586621681186124 :: NonEmpty b Source #

data ScanrSym0 a6989586621681186110 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

data ScanrSym1 a6989586621681186110 a6989586621681186111 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

Methods

sing :: Sing (ScanrSym1 d) Source #

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

data ScanrSym2 a6989586621681186110 a6989586621681186111 a6989586621681186112 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

Methods

sing :: Sing (ScanrSym2 d1 d2) Source #

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ScanrSym2 a6989586621681186110 a6989586621681186111 :: TyFun [a] (NonEmpty b) -> Type) (a6989586621681186112 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ScanrSym2 a6989586621681186110 a6989586621681186111 :: TyFun [a] (NonEmpty b) -> Type) (a6989586621681186112 :: [a]) = ScanrSym3 a6989586621681186110 a6989586621681186111 a6989586621681186112

type ScanrSym3 (a6989586621681186110 :: (~>) a ((~>) b b)) (a6989586621681186111 :: b) (a6989586621681186112 :: [a]) = Scanr a6989586621681186110 a6989586621681186111 a6989586621681186112 :: NonEmpty b Source #

data Scanl1Sym0 a6989586621681186099 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

data Scanl1Sym1 a6989586621681186099 a6989586621681186100 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

Methods

sing :: Sing (Scanl1Sym1 d) Source #

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (Scanl1Sym1 a6989586621681186099 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681186100 :: NonEmpty a) = Scanl1Sym2 a6989586621681186099 a6989586621681186100

type Scanl1Sym2 (a6989586621681186099 :: (~>) a ((~>) a a)) (a6989586621681186100 :: NonEmpty a) = Scanl1 a6989586621681186099 a6989586621681186100 :: NonEmpty a Source #

data Scanr1Sym0 a6989586621681186091 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

data Scanr1Sym1 a6989586621681186091 a6989586621681186092 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

Methods

sing :: Sing (Scanr1Sym1 d) Source #

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (Scanr1Sym1 a6989586621681186091 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681186092 :: NonEmpty a) = Scanr1Sym2 a6989586621681186091 a6989586621681186092

type Scanr1Sym2 (a6989586621681186091 :: (~>) a ((~>) a a)) (a6989586621681186092 :: NonEmpty a) = Scanr1 a6989586621681186091 a6989586621681186092 :: NonEmpty a Source #

data TransposeSym0 a6989586621681185789 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (TransposeSym0 :: TyFun (NonEmpty (NonEmpty a)) (NonEmpty (NonEmpty a)) -> Type) (a6989586621681185789 :: NonEmpty (NonEmpty a)) = TransposeSym1 a6989586621681185789

type TransposeSym1 (a6989586621681185789 :: NonEmpty (NonEmpty a)) = Transpose a6989586621681185789 :: NonEmpty (NonEmpty a) Source #

data SortBySym0 a6989586621681185781 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

data SortBySym1 a6989586621681185781 a6989586621681185782 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

Methods

sing :: Sing (SortBySym1 d) Source #

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (SortBySym1 a6989586621681185781 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681185782 :: NonEmpty a) = SortBySym2 a6989586621681185781 a6989586621681185782

type SortBySym2 (a6989586621681185781 :: (~>) a ((~>) a Ordering)) (a6989586621681185782 :: NonEmpty a) = SortBy a6989586621681185781 a6989586621681185782 :: NonEmpty a Source #

data SortWithSym0 a6989586621681185772 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

data SortWithSym1 a6989586621681185772 a6989586621681185773 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

Methods

sing :: Sing (SortWithSym1 d) Source #

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (SortWithSym1 a6989586621681185772 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681185773 :: NonEmpty a) = SortWithSym2 a6989586621681185772 a6989586621681185773

type SortWithSym2 (a6989586621681185772 :: (~>) a o) (a6989586621681185773 :: NonEmpty a) = SortWith a6989586621681185772 a6989586621681185773 :: NonEmpty a Source #

data LengthSym0 a6989586621681186282 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (LengthSym0 :: TyFun (NonEmpty a) Nat -> Type) (a6989586621681186282 :: NonEmpty a) = LengthSym1 a6989586621681186282

type LengthSym1 (a6989586621681186282 :: NonEmpty a) = Length a6989586621681186282 :: Nat Source #

data HeadSym0 a6989586621681186217 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (HeadSym0 :: TyFun (NonEmpty a) a -> Type) (a6989586621681186217 :: NonEmpty a) = HeadSym1 a6989586621681186217

type HeadSym1 (a6989586621681186217 :: NonEmpty a) = Head a6989586621681186217 :: a Source #

data TailSym0 a6989586621681186213 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (TailSym0 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681186213 :: NonEmpty a) = TailSym1 a6989586621681186213

type TailSym1 (a6989586621681186213 :: NonEmpty a) = Tail a6989586621681186213 :: [a] Source #

data LastSym0 a6989586621681186208 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (LastSym0 :: TyFun (NonEmpty a) a -> Type) (a6989586621681186208 :: NonEmpty a) = LastSym1 a6989586621681186208

type LastSym1 (a6989586621681186208 :: NonEmpty a) = Last a6989586621681186208 :: a Source #

data InitSym0 a6989586621681186203 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (InitSym0 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681186203 :: NonEmpty a) = InitSym1 a6989586621681186203

type InitSym1 (a6989586621681186203 :: NonEmpty a) = Init a6989586621681186203 :: [a] Source #

data (<|@#@$) a6989586621681186196 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

data a6989586621681186196 <|@#@$$ a6989586621681186197 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

Methods

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

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

type (<|@#@$$$) (a6989586621681186196 :: a) (a6989586621681186197 :: NonEmpty a) = (<|) a6989586621681186196 a6989586621681186197 :: NonEmpty a Source #

data ConsSym0 a6989586621681186189 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

data ConsSym1 a6989586621681186189 a6989586621681186190 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

Methods

sing :: Sing (ConsSym1 d) Source #

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ConsSym1 a6989586621681186189 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681186190 :: NonEmpty a) = ConsSym2 a6989586621681186189 a6989586621681186190

type ConsSym2 (a6989586621681186189 :: a) (a6989586621681186190 :: NonEmpty a) = Cons a6989586621681186189 a6989586621681186190 :: NonEmpty a Source #

data UnconsSym0 a6989586621681186246 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (UnconsSym0 :: TyFun (NonEmpty a) (a, Maybe (NonEmpty a)) -> Type) (a6989586621681186246 :: NonEmpty a) = UnconsSym1 a6989586621681186246

type UnconsSym1 (a6989586621681186246 :: NonEmpty a) = Uncons a6989586621681186246 :: (a, Maybe (NonEmpty a)) Source #

data UnfoldrSym0 a6989586621681186222 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

data UnfoldrSym1 a6989586621681186222 a6989586621681186223 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

Methods

sing :: Sing (UnfoldrSym1 d) Source #

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (UnfoldrSym1 a6989586621681186222 :: TyFun a (NonEmpty b) -> Type) (a6989586621681186223 :: a) = UnfoldrSym2 a6989586621681186222 a6989586621681186223

type UnfoldrSym2 (a6989586621681186222 :: (~>) a (b, Maybe a)) (a6989586621681186223 :: a) = Unfoldr a6989586621681186222 a6989586621681186223 :: NonEmpty b Source #

data SortSym0 a6989586621681186180 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (SortSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681186180 :: NonEmpty a) = SortSym1 a6989586621681186180

type SortSym1 (a6989586621681186180 :: NonEmpty a) = Sort a6989586621681186180 :: NonEmpty a Source #

data ReverseSym0 a6989586621681186075 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ReverseSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681186075 :: NonEmpty a) = ReverseSym1 a6989586621681186075

type ReverseSym1 (a6989586621681186075 :: NonEmpty a) = Reverse a6989586621681186075 :: NonEmpty a Source #

data InitsSym0 a6989586621681186147 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (InitsSym0 :: TyFun [a] (NonEmpty [a]) -> Type) (a6989586621681186147 :: [a]) = InitsSym1 a6989586621681186147

type InitsSym1 (a6989586621681186147 :: [a]) = Inits a6989586621681186147 :: NonEmpty [a] Source #

data TailsSym0 a6989586621681186141 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (TailsSym0 :: TyFun [a] (NonEmpty [a]) -> Type) (a6989586621681186141 :: [a]) = TailsSym1 a6989586621681186141

type TailsSym1 (a6989586621681186141 :: [a]) = Tails a6989586621681186141 :: NonEmpty [a] Source #

data UnfoldSym0 a6989586621681186257 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

data UnfoldSym1 a6989586621681186257 a6989586621681186258 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

Methods

sing :: Sing (UnfoldSym1 d) Source #

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (UnfoldSym1 a6989586621681186257 :: TyFun a (NonEmpty b) -> Type) (a6989586621681186258 :: a)

data InsertSym0 a6989586621681186133 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

data InsertSym1 a6989586621681186133 a6989586621681186134 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

Methods

sing :: Sing (InsertSym1 d) Source #

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (InsertSym1 a6989586621681186133 :: TyFun [a] (NonEmpty a) -> Type) (a6989586621681186134 :: [a]) = InsertSym2 a6989586621681186133 a6989586621681186134

type InsertSym2 (a6989586621681186133 :: a) (a6989586621681186134 :: [a]) = Insert a6989586621681186133 a6989586621681186134 :: NonEmpty a Source #

data TakeSym0 a6989586621681186067 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

data TakeSym1 a6989586621681186067 a6989586621681186068 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

Methods

sing :: Sing (TakeSym1 d) Source #

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (TakeSym1 a6989586621681186067 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681186068 :: NonEmpty a) = TakeSym2 a6989586621681186067 a6989586621681186068

type TakeSym2 (a6989586621681186067 :: Nat) (a6989586621681186068 :: NonEmpty a) = Take a6989586621681186067 a6989586621681186068 :: [a] Source #

data DropSym0 a6989586621681186058 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

data DropSym1 a6989586621681186058 a6989586621681186059 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

Methods

sing :: Sing (DropSym1 d) Source #

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (DropSym1 a6989586621681186058 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681186059 :: NonEmpty a) = DropSym2 a6989586621681186058 a6989586621681186059

type DropSym2 (a6989586621681186058 :: Nat) (a6989586621681186059 :: NonEmpty a) = Drop a6989586621681186058 a6989586621681186059 :: [a] Source #

data SplitAtSym0 a6989586621681186049 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

data SplitAtSym1 a6989586621681186049 a6989586621681186050 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

Methods

sing :: Sing (SplitAtSym1 d) Source #

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (SplitAtSym1 a6989586621681186049 :: TyFun (NonEmpty a) ([a], [a]) -> Type) (a6989586621681186050 :: NonEmpty a) = SplitAtSym2 a6989586621681186049 a6989586621681186050

type SplitAtSym2 (a6989586621681186049 :: Nat) (a6989586621681186050 :: NonEmpty a) = SplitAt a6989586621681186049 a6989586621681186050 :: ([a], [a]) Source #

data TakeWhileSym0 a6989586621681186040 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

data TakeWhileSym1 a6989586621681186040 a6989586621681186041 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (TakeWhileSym1 a6989586621681186040 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681186041 :: NonEmpty a) = TakeWhileSym2 a6989586621681186040 a6989586621681186041

type TakeWhileSym2 (a6989586621681186040 :: (~>) a Bool) (a6989586621681186041 :: NonEmpty a) = TakeWhile a6989586621681186040 a6989586621681186041 :: [a] Source #

data DropWhileSym0 a6989586621681186031 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

data DropWhileSym1 a6989586621681186031 a6989586621681186032 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (DropWhileSym1 a6989586621681186031 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681186032 :: NonEmpty a) = DropWhileSym2 a6989586621681186031 a6989586621681186032

type DropWhileSym2 (a6989586621681186031 :: (~>) a Bool) (a6989586621681186032 :: NonEmpty a) = DropWhile a6989586621681186031 a6989586621681186032 :: [a] Source #

data SpanSym0 a6989586621681186022 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

data SpanSym1 a6989586621681186022 a6989586621681186023 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

Methods

sing :: Sing (SpanSym1 d) Source #

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (SpanSym1 a6989586621681186022 :: TyFun (NonEmpty a) ([a], [a]) -> Type) (a6989586621681186023 :: NonEmpty a) = SpanSym2 a6989586621681186022 a6989586621681186023

type SpanSym2 (a6989586621681186022 :: (~>) a Bool) (a6989586621681186023 :: NonEmpty a) = Span a6989586621681186022 a6989586621681186023 :: ([a], [a]) Source #

data BreakSym0 a6989586621681186013 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

data BreakSym1 a6989586621681186013 a6989586621681186014 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

Methods

sing :: Sing (BreakSym1 d) Source #

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (BreakSym1 a6989586621681186013 :: TyFun (NonEmpty a) ([a], [a]) -> Type) (a6989586621681186014 :: NonEmpty a) = BreakSym2 a6989586621681186013 a6989586621681186014

type BreakSym2 (a6989586621681186013 :: (~>) a Bool) (a6989586621681186014 :: NonEmpty a) = Break a6989586621681186013 a6989586621681186014 :: ([a], [a]) Source #

data FilterSym0 a6989586621681186004 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

data FilterSym1 a6989586621681186004 a6989586621681186005 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

Methods

sing :: Sing (FilterSym1 d) Source #

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (FilterSym1 a6989586621681186004 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681186005 :: NonEmpty a) = FilterSym2 a6989586621681186004 a6989586621681186005

type FilterSym2 (a6989586621681186004 :: (~>) a Bool) (a6989586621681186005 :: NonEmpty a) = Filter a6989586621681186004 a6989586621681186005 :: [a] Source #

data PartitionSym0 a6989586621681185995 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

data PartitionSym1 a6989586621681185995 a6989586621681185996 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (PartitionSym1 a6989586621681185995 :: TyFun (NonEmpty a) ([a], [a]) -> Type) (a6989586621681185996 :: NonEmpty a) = PartitionSym2 a6989586621681185995 a6989586621681185996

type PartitionSym2 (a6989586621681185995 :: (~>) a Bool) (a6989586621681185996 :: NonEmpty a) = Partition a6989586621681185995 a6989586621681185996 :: ([a], [a]) Source #

data GroupSym0 a6989586621681185988 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupSym0 :: TyFun [a] [NonEmpty a] -> Type) (a6989586621681185988 :: [a]) = GroupSym1 a6989586621681185988

type GroupSym1 (a6989586621681185988 :: [a]) = Group a6989586621681185988 :: [NonEmpty a] Source #

data GroupBySym0 a6989586621681185955 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

data GroupBySym1 a6989586621681185955 a6989586621681185956 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

Methods

sing :: Sing (GroupBySym1 d) Source #

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupBySym1 a6989586621681185955 :: TyFun [a] [NonEmpty a] -> Type) (a6989586621681185956 :: [a]) = GroupBySym2 a6989586621681185955 a6989586621681185956

type GroupBySym2 (a6989586621681185955 :: (~>) a ((~>) a Bool)) (a6989586621681185956 :: [a]) = GroupBy a6989586621681185955 a6989586621681185956 :: [NonEmpty a] Source #

data GroupWithSym0 a6989586621681185946 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

data GroupWithSym1 a6989586621681185946 a6989586621681185947 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupWithSym1 a6989586621681185946 :: TyFun [a] [NonEmpty a] -> Type) (a6989586621681185947 :: [a]) = GroupWithSym2 a6989586621681185946 a6989586621681185947

type GroupWithSym2 (a6989586621681185946 :: (~>) a b) (a6989586621681185947 :: [a]) = GroupWith a6989586621681185946 a6989586621681185947 :: [NonEmpty a] Source #

data GroupAllWithSym0 a6989586621681185937 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

data GroupAllWithSym1 a6989586621681185937 a6989586621681185938 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupAllWithSym1 a6989586621681185937 :: TyFun [a] [NonEmpty a] -> Type) (a6989586621681185938 :: [a]) = GroupAllWithSym2 a6989586621681185937 a6989586621681185938

type GroupAllWithSym2 (a6989586621681185937 :: (~>) a b) (a6989586621681185938 :: [a]) = GroupAllWith a6989586621681185937 a6989586621681185938 :: [NonEmpty a] Source #

data Group1Sym0 a6989586621681185930 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (Group1Sym0 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621681185930 :: NonEmpty a) = Group1Sym1 a6989586621681185930

type Group1Sym1 (a6989586621681185930 :: NonEmpty a) = Group1 a6989586621681185930 :: NonEmpty (NonEmpty a) Source #

data GroupBy1Sym0 a6989586621681185903 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

data GroupBy1Sym1 a6989586621681185903 a6989586621681185904 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

Methods

sing :: Sing (GroupBy1Sym1 d) Source #

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupBy1Sym1 a6989586621681185903 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621681185904 :: NonEmpty a) = GroupBy1Sym2 a6989586621681185903 a6989586621681185904

type GroupBy1Sym2 (a6989586621681185903 :: (~>) a ((~>) a Bool)) (a6989586621681185904 :: NonEmpty a) = GroupBy1 a6989586621681185903 a6989586621681185904 :: NonEmpty (NonEmpty a) Source #

data GroupWith1Sym0 a6989586621681185896 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

data GroupWith1Sym1 a6989586621681185896 a6989586621681185897 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupWith1Sym1 a6989586621681185896 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621681185897 :: NonEmpty a) = GroupWith1Sym2 a6989586621681185896 a6989586621681185897

type GroupWith1Sym2 (a6989586621681185896 :: (~>) a b) (a6989586621681185897 :: NonEmpty a) = GroupWith1 a6989586621681185896 a6989586621681185897 :: NonEmpty (NonEmpty a) Source #

data GroupAllWith1Sym0 a6989586621681185887 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

data GroupAllWith1Sym1 a6989586621681185887 a6989586621681185888 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupAllWith1Sym1 a6989586621681185887 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621681185888 :: NonEmpty a) = GroupAllWith1Sym2 a6989586621681185887 a6989586621681185888

type GroupAllWith1Sym2 (a6989586621681185887 :: (~>) a b) (a6989586621681185888 :: NonEmpty a) = GroupAllWith1 a6989586621681185887 a6989586621681185888 :: NonEmpty (NonEmpty a) Source #

data IsPrefixOfSym0 a6989586621681185876 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

data IsPrefixOfSym1 a6989586621681185876 a6989586621681185877 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (IsPrefixOfSym1 a6989586621681185876 :: TyFun (NonEmpty a) Bool -> Type) (a6989586621681185877 :: NonEmpty a) = IsPrefixOfSym2 a6989586621681185876 a6989586621681185877

type IsPrefixOfSym2 (a6989586621681185876 :: [a]) (a6989586621681185877 :: NonEmpty a) = IsPrefixOf a6989586621681185876 a6989586621681185877 :: Bool Source #

data NubSym0 a6989586621681185807 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (NubSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681185807 :: NonEmpty a) = NubSym1 a6989586621681185807

type NubSym1 (a6989586621681185807 :: NonEmpty a) = Nub a6989586621681185807 :: NonEmpty a Source #

data NubBySym0 a6989586621681185794 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

data NubBySym1 a6989586621681185794 a6989586621681185795 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

Methods

sing :: Sing (NubBySym1 d) Source #

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (NubBySym1 a6989586621681185794 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681185795 :: NonEmpty a) = NubBySym2 a6989586621681185794 a6989586621681185795

type NubBySym2 (a6989586621681185794 :: (~>) a ((~>) a Bool)) (a6989586621681185795 :: NonEmpty a) = NubBy a6989586621681185794 a6989586621681185795 :: NonEmpty a Source #

data (!!@#@$) a6989586621681185857 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

data a6989586621681185857 !!@#@$$ a6989586621681185858 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

Methods

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

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

type (!!@#@$$$) (a6989586621681185857 :: NonEmpty a) (a6989586621681185858 :: Nat) = (!!) a6989586621681185857 a6989586621681185858 :: a Source #

data ZipSym0 a6989586621681185848 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

data ZipSym1 a6989586621681185848 a6989586621681185849 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

Methods

sing :: Sing (ZipSym1 d) Source #

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ZipSym1 a6989586621681185848 :: TyFun (NonEmpty b) (NonEmpty (a, b)) -> Type) (a6989586621681185849 :: NonEmpty b) = ZipSym2 a6989586621681185848 a6989586621681185849

type ZipSym2 (a6989586621681185848 :: NonEmpty a) (a6989586621681185849 :: NonEmpty b) = Zip a6989586621681185848 a6989586621681185849 :: NonEmpty (a, b) Source #

data ZipWithSym0 a6989586621681185837 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

data ZipWithSym1 a6989586621681185837 a6989586621681185838 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

Methods

sing :: Sing (ZipWithSym1 d) Source #

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

data ZipWithSym2 a6989586621681185837 a6989586621681185838 a6989586621681185839 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

Methods

sing :: Sing (ZipWithSym2 d1 d2) Source #

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ZipWithSym2 a6989586621681185837 a6989586621681185838 :: TyFun (NonEmpty b) (NonEmpty c) -> Type) (a6989586621681185839 :: NonEmpty b) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ZipWithSym2 a6989586621681185837 a6989586621681185838 :: TyFun (NonEmpty b) (NonEmpty c) -> Type) (a6989586621681185839 :: NonEmpty b) = ZipWithSym3 a6989586621681185837 a6989586621681185838 a6989586621681185839

type ZipWithSym3 (a6989586621681185837 :: (~>) a ((~>) b c)) (a6989586621681185838 :: NonEmpty a) (a6989586621681185839 :: NonEmpty b) = ZipWith a6989586621681185837 a6989586621681185838 a6989586621681185839 :: NonEmpty c Source #

data UnzipSym0 a6989586621681185811 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (UnzipSym0 :: TyFun (NonEmpty (a, b)) (NonEmpty a, NonEmpty b) -> Type) (a6989586621681185811 :: NonEmpty (a, b)) = UnzipSym1 a6989586621681185811

type UnzipSym1 (a6989586621681185811 :: NonEmpty (a, b)) = Unzip a6989586621681185811 :: (NonEmpty a, NonEmpty b) Source #

data FromListSym0 a6989586621681186173 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (FromListSym0 :: TyFun [a] (NonEmpty a) -> Type) (a6989586621681186173 :: [a]) = FromListSym1 a6989586621681186173

type FromListSym1 (a6989586621681186173 :: [a]) = FromList a6989586621681186173 :: NonEmpty a Source #

data ToListSym0 a6989586621681186168 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ToListSym0 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681186168 :: NonEmpty a) = ToListSym1 a6989586621681186168

type ToListSym1 (a6989586621681186168 :: NonEmpty a) = ToList a6989586621681186168 :: [a] Source #

data NonEmpty_Sym0 a6989586621681186251 Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

type NonEmpty_Sym1 (a6989586621681186251 :: [a]) = NonEmpty_ a6989586621681186251 :: Maybe (NonEmpty a) Source #

data XorSym0 a6989586621681186271 Source #

Instances

Instances details
SingI XorSym0 Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

SuppressUnusedWarnings XorSym0 Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply XorSym0 (a6989586621681186271 :: NonEmpty Bool) = XorSym1 a6989586621681186271

type XorSym1 (a6989586621681186271 :: NonEmpty Bool) = Xor a6989586621681186271 :: Bool Source #

Orphan instances

SMonadZip NonEmpty Source # 
Instance details

Methods

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

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

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

PMonadZip NonEmpty Source # 
Instance details

Associated Types

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

type MzipWith arg arg arg :: m c Source #

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