singletons-2.6: 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 :: k -> Type 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.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 :: forall a. NonEmpty a -> Type where Source #

Constructors

(:%|) :: forall a (n :: a) (n :: [a]). (Sing (n :: a)) -> (Sing (n :: [a])) -> SNonEmpty ('(:|) n n) 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 b) (a :: NonEmpty a) :: NonEmpty b where ... Source #

Equations

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

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

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

Equations

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

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

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

Equations

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

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

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

Equations

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

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

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

Equations

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

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

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

Equations

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

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

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

Equations

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

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

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

Equations

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

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

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

Equations

SortWith a_6989586621681164762 a_6989586621681164764 = Apply (Apply (Apply (Apply (.@#@$) SortBySym0) ComparingSym0) a_6989586621681164762) a_6989586621681164764 

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

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

Equations

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

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

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

Equations

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

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

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

Equations

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

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

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

Equations

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

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

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

Equations

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

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

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

Equations

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

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

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

Equations

Cons a_6989586621681165169 a_6989586621681165171 = Apply (Apply (<|@#@$) a_6989586621681165169) a_6989586621681165171 

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

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

Equations

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

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

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

Equations

Unfoldr f a = Case_6989586621681165224 f a (Let6989586621681165221Scrutinee_6989586621681163721Sym2 f a) 

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

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

Equations

Sort a_6989586621681165164 = Apply (Apply LiftSym0 ListsortSym0) a_6989586621681165164 

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

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

Equations

Reverse a_6989586621681165072 = Apply (Apply LiftSym0 ListreverseSym0) a_6989586621681165072 

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

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

Equations

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

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

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

Equations

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

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

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

Equations

Unfold f a = Case_6989586621681165246 f a (Let6989586621681165243Scrutinee_6989586621681163711Sym2 f a) 

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

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

Equations

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

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

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

Equations

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

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

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

Equations

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

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

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

Equations

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

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

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

Equations

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

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

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

Equations

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

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

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

Equations

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

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

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

Equations

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

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

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

Equations

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

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

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

Equations

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

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

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

Equations

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

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

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

Equations

GroupBy eq0 a_6989586621681164951 = Apply (Apply (Let6989586621681164955GoSym2 eq0 a_6989586621681164951) eq0) a_6989586621681164951 

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

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

Equations

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

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

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

Equations

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

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

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

Equations

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

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

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

Equations

GroupBy1 eq ('(:|) x xs) = Apply (Apply (:|@#@$) (Apply (Apply (:|@#@$) x) (Let6989586621681164902YsSym3 eq x xs))) (Apply (Apply GroupBySym0 eq) (Let6989586621681164902ZsSym3 eq x xs)) 

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

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

Equations

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

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

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

Equations

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

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

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

Equations

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

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

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

Equations

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

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

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

Equations

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

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

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

Equations

arg_6989586621681163733 !! arg_6989586621681163735 = Case_6989586621681164859 arg_6989586621681163733 arg_6989586621681163735 (Apply (Apply Tuple2Sym0 arg_6989586621681163733) arg_6989586621681163735) 

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

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

Equations

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

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

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

Equations

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

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

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

Equations

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

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

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

Equations

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

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

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

Equations

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

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

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

Equations

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

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

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

Equations

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

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

Defunctionalization symbols

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

Instances

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

data (:|@#@$$) (t6989586621679315224 :: a6989586621679069776 :: Type) :: (~>) [a6989586621679069776] (NonEmpty (a6989586621679069776 :: Type)) 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 ((:|@#@$$) t6989586621679315224 :: TyFun [a6989586621679069776] (NonEmpty a6989586621679069776) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

type (:|@#@$$$) (t6989586621679315224 :: a6989586621679069776) (t6989586621679315225 :: [a6989586621679069776]) = '(:|) t6989586621679315224 t6989586621679315225 Source #

data MapSym0 :: forall a6989586621681163527 b6989586621681163528. (~>) ((~>) a6989586621681163527 b6989586621681163528) ((~>) (NonEmpty a6989586621681163527) (NonEmpty b6989586621681163528)) 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 (a6989586621681163527 ~> b6989586621681163528) (NonEmpty a6989586621681163527 ~> NonEmpty b6989586621681163528) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (MapSym0 :: TyFun (a6989586621681163527 ~> b6989586621681163528) (NonEmpty a6989586621681163527 ~> NonEmpty b6989586621681163528) -> Type) (a6989586621681165141 :: a6989586621681163527 ~> b6989586621681163528) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (MapSym0 :: TyFun (a6989586621681163527 ~> b6989586621681163528) (NonEmpty a6989586621681163527 ~> NonEmpty b6989586621681163528) -> Type) (a6989586621681165141 :: a6989586621681163527 ~> b6989586621681163528) = MapSym1 a6989586621681165141

data MapSym1 (a6989586621681165141 :: (~>) a6989586621681163527 b6989586621681163528) :: (~>) (NonEmpty a6989586621681163527) (NonEmpty b6989586621681163528) 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 a6989586621681165141 :: TyFun (NonEmpty a6989586621681163527) (NonEmpty b6989586621681163528) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (MapSym1 a6989586621681165141 :: TyFun (NonEmpty a) (NonEmpty b) -> Type) (a6989586621681165142 :: NonEmpty a) = Map a6989586621681165141 a6989586621681165142

type MapSym2 (a6989586621681165141 :: (~>) a6989586621681163527 b6989586621681163528) (a6989586621681165142 :: NonEmpty a6989586621681163527) = Map a6989586621681165141 a6989586621681165142 Source #

data IntersperseSym0 :: forall a6989586621681163517. (~>) a6989586621681163517 ((~>) (NonEmpty a6989586621681163517) (NonEmpty a6989586621681163517)) 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 a6989586621681163517 (NonEmpty a6989586621681163517 ~> NonEmpty a6989586621681163517) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (IntersperseSym0 :: TyFun a6989586621681163517 (NonEmpty a6989586621681163517 ~> NonEmpty a6989586621681163517) -> Type) (a6989586621681165077 :: a6989586621681163517) = IntersperseSym1 a6989586621681165077

data IntersperseSym1 (a6989586621681165077 :: a6989586621681163517) :: (~>) (NonEmpty a6989586621681163517) (NonEmpty a6989586621681163517) 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 a6989586621681165077 :: TyFun (NonEmpty a6989586621681163517) (NonEmpty a6989586621681163517) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (IntersperseSym1 a6989586621681165077 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681165078 :: NonEmpty a) = Intersperse a6989586621681165077 a6989586621681165078

type IntersperseSym2 (a6989586621681165077 :: a6989586621681163517) (a6989586621681165078 :: NonEmpty a6989586621681163517) = Intersperse a6989586621681165077 a6989586621681165078 Source #

data ScanlSym0 :: forall b6989586621681163522 a6989586621681163523. (~>) ((~>) b6989586621681163522 ((~>) a6989586621681163523 b6989586621681163522)) ((~>) b6989586621681163522 ((~>) [a6989586621681163523] (NonEmpty b6989586621681163522))) 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 (b6989586621681163522 ~> (a6989586621681163523 ~> b6989586621681163522)) (b6989586621681163522 ~> ([a6989586621681163523] ~> NonEmpty b6989586621681163522)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ScanlSym0 :: TyFun (b6989586621681163522 ~> (a6989586621681163523 ~> b6989586621681163522)) (b6989586621681163522 ~> ([a6989586621681163523] ~> NonEmpty b6989586621681163522)) -> Type) (a6989586621681165112 :: b6989586621681163522 ~> (a6989586621681163523 ~> b6989586621681163522)) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ScanlSym0 :: TyFun (b6989586621681163522 ~> (a6989586621681163523 ~> b6989586621681163522)) (b6989586621681163522 ~> ([a6989586621681163523] ~> NonEmpty b6989586621681163522)) -> Type) (a6989586621681165112 :: b6989586621681163522 ~> (a6989586621681163523 ~> b6989586621681163522)) = ScanlSym1 a6989586621681165112

data ScanlSym1 (a6989586621681165112 :: (~>) b6989586621681163522 ((~>) a6989586621681163523 b6989586621681163522)) :: (~>) b6989586621681163522 ((~>) [a6989586621681163523] (NonEmpty b6989586621681163522)) 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 a6989586621681165112 :: TyFun b6989586621681163522 ([a6989586621681163523] ~> NonEmpty b6989586621681163522) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ScanlSym1 a6989586621681165112 :: TyFun b6989586621681163522 ([a6989586621681163523] ~> NonEmpty b6989586621681163522) -> Type) (a6989586621681165113 :: b6989586621681163522) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ScanlSym1 a6989586621681165112 :: TyFun b6989586621681163522 ([a6989586621681163523] ~> NonEmpty b6989586621681163522) -> Type) (a6989586621681165113 :: b6989586621681163522) = ScanlSym2 a6989586621681165112 a6989586621681165113

data ScanlSym2 (a6989586621681165112 :: (~>) b6989586621681163522 ((~>) a6989586621681163523 b6989586621681163522)) (a6989586621681165113 :: b6989586621681163522) :: (~>) [a6989586621681163523] (NonEmpty b6989586621681163522) 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 a6989586621681165113 a6989586621681165112 :: TyFun [a6989586621681163523] (NonEmpty b6989586621681163522) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ScanlSym2 a6989586621681165113 a6989586621681165112 :: TyFun [a] (NonEmpty b) -> Type) (a6989586621681165114 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ScanlSym2 a6989586621681165113 a6989586621681165112 :: TyFun [a] (NonEmpty b) -> Type) (a6989586621681165114 :: [a]) = Scanl a6989586621681165113 a6989586621681165112 a6989586621681165114

type ScanlSym3 (a6989586621681165112 :: (~>) b6989586621681163522 ((~>) a6989586621681163523 b6989586621681163522)) (a6989586621681165113 :: b6989586621681163522) (a6989586621681165114 :: [a6989586621681163523]) = Scanl a6989586621681165112 a6989586621681165113 a6989586621681165114 Source #

data ScanrSym0 :: forall a6989586621681163520 b6989586621681163521. (~>) ((~>) a6989586621681163520 ((~>) b6989586621681163521 b6989586621681163521)) ((~>) b6989586621681163521 ((~>) [a6989586621681163520] (NonEmpty b6989586621681163521))) 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 (a6989586621681163520 ~> (b6989586621681163521 ~> b6989586621681163521)) (b6989586621681163521 ~> ([a6989586621681163520] ~> NonEmpty b6989586621681163521)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ScanrSym0 :: TyFun (a6989586621681163520 ~> (b6989586621681163521 ~> b6989586621681163521)) (b6989586621681163521 ~> ([a6989586621681163520] ~> NonEmpty b6989586621681163521)) -> Type) (a6989586621681165101 :: a6989586621681163520 ~> (b6989586621681163521 ~> b6989586621681163521)) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ScanrSym0 :: TyFun (a6989586621681163520 ~> (b6989586621681163521 ~> b6989586621681163521)) (b6989586621681163521 ~> ([a6989586621681163520] ~> NonEmpty b6989586621681163521)) -> Type) (a6989586621681165101 :: a6989586621681163520 ~> (b6989586621681163521 ~> b6989586621681163521)) = ScanrSym1 a6989586621681165101

data ScanrSym1 (a6989586621681165101 :: (~>) a6989586621681163520 ((~>) b6989586621681163521 b6989586621681163521)) :: (~>) b6989586621681163521 ((~>) [a6989586621681163520] (NonEmpty b6989586621681163521)) 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 a6989586621681165101 :: TyFun b6989586621681163521 ([a6989586621681163520] ~> NonEmpty b6989586621681163521) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ScanrSym1 a6989586621681165101 :: TyFun b6989586621681163521 ([a6989586621681163520] ~> NonEmpty b6989586621681163521) -> Type) (a6989586621681165102 :: b6989586621681163521) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ScanrSym1 a6989586621681165101 :: TyFun b6989586621681163521 ([a6989586621681163520] ~> NonEmpty b6989586621681163521) -> Type) (a6989586621681165102 :: b6989586621681163521) = ScanrSym2 a6989586621681165101 a6989586621681165102

data ScanrSym2 (a6989586621681165101 :: (~>) a6989586621681163520 ((~>) b6989586621681163521 b6989586621681163521)) (a6989586621681165102 :: b6989586621681163521) :: (~>) [a6989586621681163520] (NonEmpty b6989586621681163521) 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 a6989586621681165102 a6989586621681165101 :: TyFun [a6989586621681163520] (NonEmpty b6989586621681163521) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ScanrSym2 a6989586621681165102 a6989586621681165101 :: TyFun [a] (NonEmpty b) -> Type) (a6989586621681165103 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ScanrSym2 a6989586621681165102 a6989586621681165101 :: TyFun [a] (NonEmpty b) -> Type) (a6989586621681165103 :: [a]) = Scanr a6989586621681165102 a6989586621681165101 a6989586621681165103

type ScanrSym3 (a6989586621681165101 :: (~>) a6989586621681163520 ((~>) b6989586621681163521 b6989586621681163521)) (a6989586621681165102 :: b6989586621681163521) (a6989586621681165103 :: [a6989586621681163520]) = Scanr a6989586621681165101 a6989586621681165102 a6989586621681165103 Source #

data Scanl1Sym0 :: forall a6989586621681163519. (~>) ((~>) a6989586621681163519 ((~>) a6989586621681163519 a6989586621681163519)) ((~>) (NonEmpty a6989586621681163519) (NonEmpty a6989586621681163519)) 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 (a6989586621681163519 ~> (a6989586621681163519 ~> a6989586621681163519)) (NonEmpty a6989586621681163519 ~> NonEmpty a6989586621681163519) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (Scanl1Sym0 :: TyFun (a6989586621681163519 ~> (a6989586621681163519 ~> a6989586621681163519)) (NonEmpty a6989586621681163519 ~> NonEmpty a6989586621681163519) -> Type) (a6989586621681165094 :: a6989586621681163519 ~> (a6989586621681163519 ~> a6989586621681163519)) = Scanl1Sym1 a6989586621681165094

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (Scanl1Sym1 a6989586621681165094 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681165095 :: NonEmpty a) = Scanl1 a6989586621681165094 a6989586621681165095

type Scanl1Sym2 (a6989586621681165094 :: (~>) a6989586621681163519 ((~>) a6989586621681163519 a6989586621681163519)) (a6989586621681165095 :: NonEmpty a6989586621681163519) = Scanl1 a6989586621681165094 a6989586621681165095 Source #

data Scanr1Sym0 :: forall a6989586621681163518. (~>) ((~>) a6989586621681163518 ((~>) a6989586621681163518 a6989586621681163518)) ((~>) (NonEmpty a6989586621681163518) (NonEmpty a6989586621681163518)) 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 (a6989586621681163518 ~> (a6989586621681163518 ~> a6989586621681163518)) (NonEmpty a6989586621681163518 ~> NonEmpty a6989586621681163518) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (Scanr1Sym0 :: TyFun (a6989586621681163518 ~> (a6989586621681163518 ~> a6989586621681163518)) (NonEmpty a6989586621681163518 ~> NonEmpty a6989586621681163518) -> Type) (a6989586621681165087 :: a6989586621681163518 ~> (a6989586621681163518 ~> a6989586621681163518)) = Scanr1Sym1 a6989586621681165087

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (Scanr1Sym1 a6989586621681165087 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681165088 :: NonEmpty a) = Scanr1 a6989586621681165087 a6989586621681165088

type Scanr1Sym2 (a6989586621681165087 :: (~>) a6989586621681163518 ((~>) a6989586621681163518 a6989586621681163518)) (a6989586621681165088 :: NonEmpty a6989586621681163518) = Scanr1 a6989586621681165087 a6989586621681165088 Source #

data TransposeSym0 :: forall a6989586621681163483. (~>) (NonEmpty (NonEmpty a6989586621681163483)) (NonEmpty (NonEmpty a6989586621681163483)) 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 a6989586621681163483)) (NonEmpty (NonEmpty a6989586621681163483)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

type TransposeSym1 (a6989586621681164782 :: NonEmpty (NonEmpty a6989586621681163483)) = Transpose a6989586621681164782 Source #

data SortBySym0 :: forall a6989586621681163482. (~>) ((~>) a6989586621681163482 ((~>) a6989586621681163482 Ordering)) ((~>) (NonEmpty a6989586621681163482) (NonEmpty a6989586621681163482)) 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 (a6989586621681163482 ~> (a6989586621681163482 ~> Ordering)) (NonEmpty a6989586621681163482 ~> NonEmpty a6989586621681163482) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (SortBySym0 :: TyFun (a6989586621681163482 ~> (a6989586621681163482 ~> Ordering)) (NonEmpty a6989586621681163482 ~> NonEmpty a6989586621681163482) -> Type) (a6989586621681164772 :: a6989586621681163482 ~> (a6989586621681163482 ~> Ordering)) = SortBySym1 a6989586621681164772

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (SortBySym1 a6989586621681164772 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681164773 :: NonEmpty a) = SortBy a6989586621681164772 a6989586621681164773

type SortBySym2 (a6989586621681164772 :: (~>) a6989586621681163482 ((~>) a6989586621681163482 Ordering)) (a6989586621681164773 :: NonEmpty a6989586621681163482) = SortBy a6989586621681164772 a6989586621681164773 Source #

data SortWithSym0 :: forall a6989586621681163481 o6989586621681163480. (~>) ((~>) a6989586621681163481 o6989586621681163480) ((~>) (NonEmpty a6989586621681163481) (NonEmpty a6989586621681163481)) 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 (a6989586621681163481 ~> o6989586621681163480) (NonEmpty a6989586621681163481 ~> NonEmpty a6989586621681163481) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (SortWithSym0 :: TyFun (a6989586621681163481 ~> o6989586621681163480) (NonEmpty a6989586621681163481 ~> NonEmpty a6989586621681163481) -> Type) (a6989586621681164766 :: a6989586621681163481 ~> o6989586621681163480) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (SortWithSym0 :: TyFun (a6989586621681163481 ~> o6989586621681163480) (NonEmpty a6989586621681163481 ~> NonEmpty a6989586621681163481) -> Type) (a6989586621681164766 :: a6989586621681163481 ~> o6989586621681163480) = SortWithSym1 a6989586621681164766

data SortWithSym1 (a6989586621681164766 :: (~>) a6989586621681163481 o6989586621681163480) :: (~>) (NonEmpty a6989586621681163481) (NonEmpty a6989586621681163481) 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 a6989586621681164766 :: TyFun (NonEmpty a6989586621681163481) (NonEmpty a6989586621681163481) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (SortWithSym1 a6989586621681164766 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681164767 :: NonEmpty a) = SortWith a6989586621681164766 a6989586621681164767

type SortWithSym2 (a6989586621681164766 :: (~>) a6989586621681163481 o6989586621681163480) (a6989586621681164767 :: NonEmpty a6989586621681163481) = SortWith a6989586621681164766 a6989586621681164767 Source #

data LengthSym0 :: forall a6989586621681163546. (~>) (NonEmpty a6989586621681163546) Nat 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 a6989586621681163546) Nat -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

type LengthSym1 (a6989586621681165265 :: NonEmpty a6989586621681163546) = Length a6989586621681165265 Source #

data HeadSym0 :: forall a6989586621681163539. (~>) (NonEmpty a6989586621681163539) a6989586621681163539 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 a6989586621681163539) a6989586621681163539 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

type HeadSym1 (a6989586621681165197 :: NonEmpty a6989586621681163539) = Head a6989586621681165197 Source #

data TailSym0 :: forall a6989586621681163538. (~>) (NonEmpty a6989586621681163538) [a6989586621681163538] 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 a6989586621681163538) [a6989586621681163538] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

type TailSym1 (a6989586621681165194 :: NonEmpty a6989586621681163538) = Tail a6989586621681165194 Source #

data LastSym0 :: forall a6989586621681163537. (~>) (NonEmpty a6989586621681163537) a6989586621681163537 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 a6989586621681163537) a6989586621681163537 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

type LastSym1 (a6989586621681165190 :: NonEmpty a6989586621681163537) = Last a6989586621681165190 Source #

data InitSym0 :: forall a6989586621681163536. (~>) (NonEmpty a6989586621681163536) [a6989586621681163536] 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 a6989586621681163536) [a6989586621681163536] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

type InitSym1 (a6989586621681165186 :: NonEmpty a6989586621681163536) = Init a6989586621681165186 Source #

data (<|@#@$) :: forall a6989586621681163535. (~>) a6989586621681163535 ((~>) (NonEmpty a6989586621681163535) (NonEmpty a6989586621681163535)) Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

data (<|@#@$$) (a6989586621681165179 :: a6989586621681163535) :: (~>) (NonEmpty a6989586621681163535) (NonEmpty a6989586621681163535) 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 ((<|@#@$$) a6989586621681165179 :: TyFun (NonEmpty a6989586621681163535) (NonEmpty a6989586621681163535) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

type (<|@#@$$$) (a6989586621681165179 :: a6989586621681163535) (a6989586621681165180 :: NonEmpty a6989586621681163535) = (<|) a6989586621681165179 a6989586621681165180 Source #

data ConsSym0 :: forall a6989586621681163534. (~>) a6989586621681163534 ((~>) (NonEmpty a6989586621681163534) (NonEmpty a6989586621681163534)) 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 a6989586621681163534 (NonEmpty a6989586621681163534 ~> NonEmpty a6989586621681163534) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ConsSym0 :: TyFun a6989586621681163534 (NonEmpty a6989586621681163534 ~> NonEmpty a6989586621681163534) -> Type) (a6989586621681165173 :: a6989586621681163534) = ConsSym1 a6989586621681165173

data ConsSym1 (a6989586621681165173 :: a6989586621681163534) :: (~>) (NonEmpty a6989586621681163534) (NonEmpty a6989586621681163534) 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 a6989586621681165173 :: TyFun (NonEmpty a6989586621681163534) (NonEmpty a6989586621681163534) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ConsSym1 a6989586621681165173 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681165174 :: NonEmpty a) = Cons a6989586621681165173 a6989586621681165174

type ConsSym2 (a6989586621681165173 :: a6989586621681163534) (a6989586621681165174 :: NonEmpty a6989586621681163534) = Cons a6989586621681165173 a6989586621681165174 Source #

data UnconsSym0 :: forall a6989586621681163542. (~>) (NonEmpty a6989586621681163542) (a6989586621681163542, Maybe (NonEmpty a6989586621681163542)) 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 a6989586621681163542) (a6989586621681163542, Maybe (NonEmpty a6989586621681163542)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

type UnconsSym1 (a6989586621681165229 :: NonEmpty a6989586621681163542) = Uncons a6989586621681165229 Source #

data UnfoldrSym0 :: forall a6989586621681163540 b6989586621681163541. (~>) ((~>) a6989586621681163540 (b6989586621681163541, Maybe a6989586621681163540)) ((~>) a6989586621681163540 (NonEmpty b6989586621681163541)) 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 (a6989586621681163540 ~> (b6989586621681163541, Maybe a6989586621681163540)) (a6989586621681163540 ~> NonEmpty b6989586621681163541) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (UnfoldrSym0 :: TyFun (a6989586621681163540 ~> (b6989586621681163541, Maybe a6989586621681163540)) (a6989586621681163540 ~> NonEmpty b6989586621681163541) -> Type) (a6989586621681165200 :: a6989586621681163540 ~> (b6989586621681163541, Maybe a6989586621681163540)) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (UnfoldrSym0 :: TyFun (a6989586621681163540 ~> (b6989586621681163541, Maybe a6989586621681163540)) (a6989586621681163540 ~> NonEmpty b6989586621681163541) -> Type) (a6989586621681165200 :: a6989586621681163540 ~> (b6989586621681163541, Maybe a6989586621681163540)) = UnfoldrSym1 a6989586621681165200

data UnfoldrSym1 (a6989586621681165200 :: (~>) a6989586621681163540 (b6989586621681163541, Maybe a6989586621681163540)) :: (~>) a6989586621681163540 (NonEmpty b6989586621681163541) 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 a6989586621681165200 :: TyFun a6989586621681163540 (NonEmpty b6989586621681163541) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (UnfoldrSym1 a6989586621681165200 :: TyFun a (NonEmpty b) -> Type) (a6989586621681165201 :: a) = Unfoldr a6989586621681165200 a6989586621681165201

type UnfoldrSym2 (a6989586621681165200 :: (~>) a6989586621681163540 (b6989586621681163541, Maybe a6989586621681163540)) (a6989586621681165201 :: a6989586621681163540) = Unfoldr a6989586621681165200 a6989586621681165201 Source #

data SortSym0 :: forall a6989586621681163533. (~>) (NonEmpty a6989586621681163533) (NonEmpty a6989586621681163533) 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 a6989586621681163533) (NonEmpty a6989586621681163533) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

type SortSym1 (a6989586621681165166 :: NonEmpty a6989586621681163533) = Sort a6989586621681165166 Source #

data ReverseSym0 :: forall a6989586621681163516. (~>) (NonEmpty a6989586621681163516) (NonEmpty a6989586621681163516) 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 a6989586621681163516) (NonEmpty a6989586621681163516) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

type ReverseSym1 (a6989586621681165074 :: NonEmpty a6989586621681163516) = Reverse a6989586621681165074 Source #

data InitsSym0 :: forall a6989586621681163526. (~>) [a6989586621681163526] (NonEmpty [a6989586621681163526]) Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

type InitsSym1 (a6989586621681165138 :: [a6989586621681163526]) = Inits a6989586621681165138 Source #

data TailsSym0 :: forall a6989586621681163525. (~>) [a6989586621681163525] (NonEmpty [a6989586621681163525]) Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

type TailsSym1 (a6989586621681165133 :: [a6989586621681163525]) = Tails a6989586621681165133 Source #

data UnfoldSym0 :: forall a6989586621681163544 b6989586621681163545. (~>) ((~>) a6989586621681163544 (b6989586621681163545, Maybe a6989586621681163544)) ((~>) a6989586621681163544 (NonEmpty b6989586621681163545)) 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 (a6989586621681163544 ~> (b6989586621681163545, Maybe a6989586621681163544)) (a6989586621681163544 ~> NonEmpty b6989586621681163545) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (UnfoldSym0 :: TyFun (a6989586621681163544 ~> (b6989586621681163545, Maybe a6989586621681163544)) (a6989586621681163544 ~> NonEmpty b6989586621681163545) -> Type) (a6989586621681165237 :: a6989586621681163544 ~> (b6989586621681163545, Maybe a6989586621681163544)) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (UnfoldSym0 :: TyFun (a6989586621681163544 ~> (b6989586621681163545, Maybe a6989586621681163544)) (a6989586621681163544 ~> NonEmpty b6989586621681163545) -> Type) (a6989586621681165237 :: a6989586621681163544 ~> (b6989586621681163545, Maybe a6989586621681163544)) = UnfoldSym1 a6989586621681165237

data UnfoldSym1 (a6989586621681165237 :: (~>) a6989586621681163544 (b6989586621681163545, Maybe a6989586621681163544)) :: (~>) a6989586621681163544 (NonEmpty b6989586621681163545) 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 a6989586621681165237 :: TyFun a6989586621681163544 (NonEmpty b6989586621681163545) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (UnfoldSym1 a6989586621681165237 :: TyFun a (NonEmpty b) -> Type) (a6989586621681165238 :: a) = Unfold a6989586621681165237 a6989586621681165238

data InsertSym0 :: forall a6989586621681163524. (~>) a6989586621681163524 ((~>) [a6989586621681163524] (NonEmpty a6989586621681163524)) 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 a6989586621681163524 ([a6989586621681163524] ~> NonEmpty a6989586621681163524) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

data InsertSym1 (a6989586621681165123 :: a6989586621681163524) :: (~>) [a6989586621681163524] (NonEmpty a6989586621681163524) 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 a6989586621681165123 :: TyFun [a6989586621681163524] (NonEmpty a6989586621681163524) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

type InsertSym2 (a6989586621681165123 :: a6989586621681163524) (a6989586621681165124 :: [a6989586621681163524]) = Insert a6989586621681165123 a6989586621681165124 Source #

data TakeSym0 :: forall a6989586621681163515. (~>) Nat ((~>) (NonEmpty a6989586621681163515) [a6989586621681163515]) 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 a6989586621681163515 ~> [a6989586621681163515]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

data TakeSym1 (a6989586621681165064 :: Nat) :: forall a6989586621681163515. (~>) (NonEmpty a6989586621681163515) [a6989586621681163515] Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

Methods

sing :: Sing (TakeSym1 d a) Source #

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

type TakeSym2 (a6989586621681165064 :: Nat) (a6989586621681165065 :: NonEmpty a6989586621681163515) = Take a6989586621681165064 a6989586621681165065 Source #

data DropSym0 :: forall a6989586621681163514. (~>) Nat ((~>) (NonEmpty a6989586621681163514) [a6989586621681163514]) 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 a6989586621681163514 ~> [a6989586621681163514]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

data DropSym1 (a6989586621681165056 :: Nat) :: forall a6989586621681163514. (~>) (NonEmpty a6989586621681163514) [a6989586621681163514] Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

Methods

sing :: Sing (DropSym1 d a) Source #

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

type DropSym2 (a6989586621681165056 :: Nat) (a6989586621681165057 :: NonEmpty a6989586621681163514) = Drop a6989586621681165056 a6989586621681165057 Source #

data SplitAtSym0 :: forall a6989586621681163513. (~>) Nat ((~>) (NonEmpty a6989586621681163513) ([a6989586621681163513], [a6989586621681163513])) 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 a6989586621681163513 ~> ([a6989586621681163513], [a6989586621681163513])) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

data SplitAtSym1 (a6989586621681165048 :: Nat) :: forall a6989586621681163513. (~>) (NonEmpty a6989586621681163513) ([a6989586621681163513], [a6989586621681163513]) Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

Methods

sing :: Sing (SplitAtSym1 d a) Source #

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

type SplitAtSym2 (a6989586621681165048 :: Nat) (a6989586621681165049 :: NonEmpty a6989586621681163513) = SplitAt a6989586621681165048 a6989586621681165049 Source #

data TakeWhileSym0 :: forall a6989586621681163512. (~>) ((~>) a6989586621681163512 Bool) ((~>) (NonEmpty a6989586621681163512) [a6989586621681163512]) 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 (a6989586621681163512 ~> Bool) (NonEmpty a6989586621681163512 ~> [a6989586621681163512]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

type TakeWhileSym2 (a6989586621681165040 :: (~>) a6989586621681163512 Bool) (a6989586621681165041 :: NonEmpty a6989586621681163512) = TakeWhile a6989586621681165040 a6989586621681165041 Source #

data DropWhileSym0 :: forall a6989586621681163511. (~>) ((~>) a6989586621681163511 Bool) ((~>) (NonEmpty a6989586621681163511) [a6989586621681163511]) 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 (a6989586621681163511 ~> Bool) (NonEmpty a6989586621681163511 ~> [a6989586621681163511]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

type DropWhileSym2 (a6989586621681165032 :: (~>) a6989586621681163511 Bool) (a6989586621681165033 :: NonEmpty a6989586621681163511) = DropWhile a6989586621681165032 a6989586621681165033 Source #

data SpanSym0 :: forall a6989586621681163510. (~>) ((~>) a6989586621681163510 Bool) ((~>) (NonEmpty a6989586621681163510) ([a6989586621681163510], [a6989586621681163510])) 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 (a6989586621681163510 ~> Bool) (NonEmpty a6989586621681163510 ~> ([a6989586621681163510], [a6989586621681163510])) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

type SpanSym2 (a6989586621681165024 :: (~>) a6989586621681163510 Bool) (a6989586621681165025 :: NonEmpty a6989586621681163510) = Span a6989586621681165024 a6989586621681165025 Source #

data BreakSym0 :: forall a6989586621681163509. (~>) ((~>) a6989586621681163509 Bool) ((~>) (NonEmpty a6989586621681163509) ([a6989586621681163509], [a6989586621681163509])) 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 (a6989586621681163509 ~> Bool) (NonEmpty a6989586621681163509 ~> ([a6989586621681163509], [a6989586621681163509])) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

type BreakSym2 (a6989586621681165016 :: (~>) a6989586621681163509 Bool) (a6989586621681165017 :: NonEmpty a6989586621681163509) = Break a6989586621681165016 a6989586621681165017 Source #

data FilterSym0 :: forall a6989586621681163508. (~>) ((~>) a6989586621681163508 Bool) ((~>) (NonEmpty a6989586621681163508) [a6989586621681163508]) 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 (a6989586621681163508 ~> Bool) (NonEmpty a6989586621681163508 ~> [a6989586621681163508]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

type FilterSym2 (a6989586621681165008 :: (~>) a6989586621681163508 Bool) (a6989586621681165009 :: NonEmpty a6989586621681163508) = Filter a6989586621681165008 a6989586621681165009 Source #

data PartitionSym0 :: forall a6989586621681163507. (~>) ((~>) a6989586621681163507 Bool) ((~>) (NonEmpty a6989586621681163507) ([a6989586621681163507], [a6989586621681163507])) 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 (a6989586621681163507 ~> Bool) (NonEmpty a6989586621681163507 ~> ([a6989586621681163507], [a6989586621681163507])) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

type PartitionSym2 (a6989586621681165000 :: (~>) a6989586621681163507 Bool) (a6989586621681165001 :: NonEmpty a6989586621681163507) = Partition a6989586621681165000 a6989586621681165001 Source #

data GroupSym0 :: forall a6989586621681163506. (~>) [a6989586621681163506] [NonEmpty a6989586621681163506] 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 [a6989586621681163506] [NonEmpty a6989586621681163506] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

type GroupSym1 (a6989586621681164997 :: [a6989586621681163506]) = Group a6989586621681164997 Source #

data GroupBySym0 :: forall a6989586621681163505. (~>) ((~>) a6989586621681163505 ((~>) a6989586621681163505 Bool)) ((~>) [a6989586621681163505] [NonEmpty a6989586621681163505]) 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 (a6989586621681163505 ~> (a6989586621681163505 ~> Bool)) ([a6989586621681163505] ~> [NonEmpty a6989586621681163505]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

type GroupBySym2 (a6989586621681164947 :: (~>) a6989586621681163505 ((~>) a6989586621681163505 Bool)) (a6989586621681164948 :: [a6989586621681163505]) = GroupBy a6989586621681164947 a6989586621681164948 Source #

data GroupWithSym0 :: forall a6989586621681163504 b6989586621681163503. (~>) ((~>) a6989586621681163504 b6989586621681163503) ((~>) [a6989586621681163504] [NonEmpty a6989586621681163504]) 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 (a6989586621681163504 ~> b6989586621681163503) ([a6989586621681163504] ~> [NonEmpty a6989586621681163504]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupWithSym0 :: TyFun (a6989586621681163504 ~> b6989586621681163503) ([a6989586621681163504] ~> [NonEmpty a6989586621681163504]) -> Type) (a6989586621681164939 :: a6989586621681163504 ~> b6989586621681163503) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupWithSym0 :: TyFun (a6989586621681163504 ~> b6989586621681163503) ([a6989586621681163504] ~> [NonEmpty a6989586621681163504]) -> Type) (a6989586621681164939 :: a6989586621681163504 ~> b6989586621681163503) = GroupWithSym1 a6989586621681164939

data GroupWithSym1 (a6989586621681164939 :: (~>) a6989586621681163504 b6989586621681163503) :: (~>) [a6989586621681163504] [NonEmpty a6989586621681163504] 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 a6989586621681164939 :: TyFun [a6989586621681163504] [NonEmpty a6989586621681163504] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

type GroupWithSym2 (a6989586621681164939 :: (~>) a6989586621681163504 b6989586621681163503) (a6989586621681164940 :: [a6989586621681163504]) = GroupWith a6989586621681164939 a6989586621681164940 Source #

data GroupAllWithSym0 :: forall a6989586621681163502 b6989586621681163501. (~>) ((~>) a6989586621681163502 b6989586621681163501) ((~>) [a6989586621681163502] [NonEmpty a6989586621681163502]) 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 (a6989586621681163502 ~> b6989586621681163501) ([a6989586621681163502] ~> [NonEmpty a6989586621681163502]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupAllWithSym0 :: TyFun (a6989586621681163502 ~> b6989586621681163501) ([a6989586621681163502] ~> [NonEmpty a6989586621681163502]) -> Type) (a6989586621681164931 :: a6989586621681163502 ~> b6989586621681163501) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupAllWithSym0 :: TyFun (a6989586621681163502 ~> b6989586621681163501) ([a6989586621681163502] ~> [NonEmpty a6989586621681163502]) -> Type) (a6989586621681164931 :: a6989586621681163502 ~> b6989586621681163501) = GroupAllWithSym1 a6989586621681164931

data GroupAllWithSym1 (a6989586621681164931 :: (~>) a6989586621681163502 b6989586621681163501) :: (~>) [a6989586621681163502] [NonEmpty a6989586621681163502] 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 a6989586621681164931 :: TyFun [a6989586621681163502] [NonEmpty a6989586621681163502] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

type GroupAllWithSym2 (a6989586621681164931 :: (~>) a6989586621681163502 b6989586621681163501) (a6989586621681164932 :: [a6989586621681163502]) = GroupAllWith a6989586621681164931 a6989586621681164932 Source #

data Group1Sym0 :: forall a6989586621681163500. (~>) (NonEmpty a6989586621681163500) (NonEmpty (NonEmpty a6989586621681163500)) 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 a6989586621681163500) (NonEmpty (NonEmpty a6989586621681163500)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

type Group1Sym1 (a6989586621681164928 :: NonEmpty a6989586621681163500) = Group1 a6989586621681164928 Source #

data GroupBy1Sym0 :: forall a6989586621681163499. (~>) ((~>) a6989586621681163499 ((~>) a6989586621681163499 Bool)) ((~>) (NonEmpty a6989586621681163499) (NonEmpty (NonEmpty a6989586621681163499))) 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 (a6989586621681163499 ~> (a6989586621681163499 ~> Bool)) (NonEmpty a6989586621681163499 ~> NonEmpty (NonEmpty a6989586621681163499)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupBy1Sym0 :: TyFun (a6989586621681163499 ~> (a6989586621681163499 ~> Bool)) (NonEmpty a6989586621681163499 ~> NonEmpty (NonEmpty a6989586621681163499)) -> Type) (a6989586621681164895 :: a6989586621681163499 ~> (a6989586621681163499 ~> Bool)) = GroupBy1Sym1 a6989586621681164895

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupBy1Sym1 a6989586621681164895 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621681164896 :: NonEmpty a) = GroupBy1 a6989586621681164895 a6989586621681164896

type GroupBy1Sym2 (a6989586621681164895 :: (~>) a6989586621681163499 ((~>) a6989586621681163499 Bool)) (a6989586621681164896 :: NonEmpty a6989586621681163499) = GroupBy1 a6989586621681164895 a6989586621681164896 Source #

data GroupWith1Sym0 :: forall a6989586621681163498 b6989586621681163497. (~>) ((~>) a6989586621681163498 b6989586621681163497) ((~>) (NonEmpty a6989586621681163498) (NonEmpty (NonEmpty a6989586621681163498))) 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 (a6989586621681163498 ~> b6989586621681163497) (NonEmpty a6989586621681163498 ~> NonEmpty (NonEmpty a6989586621681163498)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupWith1Sym0 :: TyFun (a6989586621681163498 ~> b6989586621681163497) (NonEmpty a6989586621681163498 ~> NonEmpty (NonEmpty a6989586621681163498)) -> Type) (a6989586621681164887 :: a6989586621681163498 ~> b6989586621681163497) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupWith1Sym0 :: TyFun (a6989586621681163498 ~> b6989586621681163497) (NonEmpty a6989586621681163498 ~> NonEmpty (NonEmpty a6989586621681163498)) -> Type) (a6989586621681164887 :: a6989586621681163498 ~> b6989586621681163497) = GroupWith1Sym1 a6989586621681164887

data GroupWith1Sym1 (a6989586621681164887 :: (~>) a6989586621681163498 b6989586621681163497) :: (~>) (NonEmpty a6989586621681163498) (NonEmpty (NonEmpty a6989586621681163498)) 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 a6989586621681164887 :: TyFun (NonEmpty a6989586621681163498) (NonEmpty (NonEmpty a6989586621681163498)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupWith1Sym1 a6989586621681164887 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621681164888 :: NonEmpty a) = GroupWith1 a6989586621681164887 a6989586621681164888

type GroupWith1Sym2 (a6989586621681164887 :: (~>) a6989586621681163498 b6989586621681163497) (a6989586621681164888 :: NonEmpty a6989586621681163498) = GroupWith1 a6989586621681164887 a6989586621681164888 Source #

data GroupAllWith1Sym0 :: forall a6989586621681163496 b6989586621681163495. (~>) ((~>) a6989586621681163496 b6989586621681163495) ((~>) (NonEmpty a6989586621681163496) (NonEmpty (NonEmpty a6989586621681163496))) 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 (a6989586621681163496 ~> b6989586621681163495) (NonEmpty a6989586621681163496 ~> NonEmpty (NonEmpty a6989586621681163496)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupAllWith1Sym0 :: TyFun (a6989586621681163496 ~> b6989586621681163495) (NonEmpty a6989586621681163496 ~> NonEmpty (NonEmpty a6989586621681163496)) -> Type) (a6989586621681164879 :: a6989586621681163496 ~> b6989586621681163495) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupAllWith1Sym0 :: TyFun (a6989586621681163496 ~> b6989586621681163495) (NonEmpty a6989586621681163496 ~> NonEmpty (NonEmpty a6989586621681163496)) -> Type) (a6989586621681164879 :: a6989586621681163496 ~> b6989586621681163495) = GroupAllWith1Sym1 a6989586621681164879

data GroupAllWith1Sym1 (a6989586621681164879 :: (~>) a6989586621681163496 b6989586621681163495) :: (~>) (NonEmpty a6989586621681163496) (NonEmpty (NonEmpty a6989586621681163496)) 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 a6989586621681164879 :: TyFun (NonEmpty a6989586621681163496) (NonEmpty (NonEmpty a6989586621681163496)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (GroupAllWith1Sym1 a6989586621681164879 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621681164880 :: NonEmpty a) = GroupAllWith1 a6989586621681164879 a6989586621681164880

type GroupAllWith1Sym2 (a6989586621681164879 :: (~>) a6989586621681163496 b6989586621681163495) (a6989586621681164880 :: NonEmpty a6989586621681163496) = GroupAllWith1 a6989586621681164879 a6989586621681164880 Source #

data IsPrefixOfSym0 :: forall a6989586621681163494. (~>) [a6989586621681163494] ((~>) (NonEmpty a6989586621681163494) Bool) 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 [a6989586621681163494] (NonEmpty a6989586621681163494 ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

data IsPrefixOfSym1 (a6989586621681164871 :: [a6989586621681163494]) :: (~>) (NonEmpty a6989586621681163494) Bool 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 a6989586621681164871 :: TyFun (NonEmpty a6989586621681163494) Bool -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (IsPrefixOfSym1 a6989586621681164871 :: TyFun (NonEmpty a) Bool -> Type) (a6989586621681164872 :: NonEmpty a) = IsPrefixOf a6989586621681164871 a6989586621681164872

type IsPrefixOfSym2 (a6989586621681164871 :: [a6989586621681163494]) (a6989586621681164872 :: NonEmpty a6989586621681163494) = IsPrefixOf a6989586621681164871 a6989586621681164872 Source #

data NubSym0 :: forall a6989586621681163485. (~>) (NonEmpty a6989586621681163485) (NonEmpty a6989586621681163485) 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 a6989586621681163485) (NonEmpty a6989586621681163485) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

type NubSym1 (a6989586621681164802 :: NonEmpty a6989586621681163485) = Nub a6989586621681164802 Source #

data NubBySym0 :: forall a6989586621681163484. (~>) ((~>) a6989586621681163484 ((~>) a6989586621681163484 Bool)) ((~>) (NonEmpty a6989586621681163484) (NonEmpty a6989586621681163484)) 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 (a6989586621681163484 ~> (a6989586621681163484 ~> Bool)) (NonEmpty a6989586621681163484 ~> NonEmpty a6989586621681163484) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (NubBySym0 :: TyFun (a6989586621681163484 ~> (a6989586621681163484 ~> Bool)) (NonEmpty a6989586621681163484 ~> NonEmpty a6989586621681163484) -> Type) (a6989586621681164785 :: a6989586621681163484 ~> (a6989586621681163484 ~> Bool)) = NubBySym1 a6989586621681164785

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (NubBySym1 a6989586621681164785 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681164786 :: NonEmpty a) = NubBy a6989586621681164785 a6989586621681164786

type NubBySym2 (a6989586621681164785 :: (~>) a6989586621681163484 ((~>) a6989586621681163484 Bool)) (a6989586621681164786 :: NonEmpty a6989586621681163484) = NubBy a6989586621681164785 a6989586621681164786 Source #

data (!!@#@$) :: forall a6989586621681163493. (~>) (NonEmpty a6989586621681163493) ((~>) Nat a6989586621681163493) Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

data (!!@#@$$) (a6989586621681164853 :: NonEmpty a6989586621681163493) :: (~>) Nat a6989586621681163493 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 ((!!@#@$$) a6989586621681164853 :: TyFun Nat a6989586621681163493 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

type (!!@#@$$$) (a6989586621681164853 :: NonEmpty a6989586621681163493) (a6989586621681164854 :: Nat) = (!!) a6989586621681164853 a6989586621681164854 Source #

data ZipSym0 :: forall a6989586621681163491 b6989586621681163492. (~>) (NonEmpty a6989586621681163491) ((~>) (NonEmpty b6989586621681163492) (NonEmpty (a6989586621681163491, b6989586621681163492))) 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 a6989586621681163491) (NonEmpty b6989586621681163492 ~> NonEmpty (a6989586621681163491, b6989586621681163492)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ZipSym0 :: TyFun (NonEmpty a6989586621681163491) (NonEmpty b6989586621681163492 ~> NonEmpty (a6989586621681163491, b6989586621681163492)) -> Type) (a6989586621681164845 :: NonEmpty a6989586621681163491) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ZipSym0 :: TyFun (NonEmpty a6989586621681163491) (NonEmpty b6989586621681163492 ~> NonEmpty (a6989586621681163491, b6989586621681163492)) -> Type) (a6989586621681164845 :: NonEmpty a6989586621681163491) = ZipSym1 a6989586621681164845 b6989586621681163492 :: TyFun (NonEmpty b6989586621681163492) (NonEmpty (a6989586621681163491, b6989586621681163492)) -> Type

data ZipSym1 (a6989586621681164845 :: NonEmpty a6989586621681163491) :: forall b6989586621681163492. (~>) (NonEmpty b6989586621681163492) (NonEmpty (a6989586621681163491, b6989586621681163492)) Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

Methods

sing :: Sing (ZipSym1 d b) Source #

SuppressUnusedWarnings (ZipSym1 a6989586621681164845 b6989586621681163492 :: TyFun (NonEmpty b6989586621681163492) (NonEmpty (a6989586621681163491, b6989586621681163492)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

type ZipSym2 (a6989586621681164845 :: NonEmpty a6989586621681163491) (a6989586621681164846 :: NonEmpty b6989586621681163492) = Zip a6989586621681164845 a6989586621681164846 Source #

data ZipWithSym0 :: forall a6989586621681163488 b6989586621681163489 c6989586621681163490. (~>) ((~>) a6989586621681163488 ((~>) b6989586621681163489 c6989586621681163490)) ((~>) (NonEmpty a6989586621681163488) ((~>) (NonEmpty b6989586621681163489) (NonEmpty c6989586621681163490))) 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 (a6989586621681163488 ~> (b6989586621681163489 ~> c6989586621681163490)) (NonEmpty a6989586621681163488 ~> (NonEmpty b6989586621681163489 ~> NonEmpty c6989586621681163490)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ZipWithSym0 :: TyFun (a6989586621681163488 ~> (b6989586621681163489 ~> c6989586621681163490)) (NonEmpty a6989586621681163488 ~> (NonEmpty b6989586621681163489 ~> NonEmpty c6989586621681163490)) -> Type) (a6989586621681164834 :: a6989586621681163488 ~> (b6989586621681163489 ~> c6989586621681163490)) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ZipWithSym0 :: TyFun (a6989586621681163488 ~> (b6989586621681163489 ~> c6989586621681163490)) (NonEmpty a6989586621681163488 ~> (NonEmpty b6989586621681163489 ~> NonEmpty c6989586621681163490)) -> Type) (a6989586621681164834 :: a6989586621681163488 ~> (b6989586621681163489 ~> c6989586621681163490)) = ZipWithSym1 a6989586621681164834

data ZipWithSym1 (a6989586621681164834 :: (~>) a6989586621681163488 ((~>) b6989586621681163489 c6989586621681163490)) :: (~>) (NonEmpty a6989586621681163488) ((~>) (NonEmpty b6989586621681163489) (NonEmpty c6989586621681163490)) 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 a6989586621681164834 :: TyFun (NonEmpty a6989586621681163488) (NonEmpty b6989586621681163489 ~> NonEmpty c6989586621681163490) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ZipWithSym1 a6989586621681164834 :: TyFun (NonEmpty a6989586621681163488) (NonEmpty b6989586621681163489 ~> NonEmpty c6989586621681163490) -> Type) (a6989586621681164835 :: NonEmpty a6989586621681163488) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ZipWithSym1 a6989586621681164834 :: TyFun (NonEmpty a6989586621681163488) (NonEmpty b6989586621681163489 ~> NonEmpty c6989586621681163490) -> Type) (a6989586621681164835 :: NonEmpty a6989586621681163488) = ZipWithSym2 a6989586621681164834 a6989586621681164835

data ZipWithSym2 (a6989586621681164834 :: (~>) a6989586621681163488 ((~>) b6989586621681163489 c6989586621681163490)) (a6989586621681164835 :: NonEmpty a6989586621681163488) :: (~>) (NonEmpty b6989586621681163489) (NonEmpty c6989586621681163490) 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 a6989586621681164835 a6989586621681164834 :: TyFun (NonEmpty b6989586621681163489) (NonEmpty c6989586621681163490) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ZipWithSym2 a6989586621681164835 a6989586621681164834 :: TyFun (NonEmpty b) (NonEmpty c) -> Type) (a6989586621681164836 :: NonEmpty b) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (ZipWithSym2 a6989586621681164835 a6989586621681164834 :: TyFun (NonEmpty b) (NonEmpty c) -> Type) (a6989586621681164836 :: NonEmpty b) = ZipWith a6989586621681164835 a6989586621681164834 a6989586621681164836

type ZipWithSym3 (a6989586621681164834 :: (~>) a6989586621681163488 ((~>) b6989586621681163489 c6989586621681163490)) (a6989586621681164835 :: NonEmpty a6989586621681163488) (a6989586621681164836 :: NonEmpty b6989586621681163489) = ZipWith a6989586621681164834 a6989586621681164835 a6989586621681164836 Source #

data UnzipSym0 :: forall a6989586621681163486 b6989586621681163487. (~>) (NonEmpty (a6989586621681163486, b6989586621681163487)) (NonEmpty a6989586621681163486, NonEmpty b6989586621681163487) 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 (a6989586621681163486, b6989586621681163487)) (NonEmpty a6989586621681163486, NonEmpty b6989586621681163487) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

type Apply (UnzipSym0 :: TyFun (NonEmpty (a, b)) (NonEmpty a, NonEmpty b) -> Type) (a6989586621681164805 :: 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) (a6989586621681164805 :: NonEmpty (a, b)) = Unzip a6989586621681164805

type UnzipSym1 (a6989586621681164805 :: NonEmpty (a6989586621681163486, b6989586621681163487)) = Unzip a6989586621681164805 Source #

data FromListSym0 :: forall a6989586621681163532. (~>) [a6989586621681163532] (NonEmpty a6989586621681163532) Source #

Instances

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

type FromListSym1 (a6989586621681165160 :: [a6989586621681163532]) = FromList a6989586621681165160 Source #

data ToListSym0 :: forall a6989586621681163531. (~>) (NonEmpty a6989586621681163531) [a6989586621681163531] 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 a6989586621681163531) [a6989586621681163531] -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

type ToListSym1 (a6989586621681165156 :: NonEmpty a6989586621681163531) = ToList a6989586621681165156 Source #

data NonEmpty_Sym0 :: forall a6989586621681163543. (~>) [a6989586621681163543] (Maybe (NonEmpty a6989586621681163543)) 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 [a6989586621681163543] (Maybe (NonEmpty a6989586621681163543)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

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

Defined in Data.Singletons.Prelude.List.NonEmpty

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

type NonEmpty_Sym1 (a6989586621681165233 :: [a6989586621681163543]) = NonEmpty_ a6989586621681165233 Source #

data XorSym0 :: (~>) (NonEmpty Bool) Bool 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 (a6989586621681165252 :: NonEmpty Bool) Source # 
Instance details

Defined in Data.Singletons.Prelude.List.NonEmpty

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

type XorSym1 (a6989586621681165252 :: NonEmpty Bool) = Xor a6989586621681165252 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 #