Copyright | (C) 2013 Richard Eisenberg |
---|---|
License | BSD-style (see LICENSE) |
Maintainer | Ryan Scott |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Data.Singletons
Description
This module exports the basic definitions to use singletons. For routine
use, consider importing Prelude
, which exports constructors
for singletons based on types in the Prelude
.
You may also want to read the original papers presenting this library, available at http://cs.brynmawr.edu/~rae/papers/2012/singletons/paper.pdf and http://cs.brynmawr.edu/~rae/papers/2014/promotion/promotion.pdf.
Synopsis
- type family Sing
- newtype SLambda f = SLambda {}
- (@@) :: forall k1 k2 (f :: k1 ~> k2) (t :: k1). Sing f -> Sing t -> Sing (f @@ t)
- class SingI a where
- class SingKind k where
- type KindOf (a :: k) = k
- type SameKind a b = ()
- data SingInstance a where
- SingInstance :: SingI a => SingInstance a
- data SomeSing k where
- singInstance :: forall k (a :: k). Sing a -> SingInstance a
- pattern Sing :: forall k (a :: k). () => SingI a => Sing a
- withSingI :: Sing n -> (SingI n => r) -> r
- withSomeSing :: forall k r. SingKind k => Demote k -> (forall (a :: k). Sing a -> r) -> r
- pattern FromSing :: SingKind k => forall (a :: k). Sing a -> Demote k
- singByProxy :: SingI a => proxy a -> Sing a
- demote :: forall a. (SingKind (KindOf a), SingI a) => Demote (KindOf a)
- singByProxy# :: SingI a => Proxy# a -> Sing a
- withSing :: SingI a => (Sing a -> b) -> b
- singThat :: forall k (a :: k). (SingKind k, SingI a) => (Demote k -> Bool) -> Maybe (Sing a)
- newtype WrappedSing a where
- WrapSing :: forall k (a :: k). {..} -> WrappedSing a
- newtype SWrappedSing ws where
- SWrapSing :: forall k (a :: k) (ws :: WrappedSing a). {..} -> SWrappedSing ws
- type family UnwrapSing ws where ...
- data TyFun a b
- type (~>) a b = TyFun a b -> Type
- type TyCon1 = TyCon
- type TyCon2 = TyCon
- type TyCon3 = TyCon
- type TyCon4 = TyCon
- type TyCon5 = TyCon
- type TyCon6 = TyCon
- type TyCon7 = TyCon
- type TyCon8 = TyCon
- data family TyCon
- type family Apply f x
- type (@@) a b = Apply a b
- type family ApplyTyCon where ...
- data ApplyTyConAux1 f z
- data ApplyTyConAux2 f z
- singFun1 :: forall f. SingFunction1 f -> Sing f
- singFun2 :: forall f. SingFunction2 f -> Sing f
- singFun3 :: forall f. SingFunction3 f -> Sing f
- singFun4 :: forall f. SingFunction4 f -> Sing f
- singFun5 :: forall f. SingFunction5 f -> Sing f
- singFun6 :: forall f. SingFunction6 f -> Sing f
- singFun7 :: forall f. SingFunction7 f -> Sing f
- singFun8 :: forall f. SingFunction8 f -> Sing f
- unSingFun1 :: forall f. Sing f -> SingFunction1 f
- unSingFun2 :: forall f. Sing f -> SingFunction2 f
- unSingFun3 :: forall f. Sing f -> SingFunction3 f
- unSingFun4 :: forall f. Sing f -> SingFunction4 f
- unSingFun5 :: forall f. Sing f -> SingFunction5 f
- unSingFun6 :: forall f. Sing f -> SingFunction6 f
- unSingFun7 :: forall f. Sing f -> SingFunction7 f
- unSingFun8 :: forall f. Sing f -> SingFunction8 f
- pattern SLambda2 :: forall f. SingFunction2 f -> Sing f
- applySing2 :: forall a1 a2 b (f :: a1 ~> (a2 ~> b)). Sing f -> forall (t1 :: a1) (t2 :: a2). Sing t1 -> Sing t2 -> Sing ((f @@ t1) @@ t2)
- pattern SLambda3 :: forall f. SingFunction3 f -> Sing f
- applySing3 :: forall a1 a2 a3 b (f :: a1 ~> (a2 ~> (a3 ~> b))). Sing f -> forall (t1 :: a1) (t2 :: a2) (t3 :: a3). Sing t1 -> Sing t2 -> Sing t3 -> Sing (((f @@ t1) @@ t2) @@ t3)
- pattern SLambda4 :: forall f. SingFunction4 f -> Sing f
- applySing4 :: forall a1 a2 a3 a4 b (f :: a1 ~> (a2 ~> (a3 ~> (a4 ~> b)))). Sing f -> forall (t1 :: a1) (t2 :: a2) (t3 :: a3) (t4 :: a4). Sing t1 -> Sing t2 -> Sing t3 -> Sing t4 -> Sing ((((f @@ t1) @@ t2) @@ t3) @@ t4)
- pattern SLambda5 :: forall f. SingFunction5 f -> Sing f
- applySing5 :: forall a1 a2 a3 a4 a5 b (f :: a1 ~> (a2 ~> (a3 ~> (a4 ~> (a5 ~> b))))). Sing f -> forall (t1 :: a1) (t2 :: a2) (t3 :: a3) (t4 :: a4) (t5 :: a5). Sing t1 -> Sing t2 -> Sing t3 -> Sing t4 -> Sing t5 -> Sing (((((f @@ t1) @@ t2) @@ t3) @@ t4) @@ t5)
- pattern SLambda6 :: forall f. SingFunction6 f -> Sing f
- applySing6 :: forall a1 a2 a3 a4 a5 a6 b (f :: a1 ~> (a2 ~> (a3 ~> (a4 ~> (a5 ~> (a6 ~> b)))))). Sing f -> forall (t1 :: a1) (t2 :: a2) (t3 :: a3) (t4 :: a4) (t5 :: a5) (t6 :: a6). Sing t1 -> Sing t2 -> Sing t3 -> Sing t4 -> Sing t5 -> Sing t6 -> Sing ((((((f @@ t1) @@ t2) @@ t3) @@ t4) @@ t5) @@ t6)
- pattern SLambda7 :: forall f. SingFunction7 f -> Sing f
- applySing7 :: forall a1 a2 a3 a4 a5 a6 a7 b (f :: a1 ~> (a2 ~> (a3 ~> (a4 ~> (a5 ~> (a6 ~> (a7 ~> b))))))). Sing f -> forall (t1 :: a1) (t2 :: a2) (t3 :: a3) (t4 :: a4) (t5 :: a5) (t6 :: a6) (t7 :: a7). Sing t1 -> Sing t2 -> Sing t3 -> Sing t4 -> Sing t5 -> Sing t6 -> Sing t7 -> Sing (((((((f @@ t1) @@ t2) @@ t3) @@ t4) @@ t5) @@ t6) @@ t7)
- pattern SLambda8 :: forall f. SingFunction8 f -> Sing f
- applySing8 :: forall a1 a2 a3 a4 a5 a6 a7 a8 b (f :: a1 ~> (a2 ~> (a3 ~> (a4 ~> (a5 ~> (a6 ~> (a7 ~> (a8 ~> b)))))))). Sing f -> forall (t1 :: a1) (t2 :: a2) (t3 :: a3) (t4 :: a4) (t5 :: a5) (t6 :: a6) (t7 :: a7) (t8 :: a8). Sing t1 -> Sing t2 -> Sing t3 -> Sing t4 -> Sing t5 -> Sing t6 -> Sing t7 -> Sing t8 -> Sing ((((((((f @@ t1) @@ t2) @@ t3) @@ t4) @@ t5) @@ t6) @@ t7) @@ t8)
- type SingFunction1 f = forall t. Sing t -> Sing (f @@ t)
- type SingFunction2 f = forall t1 t2. Sing t1 -> Sing t2 -> Sing ((f @@ t1) @@ t2)
- type SingFunction3 f = forall t1 t2 t3. Sing t1 -> Sing t2 -> Sing t3 -> Sing (((f @@ t1) @@ t2) @@ t3)
- type SingFunction4 f = forall t1 t2 t3 t4. Sing t1 -> Sing t2 -> Sing t3 -> Sing t4 -> Sing ((((f @@ t1) @@ t2) @@ t3) @@ t4)
- type SingFunction5 f = forall t1 t2 t3 t4 t5. Sing t1 -> Sing t2 -> Sing t3 -> Sing t4 -> Sing t5 -> Sing (((((f @@ t1) @@ t2) @@ t3) @@ t4) @@ t5)
- type SingFunction6 f = forall t1 t2 t3 t4 t5 t6. Sing t1 -> Sing t2 -> Sing t3 -> Sing t4 -> Sing t5 -> Sing t6 -> Sing ((((((f @@ t1) @@ t2) @@ t3) @@ t4) @@ t5) @@ t6)
- type SingFunction7 f = forall t1 t2 t3 t4 t5 t6 t7. Sing t1 -> Sing t2 -> Sing t3 -> Sing t4 -> Sing t5 -> Sing t6 -> Sing t7 -> Sing (((((((f @@ t1) @@ t2) @@ t3) @@ t4) @@ t5) @@ t6) @@ t7)
- type SingFunction8 f = forall t1 t2 t3 t4 t5 t6 t7 t8. Sing t1 -> Sing t2 -> Sing t3 -> Sing t4 -> Sing t5 -> Sing t6 -> Sing t7 -> Sing t8 -> Sing ((((((((f @@ t1) @@ t2) @@ t3) @@ t4) @@ t5) @@ t6) @@ t7) @@ t8)
- data Proxy (t :: k) = Proxy
- data DemoteSym0 a6989586621681337317
- type DemoteSym1 (a6989586621681337317 :: Type) = Demote a6989586621681337317 :: Type
- data SameKindSym0 a6989586621681337319
- data SameKindSym1 a6989586621681337319 a6989586621681337320
- type SameKindSym2 (a6989586621681337319 :: k) (a6989586621681337320 :: k) = SameKind a6989586621681337319 a6989586621681337320 :: Constraint
- data KindOfSym0 a6989586621681337322
- type KindOfSym1 (a6989586621681337322 :: k) = KindOf a6989586621681337322 :: Type
- data (~>@#@$) a6989586621681337324
- data a6989586621681337324 ~>@#@$$ a6989586621681337325
- type (~>@#@$$$) (a6989586621681337324 :: Type) (a6989586621681337325 :: Type) = (~>) a6989586621681337324 a6989586621681337325 :: Type
- data ApplySym0 a6989586621681337327
- data ApplySym1 a6989586621681337327 a6989586621681337328
- type ApplySym2 (a6989586621681337327 :: (~>) k1 k2) (a6989586621681337328 :: k1) = Apply a6989586621681337327 a6989586621681337328 :: k2
- data (@@@#@$) a6989586621681337330
- data a6989586621681337330 @@@#@$$ a6989586621681337331
- type (@@@#@$$$) (a6989586621681337330 :: (~>) k1 k2) (a6989586621681337331 :: k1) = (@@) a6989586621681337330 a6989586621681337331 :: k2
Main singleton definitions
The singleton kind-indexed type family.
Instances
(@@) :: forall k1 k2 (f :: k1 ~> k2) (t :: k1). Sing f -> Sing t -> Sing (f @@ t) infixl 9 Source #
An infix synonym for applySing
A SingI
constraint is essentially an implicitly-passed singleton.
If you need to satisfy this constraint with an explicit singleton, please
see withSingI
or the Sing
pattern synonym.
Methods
Produce the singleton explicitly. You will likely need the ScopedTypeVariables
extension to use this method the way you want.
Instances
class SingKind k where Source #
The SingKind
class is a kind class. It classifies all kinds
for which singletons are defined. The class supports converting between a singleton
type and the base (unrefined) type which it is built from.
For a SingKind
instance to be well behaved, it should obey the following laws:
toSing
.fromSing
≡SomeSing
(\x ->withSomeSing
xfromSing
) ≡id
The final law can also be expressed in terms of the FromSing
pattern
synonym:
(\(FromSing
sing) ->FromSing
sing) ≡id
Associated Types
type Demote k = (r :: Type) | r -> k Source #
Get a base type from the promoted kind. For example,
Demote Bool
will be the type Bool
. Rarely, the type and kind do not
match. For example, Demote Nat
is Natural
.
Methods
fromSing :: Sing (a :: k) -> Demote k Source #
Convert a singleton to its unrefined version.
toSing :: Demote k -> SomeSing k Source #
Convert an unrefined type to an existentially-quantified singleton type.
Instances
Working with singletons
type KindOf (a :: k) = k Source #
Convenient synonym to refer to the kind of a type variable:
type KindOf (a :: k) = k
type SameKind a b = () Source #
Force GHC to unify the kinds of a
and b
. Note that SameKind a b
is
different from KindOf a ~ KindOf b
in that the former makes the kinds
unify immediately, whereas the latter is a proposition that GHC considers
as possibly false.
data SingInstance a where Source #
A SingInstance
wraps up a SingI
instance for explicit handling.
Constructors
SingInstance :: SingI a => SingInstance a |
data SomeSing k where Source #
An existentially-quantified singleton. This type is useful when you want a singleton type, but there is no way of knowing, at compile-time, what the type index will be. To make use of this type, you will generally have to use a pattern-match:
foo :: Bool -> ... foo b = case toSing b of SomeSing sb -> {- fancy dependently-typed code with sb -}
An example like the one above may be easier to write using withSomeSing
.
Instances
SBounded k => Bounded (SomeSing k) Source # | |
SEnum k => Enum (SomeSing k) Source # | |
Defined in Data.Singletons Methods succ :: SomeSing k -> SomeSing k # pred :: SomeSing k -> SomeSing k # fromEnum :: SomeSing k -> Int # enumFrom :: SomeSing k -> [SomeSing k] # enumFromThen :: SomeSing k -> SomeSing k -> [SomeSing k] # enumFromTo :: SomeSing k -> SomeSing k -> [SomeSing k] # enumFromThenTo :: SomeSing k -> SomeSing k -> SomeSing k -> [SomeSing k] # | |
SEq k => Eq (SomeSing k) Source # | |
SNum k => Num (SomeSing k) Source # | |
Defined in Data.Singletons | |
SOrd k => Ord (SomeSing k) Source # | |
ShowSing k => Show (SomeSing k) Source # | |
SIsString k => IsString (SomeSing k) Source # | |
Defined in Data.Singletons Methods fromString :: String -> SomeSing k # | |
SSemigroup k => Semigroup (SomeSing k) Source # | |
SMonoid k => Monoid (SomeSing k) Source # | |
singInstance :: forall k (a :: k). Sing a -> SingInstance a Source #
Get an implicit singleton (a SingI
instance) from an explicit one.
pattern Sing :: forall k (a :: k). () => SingI a => Sing a Source #
An explicitly bidirectional pattern synonym for implicit singletons.
As an expression: Constructs a singleton Sing a
given a
implicit singleton constraint SingI a
.
As a pattern: Matches on an explicit Sing a
witness bringing
an implicit SingI a
constraint into scope.
withSingI :: Sing n -> (SingI n => r) -> r Source #
Convenience function for creating a context with an implicit singleton available.
Arguments
:: forall k r. SingKind k | |
=> Demote k | The original datatype |
-> (forall (a :: k). Sing a -> r) | Function expecting a singleton |
-> r |
Convert a normal datatype (like Bool
) to a singleton for that datatype,
passing it into a continuation.
pattern FromSing :: SingKind k => forall (a :: k). Sing a -> Demote k Source #
An explicitly bidirectional pattern synonym for going between a singleton and the corresponding demoted term.
As an expression: this takes a singleton to its demoted (base) type.
>>>
:t FromSing \@Bool
FromSing \@Bool :: Sing a -> Bool>>>
FromSing SFalse
False
As a pattern: It extracts a singleton from its demoted (base) type.
singAnd ::Bool
->Bool
->SomeSing
Bool
singAnd (FromSing
singBool1) (FromSing
singBool2) =SomeSing
(singBool1 %&& singBool2)
instead of writing it with withSomeSing
:
singAnd bool1 bool2 =withSomeSing
bool1 $ singBool1 ->withSomeSing
bool2 $ singBool2 ->SomeSing
(singBool1 %&& singBool2)
singByProxy :: SingI a => proxy a -> Sing a Source #
Allows creation of a singleton when a proxy is at hand.
demote :: forall a. (SingKind (KindOf a), SingI a) => Demote (KindOf a) Source #
A convenience function that takes a type as input and demotes it to its
value-level counterpart as output. This uses SingKind
and SingI
behind
the scenes, so
.demote
= fromSing
sing
This function is intended to be used with TypeApplications
. For example:
>>>
demote @True
True
>>>
demote @(Nothing :: Maybe Ordering)
Nothing
singByProxy# :: SingI a => Proxy# a -> Sing a Source #
Allows creation of a singleton when a proxy#
is at hand.
withSing :: SingI a => (Sing a -> b) -> b Source #
A convenience function useful when we need to name a singleton value
multiple times. Without this function, each use of sing
could potentially
refer to a different singleton, and one has to use type signatures (often
with ScopedTypeVariables
) to ensure that they are the same.
singThat :: forall k (a :: k). (SingKind k, SingI a) => (Demote k -> Bool) -> Maybe (Sing a) Source #
A convenience function that names a singleton satisfying a certain
property. If the singleton does not satisfy the property, then the function
returns Nothing
. The property is expressed in terms of the underlying
representation of the singleton.
WrappedSing
newtype WrappedSing a where Source #
A newtype around Sing
.
Since Sing
is a type family, it cannot be used directly in type class
instances. As one example, one cannot write a catch-all
instance
. On the other hand,
SDecide
k => TestEquality
(Sing
k)WrappedSing
is a perfectly ordinary data type, which means that it is
quite possible to define an
instance
.SDecide
k => TestEquality
(WrappedSing
k)
Constructors
WrapSing | |
Fields
|
Instances
newtype SWrappedSing ws where Source #
The singleton for WrappedSing
s. Informally, this is the singleton type
for other singletons.
Constructors
SWrapSing | |
Fields
|
Instances
ShowSing k => Show (SWrappedSing ws) Source # | |
Defined in Data.Singletons.ShowSing Methods showsPrec :: Int -> SWrappedSing ws -> ShowS # show :: SWrappedSing ws -> String # showList :: [SWrappedSing ws] -> ShowS # |
type family UnwrapSing ws where ... Source #
Equations
UnwrapSing ('WrapSing s) = s |
Aside from being a data type to hang instances off of, WrappedSing
has
another purpose as a general-purpose mechanism for allowing one to write
code that uses singletons of other singletons. For instance, suppose you
had the following data type:
data T :: Type -> Type where
MkT :: forall a (x :: a). Sing
x -> F a -> T a
A naïve attempt at defining a singleton for T
would look something like
this:
data ST :: forall a. T a -> Type where SMkT :: forall a (x :: a) (sx ::Sing
x) (f :: F a).Sing
sx ->Sing
f -> ST (MkT sx f)
But there is a problem here: what exactly is
? If Sing
sxx
were True
,
for instance, then sx
would be STrue
, but it's not clear what
should be. One could define Sing
STrue
SSBool
to be the singleton of
SBool
s, but in order to be thorough, one would have to generate a singleton
for every singleton type out there. Plus, it's not clear when to stop. Should
we also generate SSSBool
, SSSSBool
, etc.?
Instead, WrappedSing
and its singleton SWrappedSing
provide a way to talk
about singletons of other arbitrary singletons without the need to generate a
bazillion instances. For reference, here is the definition of SWrappedSing
:
newtypeSWrappedSing
:: forall k (a :: k).WrappedSing
a -> Type whereSWrapSing
:: forall k (a :: k) (ws ::WrappedSing
a). {sUnwrapSing
::Sing
a } ->SWrappedSing
ws type instanceSing
@(WrappedSing
a) =SWrappedSing
SWrappedSing
is a bit of an unusual singleton in that its field is a
singleton for
, not Sing
@k
. But that's exactly the
point—a singleton of a singleton contains as much type information as the
underlying singleton itself, so we can get away with just WrappedSing
@k
.Sing
@k
As an example of this in action, here is how you would define the singleton
for the earlier T
type:
data ST :: forall a. T a -> Type where SMkT :: forall a (x :: a) (sx ::Sing
x) (f :: F a).Sing
(WrapSing
sx) ->Sing
f -> ST (MkT sx f)
With this technique, we won't need anything like SSBool
in order to
instantiate x
with True
. Instead, the field of type
will simply be a newtype around Sing
(WrapSing
sx)SBool
. In general,
you'll need n layers of WrapSing
if you wish to single a singleton n
times.
Note that this is not the only possible way to define a singleton for T
.
An alternative approach that does not make use of singletons-of-singletons is
discussed at some length
here.
Due to the technical limitations of this approach, however, we do not use it
in singletons
at the moment, instead favoring the
slightly-clunkier-but-more-reliable WrappedSing
approach.
Defunctionalization
Representation of the kind of a type-level function. The difference between term-level arrows and this type-level arrow is that at the term level applications can be unsaturated, whereas at the type level all applications have to be fully saturated.
Instances
type (~>) a b = TyFun a b -> Type infixr 0 Source #
Something of kind `a ~> b` is a defunctionalized type function that is not necessarily generative or injective.
Wrapper for converting the normal type-level arrow into a ~>
.
For example, given:
data Nat = Zero | Succ Nat type family Map (a :: a ~> b) (a :: [a]) :: [b] Map f '[] = '[] Map f (x ': xs) = Apply f x ': Map f xs
We can write:
Map (TyCon1 Succ) [Zero, Succ Zero]
Workhorse for the TyCon1
, etc., types. This can be used directly
in place of any of the TyConN
types, but it will work only with
monomorphic types. When GHC#14645 is fixed, this should fully supersede
the TyConN
types.
Instances
(forall (a :: k). SingI a => SingI (f a), (ApplyTyCon :: (k -> k_last) -> k ~> k_last) ~ (ApplyTyConAux1 :: (k -> k_last) -> TyFun k k_last -> Type)) => SingI (TyCon1 f :: k ~> k_last) Source # | |
(forall (a1 :: k2) (a2 :: k1). (SingI a1, SingI a2) => SingI (f a1 a2), (ApplyTyCon :: (k1 -> k_last) -> k1 ~> k_last) ~ (ApplyTyConAux1 :: (k1 -> k_last) -> TyFun k1 k_last -> Type)) => SingI (TyCon2 f :: k2 ~> (k1 ~> k_last)) Source # | |
(forall (a1 :: k2) (a2 :: k3) (a3 :: k1). (SingI a1, SingI a2, SingI a3) => SingI (f a1 a2 a3), (ApplyTyCon :: (k1 -> k_last) -> k1 ~> k_last) ~ (ApplyTyConAux1 :: (k1 -> k_last) -> TyFun k1 k_last -> Type)) => SingI (TyCon3 f :: k2 ~> (k3 ~> (k1 ~> k_last))) Source # | |
(forall (a1 :: k2) (a2 :: k3) (a3 :: k4) (a4 :: k1). (SingI a1, SingI a2, SingI a3, SingI a4) => SingI (f a1 a2 a3 a4), (ApplyTyCon :: (k1 -> k_last) -> k1 ~> k_last) ~ (ApplyTyConAux1 :: (k1 -> k_last) -> TyFun k1 k_last -> Type)) => SingI (TyCon4 f :: k2 ~> (k3 ~> (k4 ~> (k1 ~> k_last)))) Source # | |
(forall (a1 :: k2) (a2 :: k3) (a3 :: k4) (a4 :: k5) (a5 :: k1). (SingI a1, SingI a2, SingI a3, SingI a4, SingI a5) => SingI (f a1 a2 a3 a4 a5), (ApplyTyCon :: (k1 -> k_last) -> k1 ~> k_last) ~ (ApplyTyConAux1 :: (k1 -> k_last) -> TyFun k1 k_last -> Type)) => SingI (TyCon5 f :: k2 ~> (k3 ~> (k4 ~> (k5 ~> (k1 ~> k_last))))) Source # | |
(forall (a1 :: k2) (a2 :: k3) (a3 :: k4) (a4 :: k5) (a5 :: k6) (a6 :: k1). (SingI a1, SingI a2, SingI a3, SingI a4, SingI a5, SingI a6) => SingI (f a1 a2 a3 a4 a5 a6), (ApplyTyCon :: (k1 -> k_last) -> k1 ~> k_last) ~ (ApplyTyConAux1 :: (k1 -> k_last) -> TyFun k1 k_last -> Type)) => SingI (TyCon6 f :: k2 ~> (k3 ~> (k4 ~> (k5 ~> (k6 ~> (k1 ~> k_last)))))) Source # | |
(forall (a1 :: k2) (a2 :: k3) (a3 :: k4) (a4 :: k5) (a5 :: k6) (a6 :: k7) (a7 :: k1). (SingI a1, SingI a2, SingI a3, SingI a4, SingI a5, SingI a6, SingI a7) => SingI (f a1 a2 a3 a4 a5 a6 a7), (ApplyTyCon :: (k1 -> k_last) -> k1 ~> k_last) ~ (ApplyTyConAux1 :: (k1 -> k_last) -> TyFun k1 k_last -> Type)) => SingI (TyCon7 f :: k2 ~> (k3 ~> (k4 ~> (k5 ~> (k6 ~> (k7 ~> (k1 ~> k_last))))))) Source # | |
(forall (a1 :: k2) (a2 :: k3) (a3 :: k4) (a4 :: k5) (a5 :: k6) (a6 :: k7) (a7 :: k8) (a8 :: k1). (SingI a1, SingI a2, SingI a3, SingI a4, SingI a5, SingI a6, SingI a7, SingI a8) => SingI (f a1 a2 a3 a4 a5 a6 a7 a8), (ApplyTyCon :: (k1 -> k_last) -> k1 ~> k_last) ~ (ApplyTyConAux1 :: (k1 -> k_last) -> TyFun k1 k_last -> Type)) => SingI (TyCon8 f :: k2 ~> (k3 ~> (k4 ~> (k5 ~> (k6 ~> (k7 ~> (k8 ~> (k1 ~> k_last)))))))) Source # | |
type Apply (TyCon f :: k1 ~> k5) (x :: k1) Source # | |
Defined in Data.Singletons.Internal |
type family Apply f x Source #
Type level function application
Instances
type Apply NotSym0 (a6989586621679367240 :: Bool) Source # | |
Defined in Data.Singletons.Prelude.Bool | |
type Apply AllSym0 (a6989586621679840130 :: Bool) Source # | |
Defined in Data.Singletons.Prelude.Semigroup.Internal | |
type Apply AnySym0 (a6989586621679840147 :: Bool) Source # | |
Defined in Data.Singletons.Prelude.Semigroup.Internal | |
type Apply DemoteSym0 (a6989586621681337317 :: Type) Source # | |
Defined in Data.Singletons | |
type Apply KnownNatSym0 (a6989586621679491988 :: Nat) Source # | |
Defined in Data.Singletons.TypeLits | |
type Apply Log2Sym0 (a6989586621679492472 :: Nat) Source # | |
Defined in Data.Singletons.TypeLits | |
type Apply KnownSymbolSym0 (a6989586621679491990 :: Symbol) Source # | |
Defined in Data.Singletons.TypeLits | |
type Apply ShowSpaceSym0 (a6989586621680279495 :: Symbol) Source # | |
Defined in Data.Singletons.Prelude.Show | |
type Apply ShowCommaSpaceSym0 (a6989586621680279489 :: Symbol) Source # | |
Defined in Data.Singletons.Prelude.Show type Apply ShowCommaSpaceSym0 (a6989586621680279489 :: Symbol) = ShowCommaSpaceSym1 a6989586621680279489 | |
type Apply GetAllSym0 (a6989586621679840133 :: All) Source # | |
Defined in Data.Singletons.Prelude.Semigroup.Internal | |
type Apply GetAnySym0 (a6989586621679840150 :: Any) Source # | |
Defined in Data.Singletons.Prelude.Semigroup.Internal | |
type Apply ((&&@#@$$) a6989586621679366665 :: TyFun Bool Bool -> Type) (a6989586621679366666 :: Bool) Source # | |
type Apply ((||@#@$$) a6989586621679366963 :: TyFun Bool Bool -> Type) (a6989586621679366964 :: Bool) Source # | |
type Apply (ThenCmpSym1 a6989586621679394586 :: TyFun Ordering Ordering -> Type) (a6989586621679394587 :: Ordering) Source # | |
Defined in Data.Singletons.Prelude.Ord type Apply (ThenCmpSym1 a6989586621679394586 :: TyFun Ordering Ordering -> Type) (a6989586621679394587 :: Ordering) = ThenCmpSym2 a6989586621679394586 a6989586621679394587 | |
type Apply ((~>@#@$$) a6989586621681337324 :: TyFun Type Type -> Type) (a6989586621681337325 :: Type) Source # | |
type Apply ((<=?@#@$$) a6989586621679473158 :: TyFun Nat Bool -> Type) (a6989586621679473159 :: Nat) Source # | |
Defined in Data.Singletons.TypeLits.Internal | |
type Apply ((^@#@$$) a6989586621679472866 :: TyFun Nat Nat -> Type) (a6989586621679472867 :: Nat) Source # | |
type Apply (DivSym1 a6989586621679492680 :: TyFun Nat Nat -> Type) (a6989586621679492681 :: Nat) Source # | |
type Apply (ModSym1 a6989586621679493016 :: TyFun Nat Nat -> Type) (a6989586621679493017 :: Nat) Source # | |
type Apply (QuotSym1 a6989586621679493492 :: TyFun Nat Nat -> Type) (a6989586621679493493 :: Nat) Source # | |
type Apply (RemSym1 a6989586621679493481 :: TyFun Nat Nat -> Type) (a6989586621679493482 :: Nat) Source # | |
type Apply (FromIntegerSym0 :: TyFun Nat k2 -> Type) (a6989586621679517819 :: Nat) Source # | |
Defined in Data.Singletons.Prelude.Num type Apply (FromIntegerSym0 :: TyFun Nat k2 -> Type) (a6989586621679517819 :: Nat) = FromIntegerSym1 a6989586621679517819 :: k2 | |
type Apply (ToEnumSym0 :: TyFun Nat k2 -> Type) (a6989586621679758475 :: Nat) Source # | |
Defined in Data.Singletons.Prelude.Enum type Apply (ToEnumSym0 :: TyFun Nat k2 -> Type) (a6989586621679758475 :: Nat) = ToEnumSym1 a6989586621679758475 :: k2 | |
type Apply (ShowCharSym1 a6989586621680279534 :: TyFun Symbol Symbol -> Type) (a6989586621680279535 :: Symbol) Source # | |
Defined in Data.Singletons.Prelude.Show type Apply (ShowCharSym1 a6989586621680279534 :: TyFun Symbol Symbol -> Type) (a6989586621680279535 :: Symbol) = ShowCharSym2 a6989586621680279534 a6989586621680279535 | |
type Apply (ShowStringSym1 a6989586621680279523 :: TyFun Symbol Symbol -> Type) (a6989586621680279524 :: Symbol) Source # | |
Defined in Data.Singletons.Prelude.Show type Apply (ShowStringSym1 a6989586621680279523 :: TyFun Symbol Symbol -> Type) (a6989586621680279524 :: Symbol) = ShowStringSym2 a6989586621680279523 a6989586621680279524 | |
type Apply (FromStringSym0 :: TyFun Symbol k2 -> Type) (a6989586621681280469 :: Symbol) Source # | |
Defined in Data.Singletons.Prelude.IsString type Apply (FromStringSym0 :: TyFun Symbol k2 -> Type) (a6989586621681280469 :: Symbol) = FromStringSym1 a6989586621681280469 :: k2 | |
type Apply (NegateSym0 :: TyFun a a -> Type) (a6989586621679517810 :: a) Source # | |
Defined in Data.Singletons.Prelude.Num type Apply (NegateSym0 :: TyFun a a -> Type) (a6989586621679517810 :: a) = NegateSym1 a6989586621679517810 | |
type Apply (SignumSym0 :: TyFun a a -> Type) (a6989586621679517816 :: a) Source # | |
Defined in Data.Singletons.Prelude.Num type Apply (SignumSym0 :: TyFun a a -> Type) (a6989586621679517816 :: a) = SignumSym1 a6989586621679517816 | |
type Apply (AbsSym0 :: TyFun a a -> Type) (a6989586621679517813 :: a) Source # | |
type Apply (IdSym0 :: TyFun a a -> Type) (a6989586621679534205 :: a) Source # | |
type Apply (FromEnumSym0 :: TyFun a Nat -> Type) (a6989586621679758478 :: a) Source # | |
Defined in Data.Singletons.Prelude.Enum type Apply (FromEnumSym0 :: TyFun a Nat -> Type) (a6989586621679758478 :: a) = FromEnumSym1 a6989586621679758478 | |
type Apply (PredSym0 :: TyFun a a -> Type) (a6989586621679758472 :: a) Source # | |
type Apply (SuccSym0 :: TyFun a a -> Type) (a6989586621679758469 :: a) Source # | |
type Apply (Show_Sym0 :: TyFun a Symbol -> Type) (a6989586621680279573 :: a) Source # | |
type Apply (KindOfSym0 :: TyFun k Type -> Type) (a6989586621681337322 :: k) Source # | |
Defined in Data.Singletons type Apply (KindOfSym0 :: TyFun k Type -> Type) (a6989586621681337322 :: k) = KindOfSym1 a6989586621681337322 | |
type Apply (AbsurdSym0 :: TyFun Void k2 -> Type) (a6989586621679359469 :: Void) Source # | |
Defined in Data.Singletons.Prelude.Void type Apply (AbsurdSym0 :: TyFun Void k2 -> Type) (a6989586621679359469 :: Void) = AbsurdSym1 a6989586621679359469 :: k2 | |
type Apply (TypeErrorSym0 :: TyFun PErrorMessage k2 -> Type) (a6989586621681349593 :: PErrorMessage) Source # | |
Defined in Data.Singletons.TypeError type Apply (TypeErrorSym0 :: TyFun PErrorMessage k2 -> Type) (a6989586621681349593 :: PErrorMessage) = TypeErrorSym1 a6989586621681349593 :: k2 | |
type Apply ((!!@#@$$) a6989586621679968875 :: TyFun Nat a -> Type) (a6989586621679968876 :: Nat) Source # | |
type Apply ((!!@#@$$) a6989586621681185857 :: TyFun Nat a -> Type) (a6989586621681185858 :: Nat) Source # | |
type Apply (ShowListSym1 a6989586621680279577 :: TyFun Symbol Symbol -> Type) (a6989586621680279578 :: Symbol) Source # | |
Defined in Data.Singletons.Prelude.Show type Apply (ShowListSym1 a6989586621680279577 :: TyFun Symbol Symbol -> Type) (a6989586621680279578 :: Symbol) = ShowListSym2 a6989586621680279577 a6989586621680279578 | |
type Apply (ShowsSym1 a6989586621680279560 :: TyFun Symbol Symbol -> Type) (a6989586621680279561 :: Symbol) Source # | |
type Apply (ShowParenSym2 a6989586621680279507 a6989586621680279508 :: TyFun Symbol Symbol -> Type) (a6989586621680279509 :: Symbol) Source # | |
Defined in Data.Singletons.Prelude.Show | |
type Apply ((==@#@$$) a6989586621679370055 :: TyFun a Bool -> Type) (a6989586621679370056 :: a) Source # | |
type Apply ((/=@#@$$) a6989586621679370058 :: TyFun a Bool -> Type) (a6989586621679370059 :: a) Source # | |
type Apply (DefaultEqSym1 a6989586621679370061 :: TyFun k Bool -> Type) (a6989586621679370062 :: k) Source # | |
Defined in Data.Singletons.Prelude.Eq type Apply (DefaultEqSym1 a6989586621679370061 :: TyFun k Bool -> Type) (a6989586621679370062 :: k) = DefaultEqSym2 a6989586621679370061 a6989586621679370062 | |
type Apply ((<=@#@$$) a6989586621679383650 :: TyFun a Bool -> Type) (a6989586621679383651 :: a) Source # | |
type Apply (CompareSym1 a6989586621679383640 :: TyFun a Ordering -> Type) (a6989586621679383641 :: a) Source # | |
Defined in Data.Singletons.Prelude.Ord type Apply (CompareSym1 a6989586621679383640 :: TyFun a Ordering -> Type) (a6989586621679383641 :: a) = CompareSym2 a6989586621679383640 a6989586621679383641 | |
type Apply (MinSym1 a6989586621679383670 :: TyFun a a -> Type) (a6989586621679383671 :: a) Source # | |
type Apply (MaxSym1 a6989586621679383665 :: TyFun a a -> Type) (a6989586621679383666 :: a) Source # | |
type Apply ((>=@#@$$) a6989586621679383660 :: TyFun a Bool -> Type) (a6989586621679383661 :: a) Source # | |
type Apply ((>@#@$$) a6989586621679383655 :: TyFun a Bool -> Type) (a6989586621679383656 :: a) Source # | |
type Apply ((<@#@$$) a6989586621679383645 :: TyFun a Bool -> Type) (a6989586621679383646 :: a) Source # | |
type Apply (ErrorSym0 :: TyFun k0 k2 -> Type) (a6989586621679472252 :: k0) Source # | |
type Apply (ErrorWithoutStackTraceSym0 :: TyFun k0 k2 -> Type) (a6989586621679472488 :: k0) Source # | |
Defined in Data.Singletons.TypeLits.Internal type Apply (ErrorWithoutStackTraceSym0 :: TyFun k0 k2 -> Type) (a6989586621679472488 :: k0) = ErrorWithoutStackTraceSym1 a6989586621679472488 :: k2 | |
type Apply ((-@#@$$) a6989586621679517801 :: TyFun a a -> Type) (a6989586621679517802 :: a) Source # | |
type Apply ((+@#@$$) a6989586621679517796 :: TyFun a a -> Type) (a6989586621679517797 :: a) Source # | |
type Apply ((*@#@$$) a6989586621679517806 :: TyFun a a -> Type) (a6989586621679517807 :: a) Source # | |
type Apply (SubtractSym1 a6989586621679517789 :: TyFun a a -> Type) (a6989586621679517790 :: a) Source # | |
Defined in Data.Singletons.Prelude.Num type Apply (SubtractSym1 a6989586621679517789 :: TyFun a a -> Type) (a6989586621679517790 :: a) = SubtractSym2 a6989586621679517789 a6989586621679517790 | |
type Apply (AsTypeOfSym1 a6989586621679534167 :: TyFun a a -> Type) (a6989586621679534168 :: a) Source # | |
Defined in Data.Singletons.Prelude.Base type Apply (AsTypeOfSym1 a6989586621679534167 :: TyFun a a -> Type) (a6989586621679534168 :: a) = AsTypeOfSym2 a6989586621679534167 a6989586621679534168 | |
type Apply ((<>@#@$$) a6989586621679830624 :: TyFun a a -> Type) (a6989586621679830625 :: a) Source # | |
type Apply (MappendSym1 a6989586621680347244 :: TyFun a a -> Type) (a6989586621680347245 :: a) Source # | |
Defined in Data.Singletons.Prelude.Monoid type Apply (MappendSym1 a6989586621680347244 :: TyFun a a -> Type) (a6989586621680347245 :: a) = MappendSym2 a6989586621680347244 a6989586621680347245 | |
type Apply (SameKindSym1 a6989586621681337319 :: TyFun k Constraint -> Type) (a6989586621681337320 :: k) Source # | |
Defined in Data.Singletons type Apply (SameKindSym1 a6989586621681337319 :: TyFun k Constraint -> Type) (a6989586621681337320 :: k) = SameKindSym2 a6989586621681337319 a6989586621681337320 | |
type Apply (Bool_Sym2 a6989586621679365865 a6989586621679365866 :: TyFun Bool a -> Type) (a6989586621679365867 :: Bool) Source # | |
type Apply (ShowsPrecSym2 a6989586621680279568 a6989586621680279569 :: TyFun Symbol Symbol -> Type) (a6989586621680279570 :: Symbol) Source # | |
Defined in Data.Singletons.Prelude.Show type Apply (ShowsPrecSym2 a6989586621680279568 a6989586621680279569 :: TyFun Symbol Symbol -> Type) (a6989586621680279570 :: Symbol) = ShowsPrecSym3 a6989586621680279568 a6989586621680279569 a6989586621680279570 | |
type Apply (ShowListWithSym2 a6989586621680279542 a6989586621680279543 :: TyFun Symbol Symbol -> Type) (a6989586621680279544 :: Symbol) Source # | |
Defined in Data.Singletons.Prelude.Show type Apply (ShowListWithSym2 a6989586621680279542 a6989586621680279543 :: TyFun Symbol Symbol -> Type) (a6989586621680279544 :: Symbol) = ShowListWithSym3 a6989586621680279542 a6989586621680279543 a6989586621680279544 | |
type Apply (ApplyTyConAux1 f :: TyFun k1 k2 -> Type) (x :: k1) Source # | |
Defined in Data.Singletons.Internal | |
type Apply (SeqSym1 a6989586621679534120 :: TyFun b b -> Type) (a6989586621679534121 :: b) Source # | |
type Apply (UntilSym2 a6989586621679534129 a6989586621679534130 :: TyFun a a -> Type) (a6989586621679534131 :: a) Source # | |
type Apply (($!@#@$$) a6989586621679534147 :: TyFun a b -> Type) (a6989586621679534148 :: a) Source # | |
type Apply (($@#@$$) a6989586621679534156 :: TyFun a b -> Type) (a6989586621679534157 :: a) Source # | |
type Apply (ConstSym1 a6989586621679534200 :: TyFun b a -> Type) (a6989586621679534201 :: b) Source # | |
type Apply (ApplySym1 a6989586621681337327 :: TyFun k1 k2 -> Type) (a6989586621681337328 :: k1) Source # | |
type Apply ((@@@#@$$) a6989586621681337330 :: TyFun k1 k2 -> Type) (a6989586621681337331 :: k1) Source # | |
type Apply (TyCon f :: k1 ~> k5) (x :: k1) Source # | |
Defined in Data.Singletons.Internal | |
type Apply (ComparingSym2 a6989586621679383631 a6989586621679383632 :: TyFun b Ordering -> Type) (a6989586621679383633 :: b) Source # | |
Defined in Data.Singletons.Prelude.Ord type Apply (ComparingSym2 a6989586621679383631 a6989586621679383632 :: TyFun b Ordering -> Type) (a6989586621679383633 :: b) = ComparingSym3 a6989586621679383631 a6989586621679383632 a6989586621679383633 | |
type Apply (ApplyTyConAux2 f :: TyFun k4 k7 -> Type) (x :: k4) Source # | |
Defined in Data.Singletons.Internal | |
type Apply (CurrySym2 a6989586621679360434 a6989586621679360435 :: TyFun b c -> Type) (a6989586621679360436 :: b) Source # | |
type Apply (FlipSym2 a6989586621679534175 a6989586621679534176 :: TyFun a c -> Type) (a6989586621679534177 :: a) Source # | |
type Apply (a6989586621679534187 .@#@$$$ a6989586621679534188 :: TyFun a c -> Type) (a6989586621679534189 :: a) Source # | |
type Apply (OnSym3 a6989586621679747423 a6989586621679747424 a6989586621679747425 :: TyFun a c -> Type) (a6989586621679747426 :: a) Source # | |
type Apply (GuardSym0 :: TyFun Bool (f ()) -> Type) (a6989586621679559466 :: Bool) Source # | |
type Apply (JustSym0 :: TyFun a (Maybe a) -> Type) (a6989586621679304113 :: a) Source # | |
type Apply (IdentitySym0 :: TyFun a (Identity a) -> Type) (a6989586621679304610 :: a) Source # | |
Defined in Data.Singletons.Prelude.Instances type Apply (IdentitySym0 :: TyFun a (Identity a) -> Type) (a6989586621679304610 :: a) = IdentitySym1 a6989586621679304610 | |
type Apply (DownSym0 :: TyFun a (Down a) -> Type) (a6989586621679393010 :: a) Source # | |
type Apply (DualSym0 :: TyFun a (Dual a) -> Type) (a6989586621679840113 :: a) Source # | |
type Apply (SumSym0 :: TyFun a (Sum a) -> Type) (a6989586621679840169 :: a) Source # | |
type Apply (ProductSym0 :: TyFun a (Product a) -> Type) (a6989586621679840191 :: a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup.Internal type Apply (ProductSym0 :: TyFun a (Product a) -> Type) (a6989586621679840191 :: a) = ProductSym1 a6989586621679840191 | |
type Apply (MinSym0 :: TyFun a (Min a) -> Type) (a6989586621679840213 :: a) Source # | |
type Apply (MaxSym0 :: TyFun a (Max a) -> Type) (a6989586621679840235 :: a) Source # | |
type Apply (FirstSym0 :: TyFun a (First a) -> Type) (a6989586621679840257 :: a) Source # | |
type Apply (LastSym0 :: TyFun a (Last a) -> Type) (a6989586621679840279 :: a) Source # | |
type Apply (WrapMonoidSym0 :: TyFun m (WrappedMonoid m) -> Type) (a6989586621679840301 :: m) Source # | |
Defined in Data.Singletons.Prelude.Semigroup.Internal type Apply (WrapMonoidSym0 :: TyFun m (WrappedMonoid m) -> Type) (a6989586621679840301 :: m) = WrapMonoidSym1 a6989586621679840301 | |
type Apply (TextSym0 :: TyFun s (ErrorMessage' s) -> Type) (a6989586621681349583 :: s) Source # | |
Defined in Data.Singletons.TypeError | |
type Apply (PureSym0 :: TyFun a (f a) -> Type) (a6989586621679559691 :: a) Source # | |
type Apply (ReturnSym0 :: TyFun a (m a) -> Type) (a6989586621679559784 :: a) Source # | |
Defined in Data.Singletons.Prelude.Monad.Internal type Apply (ReturnSym0 :: TyFun a (m a) -> Type) (a6989586621679559784 :: a) = ReturnSym1 a6989586621679559784 :: m a | |
type Apply (EnumFromToSym1 a6989586621679758482 :: TyFun a [a] -> Type) (a6989586621679758483 :: a) Source # | |
Defined in Data.Singletons.Prelude.Enum type Apply (EnumFromToSym1 a6989586621679758482 :: TyFun a [a] -> Type) (a6989586621679758483 :: a) = EnumFromToSym2 a6989586621679758482 a6989586621679758483 | |
type Apply (ReplicateSym1 a6989586621679968895 :: TyFun a [a] -> Type) (a6989586621679968896 :: a) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ReplicateSym1 a6989586621679968895 :: TyFun a [a] -> Type) (a6989586621679968896 :: a) = ReplicateSym2 a6989586621679968895 a6989586621679968896 | |
type Apply (ShowTypeSym0 :: TyFun t (ErrorMessage' s) -> Type) (a6989586621681349585 :: t) Source # | |
Defined in Data.Singletons.TypeError type Apply (ShowTypeSym0 :: TyFun t (ErrorMessage' s) -> Type) (a6989586621681349585 :: t) = ShowTypeSym1 a6989586621681349585 :: ErrorMessage' s | |
type Apply (EnumFromThenToSym2 a6989586621679758488 a6989586621679758489 :: TyFun a [a] -> Type) (a6989586621679758490 :: a) Source # | |
Defined in Data.Singletons.Prelude.Enum type Apply (EnumFromThenToSym2 a6989586621679758488 a6989586621679758489 :: TyFun a [a] -> Type) (a6989586621679758490 :: a) = EnumFromThenToSym3 a6989586621679758488 a6989586621679758489 a6989586621679758490 | |
type Apply (UnfoldrSym1 a6989586621679969650 :: TyFun b [a] -> Type) (a6989586621679969651 :: b) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (UnfoldrSym1 a6989586621679969650 :: TyFun b [a] -> Type) (a6989586621679969651 :: b) = UnfoldrSym2 a6989586621679969650 a6989586621679969651 | |
type Apply (UnfoldrSym1 a6989586621681186222 :: TyFun a (NonEmpty b) -> Type) (a6989586621681186223 :: a) Source # | |
Defined in Data.Singletons.Prelude.List.NonEmpty type Apply (UnfoldrSym1 a6989586621681186222 :: TyFun a (NonEmpty b) -> Type) (a6989586621681186223 :: a) = UnfoldrSym2 a6989586621681186222 a6989586621681186223 | |
type Apply (UnfoldSym1 a6989586621681186257 :: TyFun a (NonEmpty b) -> Type) (a6989586621681186258 :: a) Source # | |
Defined in Data.Singletons.Prelude.List.NonEmpty type Apply (UnfoldSym1 a6989586621681186257 :: TyFun a (NonEmpty b) -> Type) (a6989586621681186258 :: a) | |
type Apply (($>@#@$$) a6989586621679731612 :: TyFun b (f b) -> Type) (a6989586621679731613 :: b) Source # | |
type Apply (a6989586621681292383 >=>@#@$$$ a6989586621681292384 :: TyFun a (m c) -> Type) (a6989586621681292385 :: a) Source # | |
Defined in Data.Singletons.Prelude.Monad | |
type Apply (a6989586621681292371 <=<@#@$$$ a6989586621681292372 :: TyFun a (m c) -> Type) (a6989586621681292373 :: a) Source # | |
Defined in Data.Singletons.Prelude.Monad | |
type Apply (&&@#@$) (a6989586621679366665 :: Bool) Source # | |
Defined in Data.Singletons.Prelude.Bool | |
type Apply (||@#@$) (a6989586621679366963 :: Bool) Source # | |
Defined in Data.Singletons.Prelude.Bool | |
type Apply ShowParenSym0 (a6989586621680279507 :: Bool) Source # | |
Defined in Data.Singletons.Prelude.Show | |
type Apply ThenCmpSym0 (a6989586621679394586 :: Ordering) Source # | |
Defined in Data.Singletons.Prelude.Ord | |
type Apply (~>@#@$) (a6989586621681337324 :: Type) Source # | |
Defined in Data.Singletons | |
type Apply (<=?@#@$) (a6989586621679473158 :: Nat) Source # | |
Defined in Data.Singletons.TypeLits.Internal | |
type Apply (^@#@$) (a6989586621679472866 :: Nat) Source # | |
Defined in Data.Singletons.TypeLits.Internal | |
type Apply DivSym0 (a6989586621679492680 :: Nat) Source # | |
Defined in Data.Singletons.TypeLits | |
type Apply ModSym0 (a6989586621679493016 :: Nat) Source # | |
Defined in Data.Singletons.TypeLits | |
type Apply QuotSym0 (a6989586621679493492 :: Nat) Source # | |
Defined in Data.Singletons.TypeLits | |
type Apply RemSym0 (a6989586621679493481 :: Nat) Source # | |
Defined in Data.Singletons.TypeLits | |
type Apply DivModSym0 (a6989586621679493510 :: Nat) Source # | |
Defined in Data.Singletons.TypeLits | |
type Apply QuotRemSym0 (a6989586621679493503 :: Nat) Source # | |
Defined in Data.Singletons.TypeLits | |
type Apply ShowCharSym0 (a6989586621680279534 :: Symbol) Source # | |
Defined in Data.Singletons.Prelude.Show | |
type Apply ShowStringSym0 (a6989586621680279523 :: Symbol) Source # | |
Defined in Data.Singletons.Prelude.Show | |
type Apply (WhenSym0 :: TyFun Bool (f () ~> f ()) -> Type) (a6989586621679559610 :: Bool) Source # | |
type Apply (UnlessSym0 :: TyFun Bool (f () ~> f ()) -> Type) (a6989586621681292265 :: Bool) Source # | |
Defined in Data.Singletons.Prelude.Monad type Apply (UnlessSym0 :: TyFun Bool (f () ~> f ()) -> Type) (a6989586621681292265 :: Bool) = UnlessSym1 a6989586621681292265 :: TyFun (f ()) (f ()) -> Type | |
type Apply (DivModSym1 a6989586621679493510 :: TyFun Nat (Nat, Nat) -> Type) (a6989586621679493511 :: Nat) Source # | |
Defined in Data.Singletons.TypeLits type Apply (DivModSym1 a6989586621679493510 :: TyFun Nat (Nat, Nat) -> Type) (a6989586621679493511 :: Nat) = DivModSym2 a6989586621679493510 a6989586621679493511 | |
type Apply (QuotRemSym1 a6989586621679493503 :: TyFun Nat (Nat, Nat) -> Type) (a6989586621679493504 :: Nat) Source # | |
Defined in Data.Singletons.TypeLits type Apply (QuotRemSym1 a6989586621679493503 :: TyFun Nat (Nat, Nat) -> Type) (a6989586621679493504 :: Nat) = QuotRemSym2 a6989586621679493503 a6989586621679493504 | |
type Apply (DropSym0 :: TyFun Nat ([a] ~> [a]) -> Type) (a6989586621679969037 :: Nat) Source # | |
type Apply (TakeSym0 :: TyFun Nat ([a] ~> [a]) -> Type) (a6989586621679969050 :: Nat) Source # | |
type Apply (SplitAtSym0 :: TyFun Nat ([a] ~> ([a], [a])) -> Type) (a6989586621679969030 :: Nat) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (SplitAtSym0 :: TyFun Nat ([a] ~> ([a], [a])) -> Type) (a6989586621679969030 :: Nat) = SplitAtSym1 a6989586621679969030 :: TyFun [a] ([a], [a]) -> Type | |
type Apply (ReplicateSym0 :: TyFun Nat (a ~> [a]) -> Type) (a6989586621679968895 :: Nat) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ReplicateSym0 :: TyFun Nat (a ~> [a]) -> Type) (a6989586621679968895 :: Nat) = ReplicateSym1 a6989586621679968895 :: TyFun a [a] -> Type | |
type Apply (ShowsPrecSym0 :: TyFun Nat (a ~> (Symbol ~> Symbol)) -> Type) (a6989586621680279568 :: Nat) Source # | |
type Apply (TakeSym0 :: TyFun Nat (NonEmpty a ~> [a]) -> Type) (a6989586621681186067 :: Nat) Source # | |
type Apply (DropSym0 :: TyFun Nat (NonEmpty a ~> [a]) -> Type) (a6989586621681186058 :: Nat) Source # | |
type Apply (SplitAtSym0 :: TyFun Nat (NonEmpty a ~> ([a], [a])) -> Type) (a6989586621681186049 :: Nat) Source # | |
Defined in Data.Singletons.Prelude.List.NonEmpty | |
type Apply ((:@#@$) :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679304138 :: a) Source # | |
type Apply ((:|@#@$) :: TyFun a ([a] ~> NonEmpty a) -> Type) (a6989586621679304206 :: a) Source # | |
type Apply (Bool_Sym0 :: TyFun a (a ~> (Bool ~> a)) -> Type) (a6989586621679365865 :: a) Source # | |
type Apply ((==@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679370055 :: a) Source # | |
type Apply ((/=@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679370058 :: a) Source # | |
type Apply (DefaultEqSym0 :: TyFun k (k ~> Bool) -> Type) (a6989586621679370061 :: k) Source # | |
Defined in Data.Singletons.Prelude.Eq type Apply (DefaultEqSym0 :: TyFun k (k ~> Bool) -> Type) (a6989586621679370061 :: k) = DefaultEqSym1 a6989586621679370061 | |
type Apply ((<=@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679383650 :: a) Source # | |
type Apply (CompareSym0 :: TyFun a (a ~> Ordering) -> Type) (a6989586621679383640 :: a) Source # | |
Defined in Data.Singletons.Prelude.Ord type Apply (CompareSym0 :: TyFun a (a ~> Ordering) -> Type) (a6989586621679383640 :: a) = CompareSym1 a6989586621679383640 | |
type Apply (MinSym0 :: TyFun a (a ~> a) -> Type) (a6989586621679383670 :: a) Source # | |
type Apply (MaxSym0 :: TyFun a (a ~> a) -> Type) (a6989586621679383665 :: a) Source # | |
type Apply ((>=@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679383660 :: a) Source # | |
type Apply ((>@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679383655 :: a) Source # | |
type Apply ((<@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679383645 :: a) Source # | |
type Apply (FromMaybeSym0 :: TyFun a (Maybe a ~> a) -> Type) (a6989586621679502222 :: a) Source # | |
Defined in Data.Singletons.Prelude.Maybe type Apply (FromMaybeSym0 :: TyFun a (Maybe a ~> a) -> Type) (a6989586621679502222 :: a) = FromMaybeSym1 a6989586621679502222 | |
type Apply ((-@#@$) :: TyFun a (a ~> a) -> Type) (a6989586621679517801 :: a) Source # | |
type Apply ((+@#@$) :: TyFun a (a ~> a) -> Type) (a6989586621679517796 :: a) Source # | |
type Apply ((*@#@$) :: TyFun a (a ~> a) -> Type) (a6989586621679517806 :: a) Source # | |
type Apply (SubtractSym0 :: TyFun a (a ~> a) -> Type) (a6989586621679517789 :: a) Source # | |
Defined in Data.Singletons.Prelude.Num type Apply (SubtractSym0 :: TyFun a (a ~> a) -> Type) (a6989586621679517789 :: a) = SubtractSym1 a6989586621679517789 | |
type Apply (AsTypeOfSym0 :: TyFun a (a ~> a) -> Type) (a6989586621679534167 :: a) Source # | |
Defined in Data.Singletons.Prelude.Base type Apply (AsTypeOfSym0 :: TyFun a (a ~> a) -> Type) (a6989586621679534167 :: a) = AsTypeOfSym1 a6989586621679534167 | |
type Apply (EnumFromThenToSym0 :: TyFun a (a ~> (a ~> [a])) -> Type) (a6989586621679758488 :: a) Source # | |
Defined in Data.Singletons.Prelude.Enum type Apply (EnumFromThenToSym0 :: TyFun a (a ~> (a ~> [a])) -> Type) (a6989586621679758488 :: a) = EnumFromThenToSym1 a6989586621679758488 | |
type Apply (EnumFromToSym0 :: TyFun a (a ~> [a]) -> Type) (a6989586621679758482 :: a) Source # | |
Defined in Data.Singletons.Prelude.Enum type Apply (EnumFromToSym0 :: TyFun a (a ~> [a]) -> Type) (a6989586621679758482 :: a) = EnumFromToSym1 a6989586621679758482 | |
type Apply ((<>@#@$) :: TyFun a (a ~> a) -> Type) (a6989586621679830624 :: a) Source # | |
type Apply (InsertSym0 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679969005 :: a) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (InsertSym0 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679969005 :: a) = InsertSym1 a6989586621679969005 | |
type Apply (DeleteSym0 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679969396 :: a) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DeleteSym0 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679969396 :: a) = DeleteSym1 a6989586621679969396 | |
type Apply (ElemIndicesSym0 :: TyFun a ([a] ~> [Nat]) -> Type) (a6989586621679969242 :: a) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ElemIndicesSym0 :: TyFun a ([a] ~> [Nat]) -> Type) (a6989586621679969242 :: a) = ElemIndicesSym1 a6989586621679969242 | |
type Apply (ElemIndexSym0 :: TyFun a ([a] ~> Maybe Nat) -> Type) (a6989586621679969251 :: a) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ElemIndexSym0 :: TyFun a ([a] ~> Maybe Nat) -> Type) (a6989586621679969251 :: a) = ElemIndexSym1 a6989586621679969251 | |
type Apply (IntersperseSym0 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679969993 :: a) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IntersperseSym0 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679969993 :: a) = IntersperseSym1 a6989586621679969993 | |
type Apply (ShowsSym0 :: TyFun a (Symbol ~> Symbol) -> Type) (a6989586621680279560 :: a) Source # | |
type Apply (MappendSym0 :: TyFun a (a ~> a) -> Type) (a6989586621680347244 :: a) Source # | |
Defined in Data.Singletons.Prelude.Monoid type Apply (MappendSym0 :: TyFun a (a ~> a) -> Type) (a6989586621680347244 :: a) = MappendSym1 a6989586621680347244 | |
type Apply (IntersperseSym0 :: TyFun a (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621681186080 :: a) Source # | |
Defined in Data.Singletons.Prelude.List.NonEmpty type Apply (IntersperseSym0 :: TyFun a (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621681186080 :: a) = IntersperseSym1 a6989586621681186080 | |
type Apply (InsertSym0 :: TyFun a ([a] ~> NonEmpty a) -> Type) (a6989586621681186133 :: a) Source # | |
Defined in Data.Singletons.Prelude.List.NonEmpty type Apply (InsertSym0 :: TyFun a ([a] ~> NonEmpty a) -> Type) (a6989586621681186133 :: a) = InsertSym1 a6989586621681186133 | |
type Apply ((<|@#@$) :: TyFun a (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621681186196 :: a) Source # | |
type Apply (ConsSym0 :: TyFun a (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621681186189 :: a) Source # | |
type Apply (SameKindSym0 :: TyFun k (k ~> Constraint) -> Type) (a6989586621681337319 :: k) Source # | |
Defined in Data.Singletons type Apply (SameKindSym0 :: TyFun k (k ~> Constraint) -> Type) (a6989586621681337319 :: k) = SameKindSym1 a6989586621681337319 | |
type Apply (ReplicateM_Sym0 :: TyFun Nat (m a ~> m ()) -> Type) (a6989586621681292275 :: Nat) Source # | |
Defined in Data.Singletons.Prelude.Monad type Apply (ReplicateM_Sym0 :: TyFun Nat (m a ~> m ()) -> Type) (a6989586621681292275 :: Nat) = ReplicateM_Sym1 a6989586621681292275 :: TyFun (m a) (m ()) -> Type | |
type Apply (ReplicateMSym0 :: TyFun Nat (m a ~> m [a]) -> Type) (a6989586621681292293 :: Nat) Source # | |
Defined in Data.Singletons.Prelude.Monad type Apply (ReplicateMSym0 :: TyFun Nat (m a ~> m [a]) -> Type) (a6989586621681292293 :: Nat) = ReplicateMSym1 a6989586621681292293 :: TyFun (m a) (m [a]) -> Type | |
type Apply (LeftSym0 :: TyFun a (Either a b) -> Type) (a6989586621679304182 :: a) Source # | |
type Apply (RightSym0 :: TyFun b (Either a b) -> Type) (a6989586621679304184 :: b) Source # | |
type Apply (Tuple2Sym0 :: TyFun a (b ~> (a, b)) -> Type) (a6989586621679304233 :: a) Source # | |
Defined in Data.Singletons.Prelude.Instances type Apply (Tuple2Sym0 :: TyFun a (b ~> (a, b)) -> Type) (a6989586621679304233 :: a) = Tuple2Sym1 a6989586621679304233 :: TyFun b (a, b) -> Type | |
type Apply (Bool_Sym1 a6989586621679365865 :: TyFun a (Bool ~> a) -> Type) (a6989586621679365866 :: a) Source # | |
type Apply (Maybe_Sym0 :: TyFun b ((a ~> b) ~> (Maybe a ~> b)) -> Type) (a6989586621679500654 :: b) Source # | |
Defined in Data.Singletons.Prelude.Maybe | |
type Apply (SeqSym0 :: TyFun a (b ~> b) -> Type) (a6989586621679534120 :: a) Source # | |
type Apply (ConstSym0 :: TyFun a (b ~> a) -> Type) (a6989586621679534200 :: a) Source # | |
type Apply ((&@#@$) :: TyFun a ((a ~> b) ~> b) -> Type) (a6989586621679747410 :: a) Source # | |
type Apply (EnumFromThenToSym1 a6989586621679758488 :: TyFun a (a ~> [a]) -> Type) (a6989586621679758489 :: a) Source # | |
Defined in Data.Singletons.Prelude.Enum type Apply (EnumFromThenToSym1 a6989586621679758488 :: TyFun a (a ~> [a]) -> Type) (a6989586621679758489 :: a) = EnumFromThenToSym2 a6989586621679758488 a6989586621679758489 | |
type Apply (LookupSym0 :: TyFun a ([(a, b)] ~> Maybe b) -> Type) (a6989586621679968958 :: a) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (LookupSym0 :: TyFun a ([(a, b)] ~> Maybe b) -> Type) (a6989586621679968958 :: a) = LookupSym1 a6989586621679968958 :: TyFun [(a, b)] (Maybe b) -> Type | |
type Apply (InsertBySym1 a6989586621679969324 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679969325 :: a) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (InsertBySym1 a6989586621679969324 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679969325 :: a) = InsertBySym2 a6989586621679969324 a6989586621679969325 | |
type Apply (DeleteBySym1 a6989586621679969366 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679969367 :: a) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DeleteBySym1 a6989586621679969366 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679969367 :: a) = DeleteBySym2 a6989586621679969366 a6989586621679969367 | |
type Apply (ShowsPrecSym1 a6989586621680279568 :: TyFun a (Symbol ~> Symbol) -> Type) (a6989586621680279569 :: a) Source # | |
Defined in Data.Singletons.Prelude.Show type Apply (ShowsPrecSym1 a6989586621680279568 :: TyFun a (Symbol ~> Symbol) -> Type) (a6989586621680279569 :: a) = ShowsPrecSym2 a6989586621680279568 a6989586621680279569 | |
type Apply (AsProxyTypeOfSym0 :: TyFun a (proxy a ~> a) -> Type) (a6989586621680453165 :: a) Source # | |
Defined in Data.Singletons.Prelude.Proxy type Apply (AsProxyTypeOfSym0 :: TyFun a (proxy a ~> a) -> Type) (a6989586621680453165 :: a) = AsProxyTypeOfSym1 a6989586621680453165 :: TyFun (proxy a) a -> Type | |
type Apply (ElemSym0 :: TyFun a (t a ~> Bool) -> Type) (a6989586621680492497 :: a) Source # | |
type Apply (NotElemSym0 :: TyFun a (t a ~> Bool) -> Type) (a6989586621680492244 :: a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (NotElemSym0 :: TyFun a (t a ~> Bool) -> Type) (a6989586621680492244 :: a) = NotElemSym1 a6989586621680492244 :: TyFun (t a) Bool -> Type | |
type Apply (ArgSym0 :: TyFun a (b ~> Arg a b) -> Type) (a6989586621680936903 :: a) Source # | |
type Apply (Tuple2Sym1 a6989586621679304233 :: TyFun b (a, b) -> Type) (a6989586621679304234 :: b) Source # | |
Defined in Data.Singletons.Prelude.Instances type Apply (Tuple2Sym1 a6989586621679304233 :: TyFun b (a, b) -> Type) (a6989586621679304234 :: b) = Tuple2Sym2 a6989586621679304233 a6989586621679304234 | |
type Apply (Tuple3Sym0 :: TyFun a (b ~> (c ~> (a, b, c))) -> Type) (a6989586621679304264 :: a) Source # | |
Defined in Data.Singletons.Prelude.Instances type Apply (Tuple3Sym0 :: TyFun a (b ~> (c ~> (a, b, c))) -> Type) (a6989586621679304264 :: a) = Tuple3Sym1 a6989586621679304264 :: TyFun b (c ~> (a, b, c)) -> Type | |
type Apply (ComparingSym1 a6989586621679383631 :: TyFun b (b ~> Ordering) -> Type) (a6989586621679383632 :: b) Source # | |
Defined in Data.Singletons.Prelude.Ord type Apply (ComparingSym1 a6989586621679383631 :: TyFun b (b ~> Ordering) -> Type) (a6989586621679383632 :: b) = ComparingSym2 a6989586621679383631 a6989586621679383632 | |
type Apply (FoldrSym1 a6989586621679534230 :: TyFun b ([a] ~> b) -> Type) (a6989586621679534231 :: b) Source # | |
type Apply ((<$@#@$) :: TyFun a (f b ~> f a) -> Type) (a6989586621679559672 :: a) Source # | |
type Apply (ScanrSym1 a6989586621679969778 :: TyFun b ([a] ~> [b]) -> Type) (a6989586621679969779 :: b) Source # | |
type Apply (ScanlSym1 a6989586621679969805 :: TyFun b ([a] ~> [b]) -> Type) (a6989586621679969806 :: b) Source # | |
type Apply (ArgSym1 a6989586621680936903 :: TyFun b (Arg a b) -> Type) (a6989586621680936904 :: b) Source # | |
type Apply (ScanlSym1 a6989586621681186122 :: TyFun b ([a] ~> NonEmpty b) -> Type) (a6989586621681186123 :: b) Source # | |
type Apply (ScanrSym1 a6989586621681186110 :: TyFun b ([a] ~> NonEmpty b) -> Type) (a6989586621681186111 :: b) Source # | |
type Apply (Tuple3Sym1 a6989586621679304264 :: TyFun b (c ~> (a, b, c)) -> Type) (a6989586621679304265 :: b) Source # | |
Defined in Data.Singletons.Prelude.Instances type Apply (Tuple3Sym1 a6989586621679304264 :: TyFun b (c ~> (a, b, c)) -> Type) (a6989586621679304265 :: b) = Tuple3Sym2 a6989586621679304264 a6989586621679304265 :: TyFun c (a, b, c) -> Type | |
type Apply (Tuple4Sym0 :: TyFun a (b ~> (c ~> (d ~> (a, b, c, d)))) -> Type) (a6989586621679304310 :: a) Source # | |
Defined in Data.Singletons.Prelude.Instances | |
type Apply (CurrySym1 a6989586621679360434 :: TyFun a (b ~> c) -> Type) (a6989586621679360435 :: a) Source # | |
type Apply (FlipSym1 a6989586621679534175 :: TyFun b (a ~> c) -> Type) (a6989586621679534176 :: b) Source # | |
type Apply (Foldl'Sym1 a6989586621680492472 :: TyFun b (t a ~> b) -> Type) (a6989586621680492473 :: b) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (Foldl'Sym1 a6989586621680492472 :: TyFun b (t a ~> b) -> Type) (a6989586621680492473 :: b) = Foldl'Sym2 a6989586621680492472 a6989586621680492473 :: TyFun (t a) b -> Type | |
type Apply (FoldlSym1 a6989586621680492465 :: TyFun b (t a ~> b) -> Type) (a6989586621680492466 :: b) Source # | |
type Apply (FoldrSym1 a6989586621680492451 :: TyFun b (t a ~> b) -> Type) (a6989586621680492452 :: b) Source # | |
type Apply (Foldr'Sym1 a6989586621680492458 :: TyFun b (t a ~> b) -> Type) (a6989586621680492459 :: b) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (Foldr'Sym1 a6989586621680492458 :: TyFun b (t a ~> b) -> Type) (a6989586621680492459 :: b) = Foldr'Sym2 a6989586621680492458 a6989586621680492459 :: TyFun (t a) b -> Type | |
type Apply (Tuple4Sym1 a6989586621679304310 :: TyFun b (c ~> (d ~> (a, b, c, d))) -> Type) (a6989586621679304311 :: b) Source # | |
Defined in Data.Singletons.Prelude.Instances type Apply (Tuple4Sym1 a6989586621679304310 :: TyFun b (c ~> (d ~> (a, b, c, d))) -> Type) (a6989586621679304311 :: b) = Tuple4Sym2 a6989586621679304310 a6989586621679304311 :: TyFun c (d ~> (a, b, c, d)) -> Type | |
type Apply (Tuple5Sym0 :: TyFun a (b ~> (c ~> (d ~> (e ~> (a, b, c, d, e))))) -> Type) (a6989586621679304373 :: a) Source # | |
Defined in Data.Singletons.Prelude.Instances | |
type Apply (OnSym2 a6989586621679747423 a6989586621679747424 :: TyFun a (a ~> c) -> Type) (a6989586621679747425 :: a) Source # | |
type Apply (FoldrMSym1 a6989586621680492425 :: TyFun b (t a ~> m b) -> Type) (a6989586621680492426 :: b) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (FoldrMSym1 a6989586621680492425 :: TyFun b (t a ~> m b) -> Type) (a6989586621680492426 :: b) = FoldrMSym2 a6989586621680492425 a6989586621680492426 :: TyFun (t a) (m b) -> Type | |
type Apply (FoldlMSym1 a6989586621680492407 :: TyFun b (t a ~> m b) -> Type) (a6989586621680492408 :: b) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (FoldlMSym1 a6989586621680492407 :: TyFun b (t a ~> m b) -> Type) (a6989586621680492408 :: b) = FoldlMSym2 a6989586621680492407 a6989586621680492408 :: TyFun (t a) (m b) -> Type | |
type Apply (MapAccumRSym1 a6989586621680822996 :: TyFun a (t b ~> (a, t c)) -> Type) (a6989586621680822997 :: a) Source # | |
Defined in Data.Singletons.Prelude.Traversable type Apply (MapAccumRSym1 a6989586621680822996 :: TyFun a (t b ~> (a, t c)) -> Type) (a6989586621680822997 :: a) = MapAccumRSym2 a6989586621680822996 a6989586621680822997 :: TyFun (t b) (a, t c) -> Type | |
type Apply (MapAccumLSym1 a6989586621680823006 :: TyFun a (t b ~> (a, t c)) -> Type) (a6989586621680823007 :: a) Source # | |
Defined in Data.Singletons.Prelude.Traversable type Apply (MapAccumLSym1 a6989586621680823006 :: TyFun a (t b ~> (a, t c)) -> Type) (a6989586621680823007 :: a) = MapAccumLSym2 a6989586621680823006 a6989586621680823007 :: TyFun (t b) (a, t c) -> Type | |
type Apply (Tuple4Sym2 a6989586621679304310 a6989586621679304311 :: TyFun c (d ~> (a, b, c, d)) -> Type) (a6989586621679304312 :: c) Source # | |
Defined in Data.Singletons.Prelude.Instances type Apply (Tuple4Sym2 a6989586621679304310 a6989586621679304311 :: TyFun c (d ~> (a, b, c, d)) -> Type) (a6989586621679304312 :: c) = Tuple4Sym3 a6989586621679304310 a6989586621679304311 a6989586621679304312 :: TyFun d (a, b, c, d) -> Type | |
type Apply (Tuple5Sym1 a6989586621679304373 :: TyFun b (c ~> (d ~> (e ~> (a, b, c, d, e)))) -> Type) (a6989586621679304374 :: b) Source # | |
Defined in Data.Singletons.Prelude.Instances | |
type Apply (Tuple6Sym0 :: TyFun a (b ~> (c ~> (d ~> (e ~> (f ~> (a, b, c, d, e, f)))))) -> Type) (a6989586621679304455 :: a) Source # | |
type Apply (Tuple5Sym2 a6989586621679304373 a6989586621679304374 :: TyFun c (d ~> (e ~> (a, b, c, d, e))) -> Type) (a6989586621679304375 :: c) Source # | |
Defined in Data.Singletons.Prelude.Instances type Apply (Tuple5Sym2 a6989586621679304373 a6989586621679304374 :: TyFun c (d ~> (e ~> (a, b, c, d, e))) -> Type) (a6989586621679304375 :: c) = Tuple5Sym3 a6989586621679304373 a6989586621679304374 a6989586621679304375 :: TyFun d (e ~> (a, b, c, d, e)) -> Type | |
type Apply (Tuple6Sym1 a6989586621679304455 :: TyFun b (c ~> (d ~> (e ~> (f ~> (a, b, c, d, e, f))))) -> Type) (a6989586621679304456 :: b) Source # | |
Defined in Data.Singletons.Prelude.Instances | |
type Apply (Tuple7Sym0 :: TyFun a (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g))))))) -> Type) (a6989586621679304558 :: a) Source # | |
type Apply (Tuple5Sym3 a6989586621679304373 a6989586621679304374 a6989586621679304375 :: TyFun d (e ~> (a, b, c, d, e)) -> Type) (a6989586621679304376 :: d) Source # | |
Defined in Data.Singletons.Prelude.Instances type Apply (Tuple5Sym3 a6989586621679304373 a6989586621679304374 a6989586621679304375 :: TyFun d (e ~> (a, b, c, d, e)) -> Type) (a6989586621679304376 :: d) = Tuple5Sym4 a6989586621679304373 a6989586621679304374 a6989586621679304375 a6989586621679304376 :: TyFun e (a, b, c, d, e) -> Type | |
type Apply (Tuple6Sym2 a6989586621679304455 a6989586621679304456 :: TyFun c (d ~> (e ~> (f ~> (a, b, c, d, e, f)))) -> Type) (a6989586621679304457 :: c) Source # | |
Defined in Data.Singletons.Prelude.Instances | |
type Apply (Tuple7Sym1 a6989586621679304558 :: TyFun b (c ~> (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g)))))) -> Type) (a6989586621679304559 :: b) Source # | |
Defined in Data.Singletons.Prelude.Instances | |
type Apply (Tuple6Sym3 a6989586621679304455 a6989586621679304456 a6989586621679304457 :: TyFun d (e ~> (f ~> (a, b, c, d, e, f))) -> Type) (a6989586621679304458 :: d) Source # | |
Defined in Data.Singletons.Prelude.Instances type Apply (Tuple6Sym3 a6989586621679304455 a6989586621679304456 a6989586621679304457 :: TyFun d (e ~> (f ~> (a, b, c, d, e, f))) -> Type) (a6989586621679304458 :: d) = Tuple6Sym4 a6989586621679304455 a6989586621679304456 a6989586621679304457 a6989586621679304458 :: TyFun e (f ~> (a, b, c, d, e, f)) -> Type | |
type Apply (Tuple7Sym2 a6989586621679304558 a6989586621679304559 :: TyFun c (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g))))) -> Type) (a6989586621679304560 :: c) Source # | |
Defined in Data.Singletons.Prelude.Instances type Apply (Tuple7Sym2 a6989586621679304558 a6989586621679304559 :: TyFun c (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g))))) -> Type) (a6989586621679304560 :: c) = Tuple7Sym3 a6989586621679304558 a6989586621679304559 a6989586621679304560 :: TyFun d (e ~> (f ~> (g ~> (a, b, c, d, e, f, g)))) -> Type | |
type Apply (Tuple6Sym4 a6989586621679304455 a6989586621679304456 a6989586621679304457 a6989586621679304458 :: TyFun e (f ~> (a, b, c, d, e, f)) -> Type) (a6989586621679304459 :: e) Source # | |
Defined in Data.Singletons.Prelude.Instances type Apply (Tuple6Sym4 a6989586621679304455 a6989586621679304456 a6989586621679304457 a6989586621679304458 :: TyFun e (f ~> (a, b, c, d, e, f)) -> Type) (a6989586621679304459 :: e) = Tuple6Sym5 a6989586621679304455 a6989586621679304456 a6989586621679304457 a6989586621679304458 a6989586621679304459 :: TyFun f (a, b, c, d, e, f) -> Type | |
type Apply (Tuple7Sym3 a6989586621679304558 a6989586621679304559 a6989586621679304560 :: TyFun d (e ~> (f ~> (g ~> (a, b, c, d, e, f, g)))) -> Type) (a6989586621679304561 :: d) Source # | |
Defined in Data.Singletons.Prelude.Instances type Apply (Tuple7Sym3 a6989586621679304558 a6989586621679304559 a6989586621679304560 :: TyFun d (e ~> (f ~> (g ~> (a, b, c, d, e, f, g)))) -> Type) (a6989586621679304561 :: d) = Tuple7Sym4 a6989586621679304558 a6989586621679304559 a6989586621679304560 a6989586621679304561 :: TyFun e (f ~> (g ~> (a, b, c, d, e, f, g))) -> Type | |
type Apply (Tuple7Sym4 a6989586621679304558 a6989586621679304559 a6989586621679304560 a6989586621679304561 :: TyFun e (f ~> (g ~> (a, b, c, d, e, f, g))) -> Type) (a6989586621679304562 :: e) Source # | |
Defined in Data.Singletons.Prelude.Instances type Apply (Tuple7Sym4 a6989586621679304558 a6989586621679304559 a6989586621679304560 a6989586621679304561 :: TyFun e (f ~> (g ~> (a, b, c, d, e, f, g))) -> Type) (a6989586621679304562 :: e) = Tuple7Sym5 a6989586621679304558 a6989586621679304559 a6989586621679304560 a6989586621679304561 a6989586621679304562 :: TyFun f (g ~> (a, b, c, d, e, f, g)) -> Type | |
type Apply (Tuple7Sym5 a6989586621679304558 a6989586621679304559 a6989586621679304560 a6989586621679304561 a6989586621679304562 :: TyFun f (g ~> (a, b, c, d, e, f, g)) -> Type) (a6989586621679304563 :: f) Source # | |
Defined in Data.Singletons.Prelude.Instances type Apply (Tuple7Sym5 a6989586621679304558 a6989586621679304559 a6989586621679304560 a6989586621679304561 a6989586621679304562 :: TyFun f (g ~> (a, b, c, d, e, f, g)) -> Type) (a6989586621679304563 :: f) = Tuple7Sym6 a6989586621679304558 a6989586621679304559 a6989586621679304560 a6989586621679304561 a6989586621679304562 a6989586621679304563 :: TyFun g (a, b, c, d, e, f, g) -> Type | |
type Apply (ConstSym0 :: TyFun a (Const a b) -> Type) (a6989586621680775209 :: a) Source # | |
type Apply (Tuple3Sym2 a6989586621679304264 a6989586621679304265 :: TyFun c (a, b, c) -> Type) (a6989586621679304266 :: c) Source # | |
Defined in Data.Singletons.Prelude.Instances type Apply (Tuple3Sym2 a6989586621679304264 a6989586621679304265 :: TyFun c (a, b, c) -> Type) (a6989586621679304266 :: c) = Tuple3Sym3 a6989586621679304264 a6989586621679304265 a6989586621679304266 | |
type Apply (Tuple4Sym3 a6989586621679304310 a6989586621679304311 a6989586621679304312 :: TyFun d (a, b, c, d) -> Type) (a6989586621679304313 :: d) Source # | |
Defined in Data.Singletons.Prelude.Instances type Apply (Tuple4Sym3 a6989586621679304310 a6989586621679304311 a6989586621679304312 :: TyFun d (a, b, c, d) -> Type) (a6989586621679304313 :: d) = Tuple4Sym4 a6989586621679304310 a6989586621679304311 a6989586621679304312 a6989586621679304313 | |
type Apply (Tuple5Sym4 a6989586621679304373 a6989586621679304374 a6989586621679304375 a6989586621679304376 :: TyFun e (a, b, c, d, e) -> Type) (a6989586621679304377 :: e) Source # | |
Defined in Data.Singletons.Prelude.Instances type Apply (Tuple5Sym4 a6989586621679304373 a6989586621679304374 a6989586621679304375 a6989586621679304376 :: TyFun e (a, b, c, d, e) -> Type) (a6989586621679304377 :: e) = Tuple5Sym5 a6989586621679304373 a6989586621679304374 a6989586621679304375 a6989586621679304376 a6989586621679304377 | |
type Apply (Tuple6Sym5 a6989586621679304455 a6989586621679304456 a6989586621679304457 a6989586621679304458 a6989586621679304459 :: TyFun f (a, b, c, d, e, f) -> Type) (a6989586621679304460 :: f) Source # | |
Defined in Data.Singletons.Prelude.Instances type Apply (Tuple6Sym5 a6989586621679304455 a6989586621679304456 a6989586621679304457 a6989586621679304458 a6989586621679304459 :: TyFun f (a, b, c, d, e, f) -> Type) (a6989586621679304460 :: f) = Tuple6Sym6 a6989586621679304455 a6989586621679304456 a6989586621679304457 a6989586621679304458 a6989586621679304459 a6989586621679304460 | |
type Apply (Tuple7Sym6 a6989586621679304558 a6989586621679304559 a6989586621679304560 a6989586621679304561 a6989586621679304562 a6989586621679304563 :: TyFun g (a, b, c, d, e, f, g) -> Type) (a6989586621679304564 :: g) Source # | |
Defined in Data.Singletons.Prelude.Instances type Apply (Tuple7Sym6 a6989586621679304558 a6989586621679304559 a6989586621679304560 a6989586621679304561 a6989586621679304562 a6989586621679304563 :: TyFun g (a, b, c, d, e, f, g) -> Type) (a6989586621679304564 :: g) = Tuple7Sym7 a6989586621679304558 a6989586621679304559 a6989586621679304560 a6989586621679304561 a6989586621679304562 a6989586621679304563 a6989586621679304564 | |
type Apply UnlinesSym0 (a6989586621679969412 :: [Symbol]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal | |
type Apply UnwordsSym0 (a6989586621679969402 :: [Symbol]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal | |
type Apply XorSym0 (a6989586621681186271 :: NonEmpty Bool) Source # | |
type Apply (LastSym0 :: TyFun [a] a -> Type) (a6989586621679970031 :: [a]) Source # | |
type Apply (HeadSym0 :: TyFun [a] a -> Type) (a6989586621679970037 :: [a]) Source # | |
type Apply (MconcatSym0 :: TyFun [a] a -> Type) (a6989586621680347248 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.Monoid type Apply (MconcatSym0 :: TyFun [a] a -> Type) (a6989586621680347248 :: [a]) = MconcatSym1 a6989586621680347248 | |
type Apply (FromJustSym0 :: TyFun (Maybe a) a -> Type) (a6989586621679502232 :: Maybe a) Source # | |
Defined in Data.Singletons.Prelude.Maybe type Apply (FromJustSym0 :: TyFun (Maybe a) a -> Type) (a6989586621679502232 :: Maybe a) = FromJustSym1 a6989586621679502232 | |
type Apply (IsNothingSym0 :: TyFun (Maybe a) Bool -> Type) (a6989586621679502236 :: Maybe a) Source # | |
Defined in Data.Singletons.Prelude.Maybe type Apply (IsNothingSym0 :: TyFun (Maybe a) Bool -> Type) (a6989586621679502236 :: Maybe a) = IsNothingSym1 a6989586621679502236 | |
type Apply (IsJustSym0 :: TyFun (Maybe a) Bool -> Type) (a6989586621679502239 :: Maybe a) Source # | |
Defined in Data.Singletons.Prelude.Maybe type Apply (IsJustSym0 :: TyFun (Maybe a) Bool -> Type) (a6989586621679502239 :: Maybe a) = IsJustSym1 a6989586621679502239 | |
type Apply (AndSym0 :: TyFun (t Bool) Bool -> Type) (a6989586621680492316 :: t Bool) Source # | |
type Apply (OrSym0 :: TyFun (t Bool) Bool -> Type) (a6989586621680492310 :: t Bool) Source # | |
type Apply (GetMinSym0 :: TyFun (Min a) a -> Type) (a6989586621679840216 :: Min a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup.Internal type Apply (GetMinSym0 :: TyFun (Min a) a -> Type) (a6989586621679840216 :: Min a) = GetMinSym1 a6989586621679840216 | |
type Apply (GetMaxSym0 :: TyFun (Max a) a -> Type) (a6989586621679840238 :: Max a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup.Internal type Apply (GetMaxSym0 :: TyFun (Max a) a -> Type) (a6989586621679840238 :: Max a) = GetMaxSym1 a6989586621679840238 | |
type Apply (GetFirstSym0 :: TyFun (First a) a -> Type) (a6989586621679840260 :: First a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup.Internal type Apply (GetFirstSym0 :: TyFun (First a) a -> Type) (a6989586621679840260 :: First a) = GetFirstSym1 a6989586621679840260 | |
type Apply (GetLastSym0 :: TyFun (Last a) a -> Type) (a6989586621679840282 :: Last a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup.Internal type Apply (GetLastSym0 :: TyFun (Last a) a -> Type) (a6989586621679840282 :: Last a) = GetLastSym1 a6989586621679840282 | |
type Apply (UnwrapMonoidSym0 :: TyFun (WrappedMonoid m) m -> Type) (a6989586621679840304 :: WrappedMonoid m) Source # | |
Defined in Data.Singletons.Prelude.Semigroup.Internal type Apply (UnwrapMonoidSym0 :: TyFun (WrappedMonoid m) m -> Type) (a6989586621679840304 :: WrappedMonoid m) = UnwrapMonoidSym1 a6989586621679840304 | |
type Apply (RunIdentitySym0 :: TyFun (Identity a) a -> Type) (a6989586621679304613 :: Identity a) Source # | |
Defined in Data.Singletons.Prelude.Instances type Apply (RunIdentitySym0 :: TyFun (Identity a) a -> Type) (a6989586621679304613 :: Identity a) = RunIdentitySym1 a6989586621679304613 | |
type Apply (GetDualSym0 :: TyFun (Dual a) a -> Type) (a6989586621679840116 :: Dual a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup.Internal type Apply (GetDualSym0 :: TyFun (Dual a) a -> Type) (a6989586621679840116 :: Dual a) = GetDualSym1 a6989586621679840116 | |
type Apply (GetSumSym0 :: TyFun (Sum a) a -> Type) (a6989586621679840172 :: Sum a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup.Internal type Apply (GetSumSym0 :: TyFun (Sum a) a -> Type) (a6989586621679840172 :: Sum a) = GetSumSym1 a6989586621679840172 | |
type Apply (GetProductSym0 :: TyFun (Product a) a -> Type) (a6989586621679840194 :: Product a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup.Internal type Apply (GetProductSym0 :: TyFun (Product a) a -> Type) (a6989586621679840194 :: Product a) = GetProductSym1 a6989586621679840194 | |
type Apply (GetDownSym0 :: TyFun (Down a) a -> Type) (a6989586621679393013 :: Down a) Source # | |
Defined in Data.Singletons.Prelude.Ord type Apply (GetDownSym0 :: TyFun (Down a) a -> Type) (a6989586621679393013 :: Down a) = GetDownSym1 a6989586621679393013 | |
type Apply (SconcatSym0 :: TyFun (NonEmpty a) a -> Type) (a6989586621679830628 :: NonEmpty a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup.Internal type Apply (SconcatSym0 :: TyFun (NonEmpty a) a -> Type) (a6989586621679830628 :: NonEmpty a) = SconcatSym1 a6989586621679830628 | |
type Apply (LastSym0 :: TyFun (NonEmpty a) a -> Type) (a6989586621681186208 :: NonEmpty a) Source # | |
type Apply (HeadSym0 :: TyFun (NonEmpty a) a -> Type) (a6989586621681186217 :: NonEmpty a) Source # | |
type Apply (LengthSym0 :: TyFun (NonEmpty a) Nat -> Type) (a6989586621681186282 :: NonEmpty a) Source # | |
Defined in Data.Singletons.Prelude.List.NonEmpty type Apply (LengthSym0 :: TyFun (NonEmpty a) Nat -> Type) (a6989586621681186282 :: NonEmpty a) = LengthSym1 a6989586621681186282 | |
type Apply (GenericLengthSym0 :: TyFun [a] k2 -> Type) (a6989586621679968803 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (GenericLengthSym0 :: TyFun [a] k2 -> Type) (a6989586621679968803 :: [a]) = GenericLengthSym1 a6989586621679968803 :: k2 | |
type Apply (IsPrefixOfSym1 a6989586621679969624 :: TyFun [a] Bool -> Type) (a6989586621679969625 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IsPrefixOfSym1 a6989586621679969624 :: TyFun [a] Bool -> Type) (a6989586621679969625 :: [a]) = IsPrefixOfSym2 a6989586621679969624 a6989586621679969625 | |
type Apply (IsInfixOfSym1 a6989586621679969610 :: TyFun [a] Bool -> Type) (a6989586621679969611 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IsInfixOfSym1 a6989586621679969610 :: TyFun [a] Bool -> Type) (a6989586621679969611 :: [a]) = IsInfixOfSym2 a6989586621679969610 a6989586621679969611 | |
type Apply (Foldl1'Sym1 a6989586621679969872 :: TyFun [a] a -> Type) (a6989586621679969873 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Foldl1'Sym1 a6989586621679969872 :: TyFun [a] a -> Type) (a6989586621679969873 :: [a]) = Foldl1'Sym2 a6989586621679969872 a6989586621679969873 | |
type Apply (IsSuffixOfSym1 a6989586621679969617 :: TyFun [a] Bool -> Type) (a6989586621679969618 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IsSuffixOfSym1 a6989586621679969617 :: TyFun [a] Bool -> Type) (a6989586621679969618 :: [a]) = IsSuffixOfSym2 a6989586621679969617 a6989586621679969618 | |
type Apply (FromMaybeSym1 a6989586621679502222 :: TyFun (Maybe a) a -> Type) (a6989586621679502223 :: Maybe a) Source # | |
Defined in Data.Singletons.Prelude.Maybe type Apply (FromMaybeSym1 a6989586621679502222 :: TyFun (Maybe a) a -> Type) (a6989586621679502223 :: Maybe a) = FromMaybeSym2 a6989586621679502222 a6989586621679502223 | |
type Apply (ProductSym0 :: TyFun (t a) a -> Type) (a6989586621680492510 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (ProductSym0 :: TyFun (t a) a -> Type) (a6989586621680492510 :: t a) = ProductSym1 a6989586621680492510 | |
type Apply (SumSym0 :: TyFun (t a) a -> Type) (a6989586621680492507 :: t a) Source # | |
type Apply (MinimumSym0 :: TyFun (t a) a -> Type) (a6989586621680492504 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (MinimumSym0 :: TyFun (t a) a -> Type) (a6989586621680492504 :: t a) = MinimumSym1 a6989586621680492504 | |
type Apply (MaximumSym0 :: TyFun (t a) a -> Type) (a6989586621680492501 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (MaximumSym0 :: TyFun (t a) a -> Type) (a6989586621680492501 :: t a) = MaximumSym1 a6989586621680492501 | |
type Apply (FoldSym0 :: TyFun (t m) m -> Type) (a6989586621680492441 :: t m) Source # | |
type Apply (IsPrefixOfSym1 a6989586621681185876 :: TyFun (NonEmpty a) Bool -> Type) (a6989586621681185877 :: NonEmpty a) Source # | |
Defined in Data.Singletons.Prelude.List.NonEmpty type Apply (IsPrefixOfSym1 a6989586621681185876 :: TyFun (NonEmpty a) Bool -> Type) (a6989586621681185877 :: NonEmpty a) = IsPrefixOfSym2 a6989586621681185876 a6989586621681185877 | |
type Apply (AsProxyTypeOfSym1 a6989586621680453165 :: TyFun (proxy a) a -> Type) (a6989586621680453166 :: proxy a) Source # | |
Defined in Data.Singletons.Prelude.Proxy type Apply (AsProxyTypeOfSym1 a6989586621680453165 :: TyFun (proxy a) a -> Type) (a6989586621680453166 :: proxy a) = AsProxyTypeOfSym2 a6989586621680453165 a6989586621680453166 | |
type Apply (AnySym1 a6989586621680492302 :: TyFun (t a) Bool -> Type) (a6989586621680492303 :: t a) Source # | |
type Apply (ElemSym1 a6989586621680492497 :: TyFun (t a) Bool -> Type) (a6989586621680492498 :: t a) Source # | |
type Apply (NotElemSym1 a6989586621680492244 :: TyFun (t a) Bool -> Type) (a6989586621680492245 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (NotElemSym1 a6989586621680492244 :: TyFun (t a) Bool -> Type) (a6989586621680492245 :: t a) = NotElemSym2 a6989586621680492244 a6989586621680492245 | |
type Apply (LengthSym0 :: TyFun (t a) Nat -> Type) (a6989586621680492493 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (LengthSym0 :: TyFun (t a) Nat -> Type) (a6989586621680492493 :: t a) = LengthSym1 a6989586621680492493 | |
type Apply (NullSym0 :: TyFun (t a) Bool -> Type) (a6989586621680492490 :: t a) Source # | |
type Apply (Foldl1Sym1 a6989586621680492483 :: TyFun (t a) a -> Type) (a6989586621680492484 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (Foldl1Sym1 a6989586621680492483 :: TyFun (t a) a -> Type) (a6989586621680492484 :: t a) = Foldl1Sym2 a6989586621680492483 a6989586621680492484 | |
type Apply (MaximumBySym1 a6989586621680492273 :: TyFun (t a) a -> Type) (a6989586621680492274 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (MaximumBySym1 a6989586621680492273 :: TyFun (t a) a -> Type) (a6989586621680492274 :: t a) = MaximumBySym2 a6989586621680492273 a6989586621680492274 | |
type Apply (MinimumBySym1 a6989586621680492253 :: TyFun (t a) a -> Type) (a6989586621680492254 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (MinimumBySym1 a6989586621680492253 :: TyFun (t a) a -> Type) (a6989586621680492254 :: t a) = MinimumBySym2 a6989586621680492253 a6989586621680492254 | |
type Apply (Foldr1Sym1 a6989586621680492478 :: TyFun (t a) a -> Type) (a6989586621680492479 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (Foldr1Sym1 a6989586621680492478 :: TyFun (t a) a -> Type) (a6989586621680492479 :: t a) = Foldr1Sym2 a6989586621680492478 a6989586621680492479 | |
type Apply (AllSym1 a6989586621680492293 :: TyFun (t a) Bool -> Type) (a6989586621680492294 :: t a) Source # | |
type Apply (FoldrSym2 a6989586621679534230 a6989586621679534231 :: TyFun [a] b -> Type) (a6989586621679534232 :: [a]) Source # | |
type Apply (Maybe_Sym2 a6989586621679500654 a6989586621679500655 :: TyFun (Maybe a) b -> Type) (a6989586621679500656 :: Maybe a) Source # | |
Defined in Data.Singletons.Prelude.Maybe type Apply (Maybe_Sym2 a6989586621679500654 a6989586621679500655 :: TyFun (Maybe a) b -> Type) (a6989586621679500656 :: Maybe a) = Maybe_Sym3 a6989586621679500654 a6989586621679500655 a6989586621679500656 | |
type Apply (FoldMapSym1 a6989586621680492445 :: TyFun (t a) m -> Type) (a6989586621680492446 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (FoldMapSym1 a6989586621680492445 :: TyFun (t a) m -> Type) (a6989586621680492446 :: t a) = FoldMapSym2 a6989586621680492445 a6989586621680492446 | |
type Apply (FoldMapDefaultSym1 a6989586621680822963 :: TyFun (t a) m -> Type) (a6989586621680822964 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Traversable type Apply (FoldMapDefaultSym1 a6989586621680822963 :: TyFun (t a) m -> Type) (a6989586621680822964 :: t a) = FoldMapDefaultSym2 a6989586621680822963 a6989586621680822964 | |
type Apply (Foldl'Sym2 a6989586621680492472 a6989586621680492473 :: TyFun (t a) b -> Type) (a6989586621680492474 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (Foldl'Sym2 a6989586621680492472 a6989586621680492473 :: TyFun (t a) b -> Type) (a6989586621680492474 :: t a) = Foldl'Sym3 a6989586621680492472 a6989586621680492473 a6989586621680492474 | |
type Apply (FoldlSym2 a6989586621680492465 a6989586621680492466 :: TyFun (t a) b -> Type) (a6989586621680492467 :: t a) Source # | |
type Apply (FoldrSym2 a6989586621680492451 a6989586621680492452 :: TyFun (t a) b -> Type) (a6989586621680492453 :: t a) Source # | |
type Apply (Foldr'Sym2 a6989586621680492458 a6989586621680492459 :: TyFun (t a) b -> Type) (a6989586621680492460 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (Foldr'Sym2 a6989586621680492458 a6989586621680492459 :: TyFun (t a) b -> Type) (a6989586621680492460 :: t a) = Foldr'Sym3 a6989586621680492458 a6989586621680492459 a6989586621680492460 | |
type Apply (TransposeSym0 :: TyFun [[a]] [[a]] -> Type) (a6989586621679968887 :: [[a]]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (TransposeSym0 :: TyFun [[a]] [[a]] -> Type) (a6989586621679968887 :: [[a]]) = TransposeSym1 a6989586621679968887 | |
type Apply (CatMaybesSym0 :: TyFun [Maybe a] [a] -> Type) (a6989586621679502207 :: [Maybe a]) Source # | |
Defined in Data.Singletons.Prelude.Maybe type Apply (CatMaybesSym0 :: TyFun [Maybe a] [a] -> Type) (a6989586621679502207 :: [Maybe a]) = CatMaybesSym1 a6989586621679502207 | |
type Apply (ListToMaybeSym0 :: TyFun [a] (Maybe a) -> Type) (a6989586621679502213 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.Maybe type Apply (ListToMaybeSym0 :: TyFun [a] (Maybe a) -> Type) (a6989586621679502213 :: [a]) = ListToMaybeSym1 a6989586621679502213 | |
type Apply (GroupSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679969025 :: [a]) Source # | |
type Apply (SortSym0 :: TyFun [a] [a] -> Type) (a6989586621679969000 :: [a]) Source # | |
type Apply (NubSym0 :: TyFun [a] [a] -> Type) (a6989586621679968858 :: [a]) Source # | |
type Apply (TailsSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679969632 :: [a]) Source # | |
type Apply (InitsSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679969640 :: [a]) Source # | |
type Apply (PermutationsSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679969907 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (PermutationsSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679969907 :: [a]) = PermutationsSym1 a6989586621679969907 | |
type Apply (SubsequencesSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679969981 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (SubsequencesSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679969981 :: [a]) = SubsequencesSym1 a6989586621679969981 | |
type Apply (ReverseSym0 :: TyFun [a] [a] -> Type) (a6989586621679970000 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ReverseSym0 :: TyFun [a] [a] -> Type) (a6989586621679970000 :: [a]) = ReverseSym1 a6989586621679970000 | |
type Apply (InitSym0 :: TyFun [a] [a] -> Type) (a6989586621679970015 :: [a]) Source # | |
type Apply (TailSym0 :: TyFun [a] [a] -> Type) (a6989586621679970027 :: [a]) Source # | |
type Apply (GroupSym0 :: TyFun [a] [NonEmpty a] -> Type) (a6989586621681185988 :: [a]) Source # | |
type Apply (FromListSym0 :: TyFun [a] (NonEmpty a) -> Type) (a6989586621681186173 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.NonEmpty type Apply (FromListSym0 :: TyFun [a] (NonEmpty a) -> Type) (a6989586621681186173 :: [a]) = FromListSym1 a6989586621681186173 | |
type Apply (InitsSym0 :: TyFun [a] (NonEmpty [a]) -> Type) (a6989586621681186147 :: [a]) Source # | |
type Apply (TailsSym0 :: TyFun [a] (NonEmpty [a]) -> Type) (a6989586621681186141 :: [a]) Source # | |
type Apply (NonEmpty_Sym0 :: TyFun [a] (Maybe (NonEmpty a)) -> Type) (a6989586621681186251 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.NonEmpty type Apply (NonEmpty_Sym0 :: TyFun [a] (Maybe (NonEmpty a)) -> Type) (a6989586621681186251 :: [a]) = NonEmpty_Sym1 a6989586621681186251 | |
type Apply (MaybeToListSym0 :: TyFun (Maybe a) [a] -> Type) (a6989586621679502217 :: Maybe a) Source # | |
Defined in Data.Singletons.Prelude.Maybe type Apply (MaybeToListSym0 :: TyFun (Maybe a) [a] -> Type) (a6989586621679502217 :: Maybe a) = MaybeToListSym1 a6989586621679502217 | |
type Apply (OptionSym0 :: TyFun (Maybe a) (Option a) -> Type) (a6989586621679840090 :: Maybe a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup.Internal type Apply (OptionSym0 :: TyFun (Maybe a) (Option a) -> Type) (a6989586621679840090 :: Maybe a) = OptionSym1 a6989586621679840090 | |
type Apply (FirstSym0 :: TyFun (Maybe a) (First a) -> Type) (a6989586621680350749 :: Maybe a) Source # | |
type Apply (LastSym0 :: TyFun (Maybe a) (Last a) -> Type) (a6989586621680350776 :: Maybe a) Source # | |
type Apply (GetOptionSym0 :: TyFun (Option a) (Maybe a) -> Type) (a6989586621679840093 :: Option a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup.Internal type Apply (GetOptionSym0 :: TyFun (Option a) (Maybe a) -> Type) (a6989586621679840093 :: Option a) = GetOptionSym1 a6989586621679840093 | |
type Apply (GetFirstSym0 :: TyFun (First a) (Maybe a) -> Type) (a6989586621680350752 :: First a) Source # | |
Defined in Data.Singletons.Prelude.Monoid type Apply (GetFirstSym0 :: TyFun (First a) (Maybe a) -> Type) (a6989586621680350752 :: First a) = GetFirstSym1 a6989586621680350752 | |
type Apply (GetLastSym0 :: TyFun (Last a) (Maybe a) -> Type) (a6989586621680350779 :: Last a) Source # | |
Defined in Data.Singletons.Prelude.Monoid type Apply (GetLastSym0 :: TyFun (Last a) (Maybe a) -> Type) (a6989586621680350779 :: Last a) = GetLastSym1 a6989586621680350779 | |
type Apply (NubSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681185807 :: NonEmpty a) Source # | |
type Apply (Group1Sym0 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621681185930 :: NonEmpty a) Source # | |
Defined in Data.Singletons.Prelude.List.NonEmpty type Apply (Group1Sym0 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621681185930 :: NonEmpty a) = Group1Sym1 a6989586621681185930 | |
type Apply (ToListSym0 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681186168 :: NonEmpty a) Source # | |
Defined in Data.Singletons.Prelude.List.NonEmpty type Apply (ToListSym0 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681186168 :: NonEmpty a) = ToListSym1 a6989586621681186168 | |
type Apply (ReverseSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681186075 :: NonEmpty a) Source # | |
Defined in Data.Singletons.Prelude.List.NonEmpty type Apply (ReverseSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681186075 :: NonEmpty a) = ReverseSym1 a6989586621681186075 | |
type Apply (SortSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681186180 :: NonEmpty a) Source # | |
type Apply (InitSym0 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681186203 :: NonEmpty a) Source # | |
type Apply (TailSym0 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681186213 :: NonEmpty a) Source # | |
type Apply (TransposeSym0 :: TyFun (NonEmpty (NonEmpty a)) (NonEmpty (NonEmpty a)) -> Type) (a6989586621681185789 :: NonEmpty (NonEmpty a)) Source # | |
Defined in Data.Singletons.Prelude.List.NonEmpty | |
type Apply (IntercalateSym1 a6989586621679969986 :: TyFun [[a]] [a] -> Type) (a6989586621679969987 :: [[a]]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IntercalateSym1 a6989586621679969986 :: TyFun [[a]] [a] -> Type) (a6989586621679969987 :: [[a]]) = IntercalateSym2 a6989586621679969986 a6989586621679969987 | |
type Apply (RightsSym0 :: TyFun [Either a b] [b] -> Type) (a6989586621680472079 :: [Either a b]) Source # | |
Defined in Data.Singletons.Prelude.Either type Apply (RightsSym0 :: TyFun [Either a b] [b] -> Type) (a6989586621680472079 :: [Either a b]) = RightsSym1 a6989586621680472079 | |
type Apply (LeftsSym0 :: TyFun [Either a b] [a] -> Type) (a6989586621680472085 :: [Either a b]) Source # | |
type Apply ((:@#@$$) a6989586621679304138 :: TyFun [a] [a] -> Type) (a6989586621679304139 :: [a]) Source # | |
type Apply ((:|@#@$$) a6989586621679304206 :: TyFun [a] (NonEmpty a) -> Type) (a6989586621679304207 :: [a]) Source # | |
type Apply ((++@#@$$) a6989586621679534210 :: TyFun [a] [a] -> Type) (a6989586621679534211 :: [a]) Source # | |
type Apply (NubBySym1 a6989586621679968840 :: TyFun [a] [a] -> Type) (a6989586621679968841 :: [a]) Source # | |
type Apply (DropSym1 a6989586621679969037 :: TyFun [a] [a] -> Type) (a6989586621679969038 :: [a]) Source # | |
type Apply (TakeSym1 a6989586621679969050 :: TyFun [a] [a] -> Type) (a6989586621679969051 :: [a]) Source # | |
type Apply (GroupBySym1 a6989586621679968973 :: TyFun [a] [[a]] -> Type) (a6989586621679968974 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (GroupBySym1 a6989586621679968973 :: TyFun [a] [[a]] -> Type) (a6989586621679968974 :: [a]) = GroupBySym2 a6989586621679968973 a6989586621679968974 | |
type Apply (DropWhileSym1 a6989586621679969152 :: TyFun [a] [a] -> Type) (a6989586621679969153 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DropWhileSym1 a6989586621679969152 :: TyFun [a] [a] -> Type) (a6989586621679969153 :: [a]) = DropWhileSym2 a6989586621679969152 a6989586621679969153 | |
type Apply (TakeWhileSym1 a6989586621679969167 :: TyFun [a] [a] -> Type) (a6989586621679969168 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (TakeWhileSym1 a6989586621679969167 :: TyFun [a] [a] -> Type) (a6989586621679969168 :: [a]) = TakeWhileSym2 a6989586621679969167 a6989586621679969168 | |
type Apply (FilterSym1 a6989586621679969267 :: TyFun [a] [a] -> Type) (a6989586621679969268 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (FilterSym1 a6989586621679969267 :: TyFun [a] [a] -> Type) (a6989586621679969268 :: [a]) = FilterSym2 a6989586621679969267 a6989586621679969268 | |
type Apply (InsertSym1 a6989586621679969005 :: TyFun [a] [a] -> Type) (a6989586621679969006 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (InsertSym1 a6989586621679969005 :: TyFun [a] [a] -> Type) (a6989586621679969006 :: [a]) = InsertSym2 a6989586621679969005 a6989586621679969006 | |
type Apply (SortBySym1 a6989586621679969344 :: TyFun [a] [a] -> Type) (a6989586621679969345 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (SortBySym1 a6989586621679969344 :: TyFun [a] [a] -> Type) (a6989586621679969345 :: [a]) = SortBySym2 a6989586621679969344 a6989586621679969345 | |
type Apply (UnionSym1 a6989586621679968812 :: TyFun [a] [a] -> Type) (a6989586621679968813 :: [a]) Source # | |
type Apply (DeleteSym1 a6989586621679969396 :: TyFun [a] [a] -> Type) (a6989586621679969397 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DeleteSym1 a6989586621679969396 :: TyFun [a] [a] -> Type) (a6989586621679969397 :: [a]) = DeleteSym2 a6989586621679969396 a6989586621679969397 | |
type Apply ((\\@#@$$) a6989586621679969385 :: TyFun [a] [a] -> Type) (a6989586621679969386 :: [a]) Source # | |
type Apply (FindIndicesSym1 a6989586621679969210 :: TyFun [a] [Nat] -> Type) (a6989586621679969211 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (FindIndicesSym1 a6989586621679969210 :: TyFun [a] [Nat] -> Type) (a6989586621679969211 :: [a]) = FindIndicesSym2 a6989586621679969210 a6989586621679969211 | |
type Apply (ElemIndicesSym1 a6989586621679969242 :: TyFun [a] [Nat] -> Type) (a6989586621679969243 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ElemIndicesSym1 a6989586621679969242 :: TyFun [a] [Nat] -> Type) (a6989586621679969243 :: [a]) = ElemIndicesSym2 a6989586621679969242 a6989586621679969243 | |
type Apply (FindIndexSym1 a6989586621679969233 :: TyFun [a] (Maybe Nat) -> Type) (a6989586621679969234 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (FindIndexSym1 a6989586621679969233 :: TyFun [a] (Maybe Nat) -> Type) (a6989586621679969234 :: [a]) = FindIndexSym2 a6989586621679969233 a6989586621679969234 | |
type Apply (ElemIndexSym1 a6989586621679969251 :: TyFun [a] (Maybe Nat) -> Type) (a6989586621679969252 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ElemIndexSym1 a6989586621679969251 :: TyFun [a] (Maybe Nat) -> Type) (a6989586621679969252 :: [a]) = ElemIndexSym2 a6989586621679969251 a6989586621679969252 | |
type Apply (Scanr1Sym1 a6989586621679969758 :: TyFun [a] [a] -> Type) (a6989586621679969759 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Scanr1Sym1 a6989586621679969758 :: TyFun [a] [a] -> Type) (a6989586621679969759 :: [a]) = Scanr1Sym2 a6989586621679969758 a6989586621679969759 | |
type Apply (Scanl1Sym1 a6989586621679969796 :: TyFun [a] [a] -> Type) (a6989586621679969797 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Scanl1Sym1 a6989586621679969796 :: TyFun [a] [a] -> Type) (a6989586621679969797 :: [a]) = Scanl1Sym2 a6989586621679969796 a6989586621679969797 | |
type Apply (IntersectSym1 a6989586621679969203 :: TyFun [a] [a] -> Type) (a6989586621679969204 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IntersectSym1 a6989586621679969203 :: TyFun [a] [a] -> Type) (a6989586621679969204 :: [a]) = IntersectSym2 a6989586621679969203 a6989586621679969204 | |
type Apply (IntersperseSym1 a6989586621679969993 :: TyFun [a] [a] -> Type) (a6989586621679969994 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IntersperseSym1 a6989586621679969993 :: TyFun [a] [a] -> Type) (a6989586621679969994 :: [a]) = IntersperseSym2 a6989586621679969993 a6989586621679969994 | |
type Apply (DropWhileEndSym1 a6989586621679969135 :: TyFun [a] [a] -> Type) (a6989586621679969136 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DropWhileEndSym1 a6989586621679969135 :: TyFun [a] [a] -> Type) (a6989586621679969136 :: [a]) = DropWhileEndSym2 a6989586621679969135 a6989586621679969136 | |
type Apply (StripPrefixSym1 a6989586621680091346 :: TyFun [a] (Maybe [a]) -> Type) (a6989586621680091347 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (StripPrefixSym1 a6989586621680091346 :: TyFun [a] (Maybe [a]) -> Type) (a6989586621680091347 :: [a]) = StripPrefixSym2 a6989586621680091346 a6989586621680091347 | |
type Apply (GroupBySym1 a6989586621681185955 :: TyFun [a] [NonEmpty a] -> Type) (a6989586621681185956 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.NonEmpty type Apply (GroupBySym1 a6989586621681185955 :: TyFun [a] [NonEmpty a] -> Type) (a6989586621681185956 :: [a]) = GroupBySym2 a6989586621681185955 a6989586621681185956 | |
type Apply (InsertSym1 a6989586621681186133 :: TyFun [a] (NonEmpty a) -> Type) (a6989586621681186134 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.NonEmpty type Apply (InsertSym1 a6989586621681186133 :: TyFun [a] (NonEmpty a) -> Type) (a6989586621681186134 :: [a]) = InsertSym2 a6989586621681186133 a6989586621681186134 | |
type Apply (WhenSym1 a6989586621679559610 :: TyFun (f ()) (f ()) -> Type) (a6989586621679559611 :: f ()) Source # | |
type Apply (JoinSym0 :: TyFun (m (m a)) (m a) -> Type) (a6989586621679559626 :: m (m a)) Source # | |
type Apply (VoidSym0 :: TyFun (f a) (f ()) -> Type) (a6989586621679731603 :: f a) Source # | |
type Apply (ToListSym0 :: TyFun (t a) [a] -> Type) (a6989586621680492487 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (ToListSym0 :: TyFun (t a) [a] -> Type) (a6989586621680492487 :: t a) = ToListSym1 a6989586621680492487 | |
type Apply (ConcatSym0 :: TyFun (t [a]) [a] -> Type) (a6989586621680492332 :: t [a]) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (ConcatSym0 :: TyFun (t [a]) [a] -> Type) (a6989586621680492332 :: t [a]) = ConcatSym1 a6989586621680492332 | |
type Apply (OptionalSym0 :: TyFun (f a) (f (Maybe a)) -> Type) (a6989586621681282965 :: f a) Source # | |
Defined in Data.Singletons.Prelude.Applicative type Apply (OptionalSym0 :: TyFun (f a) (f (Maybe a)) -> Type) (a6989586621681282965 :: f a) = OptionalSym1 a6989586621681282965 | |
type Apply (UnlessSym1 a6989586621681292265 :: TyFun (f ()) (f ()) -> Type) (a6989586621681292266 :: f ()) Source # | |
Defined in Data.Singletons.Prelude.Monad type Apply (UnlessSym1 a6989586621681292265 :: TyFun (f ()) (f ()) -> Type) (a6989586621681292266 :: f ()) = UnlessSym2 a6989586621681292265 a6989586621681292266 | |
type Apply (NubBySym1 a6989586621681185794 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681185795 :: NonEmpty a) Source # | |
type Apply (GroupBy1Sym1 a6989586621681185903 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621681185904 :: NonEmpty a) Source # | |
Defined in Data.Singletons.Prelude.List.NonEmpty type Apply (GroupBy1Sym1 a6989586621681185903 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621681185904 :: NonEmpty a) = GroupBy1Sym2 a6989586621681185903 a6989586621681185904 | |
type Apply (IntersperseSym1 a6989586621681186080 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681186081 :: NonEmpty a) Source # | |
Defined in Data.Singletons.Prelude.List.NonEmpty type Apply (IntersperseSym1 a6989586621681186080 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681186081 :: NonEmpty a) = IntersperseSym2 a6989586621681186080 a6989586621681186081 | |
type Apply (TakeSym1 a6989586621681186067 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681186068 :: NonEmpty a) Source # | |
type Apply (DropSym1 a6989586621681186058 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681186059 :: NonEmpty a) Source # | |
type Apply (TakeWhileSym1 a6989586621681186040 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681186041 :: NonEmpty a) Source # | |
Defined in Data.Singletons.Prelude.List.NonEmpty type Apply (TakeWhileSym1 a6989586621681186040 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681186041 :: NonEmpty a) = TakeWhileSym2 a6989586621681186040 a6989586621681186041 | |
type Apply (DropWhileSym1 a6989586621681186031 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681186032 :: NonEmpty a) Source # | |
Defined in Data.Singletons.Prelude.List.NonEmpty type Apply (DropWhileSym1 a6989586621681186031 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681186032 :: NonEmpty a) = DropWhileSym2 a6989586621681186031 a6989586621681186032 | |
type Apply (FilterSym1 a6989586621681186004 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681186005 :: NonEmpty a) Source # | |
Defined in Data.Singletons.Prelude.List.NonEmpty type Apply (FilterSym1 a6989586621681186004 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681186005 :: NonEmpty a) = FilterSym2 a6989586621681186004 a6989586621681186005 | |
type Apply (SortBySym1 a6989586621681185781 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681185782 :: NonEmpty a) Source # | |
Defined in Data.Singletons.Prelude.List.NonEmpty type Apply (SortBySym1 a6989586621681185781 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681185782 :: NonEmpty a) = SortBySym2 a6989586621681185781 a6989586621681185782 | |
type Apply (Scanl1Sym1 a6989586621681186099 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681186100 :: NonEmpty a) Source # | |
Defined in Data.Singletons.Prelude.List.NonEmpty type Apply (Scanl1Sym1 a6989586621681186099 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681186100 :: NonEmpty a) = Scanl1Sym2 a6989586621681186099 a6989586621681186100 | |
type Apply (Scanr1Sym1 a6989586621681186091 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681186092 :: NonEmpty a) Source # | |
Defined in Data.Singletons.Prelude.List.NonEmpty type Apply (Scanr1Sym1 a6989586621681186091 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681186092 :: NonEmpty a) = Scanr1Sym2 a6989586621681186091 a6989586621681186092 | |
type Apply ((<|@#@$$) a6989586621681186196 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681186197 :: NonEmpty a) Source # | |
type Apply (ConsSym1 a6989586621681186189 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681186190 :: NonEmpty a) Source # | |
type Apply ((:<>:@#@$$) a6989586621681349587 :: TyFun (ErrorMessage' s) (ErrorMessage' s) -> Type) (a6989586621681349588 :: ErrorMessage' s) Source # | |
Defined in Data.Singletons.TypeError type Apply ((:<>:@#@$$) a6989586621681349587 :: TyFun (ErrorMessage' s) (ErrorMessage' s) -> Type) (a6989586621681349588 :: ErrorMessage' s) = a6989586621681349587 :<>:@#@$$$ a6989586621681349588 | |
type Apply ((:$$:@#@$$) a6989586621681349590 :: TyFun (ErrorMessage' s) (ErrorMessage' s) -> Type) (a6989586621681349591 :: ErrorMessage' s) Source # | |
Defined in Data.Singletons.TypeError type Apply ((:$$:@#@$$) a6989586621681349590 :: TyFun (ErrorMessage' s) (ErrorMessage' s) -> Type) (a6989586621681349591 :: ErrorMessage' s) = a6989586621681349590 :$$:@#@$$$ a6989586621681349591 | |
type Apply (FailSym0 :: TyFun [Char] (m a) -> Type) (a6989586621679729522 :: [Char]) Source # | |
type Apply (LookupSym1 a6989586621679968958 :: TyFun [(a, b)] (Maybe b) -> Type) (a6989586621679968959 :: [(a, b)]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (LookupSym1 a6989586621679968958 :: TyFun [(a, b)] (Maybe b) -> Type) (a6989586621679968959 :: [(a, b)]) = LookupSym2 a6989586621679968958 a6989586621679968959 | |
type Apply (MapMaybeSym1 a6989586621679502192 :: TyFun [a] [b] -> Type) (a6989586621679502193 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.Maybe type Apply (MapMaybeSym1 a6989586621679502192 :: TyFun [a] [b] -> Type) (a6989586621679502193 :: [a]) = MapMaybeSym2 a6989586621679502192 a6989586621679502193 | |
type Apply (MapSym1 a6989586621679534219 :: TyFun [a] [b] -> Type) (a6989586621679534220 :: [a]) Source # | |
type Apply (InsertBySym2 a6989586621679969324 a6989586621679969325 :: TyFun [a] [a] -> Type) (a6989586621679969326 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (InsertBySym2 a6989586621679969324 a6989586621679969325 :: TyFun [a] [a] -> Type) (a6989586621679969326 :: [a]) = InsertBySym3 a6989586621679969324 a6989586621679969325 a6989586621679969326 | |
type Apply (DeleteBySym2 a6989586621679969366 a6989586621679969367 :: TyFun [a] [a] -> Type) (a6989586621679969368 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DeleteBySym2 a6989586621679969366 a6989586621679969367 :: TyFun [a] [a] -> Type) (a6989586621679969368 :: [a]) = DeleteBySym3 a6989586621679969366 a6989586621679969367 a6989586621679969368 | |
type Apply (DeleteFirstsBySym2 a6989586621679969356 a6989586621679969357 :: TyFun [a] [a] -> Type) (a6989586621679969358 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DeleteFirstsBySym2 a6989586621679969356 a6989586621679969357 :: TyFun [a] [a] -> Type) (a6989586621679969358 :: [a]) = DeleteFirstsBySym3 a6989586621679969356 a6989586621679969357 a6989586621679969358 | |
type Apply (UnionBySym2 a6989586621679968820 a6989586621679968821 :: TyFun [a] [a] -> Type) (a6989586621679968822 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (UnionBySym2 a6989586621679968820 a6989586621679968821 :: TyFun [a] [a] -> Type) (a6989586621679968822 :: [a]) = UnionBySym3 a6989586621679968820 a6989586621679968821 a6989586621679968822 | |
type Apply (ZipSym1 a6989586621679969585 :: TyFun [b] [(a, b)] -> Type) (a6989586621679969586 :: [b]) Source # | |
type Apply (IntersectBySym2 a6989586621679969181 a6989586621679969182 :: TyFun [a] [a] -> Type) (a6989586621679969183 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IntersectBySym2 a6989586621679969181 a6989586621679969182 :: TyFun [a] [a] -> Type) (a6989586621679969183 :: [a]) = IntersectBySym3 a6989586621679969181 a6989586621679969182 a6989586621679969183 | |
type Apply (GroupWithSym1 a6989586621681185946 :: TyFun [a] [NonEmpty a] -> Type) (a6989586621681185947 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.NonEmpty type Apply (GroupWithSym1 a6989586621681185946 :: TyFun [a] [NonEmpty a] -> Type) (a6989586621681185947 :: [a]) = GroupWithSym2 a6989586621681185946 a6989586621681185947 | |
type Apply (GroupAllWithSym1 a6989586621681185937 :: TyFun [a] [NonEmpty a] -> Type) (a6989586621681185938 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.NonEmpty type Apply (GroupAllWithSym1 a6989586621681185937 :: TyFun [a] [NonEmpty a] -> Type) (a6989586621681185938 :: [a]) = GroupAllWithSym2 a6989586621681185937 a6989586621681185938 | |
type Apply (FilterMSym1 a6989586621681292398 :: TyFun [a] (m [a]) -> Type) (a6989586621681292399 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.Monad type Apply (FilterMSym1 a6989586621681292398 :: TyFun [a] (m [a]) -> Type) (a6989586621681292399 :: [a]) = FilterMSym2 a6989586621681292398 a6989586621681292399 | |
type Apply (SequenceA_Sym0 :: TyFun (t (f a)) (f ()) -> Type) (a6989586621680492361 :: t (f a)) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (SequenceA_Sym0 :: TyFun (t (f a)) (f ()) -> Type) (a6989586621680492361 :: t (f a)) = SequenceA_Sym1 a6989586621680492361 | |
type Apply (Sequence_Sym0 :: TyFun (t (m a)) (m ()) -> Type) (a6989586621680492355 :: t (m a)) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (Sequence_Sym0 :: TyFun (t (m a)) (m ()) -> Type) (a6989586621680492355 :: t (m a)) = Sequence_Sym1 a6989586621680492355 | |
type Apply (FindSym1 a6989586621680492226 :: TyFun (t a) (Maybe a) -> Type) (a6989586621680492227 :: t a) Source # | |
type Apply (SequenceASym0 :: TyFun (t (f a)) (f (t a)) -> Type) (a6989586621680816746 :: t (f a)) Source # | |
Defined in Data.Singletons.Prelude.Traversable type Apply (SequenceASym0 :: TyFun (t (f a)) (f (t a)) -> Type) (a6989586621680816746 :: t (f a)) = SequenceASym1 a6989586621680816746 | |
type Apply (SequenceSym0 :: TyFun (t (m a)) (m (t a)) -> Type) (a6989586621680816754 :: t (m a)) Source # | |
Defined in Data.Singletons.Prelude.Traversable type Apply (SequenceSym0 :: TyFun (t (m a)) (m (t a)) -> Type) (a6989586621680816754 :: t (m a)) = SequenceSym1 a6989586621680816754 | |
type Apply (MfilterSym1 a6989586621681292236 :: TyFun (m a) (m a) -> Type) (a6989586621681292237 :: m a) Source # | |
Defined in Data.Singletons.Prelude.Monad type Apply (MfilterSym1 a6989586621681292236 :: TyFun (m a) (m a) -> Type) (a6989586621681292237 :: m a) = MfilterSym2 a6989586621681292236 a6989586621681292237 | |
type Apply (ReplicateM_Sym1 a6989586621681292275 :: TyFun (m a) (m ()) -> Type) (a6989586621681292276 :: m a) Source # | |
Defined in Data.Singletons.Prelude.Monad type Apply (ReplicateM_Sym1 a6989586621681292275 :: TyFun (m a) (m ()) -> Type) (a6989586621681292276 :: m a) = ReplicateM_Sym2 a6989586621681292275 a6989586621681292276 | |
type Apply (ReplicateMSym1 a6989586621681292293 :: TyFun (m a) (m [a]) -> Type) (a6989586621681292294 :: m a) Source # | |
Defined in Data.Singletons.Prelude.Monad type Apply (ReplicateMSym1 a6989586621681292293 :: TyFun (m a) (m [a]) -> Type) (a6989586621681292294 :: m a) = ReplicateMSym2 a6989586621681292293 a6989586621681292294 | |
type Apply (ZipSym1 a6989586621681185848 :: TyFun (NonEmpty b) (NonEmpty (a, b)) -> Type) (a6989586621681185849 :: NonEmpty b) Source # | |
type Apply (GroupWith1Sym1 a6989586621681185896 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621681185897 :: NonEmpty a) Source # | |
Defined in Data.Singletons.Prelude.List.NonEmpty type Apply (GroupWith1Sym1 a6989586621681185896 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621681185897 :: NonEmpty a) = GroupWith1Sym2 a6989586621681185896 a6989586621681185897 | |
type Apply (MapSym1 a6989586621681186152 :: TyFun (NonEmpty a) (NonEmpty b) -> Type) (a6989586621681186153 :: NonEmpty a) Source # | |
type Apply (SortWithSym1 a6989586621681185772 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681185773 :: NonEmpty a) Source # | |
Defined in Data.Singletons.Prelude.List.NonEmpty type Apply (SortWithSym1 a6989586621681185772 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681185773 :: NonEmpty a) = SortWithSym2 a6989586621681185772 a6989586621681185773 | |
type Apply (GroupAllWith1Sym1 a6989586621681185887 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621681185888 :: NonEmpty a) Source # | |
Defined in Data.Singletons.Prelude.List.NonEmpty type Apply (GroupAllWith1Sym1 a6989586621681185887 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621681185888 :: NonEmpty a) = GroupAllWith1Sym2 a6989586621681185887 a6989586621681185888 | |
type Apply (ScanrSym2 a6989586621679969778 a6989586621679969779 :: TyFun [a] [b] -> Type) (a6989586621679969780 :: [a]) Source # | |
type Apply (ScanlSym2 a6989586621679969805 a6989586621679969806 :: TyFun [a] [b] -> Type) (a6989586621679969807 :: [a]) Source # | |
type Apply (ScanlSym2 a6989586621681186122 a6989586621681186123 :: TyFun [a] (NonEmpty b) -> Type) (a6989586621681186124 :: [a]) Source # | |
type Apply (ScanrSym2 a6989586621681186110 a6989586621681186111 :: TyFun [a] (NonEmpty b) -> Type) (a6989586621681186112 :: [a]) Source # | |
type Apply (FmapSym1 a6989586621679559667 :: TyFun (f a) (f b) -> Type) (a6989586621679559668 :: f a) Source # | |
type Apply ((<$@#@$$) a6989586621679559672 :: TyFun (f b) (f a) -> Type) (a6989586621679559673 :: f b) Source # | |
type Apply ((<*>@#@$$) a6989586621679559695 :: TyFun (f a) (f b) -> Type) (a6989586621679559696 :: f a) Source # | |
Defined in Data.Singletons.Prelude.Monad.Internal type Apply ((<*>@#@$$) a6989586621679559695 :: TyFun (f a) (f b) -> Type) (a6989586621679559696 :: f a) = a6989586621679559695 <*>@#@$$$ a6989586621679559696 | |
type Apply ((<**>@#@$$) a6989586621679559655 :: TyFun (f (a ~> b)) (f b) -> Type) (a6989586621679559656 :: f (a ~> b)) Source # | |
Defined in Data.Singletons.Prelude.Monad.Internal type Apply ((<**>@#@$$) a6989586621679559655 :: TyFun (f (a ~> b)) (f b) -> Type) (a6989586621679559656 :: f (a ~> b)) = a6989586621679559655 <**>@#@$$$ a6989586621679559656 | |
type Apply (LiftASym1 a6989586621679559644 :: TyFun (f a) (f b) -> Type) (a6989586621679559645 :: f a) Source # | |
type Apply ((=<<@#@$$) a6989586621679559620 :: TyFun (m a) (m b) -> Type) (a6989586621679559621 :: m a) Source # | |
Defined in Data.Singletons.Prelude.Monad.Internal type Apply ((=<<@#@$$) a6989586621679559620 :: TyFun (m a) (m b) -> Type) (a6989586621679559621 :: m a) = a6989586621679559620 =<<@#@$$$ a6989586621679559621 | |
type Apply (LiftMSym1 a6989586621679559599 :: TyFun (m a1) (m r) -> Type) (a6989586621679559600 :: m a1) Source # | |
type Apply (ApSym1 a6989586621679559470 :: TyFun (m a) (m b) -> Type) (a6989586621679559471 :: m a) Source # | |
type Apply ((<|>@#@$$) a6989586621679559816 :: TyFun (f a) (f a) -> Type) (a6989586621679559817 :: f a) Source # | |
Defined in Data.Singletons.Prelude.Monad.Internal type Apply ((<|>@#@$$) a6989586621679559816 :: TyFun (f a) (f a) -> Type) (a6989586621679559817 :: f a) = a6989586621679559816 <|>@#@$$$ a6989586621679559817 | |
type Apply (MplusSym1 a6989586621679559822 :: TyFun (m a) (m a) -> Type) (a6989586621679559823 :: m a) Source # | |
type Apply ((<$>@#@$$) a6989586621679731630 :: TyFun (f a) (f b) -> Type) (a6989586621679731631 :: f a) Source # | |
Defined in Data.Singletons.Prelude.Functor type Apply ((<$>@#@$$) a6989586621679731630 :: TyFun (f a) (f b) -> Type) (a6989586621679731631 :: f a) = a6989586621679731630 <$>@#@$$$ a6989586621679731631 | |
type Apply (AsumSym0 :: TyFun (t (f a)) (f a) -> Type) (a6989586621680492349 :: t (f a)) Source # | |
type Apply (MsumSym0 :: TyFun (t (m a)) (m a) -> Type) (a6989586621680492343 :: t (m a)) Source # | |
type Apply (ConcatMapSym1 a6989586621680492321 :: TyFun (t a) [b] -> Type) (a6989586621680492322 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (ConcatMapSym1 a6989586621680492321 :: TyFun (t a) [b] -> Type) (a6989586621680492322 :: t a) = ConcatMapSym2 a6989586621680492321 a6989586621680492322 | |
type Apply (FmapDefaultSym1 a6989586621680822982 :: TyFun (t a) (t b) -> Type) (a6989586621680822983 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Traversable type Apply (FmapDefaultSym1 a6989586621680822982 :: TyFun (t a) (t b) -> Type) (a6989586621680822983 :: t a) = FmapDefaultSym2 a6989586621680822982 a6989586621680822983 | |
type Apply (MzipSym1 a6989586621681150519 :: TyFun (m b) (m (a, b)) -> Type) (a6989586621681150520 :: m b) Source # | |
type Apply ((<$!>@#@$$) a6989586621681292252 :: TyFun (m a) (m b) -> Type) (a6989586621681292253 :: m a) Source # | |
Defined in Data.Singletons.Prelude.Monad type Apply ((<$!>@#@$$) a6989586621681292252 :: TyFun (m a) (m b) -> Type) (a6989586621681292253 :: m a) = a6989586621681292252 <$!>@#@$$$ a6989586621681292253 | |
type Apply (ZipWithSym2 a6989586621679969561 a6989586621679969562 :: TyFun [b] [c] -> Type) (a6989586621679969563 :: [b]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWithSym2 a6989586621679969561 a6989586621679969562 :: TyFun [b] [c] -> Type) (a6989586621679969563 :: [b]) = ZipWithSym3 a6989586621679969561 a6989586621679969562 a6989586621679969563 | |
type Apply (Zip3Sym2 a6989586621679969573 a6989586621679969574 :: TyFun [c] [(a, b, c)] -> Type) (a6989586621679969575 :: [c]) Source # | |
type Apply (MapAndUnzipMSym1 a6989586621681292357 :: TyFun [a] (m ([b], [c])) -> Type) (a6989586621681292358 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.Monad type Apply (MapAndUnzipMSym1 a6989586621681292357 :: TyFun [a] (m ([b], [c])) -> Type) (a6989586621681292358 :: [a]) = MapAndUnzipMSym2 a6989586621681292357 a6989586621681292358 | |
type Apply ((<*@#@$$) a6989586621679559712 :: TyFun (f b) (f a) -> Type) (a6989586621679559713 :: f b) Source # | |
type Apply ((*>@#@$$) a6989586621679559707 :: TyFun (f b) (f b) -> Type) (a6989586621679559708 :: f b) Source # | |
type Apply ((>>@#@$$) a6989586621679559780 :: TyFun (m b) (m b) -> Type) (a6989586621679559781 :: m b) Source # | |
type Apply (Traverse_Sym1 a6989586621680492399 :: TyFun (t a) (f ()) -> Type) (a6989586621680492400 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (Traverse_Sym1 a6989586621680492399 :: TyFun (t a) (f ()) -> Type) (a6989586621680492400 :: t a) = Traverse_Sym2 a6989586621680492399 a6989586621680492400 | |
type Apply (MapM_Sym1 a6989586621680492379 :: TyFun (t a) (m ()) -> Type) (a6989586621680492380 :: t a) Source # | |
type Apply (TraverseSym1 a6989586621680816742 :: TyFun (t a) (f (t b)) -> Type) (a6989586621680816743 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Traversable type Apply (TraverseSym1 a6989586621680816742 :: TyFun (t a) (f (t b)) -> Type) (a6989586621680816743 :: t a) = TraverseSym2 a6989586621680816742 a6989586621680816743 | |
type Apply (MapMSym1 a6989586621680816750 :: TyFun (t a) (m (t b)) -> Type) (a6989586621680816751 :: t a) Source # | |
type Apply (ZipWithSym2 a6989586621681185837 a6989586621681185838 :: TyFun (NonEmpty b) (NonEmpty c) -> Type) (a6989586621681185839 :: NonEmpty b) Source # | |
Defined in Data.Singletons.Prelude.List.NonEmpty type Apply (ZipWithSym2 a6989586621681185837 a6989586621681185838 :: TyFun (NonEmpty b) (NonEmpty c) -> Type) (a6989586621681185839 :: NonEmpty b) = ZipWithSym3 a6989586621681185837 a6989586621681185838 a6989586621681185839 | |
type Apply (ZipWithM_Sym2 a6989586621681292338 a6989586621681292339 :: TyFun [b] (m ()) -> Type) (a6989586621681292340 :: [b]) Source # | |
Defined in Data.Singletons.Prelude.Monad type Apply (ZipWithM_Sym2 a6989586621681292338 a6989586621681292339 :: TyFun [b] (m ()) -> Type) (a6989586621681292340 :: [b]) = ZipWithM_Sym3 a6989586621681292338 a6989586621681292339 a6989586621681292340 | |
type Apply (ZipWithMSym2 a6989586621681292348 a6989586621681292349 :: TyFun [b] (m [c]) -> Type) (a6989586621681292350 :: [b]) Source # | |
Defined in Data.Singletons.Prelude.Monad type Apply (ZipWithMSym2 a6989586621681292348 a6989586621681292349 :: TyFun [b] (m [c]) -> Type) (a6989586621681292350 :: [b]) = ZipWithMSym3 a6989586621681292348 a6989586621681292349 a6989586621681292350 | |
type Apply (LiftA2Sym2 a6989586621679559701 a6989586621679559702 :: TyFun (f b) (f c) -> Type) (a6989586621679559703 :: f b) Source # | |
Defined in Data.Singletons.Prelude.Monad.Internal type Apply (LiftA2Sym2 a6989586621679559701 a6989586621679559702 :: TyFun (f b) (f c) -> Type) (a6989586621679559703 :: f b) = LiftA2Sym3 a6989586621679559701 a6989586621679559702 a6989586621679559703 | |
type Apply (LiftM2Sym2 a6989586621679559582 a6989586621679559583 :: TyFun (m a2) (m r) -> Type) (a6989586621679559584 :: m a2) Source # | |
Defined in Data.Singletons.Prelude.Monad.Internal type Apply (LiftM2Sym2 a6989586621679559582 a6989586621679559583 :: TyFun (m a2) (m r) -> Type) (a6989586621679559584 :: m a2) = LiftM2Sym3 a6989586621679559582 a6989586621679559583 a6989586621679559584 | |
type Apply (FoldrMSym2 a6989586621680492425 a6989586621680492426 :: TyFun (t a) (m b) -> Type) (a6989586621680492427 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (FoldrMSym2 a6989586621680492425 a6989586621680492426 :: TyFun (t a) (m b) -> Type) (a6989586621680492427 :: t a) = FoldrMSym3 a6989586621680492425 a6989586621680492426 a6989586621680492427 | |
type Apply (FoldlMSym2 a6989586621680492407 a6989586621680492408 :: TyFun (t a) (m b) -> Type) (a6989586621680492409 :: t a) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (FoldlMSym2 a6989586621680492407 a6989586621680492408 :: TyFun (t a) (m b) -> Type) (a6989586621680492409 :: t a) = FoldlMSym3 a6989586621680492407 a6989586621680492408 a6989586621680492409 | |
type Apply (MzipWithSym2 a6989586621681150525 a6989586621681150526 :: TyFun (m b) (m c) -> Type) (a6989586621681150527 :: m b) Source # | |
Defined in Data.Singletons.Prelude.Monad.Zip type Apply (MzipWithSym2 a6989586621681150525 a6989586621681150526 :: TyFun (m b) (m c) -> Type) (a6989586621681150527 :: m b) = MzipWithSym3 a6989586621681150525 a6989586621681150526 a6989586621681150527 | |
type Apply (ZipWith3Sym3 a6989586621679969546 a6989586621679969547 a6989586621679969548 :: TyFun [c] [d] -> Type) (a6989586621679969549 :: [c]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith3Sym3 a6989586621679969546 a6989586621679969547 a6989586621679969548 :: TyFun [c] [d] -> Type) (a6989586621679969549 :: [c]) = ZipWith3Sym4 a6989586621679969546 a6989586621679969547 a6989586621679969548 a6989586621679969549 | |
type Apply (Zip4Sym3 a6989586621680091335 a6989586621680091336 a6989586621680091337 :: TyFun [d] [(a, b, c, d)] -> Type) (a6989586621680091338 :: [d]) Source # | |
type Apply (LiftA3Sym3 a6989586621679559633 a6989586621679559634 a6989586621679559635 :: TyFun (f c) (f d) -> Type) (a6989586621679559636 :: f c) Source # | |
Defined in Data.Singletons.Prelude.Monad.Internal type Apply (LiftA3Sym3 a6989586621679559633 a6989586621679559634 a6989586621679559635 :: TyFun (f c) (f d) -> Type) (a6989586621679559636 :: f c) | |
type Apply (LiftM3Sym3 a6989586621679559558 a6989586621679559559 a6989586621679559560 :: TyFun (m a3) (m r) -> Type) (a6989586621679559561 :: m a3) Source # | |
Defined in Data.Singletons.Prelude.Monad.Internal type Apply (LiftM3Sym3 a6989586621679559558 a6989586621679559559 a6989586621679559560 :: TyFun (m a3) (m r) -> Type) (a6989586621679559561 :: m a3) = LiftM3Sym4 a6989586621679559558 a6989586621679559559 a6989586621679559560 a6989586621679559561 | |
type Apply (ZipWith4Sym4 a6989586621680091215 a6989586621680091216 a6989586621680091217 a6989586621680091218 :: TyFun [d] [e] -> Type) (a6989586621680091219 :: [d]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith4Sym4 a6989586621680091215 a6989586621680091216 a6989586621680091217 a6989586621680091218 :: TyFun [d] [e] -> Type) (a6989586621680091219 :: [d]) = ZipWith4Sym5 a6989586621680091215 a6989586621680091216 a6989586621680091217 a6989586621680091218 a6989586621680091219 | |
type Apply (Zip5Sym4 a6989586621680091312 a6989586621680091313 a6989586621680091314 a6989586621680091315 :: TyFun [e] [(a, b, c, d, e)] -> Type) (a6989586621680091316 :: [e]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal | |
type Apply (LiftM4Sym4 a6989586621679559527 a6989586621679559528 a6989586621679559529 a6989586621679559530 :: TyFun (m a4) (m r) -> Type) (a6989586621679559531 :: m a4) Source # | |
Defined in Data.Singletons.Prelude.Monad.Internal type Apply (LiftM4Sym4 a6989586621679559527 a6989586621679559528 a6989586621679559529 a6989586621679559530 :: TyFun (m a4) (m r) -> Type) (a6989586621679559531 :: m a4) = LiftM4Sym5 a6989586621679559527 a6989586621679559528 a6989586621679559529 a6989586621679559530 a6989586621679559531 | |
type Apply (ZipWith5Sym5 a6989586621680091192 a6989586621680091193 a6989586621680091194 a6989586621680091195 a6989586621680091196 :: TyFun [e] [f] -> Type) (a6989586621680091197 :: [e]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith5Sym5 a6989586621680091192 a6989586621680091193 a6989586621680091194 a6989586621680091195 a6989586621680091196 :: TyFun [e] [f] -> Type) (a6989586621680091197 :: [e]) = ZipWith5Sym6 a6989586621680091192 a6989586621680091193 a6989586621680091194 a6989586621680091195 a6989586621680091196 a6989586621680091197 | |
type Apply (Zip6Sym5 a6989586621680091284 a6989586621680091285 a6989586621680091286 a6989586621680091287 a6989586621680091288 :: TyFun [f] [(a, b, c, d, e, f)] -> Type) (a6989586621680091289 :: [f]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip6Sym5 a6989586621680091284 a6989586621680091285 a6989586621680091286 a6989586621680091287 a6989586621680091288 :: TyFun [f] [(a, b, c, d, e, f)] -> Type) (a6989586621680091289 :: [f]) = Zip6Sym6 a6989586621680091284 a6989586621680091285 a6989586621680091286 a6989586621680091287 a6989586621680091288 a6989586621680091289 | |
type Apply (LiftM5Sym5 a6989586621679559489 a6989586621679559490 a6989586621679559491 a6989586621679559492 a6989586621679559493 :: TyFun (m a5) (m r) -> Type) (a6989586621679559494 :: m a5) Source # | |
Defined in Data.Singletons.Prelude.Monad.Internal type Apply (LiftM5Sym5 a6989586621679559489 a6989586621679559490 a6989586621679559491 a6989586621679559492 a6989586621679559493 :: TyFun (m a5) (m r) -> Type) (a6989586621679559494 :: m a5) = LiftM5Sym6 a6989586621679559489 a6989586621679559490 a6989586621679559491 a6989586621679559492 a6989586621679559493 a6989586621679559494 | |
type Apply (ZipWith6Sym6 a6989586621680091165 a6989586621680091166 a6989586621680091167 a6989586621680091168 a6989586621680091169 a6989586621680091170 :: TyFun [f] [g] -> Type) (a6989586621680091171 :: [f]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith6Sym6 a6989586621680091165 a6989586621680091166 a6989586621680091167 a6989586621680091168 a6989586621680091169 a6989586621680091170 :: TyFun [f] [g] -> Type) (a6989586621680091171 :: [f]) = ZipWith6Sym7 a6989586621680091165 a6989586621680091166 a6989586621680091167 a6989586621680091168 a6989586621680091169 a6989586621680091170 a6989586621680091171 | |
type Apply (Zip7Sym6 a6989586621680091251 a6989586621680091252 a6989586621680091253 a6989586621680091254 a6989586621680091255 a6989586621680091256 :: TyFun [g] [(a, b, c, d, e, f, g)] -> Type) (a6989586621680091257 :: [g]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip7Sym6 a6989586621680091251 a6989586621680091252 a6989586621680091253 a6989586621680091254 a6989586621680091255 a6989586621680091256 :: TyFun [g] [(a, b, c, d, e, f, g)] -> Type) (a6989586621680091257 :: [g]) = Zip7Sym7 a6989586621680091251 a6989586621680091252 a6989586621680091253 a6989586621680091254 a6989586621680091255 a6989586621680091256 a6989586621680091257 | |
type Apply (ZipWith7Sym7 a6989586621680091134 a6989586621680091135 a6989586621680091136 a6989586621680091137 a6989586621680091138 a6989586621680091139 a6989586621680091140 :: TyFun [g] [h] -> Type) (a6989586621680091141 :: [g]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith7Sym7 a6989586621680091134 a6989586621680091135 a6989586621680091136 a6989586621680091137 a6989586621680091138 a6989586621680091139 a6989586621680091140 :: TyFun [g] [h] -> Type) (a6989586621680091141 :: [g]) = ZipWith7Sym8 a6989586621680091134 a6989586621680091135 a6989586621680091136 a6989586621680091137 a6989586621680091138 a6989586621680091139 a6989586621680091140 a6989586621680091141 | |
type Apply ((++@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679534210 :: [a]) Source # | |
type Apply ((!!@#@$) :: TyFun [a] (Nat ~> a) -> Type) (a6989586621679968875 :: [a]) Source # | |
type Apply (UnionSym0 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679968812 :: [a]) Source # | |
type Apply ((\\@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679969385 :: [a]) Source # | |
type Apply (IsPrefixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) (a6989586621679969624 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IsPrefixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) (a6989586621679969624 :: [a]) = IsPrefixOfSym1 a6989586621679969624 | |
type Apply (IsInfixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) (a6989586621679969610 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IsInfixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) (a6989586621679969610 :: [a]) = IsInfixOfSym1 a6989586621679969610 | |
type Apply (IntersectSym0 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679969203 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IntersectSym0 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679969203 :: [a]) = IntersectSym1 a6989586621679969203 | |
type Apply (IntercalateSym0 :: TyFun [a] ([[a]] ~> [a]) -> Type) (a6989586621679969986 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IntercalateSym0 :: TyFun [a] ([[a]] ~> [a]) -> Type) (a6989586621679969986 :: [a]) = IntercalateSym1 a6989586621679969986 | |
type Apply (IsSuffixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) (a6989586621679969617 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IsSuffixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) (a6989586621679969617 :: [a]) = IsSuffixOfSym1 a6989586621679969617 | |
type Apply (StripPrefixSym0 :: TyFun [a] ([a] ~> Maybe [a]) -> Type) (a6989586621680091346 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (StripPrefixSym0 :: TyFun [a] ([a] ~> Maybe [a]) -> Type) (a6989586621680091346 :: [a]) = StripPrefixSym1 a6989586621680091346 | |
type Apply (ShowListSym0 :: TyFun [a] (Symbol ~> Symbol) -> Type) (a6989586621680279577 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.Show type Apply (ShowListSym0 :: TyFun [a] (Symbol ~> Symbol) -> Type) (a6989586621680279577 :: [a]) = ShowListSym1 a6989586621680279577 | |
type Apply (IsPrefixOfSym0 :: TyFun [a] (NonEmpty a ~> Bool) -> Type) (a6989586621681185876 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.NonEmpty type Apply (IsPrefixOfSym0 :: TyFun [a] (NonEmpty a ~> Bool) -> Type) (a6989586621681185876 :: [a]) = IsPrefixOfSym1 a6989586621681185876 | |
type Apply ((!!@#@$) :: TyFun (NonEmpty a) (Nat ~> a) -> Type) (a6989586621681185857 :: NonEmpty a) Source # | |
type Apply (UnconsSym0 :: TyFun (NonEmpty a) (a, Maybe (NonEmpty a)) -> Type) (a6989586621681186246 :: NonEmpty a) Source # | |
Defined in Data.Singletons.Prelude.List.NonEmpty type Apply (UnconsSym0 :: TyFun (NonEmpty a) (a, Maybe (NonEmpty a)) -> Type) (a6989586621681186246 :: NonEmpty a) = UnconsSym1 a6989586621681186246 | |
type Apply ((:<>:@#@$) :: TyFun (ErrorMessage' s) (ErrorMessage' s ~> ErrorMessage' s) -> Type) (a6989586621681349587 :: ErrorMessage' s) Source # | |
Defined in Data.Singletons.TypeError type Apply ((:<>:@#@$) :: TyFun (ErrorMessage' s) (ErrorMessage' s ~> ErrorMessage' s) -> Type) (a6989586621681349587 :: ErrorMessage' s) = (:<>:@#@$$) a6989586621681349587 | |
type Apply ((:$$:@#@$) :: TyFun (ErrorMessage' s) (ErrorMessage' s ~> ErrorMessage' s) -> Type) (a6989586621681349590 :: ErrorMessage' s) Source # | |
Defined in Data.Singletons.TypeError type Apply ((:$$:@#@$) :: TyFun (ErrorMessage' s) (ErrorMessage' s ~> ErrorMessage' s) -> Type) (a6989586621681349590 :: ErrorMessage' s) = (:$$:@#@$$) a6989586621681349590 | |
type Apply (UnzipSym0 :: TyFun [(a, b)] ([a], [b]) -> Type) (a6989586621679969527 :: [(a, b)]) Source # | |
type Apply (PartitionSym1 a6989586621679968951 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679968952 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (PartitionSym1 a6989586621679968951 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679968952 :: [a]) = PartitionSym2 a6989586621679968951 a6989586621679968952 | |
type Apply (SplitAtSym1 a6989586621679969030 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679969031 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (SplitAtSym1 a6989586621679969030 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679969031 :: [a]) = SplitAtSym2 a6989586621679969030 a6989586621679969031 | |
type Apply (BreakSym1 a6989586621679969063 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679969064 :: [a]) Source # | |
type Apply (SpanSym1 a6989586621679969098 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679969099 :: [a]) Source # | |
type Apply (DeleteFirstsBySym1 a6989586621679969356 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679969357 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DeleteFirstsBySym1 a6989586621679969356 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679969357 :: [a]) = DeleteFirstsBySym2 a6989586621679969356 a6989586621679969357 | |
type Apply (UnionBySym1 a6989586621679968820 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679968821 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (UnionBySym1 a6989586621679968820 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679968821 :: [a]) = UnionBySym2 a6989586621679968820 a6989586621679968821 | |
type Apply (ZipSym0 :: TyFun [a] ([b] ~> [(a, b)]) -> Type) (a6989586621679969585 :: [a]) Source # | |
type Apply (IntersectBySym1 a6989586621679969181 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679969182 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IntersectBySym1 a6989586621679969181 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679969182 :: [a]) = IntersectBySym2 a6989586621679969181 a6989586621679969182 | |
type Apply (ShowListWithSym1 a6989586621680279542 :: TyFun [a] (Symbol ~> Symbol) -> Type) (a6989586621680279543 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.Show type Apply (ShowListWithSym1 a6989586621680279542 :: TyFun [a] (Symbol ~> Symbol) -> Type) (a6989586621680279543 :: [a]) = ShowListWithSym2 a6989586621680279542 a6989586621680279543 | |
type Apply (UnzipSym0 :: TyFun (NonEmpty (a, b)) (NonEmpty a, NonEmpty b) -> Type) (a6989586621681185811 :: NonEmpty (a, b)) Source # | |
type Apply (ZipSym0 :: TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty (a, b)) -> Type) (a6989586621681185848 :: NonEmpty a) Source # | |
type Apply (SplitAtSym1 a6989586621681186049 :: TyFun (NonEmpty a) ([a], [a]) -> Type) (a6989586621681186050 :: NonEmpty a) Source # | |
Defined in Data.Singletons.Prelude.List.NonEmpty type Apply (SplitAtSym1 a6989586621681186049 :: TyFun (NonEmpty a) ([a], [a]) -> Type) (a6989586621681186050 :: NonEmpty a) = SplitAtSym2 a6989586621681186049 a6989586621681186050 | |
type Apply (SpanSym1 a6989586621681186022 :: TyFun (NonEmpty a) ([a], [a]) -> Type) (a6989586621681186023 :: NonEmpty a) Source # | |
type Apply (BreakSym1 a6989586621681186013 :: TyFun (NonEmpty a) ([a], [a]) -> Type) (a6989586621681186014 :: NonEmpty a) Source # | |
type Apply (PartitionSym1 a6989586621681185995 :: TyFun (NonEmpty a) ([a], [a]) -> Type) (a6989586621681185996 :: NonEmpty a) Source # | |
Defined in Data.Singletons.Prelude.List.NonEmpty type Apply (PartitionSym1 a6989586621681185995 :: TyFun (NonEmpty a) ([a], [a]) -> Type) (a6989586621681185996 :: NonEmpty a) = PartitionSym2 a6989586621681185995 a6989586621681185996 | |
type Apply (Zip3Sym0 :: TyFun [a] ([b] ~> ([c] ~> [(a, b, c)])) -> Type) (a6989586621679969573 :: [a]) Source # | |
type Apply ((<*>@#@$) :: TyFun (f (a ~> b)) (f a ~> f b) -> Type) (a6989586621679559695 :: f (a ~> b)) Source # | |
Defined in Data.Singletons.Prelude.Monad.Internal | |
type Apply ((<**>@#@$) :: TyFun (f a) (f (a ~> b) ~> f b) -> Type) (a6989586621679559655 :: f a) Source # | |
Defined in Data.Singletons.Prelude.Monad.Internal type Apply ((<**>@#@$) :: TyFun (f a) (f (a ~> b) ~> f b) -> Type) (a6989586621679559655 :: f a) = (<**>@#@$$) a6989586621679559655 :: TyFun (f (a ~> b)) (f b) -> Type | |
type Apply ((>>=@#@$) :: TyFun (m a) ((a ~> m b) ~> m b) -> Type) (a6989586621679559775 :: m a) Source # | |
type Apply (ApSym0 :: TyFun (m (a ~> b)) (m a ~> m b) -> Type) (a6989586621679559470 :: m (a ~> b)) Source # | |
type Apply ((<|>@#@$) :: TyFun (f a) (f a ~> f a) -> Type) (a6989586621679559816 :: f a) Source # | |
Defined in Data.Singletons.Prelude.Monad.Internal | |
type Apply (MplusSym0 :: TyFun (m a) (m a ~> m a) -> Type) (a6989586621679559822 :: m a) Source # | |
type Apply (($>@#@$) :: TyFun (f a) (b ~> f b) -> Type) (a6989586621679731612 :: f a) Source # | |
type Apply ((<&>@#@$) :: TyFun (f a) ((a ~> b) ~> f b) -> Type) (a6989586621679731619 :: f a) Source # | |
type Apply (MzipSym0 :: TyFun (m a) (m b ~> m (a, b)) -> Type) (a6989586621681150519 :: m a) Source # | |
type Apply (MunzipSym0 :: TyFun (m (a, b)) (m a, m b) -> Type) (a6989586621681150530 :: m (a, b)) Source # | |
Defined in Data.Singletons.Prelude.Monad.Zip type Apply (MunzipSym0 :: TyFun (m (a, b)) (m a, m b) -> Type) (a6989586621681150530 :: m (a, b)) = MunzipSym1 a6989586621681150530 | |
type Apply (ZipWithSym1 a6989586621679969561 :: TyFun [a] ([b] ~> [c]) -> Type) (a6989586621679969562 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWithSym1 a6989586621679969561 :: TyFun [a] ([b] ~> [c]) -> Type) (a6989586621679969562 :: [a]) = ZipWithSym2 a6989586621679969561 a6989586621679969562 | |
type Apply (Zip3Sym1 a6989586621679969573 :: TyFun [b] ([c] ~> [(a, b, c)]) -> Type) (a6989586621679969574 :: [b]) Source # | |
type Apply (Zip4Sym0 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> [(a, b, c, d)]))) -> Type) (a6989586621680091335 :: [a]) Source # | |
type Apply ((<*@#@$) :: TyFun (f a) (f b ~> f a) -> Type) (a6989586621679559712 :: f a) Source # | |
type Apply ((*>@#@$) :: TyFun (f a) (f b ~> f b) -> Type) (a6989586621679559707 :: f a) Source # | |
type Apply ((>>@#@$) :: TyFun (m a) (m b ~> m b) -> Type) (a6989586621679559780 :: m a) Source # | |
type Apply (For_Sym0 :: TyFun (t a) ((a ~> f b) ~> f ()) -> Type) (a6989586621680492390 :: t a) Source # | |
type Apply (ForM_Sym0 :: TyFun (t a) ((a ~> m b) ~> m ()) -> Type) (a6989586621680492370 :: t a) Source # | |
type Apply (ForMSym0 :: TyFun (t a) ((a ~> m b) ~> m (t b)) -> Type) (a6989586621680823019 :: t a) Source # | |
type Apply (ForSym0 :: TyFun (t a) ((a ~> f b) ~> f (t b)) -> Type) (a6989586621680823030 :: t a) Source # | |
type Apply (ZipWithSym1 a6989586621681185837 :: TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty c) -> Type) (a6989586621681185838 :: NonEmpty a) Source # | |
Defined in Data.Singletons.Prelude.List.NonEmpty type Apply (ZipWithSym1 a6989586621681185837 :: TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty c) -> Type) (a6989586621681185838 :: NonEmpty a) = ZipWithSym2 a6989586621681185837 a6989586621681185838 | |
type Apply (ZipWith3Sym1 a6989586621679969546 :: TyFun [a] ([b] ~> ([c] ~> [d])) -> Type) (a6989586621679969547 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith3Sym1 a6989586621679969546 :: TyFun [a] ([b] ~> ([c] ~> [d])) -> Type) (a6989586621679969547 :: [a]) = ZipWith3Sym2 a6989586621679969546 a6989586621679969547 | |
type Apply (Zip5Sym0 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> [(a, b, c, d, e)])))) -> Type) (a6989586621680091312 :: [a]) Source # | |
type Apply (Zip4Sym1 a6989586621680091335 :: TyFun [b] ([c] ~> ([d] ~> [(a, b, c, d)])) -> Type) (a6989586621680091336 :: [b]) Source # | |
type Apply (ZipWithM_Sym1 a6989586621681292338 :: TyFun [a] ([b] ~> m ()) -> Type) (a6989586621681292339 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.Monad type Apply (ZipWithM_Sym1 a6989586621681292338 :: TyFun [a] ([b] ~> m ()) -> Type) (a6989586621681292339 :: [a]) = ZipWithM_Sym2 a6989586621681292338 a6989586621681292339 | |
type Apply (ZipWithMSym1 a6989586621681292348 :: TyFun [a] ([b] ~> m [c]) -> Type) (a6989586621681292349 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.Monad type Apply (ZipWithMSym1 a6989586621681292348 :: TyFun [a] ([b] ~> m [c]) -> Type) (a6989586621681292349 :: [a]) = ZipWithMSym2 a6989586621681292348 a6989586621681292349 | |
type Apply (LiftA2Sym1 a6989586621679559701 :: TyFun (f a) (f b ~> f c) -> Type) (a6989586621679559702 :: f a) Source # | |
Defined in Data.Singletons.Prelude.Monad.Internal type Apply (LiftA2Sym1 a6989586621679559701 :: TyFun (f a) (f b ~> f c) -> Type) (a6989586621679559702 :: f a) = LiftA2Sym2 a6989586621679559701 a6989586621679559702 | |
type Apply (LiftM2Sym1 a6989586621679559582 :: TyFun (m a1) (m a2 ~> m r) -> Type) (a6989586621679559583 :: m a1) Source # | |
Defined in Data.Singletons.Prelude.Monad.Internal type Apply (LiftM2Sym1 a6989586621679559582 :: TyFun (m a1) (m a2 ~> m r) -> Type) (a6989586621679559583 :: m a1) = LiftM2Sym2 a6989586621679559582 a6989586621679559583 | |
type Apply (MzipWithSym1 a6989586621681150525 :: TyFun (m a) (m b ~> m c) -> Type) (a6989586621681150526 :: m a) Source # | |
Defined in Data.Singletons.Prelude.Monad.Zip type Apply (MzipWithSym1 a6989586621681150525 :: TyFun (m a) (m b ~> m c) -> Type) (a6989586621681150526 :: m a) = MzipWithSym2 a6989586621681150525 a6989586621681150526 | |
type Apply (ZipWith3Sym2 a6989586621679969546 a6989586621679969547 :: TyFun [b] ([c] ~> [d]) -> Type) (a6989586621679969548 :: [b]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith3Sym2 a6989586621679969546 a6989586621679969547 :: TyFun [b] ([c] ~> [d]) -> Type) (a6989586621679969548 :: [b]) = ZipWith3Sym3 a6989586621679969546 a6989586621679969547 a6989586621679969548 | |
type Apply (ZipWith4Sym1 a6989586621680091215 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> [e]))) -> Type) (a6989586621680091216 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith4Sym1 a6989586621680091215 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> [e]))) -> Type) (a6989586621680091216 :: [a]) = ZipWith4Sym2 a6989586621680091215 a6989586621680091216 | |
type Apply (Zip6Sym0 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)]))))) -> Type) (a6989586621680091284 :: [a]) Source # | |
type Apply (Zip5Sym1 a6989586621680091312 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> [(a, b, c, d, e)]))) -> Type) (a6989586621680091313 :: [b]) Source # | |
type Apply (Zip4Sym2 a6989586621680091335 a6989586621680091336 :: TyFun [c] ([d] ~> [(a, b, c, d)]) -> Type) (a6989586621680091337 :: [c]) Source # | |
type Apply (LiftA3Sym1 a6989586621679559633 :: TyFun (f a) (f b ~> (f c ~> f d)) -> Type) (a6989586621679559634 :: f a) Source # | |
Defined in Data.Singletons.Prelude.Monad.Internal type Apply (LiftA3Sym1 a6989586621679559633 :: TyFun (f a) (f b ~> (f c ~> f d)) -> Type) (a6989586621679559634 :: f a) = LiftA3Sym2 a6989586621679559633 a6989586621679559634 | |
type Apply (LiftM3Sym1 a6989586621679559558 :: TyFun (m a1) (m a2 ~> (m a3 ~> m r)) -> Type) (a6989586621679559559 :: m a1) Source # | |
Defined in Data.Singletons.Prelude.Monad.Internal type Apply (LiftM3Sym1 a6989586621679559558 :: TyFun (m a1) (m a2 ~> (m a3 ~> m r)) -> Type) (a6989586621679559559 :: m a1) = LiftM3Sym2 a6989586621679559558 a6989586621679559559 | |
type Apply (MapAccumRSym2 a6989586621680822996 a6989586621680822997 :: TyFun (t b) (a, t c) -> Type) (a6989586621680822998 :: t b) Source # | |
Defined in Data.Singletons.Prelude.Traversable type Apply (MapAccumRSym2 a6989586621680822996 a6989586621680822997 :: TyFun (t b) (a, t c) -> Type) (a6989586621680822998 :: t b) = MapAccumRSym3 a6989586621680822996 a6989586621680822997 a6989586621680822998 | |
type Apply (MapAccumLSym2 a6989586621680823006 a6989586621680823007 :: TyFun (t b) (a, t c) -> Type) (a6989586621680823008 :: t b) Source # | |
Defined in Data.Singletons.Prelude.Traversable type Apply (MapAccumLSym2 a6989586621680823006 a6989586621680823007 :: TyFun (t b) (a, t c) -> Type) (a6989586621680823008 :: t b) = MapAccumLSym3 a6989586621680823006 a6989586621680823007 a6989586621680823008 | |
type Apply (ZipWith5Sym1 a6989586621680091192 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> [f])))) -> Type) (a6989586621680091193 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith5Sym1 a6989586621680091192 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> [f])))) -> Type) (a6989586621680091193 :: [a]) = ZipWith5Sym2 a6989586621680091192 a6989586621680091193 | |
type Apply (ZipWith4Sym2 a6989586621680091215 a6989586621680091216 :: TyFun [b] ([c] ~> ([d] ~> [e])) -> Type) (a6989586621680091217 :: [b]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith4Sym2 a6989586621680091215 a6989586621680091216 :: TyFun [b] ([c] ~> ([d] ~> [e])) -> Type) (a6989586621680091217 :: [b]) = ZipWith4Sym3 a6989586621680091215 a6989586621680091216 a6989586621680091217 | |
type Apply (Zip7Sym0 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])))))) -> Type) (a6989586621680091251 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal | |
type Apply (Zip6Sym1 a6989586621680091284 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)])))) -> Type) (a6989586621680091285 :: [b]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal | |
type Apply (Zip5Sym2 a6989586621680091312 a6989586621680091313 :: TyFun [c] ([d] ~> ([e] ~> [(a, b, c, d, e)])) -> Type) (a6989586621680091314 :: [c]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal | |
type Apply (LiftA3Sym2 a6989586621679559633 a6989586621679559634 :: TyFun (f b) (f c ~> f d) -> Type) (a6989586621679559635 :: f b) Source # | |
Defined in Data.Singletons.Prelude.Monad.Internal type Apply (LiftA3Sym2 a6989586621679559633 a6989586621679559634 :: TyFun (f b) (f c ~> f d) -> Type) (a6989586621679559635 :: f b) = LiftA3Sym3 a6989586621679559633 a6989586621679559634 a6989586621679559635 | |
type Apply (LiftM3Sym2 a6989586621679559558 a6989586621679559559 :: TyFun (m a2) (m a3 ~> m r) -> Type) (a6989586621679559560 :: m a2) Source # | |
Defined in Data.Singletons.Prelude.Monad.Internal type Apply (LiftM3Sym2 a6989586621679559558 a6989586621679559559 :: TyFun (m a2) (m a3 ~> m r) -> Type) (a6989586621679559560 :: m a2) = LiftM3Sym3 a6989586621679559558 a6989586621679559559 a6989586621679559560 | |
type Apply (LiftM4Sym1 a6989586621679559527 :: TyFun (m a1) (m a2 ~> (m a3 ~> (m a4 ~> m r))) -> Type) (a6989586621679559528 :: m a1) Source # | |
Defined in Data.Singletons.Prelude.Monad.Internal type Apply (LiftM4Sym1 a6989586621679559527 :: TyFun (m a1) (m a2 ~> (m a3 ~> (m a4 ~> m r))) -> Type) (a6989586621679559528 :: m a1) = LiftM4Sym2 a6989586621679559527 a6989586621679559528 | |
type Apply (ZipWith6Sym1 a6989586621680091165 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g]))))) -> Type) (a6989586621680091166 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith6Sym1 a6989586621680091165 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g]))))) -> Type) (a6989586621680091166 :: [a]) = ZipWith6Sym2 a6989586621680091165 a6989586621680091166 | |
type Apply (ZipWith5Sym2 a6989586621680091192 a6989586621680091193 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> [f]))) -> Type) (a6989586621680091194 :: [b]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith5Sym2 a6989586621680091192 a6989586621680091193 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> [f]))) -> Type) (a6989586621680091194 :: [b]) = ZipWith5Sym3 a6989586621680091192 a6989586621680091193 a6989586621680091194 | |
type Apply (ZipWith4Sym3 a6989586621680091215 a6989586621680091216 a6989586621680091217 :: TyFun [c] ([d] ~> [e]) -> Type) (a6989586621680091218 :: [c]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith4Sym3 a6989586621680091215 a6989586621680091216 a6989586621680091217 :: TyFun [c] ([d] ~> [e]) -> Type) (a6989586621680091218 :: [c]) = ZipWith4Sym4 a6989586621680091215 a6989586621680091216 a6989586621680091217 a6989586621680091218 | |
type Apply (Zip7Sym1 a6989586621680091251 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))))) -> Type) (a6989586621680091252 :: [b]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal | |
type Apply (Zip6Sym2 a6989586621680091284 a6989586621680091285 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)]))) -> Type) (a6989586621680091286 :: [c]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal | |
type Apply (Zip5Sym3 a6989586621680091312 a6989586621680091313 a6989586621680091314 :: TyFun [d] ([e] ~> [(a, b, c, d, e)]) -> Type) (a6989586621680091315 :: [d]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal | |
type Apply (LiftM4Sym2 a6989586621679559527 a6989586621679559528 :: TyFun (m a2) (m a3 ~> (m a4 ~> m r)) -> Type) (a6989586621679559529 :: m a2) Source # | |
Defined in Data.Singletons.Prelude.Monad.Internal type Apply (LiftM4Sym2 a6989586621679559527 a6989586621679559528 :: TyFun (m a2) (m a3 ~> (m a4 ~> m r)) -> Type) (a6989586621679559529 :: m a2) = LiftM4Sym3 a6989586621679559527 a6989586621679559528 a6989586621679559529 | |
type Apply (LiftM5Sym1 a6989586621679559489 :: TyFun (m a1) (m a2 ~> (m a3 ~> (m a4 ~> (m a5 ~> m r)))) -> Type) (a6989586621679559490 :: m a1) Source # | |
Defined in Data.Singletons.Prelude.Monad.Internal type Apply (LiftM5Sym1 a6989586621679559489 :: TyFun (m a1) (m a2 ~> (m a3 ~> (m a4 ~> (m a5 ~> m r)))) -> Type) (a6989586621679559490 :: m a1) = LiftM5Sym2 a6989586621679559489 a6989586621679559490 | |
type Apply (ZipWith7Sym1 a6989586621680091134 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h])))))) -> Type) (a6989586621680091135 :: [a]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal | |
type Apply (ZipWith6Sym2 a6989586621680091165 a6989586621680091166 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g])))) -> Type) (a6989586621680091167 :: [b]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith6Sym2 a6989586621680091165 a6989586621680091166 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g])))) -> Type) (a6989586621680091167 :: [b]) = ZipWith6Sym3 a6989586621680091165 a6989586621680091166 a6989586621680091167 | |
type Apply (ZipWith5Sym3 a6989586621680091192 a6989586621680091193 a6989586621680091194 :: TyFun [c] ([d] ~> ([e] ~> [f])) -> Type) (a6989586621680091195 :: [c]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith5Sym3 a6989586621680091192 a6989586621680091193 a6989586621680091194 :: TyFun [c] ([d] ~> ([e] ~> [f])) -> Type) (a6989586621680091195 :: [c]) = ZipWith5Sym4 a6989586621680091192 a6989586621680091193 a6989586621680091194 a6989586621680091195 | |
type Apply (Zip7Sym2 a6989586621680091251 a6989586621680091252 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])))) -> Type) (a6989586621680091253 :: [c]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip7Sym2 a6989586621680091251 a6989586621680091252 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])))) -> Type) (a6989586621680091253 :: [c]) = Zip7Sym3 a6989586621680091251 a6989586621680091252 a6989586621680091253 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))) -> Type | |
type Apply (Zip6Sym3 a6989586621680091284 a6989586621680091285 a6989586621680091286 :: TyFun [d] ([e] ~> ([f] ~> [(a, b, c, d, e, f)])) -> Type) (a6989586621680091287 :: [d]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip6Sym3 a6989586621680091284 a6989586621680091285 a6989586621680091286 :: TyFun [d] ([e] ~> ([f] ~> [(a, b, c, d, e, f)])) -> Type) (a6989586621680091287 :: [d]) = Zip6Sym4 a6989586621680091284 a6989586621680091285 a6989586621680091286 a6989586621680091287 :: TyFun [e] ([f] ~> [(a, b, c, d, e, f)]) -> Type | |
type Apply (LiftM4Sym3 a6989586621679559527 a6989586621679559528 a6989586621679559529 :: TyFun (m a3) (m a4 ~> m r) -> Type) (a6989586621679559530 :: m a3) Source # | |
Defined in Data.Singletons.Prelude.Monad.Internal type Apply (LiftM4Sym3 a6989586621679559527 a6989586621679559528 a6989586621679559529 :: TyFun (m a3) (m a4 ~> m r) -> Type) (a6989586621679559530 :: m a3) = LiftM4Sym4 a6989586621679559527 a6989586621679559528 a6989586621679559529 a6989586621679559530 | |
type Apply (LiftM5Sym2 a6989586621679559489 a6989586621679559490 :: TyFun (m a2) (m a3 ~> (m a4 ~> (m a5 ~> m r))) -> Type) (a6989586621679559491 :: m a2) Source # | |
Defined in Data.Singletons.Prelude.Monad.Internal type Apply (LiftM5Sym2 a6989586621679559489 a6989586621679559490 :: TyFun (m a2) (m a3 ~> (m a4 ~> (m a5 ~> m r))) -> Type) (a6989586621679559491 :: m a2) = LiftM5Sym3 a6989586621679559489 a6989586621679559490 a6989586621679559491 | |
type Apply (ZipWith7Sym2 a6989586621680091134 a6989586621680091135 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h]))))) -> Type) (a6989586621680091136 :: [b]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith7Sym2 a6989586621680091134 a6989586621680091135 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h]))))) -> Type) (a6989586621680091136 :: [b]) = ZipWith7Sym3 a6989586621680091134 a6989586621680091135 a6989586621680091136 | |
type Apply (ZipWith6Sym3 a6989586621680091165 a6989586621680091166 a6989586621680091167 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> [g]))) -> Type) (a6989586621680091168 :: [c]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith6Sym3 a6989586621680091165 a6989586621680091166 a6989586621680091167 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> [g]))) -> Type) (a6989586621680091168 :: [c]) = ZipWith6Sym4 a6989586621680091165 a6989586621680091166 a6989586621680091167 a6989586621680091168 | |
type Apply (ZipWith5Sym4 a6989586621680091192 a6989586621680091193 a6989586621680091194 a6989586621680091195 :: TyFun [d] ([e] ~> [f]) -> Type) (a6989586621680091196 :: [d]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith5Sym4 a6989586621680091192 a6989586621680091193 a6989586621680091194 a6989586621680091195 :: TyFun [d] ([e] ~> [f]) -> Type) (a6989586621680091196 :: [d]) = ZipWith5Sym5 a6989586621680091192 a6989586621680091193 a6989586621680091194 a6989586621680091195 a6989586621680091196 | |
type Apply (Zip7Sym3 a6989586621680091251 a6989586621680091252 a6989586621680091253 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))) -> Type) (a6989586621680091254 :: [d]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip7Sym3 a6989586621680091251 a6989586621680091252 a6989586621680091253 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))) -> Type) (a6989586621680091254 :: [d]) = Zip7Sym4 a6989586621680091251 a6989586621680091252 a6989586621680091253 a6989586621680091254 :: TyFun [e] ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])) -> Type | |
type Apply (Zip6Sym4 a6989586621680091284 a6989586621680091285 a6989586621680091286 a6989586621680091287 :: TyFun [e] ([f] ~> [(a, b, c, d, e, f)]) -> Type) (a6989586621680091288 :: [e]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip6Sym4 a6989586621680091284 a6989586621680091285 a6989586621680091286 a6989586621680091287 :: TyFun [e] ([f] ~> [(a, b, c, d, e, f)]) -> Type) (a6989586621680091288 :: [e]) = Zip6Sym5 a6989586621680091284 a6989586621680091285 a6989586621680091286 a6989586621680091287 a6989586621680091288 :: TyFun [f] [(a, b, c, d, e, f)] -> Type | |
type Apply (LiftM5Sym3 a6989586621679559489 a6989586621679559490 a6989586621679559491 :: TyFun (m a3) (m a4 ~> (m a5 ~> m r)) -> Type) (a6989586621679559492 :: m a3) Source # | |
Defined in Data.Singletons.Prelude.Monad.Internal type Apply (LiftM5Sym3 a6989586621679559489 a6989586621679559490 a6989586621679559491 :: TyFun (m a3) (m a4 ~> (m a5 ~> m r)) -> Type) (a6989586621679559492 :: m a3) = LiftM5Sym4 a6989586621679559489 a6989586621679559490 a6989586621679559491 a6989586621679559492 | |
type Apply (ZipWith7Sym3 a6989586621680091134 a6989586621680091135 a6989586621680091136 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h])))) -> Type) (a6989586621680091137 :: [c]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith7Sym3 a6989586621680091134 a6989586621680091135 a6989586621680091136 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h])))) -> Type) (a6989586621680091137 :: [c]) = ZipWith7Sym4 a6989586621680091134 a6989586621680091135 a6989586621680091136 a6989586621680091137 | |
type Apply (ZipWith6Sym4 a6989586621680091165 a6989586621680091166 a6989586621680091167 a6989586621680091168 :: TyFun [d] ([e] ~> ([f] ~> [g])) -> Type) (a6989586621680091169 :: [d]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith6Sym4 a6989586621680091165 a6989586621680091166 a6989586621680091167 a6989586621680091168 :: TyFun [d] ([e] ~> ([f] ~> [g])) -> Type) (a6989586621680091169 :: [d]) = ZipWith6Sym5 a6989586621680091165 a6989586621680091166 a6989586621680091167 a6989586621680091168 a6989586621680091169 | |
type Apply (Zip7Sym4 a6989586621680091251 a6989586621680091252 a6989586621680091253 a6989586621680091254 :: TyFun [e] ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])) -> Type) (a6989586621680091255 :: [e]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip7Sym4 a6989586621680091251 a6989586621680091252 a6989586621680091253 a6989586621680091254 :: TyFun [e] ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])) -> Type) (a6989586621680091255 :: [e]) = Zip7Sym5 a6989586621680091251 a6989586621680091252 a6989586621680091253 a6989586621680091254 a6989586621680091255 :: TyFun [f] ([g] ~> [(a, b, c, d, e, f, g)]) -> Type | |
type Apply (LiftM5Sym4 a6989586621679559489 a6989586621679559490 a6989586621679559491 a6989586621679559492 :: TyFun (m a4) (m a5 ~> m r) -> Type) (a6989586621679559493 :: m a4) Source # | |
Defined in Data.Singletons.Prelude.Monad.Internal type Apply (LiftM5Sym4 a6989586621679559489 a6989586621679559490 a6989586621679559491 a6989586621679559492 :: TyFun (m a4) (m a5 ~> m r) -> Type) (a6989586621679559493 :: m a4) = LiftM5Sym5 a6989586621679559489 a6989586621679559490 a6989586621679559491 a6989586621679559492 a6989586621679559493 | |
type Apply (ZipWith7Sym4 a6989586621680091134 a6989586621680091135 a6989586621680091136 a6989586621680091137 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [h]))) -> Type) (a6989586621680091138 :: [d]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith7Sym4 a6989586621680091134 a6989586621680091135 a6989586621680091136 a6989586621680091137 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [h]))) -> Type) (a6989586621680091138 :: [d]) = ZipWith7Sym5 a6989586621680091134 a6989586621680091135 a6989586621680091136 a6989586621680091137 a6989586621680091138 | |
type Apply (ZipWith6Sym5 a6989586621680091165 a6989586621680091166 a6989586621680091167 a6989586621680091168 a6989586621680091169 :: TyFun [e] ([f] ~> [g]) -> Type) (a6989586621680091170 :: [e]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith6Sym5 a6989586621680091165 a6989586621680091166 a6989586621680091167 a6989586621680091168 a6989586621680091169 :: TyFun [e] ([f] ~> [g]) -> Type) (a6989586621680091170 :: [e]) = ZipWith6Sym6 a6989586621680091165 a6989586621680091166 a6989586621680091167 a6989586621680091168 a6989586621680091169 a6989586621680091170 | |
type Apply (Zip7Sym5 a6989586621680091251 a6989586621680091252 a6989586621680091253 a6989586621680091254 a6989586621680091255 :: TyFun [f] ([g] ~> [(a, b, c, d, e, f, g)]) -> Type) (a6989586621680091256 :: [f]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Zip7Sym5 a6989586621680091251 a6989586621680091252 a6989586621680091253 a6989586621680091254 a6989586621680091255 :: TyFun [f] ([g] ~> [(a, b, c, d, e, f, g)]) -> Type) (a6989586621680091256 :: [f]) = Zip7Sym6 a6989586621680091251 a6989586621680091252 a6989586621680091253 a6989586621680091254 a6989586621680091255 a6989586621680091256 :: TyFun [g] [(a, b, c, d, e, f, g)] -> Type | |
type Apply (ZipWith7Sym5 a6989586621680091134 a6989586621680091135 a6989586621680091136 a6989586621680091137 a6989586621680091138 :: TyFun [e] ([f] ~> ([g] ~> [h])) -> Type) (a6989586621680091139 :: [e]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith7Sym5 a6989586621680091134 a6989586621680091135 a6989586621680091136 a6989586621680091137 a6989586621680091138 :: TyFun [e] ([f] ~> ([g] ~> [h])) -> Type) (a6989586621680091139 :: [e]) = ZipWith7Sym6 a6989586621680091134 a6989586621680091135 a6989586621680091136 a6989586621680091137 a6989586621680091138 a6989586621680091139 | |
type Apply (ZipWith7Sym6 a6989586621680091134 a6989586621680091135 a6989586621680091136 a6989586621680091137 a6989586621680091138 a6989586621680091139 :: TyFun [f] ([g] ~> [h]) -> Type) (a6989586621680091140 :: [f]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ZipWith7Sym6 a6989586621680091134 a6989586621680091135 a6989586621680091136 a6989586621680091137 a6989586621680091138 a6989586621680091139 :: TyFun [f] ([g] ~> [h]) -> Type) (a6989586621680091140 :: [f]) = ZipWith7Sym7 a6989586621680091134 a6989586621680091135 a6989586621680091136 a6989586621680091137 a6989586621680091138 a6989586621680091139 a6989586621680091140 | |
type Apply (Unzip3Sym0 :: TyFun [(a, b, c)] ([a], [b], [c]) -> Type) (a6989586621679969509 :: [(a, b, c)]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Unzip3Sym0 :: TyFun [(a, b, c)] ([a], [b], [c]) -> Type) (a6989586621679969509 :: [(a, b, c)]) = Unzip3Sym1 a6989586621679969509 | |
type Apply (Unzip4Sym0 :: TyFun [(a, b, c, d)] ([a], [b], [c], [d]) -> Type) (a6989586621679969489 :: [(a, b, c, d)]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Unzip4Sym0 :: TyFun [(a, b, c, d)] ([a], [b], [c], [d]) -> Type) (a6989586621679969489 :: [(a, b, c, d)]) = Unzip4Sym1 a6989586621679969489 | |
type Apply (Unzip5Sym0 :: TyFun [(a, b, c, d, e)] ([a], [b], [c], [d], [e]) -> Type) (a6989586621679969467 :: [(a, b, c, d, e)]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Unzip5Sym0 :: TyFun [(a, b, c, d, e)] ([a], [b], [c], [d], [e]) -> Type) (a6989586621679969467 :: [(a, b, c, d, e)]) = Unzip5Sym1 a6989586621679969467 | |
type Apply (Unzip6Sym0 :: TyFun [(a, b, c, d, e, f)] ([a], [b], [c], [d], [e], [f]) -> Type) (a6989586621679969443 :: [(a, b, c, d, e, f)]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Unzip6Sym0 :: TyFun [(a, b, c, d, e, f)] ([a], [b], [c], [d], [e], [f]) -> Type) (a6989586621679969443 :: [(a, b, c, d, e, f)]) = Unzip6Sym1 a6989586621679969443 | |
type Apply (Unzip7Sym0 :: TyFun [(a, b, c, d, e, f, g)] ([a], [b], [c], [d], [e], [f], [g]) -> Type) (a6989586621679969417 :: [(a, b, c, d, e, f, g)]) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Unzip7Sym0 :: TyFun [(a, b, c, d, e, f, g)] ([a], [b], [c], [d], [e], [f], [g]) -> Type) (a6989586621679969417 :: [(a, b, c, d, e, f, g)]) = Unzip7Sym1 a6989586621679969417 | |
type Apply (IsRightSym0 :: TyFun (Either a b) Bool -> Type) (a6989586621680472054 :: Either a b) Source # | |
Defined in Data.Singletons.Prelude.Either type Apply (IsRightSym0 :: TyFun (Either a b) Bool -> Type) (a6989586621680472054 :: Either a b) = IsRightSym1 a6989586621680472054 | |
type Apply (IsLeftSym0 :: TyFun (Either a b) Bool -> Type) (a6989586621680472057 :: Either a b) Source # | |
Defined in Data.Singletons.Prelude.Either type Apply (IsLeftSym0 :: TyFun (Either a b) Bool -> Type) (a6989586621680472057 :: Either a b) = IsLeftSym1 a6989586621680472057 | |
type Apply (SndSym0 :: TyFun (a, b) b -> Type) (a6989586621679360442 :: (a, b)) Source # | |
type Apply (FstSym0 :: TyFun (a, b) a -> Type) (a6989586621679360446 :: (a, b)) Source # | |
type Apply ((&@#@$$) a6989586621679747410 :: TyFun (a ~> b) b -> Type) (a6989586621679747411 :: a ~> b) Source # | |
type Apply (UncurrySym1 a6989586621679360426 :: TyFun (a, b) c -> Type) (a6989586621679360427 :: (a, b)) Source # | |
Defined in Data.Singletons.Prelude.Tuple type Apply (UncurrySym1 a6989586621679360426 :: TyFun (a, b) c -> Type) (a6989586621679360427 :: (a, b)) = UncurrySym2 a6989586621679360426 a6989586621679360427 | |
type Apply (Either_Sym2 a6989586621680470389 a6989586621680470390 :: TyFun (Either a b) c -> Type) (a6989586621680470391 :: Either a b) Source # | |
Defined in Data.Singletons.Prelude.Either type Apply (Either_Sym2 a6989586621680470389 a6989586621680470390 :: TyFun (Either a b) c -> Type) (a6989586621680470391 :: Either a b) = Either_Sym3 a6989586621680470389 a6989586621680470390 a6989586621680470391 | |
type Apply ((>>=@#@$$) a6989586621679559775 :: TyFun (a ~> m b) (m b) -> Type) (a6989586621679559776 :: a ~> m b) Source # | |
Defined in Data.Singletons.Prelude.Monad.Internal | |
type Apply ((<&>@#@$$) a6989586621679731619 :: TyFun (a ~> b) (f b) -> Type) (a6989586621679731620 :: a ~> b) Source # | |
Defined in Data.Singletons.Prelude.Functor | |
type Apply (For_Sym1 a6989586621680492390 :: TyFun (a ~> f b) (f ()) -> Type) (a6989586621680492391 :: a ~> f b) Source # | |
type Apply (ForM_Sym1 a6989586621680492370 :: TyFun (a ~> m b) (m ()) -> Type) (a6989586621680492371 :: a ~> m b) Source # | |
type Apply (ForMSym1 a6989586621680823019 :: TyFun (a ~> m b) (m (t b)) -> Type) (a6989586621680823020 :: a ~> m b) Source # | |
type Apply (ForSym1 a6989586621680823030 :: TyFun (a ~> f b) (f (t b)) -> Type) (a6989586621680823031 :: a ~> f b) Source # | |
type Apply (ShowParenSym1 a6989586621680279507 :: TyFun (Symbol ~> Symbol) (Symbol ~> Symbol) -> Type) (a6989586621680279508 :: Symbol ~> Symbol) Source # | |
Defined in Data.Singletons.Prelude.Show | |
type Apply (UntilSym0 :: TyFun (a ~> Bool) ((a ~> a) ~> (a ~> a)) -> Type) (a6989586621679534129 :: a ~> Bool) Source # | |
type Apply (NubBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [a]) -> Type) (a6989586621679968840 :: a ~> (a ~> Bool)) Source # | |
type Apply (PartitionSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621679968951 :: a ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (PartitionSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621679968951 :: a ~> Bool) = PartitionSym1 a6989586621679968951 | |
type Apply (BreakSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621679969063 :: a ~> Bool) Source # | |
type Apply (SpanSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621679969098 :: a ~> Bool) Source # | |
type Apply (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [[a]]) -> Type) (a6989586621679968973 :: a ~> (a ~> Bool)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal | |
type Apply (DropWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679969152 :: a ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DropWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679969152 :: a ~> Bool) = DropWhileSym1 a6989586621679969152 | |
type Apply (TakeWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679969167 :: a ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (TakeWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679969167 :: a ~> Bool) = TakeWhileSym1 a6989586621679969167 | |
type Apply (FilterSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679969267 :: a ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (FilterSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679969267 :: a ~> Bool) = FilterSym1 a6989586621679969267 | |
type Apply (InsertBySym0 :: TyFun (a ~> (a ~> Ordering)) (a ~> ([a] ~> [a])) -> Type) (a6989586621679969324 :: a ~> (a ~> Ordering)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal | |
type Apply (SortBySym0 :: TyFun (a ~> (a ~> Ordering)) ([a] ~> [a]) -> Type) (a6989586621679969344 :: a ~> (a ~> Ordering)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal | |
type Apply (DeleteBySym0 :: TyFun (a ~> (a ~> Bool)) (a ~> ([a] ~> [a])) -> Type) (a6989586621679969366 :: a ~> (a ~> Bool)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal | |
type Apply (DeleteFirstsBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) (a6989586621679969356 :: a ~> (a ~> Bool)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal | |
type Apply (UnionBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) (a6989586621679968820 :: a ~> (a ~> Bool)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal | |
type Apply (FindIndicesSym0 :: TyFun (a ~> Bool) ([a] ~> [Nat]) -> Type) (a6989586621679969210 :: a ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.List.Internal | |
type Apply (FindIndexSym0 :: TyFun (a ~> Bool) ([a] ~> Maybe Nat) -> Type) (a6989586621679969233 :: a ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.List.Internal | |
type Apply (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) (a6989586621679969758 :: a ~> (a ~> a)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) (a6989586621679969758 :: a ~> (a ~> a)) = Scanr1Sym1 a6989586621679969758 | |
type Apply (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) (a6989586621679969796 :: a ~> (a ~> a)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) (a6989586621679969796 :: a ~> (a ~> a)) = Scanl1Sym1 a6989586621679969796 | |
type Apply (IntersectBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) (a6989586621679969181 :: a ~> (a ~> Bool)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal | |
type Apply (Foldl1'Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> a) -> Type) (a6989586621679969872 :: a ~> (a ~> a)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Foldl1'Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> a) -> Type) (a6989586621679969872 :: a ~> (a ~> a)) = Foldl1'Sym1 a6989586621679969872 | |
type Apply (DropWhileEndSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679969135 :: a ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DropWhileEndSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679969135 :: a ~> Bool) = DropWhileEndSym1 a6989586621679969135 | |
type Apply (ShowListWithSym0 :: TyFun (a ~> (Symbol ~> Symbol)) ([a] ~> (Symbol ~> Symbol)) -> Type) (a6989586621680279542 :: a ~> (Symbol ~> Symbol)) Source # | |
type Apply (NubBySym0 :: TyFun (a ~> (a ~> Bool)) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621681185794 :: a ~> (a ~> Bool)) Source # | |
type Apply (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [NonEmpty a]) -> Type) (a6989586621681185955 :: a ~> (a ~> Bool)) Source # | |
Defined in Data.Singletons.Prelude.List.NonEmpty | |
type Apply (GroupBy1Sym0 :: TyFun (a ~> (a ~> Bool)) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) (a6989586621681185903 :: a ~> (a ~> Bool)) Source # | |
type Apply (TakeWhileSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) (a6989586621681186040 :: a ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.List.NonEmpty | |
type Apply (DropWhileSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) (a6989586621681186031 :: a ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.List.NonEmpty | |
type Apply (SpanSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) (a6989586621681186022 :: a ~> Bool) Source # | |
type Apply (BreakSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) (a6989586621681186013 :: a ~> Bool) Source # | |
type Apply (FilterSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) (a6989586621681186004 :: a ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.List.NonEmpty | |
type Apply (PartitionSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) (a6989586621681185995 :: a ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.List.NonEmpty | |
type Apply (SortBySym0 :: TyFun (a ~> (a ~> Ordering)) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621681185781 :: a ~> (a ~> Ordering)) Source # | |
Defined in Data.Singletons.Prelude.List.NonEmpty | |
type Apply (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621681186099 :: a ~> (a ~> a)) Source # | |
Defined in Data.Singletons.Prelude.List.NonEmpty | |
type Apply (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621681186091 :: a ~> (a ~> a)) Source # | |
Defined in Data.Singletons.Prelude.List.NonEmpty | |
type Apply (SwapSym0 :: TyFun (a, b) (b, a) -> Type) (a6989586621679360420 :: (a, b)) Source # | |
type Apply (ComparingSym0 :: TyFun (b ~> a) (b ~> (b ~> Ordering)) -> Type) (a6989586621679383631 :: b ~> a) Source # | |
Defined in Data.Singletons.Prelude.Ord type Apply (ComparingSym0 :: TyFun (b ~> a) (b ~> (b ~> Ordering)) -> Type) (a6989586621679383631 :: b ~> a) = ComparingSym1 a6989586621679383631 | |
type Apply (MapMaybeSym0 :: TyFun (a ~> Maybe b) ([a] ~> [b]) -> Type) (a6989586621679502192 :: a ~> Maybe b) Source # | |
Defined in Data.Singletons.Prelude.Maybe type Apply (MapMaybeSym0 :: TyFun (a ~> Maybe b) ([a] ~> [b]) -> Type) (a6989586621679502192 :: a ~> Maybe b) = MapMaybeSym1 a6989586621679502192 | |
type Apply (UntilSym1 a6989586621679534129 :: TyFun (a ~> a) (a ~> a) -> Type) (a6989586621679534130 :: a ~> a) Source # | |
type Apply (($!@#@$) :: TyFun (a ~> b) (a ~> b) -> Type) (a6989586621679534147 :: a ~> b) Source # | |
type Apply (($@#@$) :: TyFun (a ~> b) (a ~> b) -> Type) (a6989586621679534156 :: a ~> b) Source # | |
type Apply (MapSym0 :: TyFun (a ~> b) ([a] ~> [b]) -> Type) (a6989586621679534219 :: a ~> b) Source # | |
type Apply (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> b)) -> Type) (a6989586621679534230 :: a ~> (b ~> b)) Source # | |
type Apply (UnfoldrSym0 :: TyFun (b ~> Maybe (a, b)) (b ~> [a]) -> Type) (a6989586621679969650 :: b ~> Maybe (a, b)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (UnfoldrSym0 :: TyFun (b ~> Maybe (a, b)) (b ~> [a]) -> Type) (a6989586621679969650 :: b ~> Maybe (a, b)) = UnfoldrSym1 a6989586621679969650 | |
type Apply (ScanrSym0 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> [b])) -> Type) (a6989586621679969778 :: a ~> (b ~> b)) Source # | |
type Apply (ScanlSym0 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> [b])) -> Type) (a6989586621679969805 :: b ~> (a ~> b)) Source # | |
type Apply (AnySym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) (a6989586621680492302 :: a ~> Bool) Source # | |
type Apply (Foldl1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) (a6989586621680492483 :: a ~> (a ~> a)) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Apply (MaximumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) (a6989586621680492273 :: a ~> (a ~> Ordering)) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Apply (MinimumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) (a6989586621680492253 :: a ~> (a ~> Ordering)) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Apply (Foldr1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) (a6989586621680492478 :: a ~> (a ~> a)) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Apply (AllSym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) (a6989586621680492293 :: a ~> Bool) Source # | |
type Apply (FindSym0 :: TyFun (a ~> Bool) (t a ~> Maybe a) -> Type) (a6989586621680492226 :: a ~> Bool) Source # | |
type Apply (GroupWithSym0 :: TyFun (a ~> b) ([a] ~> [NonEmpty a]) -> Type) (a6989586621681185946 :: a ~> b) Source # | |
Defined in Data.Singletons.Prelude.List.NonEmpty type Apply (GroupWithSym0 :: TyFun (a ~> b) ([a] ~> [NonEmpty a]) -> Type) (a6989586621681185946 :: a ~> b) = GroupWithSym1 a6989586621681185946 | |
type Apply (GroupAllWithSym0 :: TyFun (a ~> b) ([a] ~> [NonEmpty a]) -> Type) (a6989586621681185937 :: a ~> b) Source # | |
Defined in Data.Singletons.Prelude.List.NonEmpty type Apply (GroupAllWithSym0 :: TyFun (a ~> b) ([a] ~> [NonEmpty a]) -> Type) (a6989586621681185937 :: a ~> b) = GroupAllWithSym1 a6989586621681185937 | |
type Apply (GroupWith1Sym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) (a6989586621681185896 :: a ~> b) Source # | |
Defined in Data.Singletons.Prelude.List.NonEmpty | |
type Apply (MapSym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty b) -> Type) (a6989586621681186152 :: a ~> b) Source # | |
type Apply (SortWithSym0 :: TyFun (a ~> o) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621681185772 :: a ~> o) Source # | |
Defined in Data.Singletons.Prelude.List.NonEmpty type Apply (SortWithSym0 :: TyFun (a ~> o) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621681185772 :: a ~> o) = SortWithSym1 a6989586621681185772 | |
type Apply (GroupAllWith1Sym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) (a6989586621681185887 :: a ~> b) Source # | |
Defined in Data.Singletons.Prelude.List.NonEmpty | |
type Apply (ScanlSym0 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> NonEmpty b)) -> Type) (a6989586621681186122 :: b ~> (a ~> b)) Source # | |
type Apply (ScanrSym0 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> NonEmpty b)) -> Type) (a6989586621681186110 :: a ~> (b ~> b)) Source # | |
type Apply (UnfoldrSym0 :: TyFun (a ~> (b, Maybe a)) (a ~> NonEmpty b) -> Type) (a6989586621681186222 :: a ~> (b, Maybe a)) Source # | |
Defined in Data.Singletons.Prelude.List.NonEmpty | |
type Apply (UnfoldSym0 :: TyFun (a ~> (b, Maybe a)) (a ~> NonEmpty b) -> Type) (a6989586621681186257 :: a ~> (b, Maybe a)) Source # | |
Defined in Data.Singletons.Prelude.List.NonEmpty | |
type Apply (MfilterSym0 :: TyFun (a ~> Bool) (m a ~> m a) -> Type) (a6989586621681292236 :: a ~> Bool) Source # | |
Defined in Data.Singletons.Prelude.Monad | |
type Apply (FilterMSym0 :: TyFun (a ~> m Bool) ([a] ~> m [a]) -> Type) (a6989586621681292398 :: a ~> m Bool) Source # | |
Defined in Data.Singletons.Prelude.Monad type Apply (FilterMSym0 :: TyFun (a ~> m Bool) ([a] ~> m [a]) -> Type) (a6989586621681292398 :: a ~> m Bool) = FilterMSym1 a6989586621681292398 | |
type Apply (ApplySym0 :: TyFun (k1 ~> k2) (k1 ~> k2) -> Type) (a6989586621681337327 :: k1 ~> k2) Source # | |
type Apply ((@@@#@$) :: TyFun (k1 ~> k2) (k1 ~> k2) -> Type) (a6989586621681337330 :: k1 ~> k2) Source # | |
type Apply (CurrySym0 :: TyFun ((a, b) ~> c) (a ~> (b ~> c)) -> Type) (a6989586621679360434 :: (a, b) ~> c) Source # | |
type Apply (UncurrySym0 :: TyFun (a ~> (b ~> c)) ((a, b) ~> c) -> Type) (a6989586621679360426 :: a ~> (b ~> c)) Source # | |
Defined in Data.Singletons.Prelude.Tuple type Apply (UncurrySym0 :: TyFun (a ~> (b ~> c)) ((a, b) ~> c) -> Type) (a6989586621679360426 :: a ~> (b ~> c)) = UncurrySym1 a6989586621679360426 | |
type Apply (Maybe_Sym1 a6989586621679500654 :: TyFun (a ~> b) (Maybe a ~> b) -> Type) (a6989586621679500655 :: a ~> b) Source # | |
Defined in Data.Singletons.Prelude.Maybe type Apply (Maybe_Sym1 a6989586621679500654 :: TyFun (a ~> b) (Maybe a ~> b) -> Type) (a6989586621679500655 :: a ~> b) = Maybe_Sym2 a6989586621679500654 a6989586621679500655 | |
type Apply (FlipSym0 :: TyFun (a ~> (b ~> c)) (b ~> (a ~> c)) -> Type) (a6989586621679534175 :: a ~> (b ~> c)) Source # | |
type Apply ((.@#@$) :: TyFun (b ~> c) ((a ~> b) ~> (a ~> c)) -> Type) (a6989586621679534187 :: b ~> c) Source # | |
type Apply (FmapSym0 :: TyFun (a ~> b) (f a ~> f b) -> Type) (a6989586621679559667 :: a ~> b) Source # | |
type Apply (LiftASym0 :: TyFun (a ~> b) (f a ~> f b) -> Type) (a6989586621679559644 :: a ~> b) Source # | |
type Apply ((=<<@#@$) :: TyFun (a ~> m b) (m a ~> m b) -> Type) (a6989586621679559620 :: a ~> m b) Source # | |
Defined in Data.Singletons.Prelude.Monad.Internal | |
type Apply (LiftMSym0 :: TyFun (a1 ~> r) (m a1 ~> m r) -> Type) (a6989586621679559599 :: a1 ~> r) Source # | |
type Apply ((<$>@#@$) :: TyFun (a ~> b) (f a ~> f b) -> Type) (a6989586621679731630 :: a ~> b) Source # | |
type Apply (OnSym0 :: TyFun (b ~> (b ~> c)) ((a ~> b) ~> (a ~> (a ~> c))) -> Type) (a6989586621679747423 :: b ~> (b ~> c)) Source # | |
type Apply (ZipWithSym0 :: TyFun (a ~> (b ~> c)) ([a] ~> ([b] ~> [c])) -> Type) (a6989586621679969561 :: a ~> (b ~> c)) Source # | |
Defined in Data.Singletons.Prelude.List.Internal | |
type Apply (Either_Sym0 :: TyFun (a ~> c) ((b ~> c) ~> (Either a b ~> c)) -> Type) (a6989586621680470389 :: a ~> c) Source # | |
type Apply (Foldl'Sym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) (a6989586621680492472 :: b ~> (a ~> b)) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Apply (FoldlSym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) (a6989586621680492465 :: b ~> (a ~> b)) Source # | |
type Apply (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b)) -> Type) (a6989586621680492451 :: a ~> (b ~> b)) Source # | |
type Apply (FoldMapSym0 :: TyFun (a ~> m) (t a ~> m) -> Type) (a6989586621680492445 :: a ~> m) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (FoldMapSym0 :: TyFun (a ~> m) (t a ~> m) -> Type) (a6989586621680492445 :: a ~> m) = FoldMapSym1 a6989586621680492445 :: TyFun (t a) m -> Type | |
type Apply (Foldr'Sym0 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b)) -> Type) (a6989586621680492458 :: a ~> (b ~> b)) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Apply (ConcatMapSym0 :: TyFun (a ~> [b]) (t a ~> [b]) -> Type) (a6989586621680492321 :: a ~> [b]) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (ConcatMapSym0 :: TyFun (a ~> [b]) (t a ~> [b]) -> Type) (a6989586621680492321 :: a ~> [b]) = ConcatMapSym1 a6989586621680492321 :: TyFun (t a) [b] -> Type | |
type Apply (FoldMapDefaultSym0 :: TyFun (a ~> m) (t a ~> m) -> Type) (a6989586621680822963 :: a ~> m) Source # | |
Defined in Data.Singletons.Prelude.Traversable type Apply (FoldMapDefaultSym0 :: TyFun (a ~> m) (t a ~> m) -> Type) (a6989586621680822963 :: a ~> m) = FoldMapDefaultSym1 a6989586621680822963 :: TyFun (t a) m -> Type | |
type Apply (FmapDefaultSym0 :: TyFun (a ~> b) (t a ~> t b) -> Type) (a6989586621680822982 :: a ~> b) Source # | |
Defined in Data.Singletons.Prelude.Traversable type Apply (FmapDefaultSym0 :: TyFun (a ~> b) (t a ~> t b) -> Type) (a6989586621680822982 :: a ~> b) = FmapDefaultSym1 a6989586621680822982 :: TyFun (t a) (t b) -> Type | |
type Apply (ZipWithSym0 :: TyFun (a ~> (b ~> c)) (NonEmpty a ~> (NonEmpty b ~> NonEmpty c)) -> Type) (a6989586621681185837 :: a ~> (b ~> c)) Source # | |
Defined in Data.Singletons.Prelude.List.NonEmpty | |
type Apply ((<$!>@#@$) :: TyFun (a ~> b) (m a ~> m b) -> Type) (a6989586621681292252 :: a ~> b) Source # | |
Defined in Data.Singletons.Prelude.Monad type Apply ((<$!>@#@$) :: TyFun (a ~> b) (m a ~> m b) -> Type) (a6989586621681292252 :: a ~> b) = (<$!>@#@$$) a6989586621681292252 :: TyFun (m a) (m b) -> Type | |
type Apply ((.@#@$$) a6989586621679534187 :: TyFun (a ~> b) (a ~> c) -> Type) (a6989586621679534188 :: a ~> b) Source # | |
type Apply (LiftA2Sym0 :: TyFun (a ~> (b ~> c)) (f a ~> (f b ~> f c)) -> Type) (a6989586621679559701 :: a ~> (b ~> c)) Source # | |
Defined in Data.Singletons.Prelude.Monad.Internal | |
type Apply (LiftM2Sym0 :: TyFun (a1 ~> (a2 ~> r)) (m a1 ~> (m a2 ~> m r)) -> Type) (a6989586621679559582 :: a1 ~> (a2 ~> r)) Source # | |
Defined in Data.Singletons.Prelude.Monad.Internal | |
type Apply (OnSym1 a6989586621679747423 :: TyFun (a ~> b) (a ~> (a ~> c)) -> Type) (a6989586621679747424 :: a ~> b) Source # | |
type Apply (ZipWith3Sym0 :: TyFun (a ~> (b ~> (c ~> d))) ([a] ~> ([b] ~> ([c] ~> [d]))) -> Type) (a6989586621679969546 :: a ~> (b ~> (c ~> d))) Source # | |
Defined in Data.Singletons.Prelude.List.Internal | |
type Apply (Either_Sym1 a6989586621680470389 :: TyFun (b ~> c) (Either a b ~> c) -> Type) (a6989586621680470390 :: b ~> c) Source # | |
Defined in Data.Singletons.Prelude.Either type Apply (Either_Sym1 a6989586621680470389 :: TyFun (b ~> c) (Either a b ~> c) -> Type) (a6989586621680470390 :: b ~> c) = Either_Sym2 a6989586621680470389 a6989586621680470390 | |
type Apply (FoldrMSym0 :: TyFun (a ~> (b ~> m b)) (b ~> (t a ~> m b)) -> Type) (a6989586621680492425 :: a ~> (b ~> m b)) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Apply (FoldlMSym0 :: TyFun (b ~> (a ~> m b)) (b ~> (t a ~> m b)) -> Type) (a6989586621680492407 :: b ~> (a ~> m b)) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Apply (Traverse_Sym0 :: TyFun (a ~> f b) (t a ~> f ()) -> Type) (a6989586621680492399 :: a ~> f b) Source # | |
Defined in Data.Singletons.Prelude.Foldable type Apply (Traverse_Sym0 :: TyFun (a ~> f b) (t a ~> f ()) -> Type) (a6989586621680492399 :: a ~> f b) = Traverse_Sym1 a6989586621680492399 :: TyFun (t a) (f ()) -> Type | |
type Apply (MapM_Sym0 :: TyFun (a ~> m b) (t a ~> m ()) -> Type) (a6989586621680492379 :: a ~> m b) Source # | |
type Apply (TraverseSym0 :: TyFun (a ~> f b) (t a ~> f (t b)) -> Type) (a6989586621680816742 :: a ~> f b) Source # | |
Defined in Data.Singletons.Prelude.Traversable type Apply (TraverseSym0 :: TyFun (a ~> f b) (t a ~> f (t b)) -> Type) (a6989586621680816742 :: a ~> f b) = TraverseSym1 a6989586621680816742 :: TyFun (t a) (f (t b)) -> Type | |
type Apply (MapMSym0 :: TyFun (a ~> m b) (t a ~> m (t b)) -> Type) (a6989586621680816750 :: a ~> m b) Source # | |
type Apply (MapAccumRSym0 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c))) -> Type) (a6989586621680822996 :: a ~> (b ~> (a, c))) Source # | |
Defined in Data.Singletons.Prelude.Traversable | |
type Apply (MapAccumLSym0 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c))) -> Type) (a6989586621680823006 :: a ~> (b ~> (a, c))) Source # | |
Defined in Data.Singletons.Prelude.Traversable | |
type Apply (MzipWithSym0 :: TyFun (a ~> (b ~> c)) (m a ~> (m b ~> m c)) -> Type) (a6989586621681150525 :: a ~> (b ~> c)) Source # | |
Defined in Data.Singletons.Prelude.Monad.Zip | |
type Apply (ZipWithM_Sym0 :: TyFun (a ~> (b ~> m c)) ([a] ~> ([b] ~> m ())) -> Type) (a6989586621681292338 :: a ~> (b ~> m c)) Source # | |
Defined in Data.Singletons.Prelude.Monad | |
type Apply (ZipWithMSym0 :: TyFun (a ~> (b ~> m c)) ([a] ~> ([b] ~> m [c])) -> Type) (a6989586621681292348 :: a ~> (b ~> m c)) Source # | |
Defined in Data.Singletons.Prelude.Monad | |
type Apply (MapAndUnzipMSym0 :: TyFun (a ~> m (b, c)) ([a] ~> m ([b], [c])) -> Type) (a6989586621681292357 :: a ~> m (b, c)) Source # | |
Defined in Data.Singletons.Prelude.Monad type Apply (MapAndUnzipMSym0 :: TyFun (a ~> m (b, c)) ([a] ~> m ([b], [c])) -> Type) (a6989586621681292357 :: a ~> m (b, c)) = MapAndUnzipMSym1 a6989586621681292357 | |
type Apply ((>=>@#@$) :: TyFun (a ~> m b) ((b ~> m c) ~> (a ~> m c)) -> Type) (a6989586621681292383 :: a ~> m b) Source # | |
type Apply ((<=<@#@$) :: TyFun (b ~> m c) ((a ~> m b) ~> (a ~> m c)) -> Type) (a6989586621681292371 :: b ~> m c) Source # | |
type Apply (LiftA3Sym0 :: TyFun (a ~> (b ~> (c ~> d))) (f a ~> (f b ~> (f c ~> f d))) -> Type) (a6989586621679559633 :: a ~> (b ~> (c ~> d))) Source # | |
type Apply (LiftM3Sym0 :: TyFun (a1 ~> (a2 ~> (a3 ~> r))) (m a1 ~> (m a2 ~> (m a3 ~> m r))) -> Type) (a6989586621679559558 :: a1 ~> (a2 ~> (a3 ~> r))) Source # | |
type Apply (ZipWith4Sym0 :: TyFun (a ~> (b ~> (c ~> (d ~> e)))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> [e])))) -> Type) (a6989586621680091215 :: a ~> (b ~> (c ~> (d ~> e)))) Source # | |
type Apply ((>=>@#@$$) a6989586621681292383 :: TyFun (b ~> m c) (a ~> m c) -> Type) (a6989586621681292384 :: b ~> m c) Source # | |
Defined in Data.Singletons.Prelude.Monad | |
type Apply ((<=<@#@$$) a6989586621681292371 :: TyFun (a ~> m b) (a ~> m c) -> Type) (a6989586621681292372 :: a ~> m b) Source # | |
Defined in Data.Singletons.Prelude.Monad | |
type Apply (LiftM4Sym0 :: TyFun (a1 ~> (a2 ~> (a3 ~> (a4 ~> r)))) (m a1 ~> (m a2 ~> (m a3 ~> (m a4 ~> m r)))) -> Type) (a6989586621679559527 :: a1 ~> (a2 ~> (a3 ~> (a4 ~> r)))) Source # | |
Defined in Data.Singletons.Prelude.Monad.Internal | |
type Apply (ZipWith5Sym0 :: TyFun (a ~> (b ~> (c ~> (d ~> (e ~> f))))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> ([e] ~> [f]))))) -> Type) (a6989586621680091192 :: a ~> (b ~> (c ~> (d ~> (e ~> f))))) Source # | |
type Apply (LiftM5Sym0 :: TyFun (a1 ~> (a2 ~> (a3 ~> (a4 ~> (a5 ~> r))))) (m a1 ~> (m a2 ~> (m a3 ~> (m a4 ~> (m a5 ~> m r))))) -> Type) (a6989586621679559489 :: a1 ~> (a2 ~> (a3 ~> (a4 ~> (a5 ~> r))))) Source # | |
Defined in Data.Singletons.Prelude.Monad.Internal type Apply (LiftM5Sym0 :: TyFun (a1 ~> (a2 ~> (a3 ~> (a4 ~> (a5 ~> r))))) (m a1 ~> (m a2 ~> (m a3 ~> (m a4 ~> (m a5 ~> m r))))) -> Type) (a6989586621679559489 :: a1 ~> (a2 ~> (a3 ~> (a4 ~> (a5 ~> r))))) = LiftM5Sym1 a6989586621679559489 :: TyFun (m a1) (m a2 ~> (m a3 ~> (m a4 ~> (m a5 ~> m r)))) -> Type | |
type Apply (ZipWith6Sym0 :: TyFun (a ~> (b ~> (c ~> (d ~> (e ~> (f ~> g)))))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g])))))) -> Type) (a6989586621680091165 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> g)))))) Source # | |
type Apply (ZipWith7Sym0 :: TyFun (a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> h))))))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h]))))))) -> Type) (a6989586621680091134 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> h))))))) Source # | |
Defined in Data.Singletons.Prelude.List.Internal | |
type Apply (GetConstSym0 :: TyFun (Const a b) a -> Type) (a6989586621680776931 :: Const a b) Source # | |
Defined in Data.Singletons.Prelude.Const type Apply (GetConstSym0 :: TyFun (Const a b) a -> Type) (a6989586621680776931 :: Const a b) = GetConstSym1 a6989586621680776931 |
type family ApplyTyCon where ... Source #
Equations
ApplyTyCon @k1 @(k2 -> k3) @unmatchable_fun = ApplyTyConAux2 | |
ApplyTyCon @k1 @k2 @k2 = ApplyTyConAux1 |
data ApplyTyConAux1 f z Source #
An "internal" defunctionalization symbol used primarily in the
definition of ApplyTyCon
, as well as the SingI
instances for TyCon1
,
TyCon2
, etc.
Instances
type Apply (ApplyTyConAux1 f :: TyFun k1 k2 -> Type) (x :: k1) Source # | |
Defined in Data.Singletons.Internal |
data ApplyTyConAux2 f z Source #
An "internal" defunctionalization symbol used primarily in the
definition of ApplyTyCon
.
Instances
type Apply (ApplyTyConAux2 f :: TyFun k4 k7 -> Type) (x :: k4) Source # | |
Defined in Data.Singletons.Internal |
Defunctionalized singletons
When calling a higher-order singleton function, you need to use a
singFun...
function to wrap it. See singFun1
.
singFun1 :: forall f. SingFunction1 f -> Sing f Source #
Use this function when passing a function on singletons as a higher-order function. You will need visible type application to get this to work. For example:
falses = sMap (singFun1 @NotSym0 sNot) (STrue `SCons` STrue `SCons` SNil)
There are a family of singFun...
functions, keyed by the number
of parameters of the function.
singFun2 :: forall f. SingFunction2 f -> Sing f Source #
singFun3 :: forall f. SingFunction3 f -> Sing f Source #
singFun4 :: forall f. SingFunction4 f -> Sing f Source #
singFun5 :: forall f. SingFunction5 f -> Sing f Source #
singFun6 :: forall f. SingFunction6 f -> Sing f Source #
singFun7 :: forall f. SingFunction7 f -> Sing f Source #
singFun8 :: forall f. SingFunction8 f -> Sing f Source #
unSingFun1 :: forall f. Sing f -> SingFunction1 f Source #
This is the inverse of singFun1
, and likewise for the other
unSingFun...
functions.
unSingFun2 :: forall f. Sing f -> SingFunction2 f Source #
unSingFun3 :: forall f. Sing f -> SingFunction3 f Source #
unSingFun4 :: forall f. Sing f -> SingFunction4 f Source #
unSingFun5 :: forall f. Sing f -> SingFunction5 f Source #
unSingFun6 :: forall f. Sing f -> SingFunction6 f Source #
unSingFun7 :: forall f. Sing f -> SingFunction7 f Source #
unSingFun8 :: forall f. Sing f -> SingFunction8 f Source #
SLambda{2...8}
are explicitly bidirectional pattern synonyms for
defunctionalized singletons (
).Sing
(f :: k ~>
k' ~>
k'')
As constructors: Same as singFun{2..8}
. For example, one can turn a
binary function on singletons sTake ::
into a
defunctionalized singleton SingFunction2
TakeSym0
:Sing
(TakeSym :: Nat ~>
[a] ~>
[a])
>>> import Data.Singletons.Prelude.List >>> :set -XTypeApplications >>> >>> :tSLambda2
SLambda2
::SingFunction2
f ->Sing
f >>> :tSLambda2
@TakeSym0SLambda2
::SingFunction2
TakeSym0 ->Sing
TakeSym0 >>> :tSLambda2
@TakeSym0 sTakeSLambda2
::Sing
TakeSym0
This is useful for functions on singletons that expect a defunctionalized
singleton as an argument, such as sZipWith ::
:SingFunction3
ZipWithSym0
sZipWith :: Sing (f :: a~>
b~>
c) -> Sing (xs :: [a]) -> Sing (ys :: [b]) -> Sing (ZipWith f xs ys :: [c]) sZipWith (SLambda2
@TakeSym0 sTake) :: Sing (xs :: [Nat]) -> Sing (ys :: [[a]]) -> Sing (ZipWith TakeSym0 xs ys :: [[a]])
As patterns: Same as unSingFun{2..8}
. Gets a binary term-level
Haskell function on singletons
from a defunctionalised Sing
(x :: k) -> Sing
(y :: k') -> Sing
(f @@ x @@ y)
. Alternatively, as a record field accessor:Sing
f
applySing2 ::Sing
(f :: k~>
k'~>
k'') ->SingFunction2
f
pattern SLambda2 :: forall f. SingFunction2 f -> Sing f Source #
applySing2 :: forall a1 a2 b (f :: a1 ~> (a2 ~> b)). Sing f -> forall (t1 :: a1) (t2 :: a2). Sing t1 -> Sing t2 -> Sing ((f @@ t1) @@ t2) Source #
pattern SLambda3 :: forall f. SingFunction3 f -> Sing f Source #
applySing3 :: forall a1 a2 a3 b (f :: a1 ~> (a2 ~> (a3 ~> b))). Sing f -> forall (t1 :: a1) (t2 :: a2) (t3 :: a3). Sing t1 -> Sing t2 -> Sing t3 -> Sing (((f @@ t1) @@ t2) @@ t3) Source #
pattern SLambda4 :: forall f. SingFunction4 f -> Sing f Source #
applySing4 :: forall a1 a2 a3 a4 b (f :: a1 ~> (a2 ~> (a3 ~> (a4 ~> b)))). Sing f -> forall (t1 :: a1) (t2 :: a2) (t3 :: a3) (t4 :: a4). Sing t1 -> Sing t2 -> Sing t3 -> Sing t4 -> Sing ((((f @@ t1) @@ t2) @@ t3) @@ t4) Source #
pattern SLambda5 :: forall f. SingFunction5 f -> Sing f Source #
applySing5 :: forall a1 a2 a3 a4 a5 b (f :: a1 ~> (a2 ~> (a3 ~> (a4 ~> (a5 ~> b))))). Sing f -> forall (t1 :: a1) (t2 :: a2) (t3 :: a3) (t4 :: a4) (t5 :: a5). Sing t1 -> Sing t2 -> Sing t3 -> Sing t4 -> Sing t5 -> Sing (((((f @@ t1) @@ t2) @@ t3) @@ t4) @@ t5) Source #
pattern SLambda6 :: forall f. SingFunction6 f -> Sing f Source #
applySing6 :: forall a1 a2 a3 a4 a5 a6 b (f :: a1 ~> (a2 ~> (a3 ~> (a4 ~> (a5 ~> (a6 ~> b)))))). Sing f -> forall (t1 :: a1) (t2 :: a2) (t3 :: a3) (t4 :: a4) (t5 :: a5) (t6 :: a6). Sing t1 -> Sing t2 -> Sing t3 -> Sing t4 -> Sing t5 -> Sing t6 -> Sing ((((((f @@ t1) @@ t2) @@ t3) @@ t4) @@ t5) @@ t6) Source #
pattern SLambda7 :: forall f. SingFunction7 f -> Sing f Source #
applySing7 :: forall a1 a2 a3 a4 a5 a6 a7 b (f :: a1 ~> (a2 ~> (a3 ~> (a4 ~> (a5 ~> (a6 ~> (a7 ~> b))))))). Sing f -> forall (t1 :: a1) (t2 :: a2) (t3 :: a3) (t4 :: a4) (t5 :: a5) (t6 :: a6) (t7 :: a7). Sing t1 -> Sing t2 -> Sing t3 -> Sing t4 -> Sing t5 -> Sing t6 -> Sing t7 -> Sing (((((((f @@ t1) @@ t2) @@ t3) @@ t4) @@ t5) @@ t6) @@ t7) Source #
pattern SLambda8 :: forall f. SingFunction8 f -> Sing f Source #
applySing8 :: forall a1 a2 a3 a4 a5 a6 a7 a8 b (f :: a1 ~> (a2 ~> (a3 ~> (a4 ~> (a5 ~> (a6 ~> (a7 ~> (a8 ~> b)))))))). Sing f -> forall (t1 :: a1) (t2 :: a2) (t3 :: a3) (t4 :: a4) (t5 :: a5) (t6 :: a6) (t7 :: a7) (t8 :: a8). Sing t1 -> Sing t2 -> Sing t3 -> Sing t4 -> Sing t5 -> Sing t6 -> Sing t7 -> Sing t8 -> Sing ((((((((f @@ t1) @@ t2) @@ t3) @@ t4) @@ t5) @@ t6) @@ t7) @@ t8) Source #
These type synonyms are exported only to improve error messages; users should not have to mention them.
type SingFunction3 f = forall t1 t2 t3. Sing t1 -> Sing t2 -> Sing t3 -> Sing (((f @@ t1) @@ t2) @@ t3) Source #
type SingFunction4 f = forall t1 t2 t3 t4. Sing t1 -> Sing t2 -> Sing t3 -> Sing t4 -> Sing ((((f @@ t1) @@ t2) @@ t3) @@ t4) Source #
type SingFunction5 f = forall t1 t2 t3 t4 t5. Sing t1 -> Sing t2 -> Sing t3 -> Sing t4 -> Sing t5 -> Sing (((((f @@ t1) @@ t2) @@ t3) @@ t4) @@ t5) Source #
type SingFunction6 f = forall t1 t2 t3 t4 t5 t6. Sing t1 -> Sing t2 -> Sing t3 -> Sing t4 -> Sing t5 -> Sing t6 -> Sing ((((((f @@ t1) @@ t2) @@ t3) @@ t4) @@ t5) @@ t6) Source #
type SingFunction7 f = forall t1 t2 t3 t4 t5 t6 t7. Sing t1 -> Sing t2 -> Sing t3 -> Sing t4 -> Sing t5 -> Sing t6 -> Sing t7 -> Sing (((((((f @@ t1) @@ t2) @@ t3) @@ t4) @@ t5) @@ t6) @@ t7) Source #
type SingFunction8 f = forall t1 t2 t3 t4 t5 t6 t7 t8. Sing t1 -> Sing t2 -> Sing t3 -> Sing t4 -> Sing t5 -> Sing t6 -> Sing t7 -> Sing t8 -> Sing ((((((((f @@ t1) @@ t2) @@ t3) @@ t4) @@ t5) @@ t6) @@ t7) @@ t8) Source #
Auxiliary functions
Proxy
is a type that holds no data, but has a phantom parameter of
arbitrary type (or even kind). Its use is to provide type information, even
though there is no value available of that type (or it may be too costly to
create one).
Historically,
is a safer alternative to the
Proxy
:: Proxy
a
idiom.undefined
:: a
>>>
Proxy :: Proxy (Void, Int -> Int)
Proxy
Proxy can even hold types of higher kinds,
>>>
Proxy :: Proxy Either
Proxy
>>>
Proxy :: Proxy Functor
Proxy
>>>
Proxy :: Proxy complicatedStructure
Proxy
Constructors
Proxy |
Instances
Generic1 (Proxy :: k -> Type) | Since: base-4.6.0.0 |
PMonadPlus (Proxy :: k -> Type) Source # | |
PAlternative (Proxy :: k -> Type) Source # | |
Monad (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
Functor (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
Applicative (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
Foldable (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
Defined in Data.Foldable Methods fold :: Monoid m => Proxy m -> m # foldMap :: Monoid m => (a -> m) -> Proxy a -> m # foldMap' :: Monoid m => (a -> m) -> Proxy a -> m # foldr :: (a -> b -> b) -> b -> Proxy a -> b # foldr' :: (a -> b -> b) -> b -> Proxy a -> b # foldl :: (b -> a -> b) -> b -> Proxy a -> b # foldl' :: (b -> a -> b) -> b -> Proxy a -> b # foldr1 :: (a -> a -> a) -> Proxy a -> a # foldl1 :: (a -> a -> a) -> Proxy a -> a # elem :: Eq a => a -> Proxy a -> Bool # maximum :: Ord a => Proxy a -> a # minimum :: Ord a => Proxy a -> a # | |
Traversable (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
Eq1 (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
Ord1 (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Read1 (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Show1 (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
MonadZip (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
Alternative (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
MonadPlus (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
SMonadPlus (Proxy :: Type -> Type) Source # | |
SAlternative (Proxy :: Type -> Type) Source # | |
SMonad (Proxy :: Type -> Type) Source # | |
Defined in Data.Singletons.Prelude.Proxy Methods (%>>=) :: forall a b (t :: Proxy a) (t :: a ~> Proxy b). Sing t -> Sing t -> Sing (Apply (Apply (>>=@#@$) t) t) Source # (%>>) :: forall a b (t :: Proxy a) (t :: Proxy b). Sing t -> Sing t -> Sing (Apply (Apply (>>@#@$) t) t) Source # sReturn :: forall a (t :: a). Sing t -> Sing (Apply ReturnSym0 t) Source # | |
SApplicative (Proxy :: Type -> Type) Source # | |
Defined in Data.Singletons.Prelude.Proxy Methods sPure :: forall a (t :: a). Sing t -> Sing (Apply PureSym0 t) Source # (%<*>) :: forall a b (t :: Proxy (a ~> b)) (t :: Proxy a). Sing t -> Sing t -> Sing (Apply (Apply (<*>@#@$) t) t) Source # sLiftA2 :: forall a b c (t :: a ~> (b ~> c)) (t :: Proxy a) (t :: Proxy b). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply LiftA2Sym0 t) t) t) Source # (%*>) :: forall a b (t :: Proxy a) (t :: Proxy b). Sing t -> Sing t -> Sing (Apply (Apply (*>@#@$) t) t) Source # (%<*) :: forall a b (t :: Proxy a) (t :: Proxy b). Sing t -> Sing t -> Sing (Apply (Apply (<*@#@$) t) t) Source # | |
SFunctor (Proxy :: Type -> Type) Source # | |
PMonad (Proxy :: Type -> Type) Source # | |
PApplicative (Proxy :: Type -> Type) Source # | |
PFunctor (Proxy :: Type -> Type) Source # | |
SFoldable (Proxy :: Type -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Methods sFold :: forall m (t :: Proxy m). SMonoid m => Sing t -> Sing (Apply FoldSym0 t) Source # sFoldMap :: forall a m (t :: a ~> m) (t :: Proxy a). SMonoid m => Sing t -> Sing t -> Sing (Apply (Apply FoldMapSym0 t) t) Source # sFoldr :: forall a b (t :: a ~> (b ~> b)) (t :: b) (t :: Proxy a). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply FoldrSym0 t) t) t) Source # sFoldr' :: forall a b (t :: a ~> (b ~> b)) (t :: b) (t :: Proxy a). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply Foldr'Sym0 t) t) t) Source # sFoldl :: forall b a (t :: b ~> (a ~> b)) (t :: b) (t :: Proxy a). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply FoldlSym0 t) t) t) Source # sFoldl' :: forall b a (t :: b ~> (a ~> b)) (t :: b) (t :: Proxy a). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply Foldl'Sym0 t) t) t) Source # sFoldr1 :: forall a (t :: a ~> (a ~> a)) (t :: Proxy a). Sing t -> Sing t -> Sing (Apply (Apply Foldr1Sym0 t) t) Source # sFoldl1 :: forall a (t :: a ~> (a ~> a)) (t :: Proxy a). Sing t -> Sing t -> Sing (Apply (Apply Foldl1Sym0 t) t) Source # sToList :: forall a (t :: Proxy a). Sing t -> Sing (Apply ToListSym0 t) Source # sNull :: forall a (t :: Proxy a). Sing t -> Sing (Apply NullSym0 t) Source # sLength :: forall a (t :: Proxy a). Sing t -> Sing (Apply LengthSym0 t) Source # sElem :: forall a (t :: a) (t :: Proxy a). SEq a => Sing t -> Sing t -> Sing (Apply (Apply ElemSym0 t) t) Source # sMaximum :: forall a (t :: Proxy a). SOrd a => Sing t -> Sing (Apply MaximumSym0 t) Source # sMinimum :: forall a (t :: Proxy a). SOrd a => Sing t -> Sing (Apply MinimumSym0 t) Source # sSum :: forall a (t :: Proxy a). SNum a => Sing t -> Sing (Apply SumSym0 t) Source # sProduct :: forall a (t :: Proxy a). SNum a => Sing t -> Sing (Apply ProductSym0 t) Source # | |
PFoldable (Proxy :: Type -> Type) Source # | |
Defined in Data.Singletons.Prelude.Foldable Associated Types type FoldMap arg arg :: m Source # type Foldr arg arg arg :: b Source # type Foldr' arg arg arg :: b Source # type Foldl arg arg arg :: b Source # type Foldl' arg arg arg :: b Source # type Foldr1 arg arg :: a Source # type Foldl1 arg arg :: a Source # type ToList arg :: [a] Source # type Null arg :: Bool Source # type Length arg :: Nat Source # type Elem arg arg :: Bool Source # type Maximum arg :: a Source # | |
STraversable (Proxy :: Type -> Type) Source # | |
Defined in Data.Singletons.Prelude.Traversable Methods sTraverse :: forall a (f :: Type -> Type) b (t :: a ~> f b) (t :: Proxy a). SApplicative f => Sing t -> Sing t -> Sing (Apply (Apply TraverseSym0 t) t) Source # sSequenceA :: forall (f :: Type -> Type) a (t :: Proxy (f a)). SApplicative f => Sing t -> Sing (Apply SequenceASym0 t) Source # sMapM :: forall a (m :: Type -> Type) b (t :: a ~> m b) (t :: Proxy a). SMonad m => Sing t -> Sing t -> Sing (Apply (Apply MapMSym0 t) t) Source # sSequence :: forall (m :: Type -> Type) a (t :: Proxy (m a)). SMonad m => Sing t -> Sing (Apply SequenceSym0 t) Source # | |
PTraversable (Proxy :: Type -> Type) Source # | |
SMonadZip (Proxy :: Type -> Type) Source # | |
Defined in Data.Singletons.Prelude.Monad.Zip Methods sMzip :: forall a b (t :: Proxy a) (t :: Proxy b). Sing t -> Sing t -> Sing (Apply (Apply MzipSym0 t) t) Source # sMzipWith :: forall a b c (t :: a ~> (b ~> c)) (t :: Proxy a) (t :: Proxy b). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply MzipWithSym0 t) t) t) Source # sMunzip :: forall a b (t :: Proxy (a, b)). Sing t -> Sing (Apply MunzipSym0 t) Source # | |
PMonadZip (Proxy :: Type -> Type) Source # | |
Bounded (Proxy t) | Since: base-4.7.0.0 |
Enum (Proxy s) | Since: base-4.7.0.0 |
Eq (Proxy s) | Since: base-4.7.0.0 |
Data t => Data (Proxy t) | Since: base-4.7.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Proxy t -> c (Proxy t) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Proxy t) # toConstr :: Proxy t -> Constr # dataTypeOf :: Proxy t -> DataType # dataCast1 :: Typeable t0 => (forall d. Data d => c (t0 d)) -> Maybe (c (Proxy t)) # dataCast2 :: Typeable t0 => (forall d e. (Data d, Data e) => c (t0 d e)) -> Maybe (c (Proxy t)) # gmapT :: (forall b. Data b => b -> b) -> Proxy t -> Proxy t # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Proxy t -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Proxy t -> r # gmapQ :: (forall d. Data d => d -> u) -> Proxy t -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Proxy t -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Proxy t -> m (Proxy t) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Proxy t -> m (Proxy t) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Proxy t -> m (Proxy t) # | |
Ord (Proxy s) | Since: base-4.7.0.0 |
Read (Proxy t) | Since: base-4.7.0.0 |
Show (Proxy s) | Since: base-4.7.0.0 |
Ix (Proxy s) | Since: base-4.7.0.0 |
Defined in Data.Proxy | |
Generic (Proxy t) | Since: base-4.6.0.0 |
Semigroup (Proxy s) | Since: base-4.9.0.0 |
Monoid (Proxy s) | Since: base-4.7.0.0 |
SingKind (Proxy t) Source # | |
SDecide (Proxy t) Source # | |
PEq (Proxy s) Source # | |
SEq (Proxy s) Source # | |
SOrd (Proxy s) Source # | |
Defined in Data.Singletons.Prelude.Proxy Methods sCompare :: forall (t :: Proxy s) (t :: Proxy s). Sing t -> Sing t -> Sing (Apply (Apply CompareSym0 t) t) Source # (%<) :: forall (t :: Proxy s) (t :: Proxy s). Sing t -> Sing t -> Sing (Apply (Apply (<@#@$) t) t) Source # (%<=) :: forall (t :: Proxy s) (t :: Proxy s). Sing t -> Sing t -> Sing (Apply (Apply (<=@#@$) t) t) Source # (%>) :: forall (t :: Proxy s) (t :: Proxy s). Sing t -> Sing t -> Sing (Apply (Apply (>@#@$) t) t) Source # (%>=) :: forall (t :: Proxy s) (t :: Proxy s). Sing t -> Sing t -> Sing (Apply (Apply (>=@#@$) t) t) Source # sMax :: forall (t :: Proxy s) (t :: Proxy s). Sing t -> Sing t -> Sing (Apply (Apply MaxSym0 t) t) Source # sMin :: forall (t :: Proxy s) (t :: Proxy s). Sing t -> Sing t -> Sing (Apply (Apply MinSym0 t) t) Source # | |
POrd (Proxy s) Source # | |
SBounded (Proxy s) Source # | |
Defined in Data.Singletons.Prelude.Proxy | |
PBounded (Proxy s) Source # | |
SEnum (Proxy s) Source # | |
Defined in Data.Singletons.Prelude.Proxy Methods sSucc :: forall (t :: Proxy s). Sing t -> Sing (Apply SuccSym0 t) Source # sPred :: forall (t :: Proxy s). Sing t -> Sing (Apply PredSym0 t) Source # sToEnum :: forall (t :: Nat). Sing t -> Sing (Apply ToEnumSym0 t) Source # sFromEnum :: forall (t :: Proxy s). Sing t -> Sing (Apply FromEnumSym0 t) Source # sEnumFromTo :: forall (t :: Proxy s) (t :: Proxy s). Sing t -> Sing t -> Sing (Apply (Apply EnumFromToSym0 t) t) Source # sEnumFromThenTo :: forall (t :: Proxy s) (t :: Proxy s) (t :: Proxy s). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply EnumFromThenToSym0 t) t) t) Source # | |
PEnum (Proxy s) Source # | |
SSemigroup (Proxy s) Source # | |
PSemigroup (Proxy s) Source # | |
SShow (Proxy s) Source # | |
Defined in Data.Singletons.Prelude.Proxy Methods sShowsPrec :: forall (t :: Nat) (t :: Proxy s) (t :: Symbol). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ShowsPrecSym0 t) t) t) Source # sShow_ :: forall (t :: Proxy s). Sing t -> Sing (Apply Show_Sym0 t) Source # sShowList :: forall (t :: [Proxy s]) (t :: Symbol). Sing t -> Sing t -> Sing (Apply (Apply ShowListSym0 t) t) Source # | |
PShow (Proxy s) Source # | |
SMonoid (Proxy s) Source # | |
PMonoid (Proxy s) Source # | |
TestCoercion (SProxy :: Proxy t -> Type) Source # | |
Defined in Data.Singletons.Prelude.Proxy | |
TestEquality (SProxy :: Proxy t -> Type) Source # | |
Defined in Data.Singletons.Prelude.Proxy | |
SingI ('Proxy :: Proxy t) Source # | |
type Traverse (a2 :: a1 ~> f b) (a3 :: Proxy a1) Source # | |
Defined in Data.Singletons.Prelude.Traversable | |
type MapM (a2 :: a1 ~> m b) (a3 :: Proxy a1) Source # | |
Defined in Data.Singletons.Prelude.Traversable | |
type LiftA2 (arg1 :: a ~> (b ~> c)) (arg2 :: Proxy a) (arg3 :: Proxy b) Source # | |
type MzipWith (a2 :: a1 ~> (b ~> c)) (a3 :: Proxy a1) (a4 :: Proxy b) Source # | |
type Fmap (a2 :: a1 ~> b) (a3 :: Proxy a1) Source # | |
Defined in Data.Singletons.Prelude.Proxy | |
type FoldMap (a2 :: a1 ~> k2) (a3 :: Proxy a1) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Proxy a1) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr' (arg1 :: a ~> (b ~> b)) (arg2 :: b) (arg3 :: Proxy a) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: Proxy a1) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Proxy a) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Rep1 (Proxy :: k -> Type) | |
type Mzero Source # | |
Defined in Data.Singletons.Prelude.Proxy type Mzero | |
type Empty Source # | |
Defined in Data.Singletons.Prelude.Proxy type Empty | |
type Return (arg :: a) Source # | |
Defined in Data.Singletons.Prelude.Proxy type Return (arg :: a) | |
type Pure (a :: k1) Source # | |
Defined in Data.Singletons.Prelude.Proxy type Pure (a :: k1) | |
type Foldr1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Proxy k2) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Proxy k2) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Elem (a1 :: k1) (a2 :: Proxy k1) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Mplus (arg1 :: Proxy a) (arg2 :: Proxy a) Source # | |
Defined in Data.Singletons.Prelude.Proxy | |
type (a2 :: Proxy a1) <|> (a3 :: Proxy a1) Source # | |
Defined in Data.Singletons.Prelude.Proxy | |
type (arg1 :: a) <$ (arg2 :: Proxy b) Source # | |
Defined in Data.Singletons.Prelude.Proxy | |
type Fold (a :: Proxy k2) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type ToList (arg :: Proxy a) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Null (a2 :: Proxy a1) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Length (a2 :: Proxy a1) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Maximum (arg :: Proxy a) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Minimum (arg :: Proxy a) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Sum (a :: Proxy k2) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type Product (a :: Proxy k2) Source # | |
Defined in Data.Singletons.Prelude.Foldable | |
type SequenceA (a2 :: Proxy (f a1)) Source # | |
Defined in Data.Singletons.Prelude.Traversable | |
type Sequence (a2 :: Proxy (m a1)) Source # | |
Defined in Data.Singletons.Prelude.Traversable | |
type Munzip (arg :: Proxy (a, b)) Source # | |
Defined in Data.Singletons.Prelude.Monad.Zip | |
type (a2 :: Proxy a1) >>= (a3 :: a1 ~> Proxy b) Source # | |
Defined in Data.Singletons.Prelude.Proxy | |
type (arg1 :: Proxy a) >> (arg2 :: Proxy b) Source # | |
Defined in Data.Singletons.Prelude.Proxy | |
type (a2 :: Proxy (a1 ~> b)) <*> (a3 :: Proxy a1) Source # | |
Defined in Data.Singletons.Prelude.Proxy | |
type (arg1 :: Proxy a) *> (arg2 :: Proxy b) Source # | |
Defined in Data.Singletons.Prelude.Proxy | |
type (arg1 :: Proxy a) <* (arg2 :: Proxy b) Source # | |
Defined in Data.Singletons.Prelude.Proxy | |
type Mzip (arg1 :: Proxy a) (arg2 :: Proxy b) Source # | |
Defined in Data.Singletons.Prelude.Monad.Zip | |
type Rep (Proxy t) | |
type Demote (Proxy t) Source # | |
Defined in Data.Singletons.Prelude.Proxy | |
type Sing Source # | |
Defined in Data.Singletons.Prelude.Proxy | |
type MinBound Source # | |
Defined in Data.Singletons.Prelude.Proxy type MinBound | |
type MaxBound Source # | |
Defined in Data.Singletons.Prelude.Proxy type MaxBound | |
type Mempty Source # | |
Defined in Data.Singletons.Prelude.Proxy type Mempty | |
type Succ (a :: Proxy s) Source # | |
Defined in Data.Singletons.Prelude.Proxy | |
type Pred (a :: Proxy s) Source # | |
Defined in Data.Singletons.Prelude.Proxy | |
type ToEnum a Source # | |
Defined in Data.Singletons.Prelude.Proxy type ToEnum a | |
type FromEnum (a :: Proxy s) Source # | |
Defined in Data.Singletons.Prelude.Proxy | |
type Sconcat (a :: NonEmpty (Proxy s)) Source # | |
Defined in Data.Singletons.Prelude.Proxy | |
type Show_ (arg :: Proxy s) Source # | |
Defined in Data.Singletons.Prelude.Proxy | |
type Mconcat (a :: [Proxy s]) Source # | |
Defined in Data.Singletons.Prelude.Proxy | |
type (a1 :: Proxy s) == (a2 :: Proxy s) Source # | |
Defined in Data.Singletons.Prelude.Proxy | |
type (x :: Proxy s) /= (y :: Proxy s) Source # | |
type Compare (a1 :: Proxy s) (a2 :: Proxy s) Source # | |
Defined in Data.Singletons.Prelude.Proxy | |
type (arg1 :: Proxy s) < (arg2 :: Proxy s) Source # | |
Defined in Data.Singletons.Prelude.Proxy | |
type (arg1 :: Proxy s) <= (arg2 :: Proxy s) Source # | |
Defined in Data.Singletons.Prelude.Proxy | |
type (arg1 :: Proxy s) > (arg2 :: Proxy s) Source # | |
Defined in Data.Singletons.Prelude.Proxy | |
type (arg1 :: Proxy s) >= (arg2 :: Proxy s) Source # | |
Defined in Data.Singletons.Prelude.Proxy | |
type Max (arg1 :: Proxy s) (arg2 :: Proxy s) Source # | |
Defined in Data.Singletons.Prelude.Proxy | |
type Min (arg1 :: Proxy s) (arg2 :: Proxy s) Source # | |
Defined in Data.Singletons.Prelude.Proxy | |
type EnumFromTo (a1 :: Proxy s) (a2 :: Proxy s) Source # | |
Defined in Data.Singletons.Prelude.Proxy | |
type (a1 :: Proxy s) <> (a2 :: Proxy s) Source # | |
Defined in Data.Singletons.Prelude.Proxy | |
type ShowList (arg1 :: [Proxy s]) arg2 Source # | |
Defined in Data.Singletons.Prelude.Proxy | |
type Mappend (arg1 :: Proxy s) (arg2 :: Proxy s) Source # | |
Defined in Data.Singletons.Prelude.Proxy | |
type EnumFromThenTo (a1 :: Proxy s) (a2 :: Proxy s) (a3 :: Proxy s) Source # | |
Defined in Data.Singletons.Prelude.Proxy | |
type ShowsPrec a1 (a2 :: Proxy s) a3 Source # | |
Defined in Data.Singletons.Prelude.Proxy |
Defunctionalization symbols
data DemoteSym0 a6989586621681337317 Source #
Instances
SuppressUnusedWarnings DemoteSym0 Source # | |
Defined in Data.Singletons Methods suppressUnusedWarnings :: () Source # | |
type Apply DemoteSym0 (a6989586621681337317 :: Type) Source # | |
Defined in Data.Singletons |
data SameKindSym0 a6989586621681337319 Source #
Instances
SuppressUnusedWarnings (SameKindSym0 :: TyFun k (k ~> Constraint) -> Type) Source # | |
Defined in Data.Singletons Methods suppressUnusedWarnings :: () Source # | |
type Apply (SameKindSym0 :: TyFun k (k ~> Constraint) -> Type) (a6989586621681337319 :: k) Source # | |
Defined in Data.Singletons type Apply (SameKindSym0 :: TyFun k (k ~> Constraint) -> Type) (a6989586621681337319 :: k) = SameKindSym1 a6989586621681337319 |
data SameKindSym1 a6989586621681337319 a6989586621681337320 Source #
Instances
SuppressUnusedWarnings (SameKindSym1 a6989586621681337319 :: TyFun k Constraint -> Type) Source # | |
Defined in Data.Singletons Methods suppressUnusedWarnings :: () Source # | |
type Apply (SameKindSym1 a6989586621681337319 :: TyFun k Constraint -> Type) (a6989586621681337320 :: k) Source # | |
Defined in Data.Singletons type Apply (SameKindSym1 a6989586621681337319 :: TyFun k Constraint -> Type) (a6989586621681337320 :: k) = SameKindSym2 a6989586621681337319 a6989586621681337320 |
type SameKindSym2 (a6989586621681337319 :: k) (a6989586621681337320 :: k) = SameKind a6989586621681337319 a6989586621681337320 :: Constraint Source #
data KindOfSym0 a6989586621681337322 Source #
Instances
SuppressUnusedWarnings (KindOfSym0 :: TyFun k Type -> Type) Source # | |
Defined in Data.Singletons Methods suppressUnusedWarnings :: () Source # | |
type Apply (KindOfSym0 :: TyFun k Type -> Type) (a6989586621681337322 :: k) Source # | |
Defined in Data.Singletons type Apply (KindOfSym0 :: TyFun k Type -> Type) (a6989586621681337322 :: k) = KindOfSym1 a6989586621681337322 |
type KindOfSym1 (a6989586621681337322 :: k) = KindOf a6989586621681337322 :: Type Source #
data (~>@#@$) a6989586621681337324 infixr 0 Source #
Instances
SuppressUnusedWarnings (~>@#@$) Source # | |
Defined in Data.Singletons Methods suppressUnusedWarnings :: () Source # | |
type Apply (~>@#@$) (a6989586621681337324 :: Type) Source # | |
Defined in Data.Singletons |
data a6989586621681337324 ~>@#@$$ a6989586621681337325 infixr 0 Source #
type (~>@#@$$$) (a6989586621681337324 :: Type) (a6989586621681337325 :: Type) = (~>) a6989586621681337324 a6989586621681337325 :: Type infixr 0 Source #
data ApplySym1 a6989586621681337327 a6989586621681337328 Source #
type ApplySym2 (a6989586621681337327 :: (~>) k1 k2) (a6989586621681337328 :: k1) = Apply a6989586621681337327 a6989586621681337328 :: k2 Source #
data a6989586621681337330 @@@#@$$ a6989586621681337331 infixl 9 Source #
type (@@@#@$$$) (a6989586621681337330 :: (~>) k1 k2) (a6989586621681337331 :: k1) = (@@) a6989586621681337330 a6989586621681337331 :: k2 infixl 9 Source #
Orphan instances
SBounded k => Bounded (SomeSing k) Source # | |
SEnum k => Enum (SomeSing k) Source # | |
Methods succ :: SomeSing k -> SomeSing k # pred :: SomeSing k -> SomeSing k # fromEnum :: SomeSing k -> Int # enumFrom :: SomeSing k -> [SomeSing k] # enumFromThen :: SomeSing k -> SomeSing k -> [SomeSing k] # enumFromTo :: SomeSing k -> SomeSing k -> [SomeSing k] # enumFromThenTo :: SomeSing k -> SomeSing k -> SomeSing k -> [SomeSing k] # | |
SEq k => Eq (SomeSing k) Source # | |
SNum k => Num (SomeSing k) Source # | |
SOrd k => Ord (SomeSing k) Source # | |
ShowSing k => Show (SomeSing k) Source # | |
SIsString k => IsString (SomeSing k) Source # | |
Methods fromString :: String -> SomeSing k # | |
SSemigroup k => Semigroup (SomeSing k) Source # | |
SMonoid k => Monoid (SomeSing k) Source # | |
(forall (a :: k). SingI a => SingI (f a), (ApplyTyCon :: (k -> k_last) -> k ~> k_last) ~ (ApplyTyConAux1 :: (k -> k_last) -> TyFun k k_last -> Type)) => SingI (TyCon1 f :: k ~> k_last) Source # | |
(forall (a1 :: k2) (a2 :: k1). (SingI a1, SingI a2) => SingI (f a1 a2), (ApplyTyCon :: (k1 -> k_last) -> k1 ~> k_last) ~ (ApplyTyConAux1 :: (k1 -> k_last) -> TyFun k1 k_last -> Type)) => SingI (TyCon2 f :: k2 ~> (k1 ~> k_last)) Source # | |
(forall (a1 :: k2) (a2 :: k3) (a3 :: k1). (SingI a1, SingI a2, SingI a3) => SingI (f a1 a2 a3), (ApplyTyCon :: (k1 -> k_last) -> k1 ~> k_last) ~ (ApplyTyConAux1 :: (k1 -> k_last) -> TyFun k1 k_last -> Type)) => SingI (TyCon3 f :: k2 ~> (k3 ~> (k1 ~> k_last))) Source # | |
(forall (a1 :: k2) (a2 :: k3) (a3 :: k4) (a4 :: k1). (SingI a1, SingI a2, SingI a3, SingI a4) => SingI (f a1 a2 a3 a4), (ApplyTyCon :: (k1 -> k_last) -> k1 ~> k_last) ~ (ApplyTyConAux1 :: (k1 -> k_last) -> TyFun k1 k_last -> Type)) => SingI (TyCon4 f :: k2 ~> (k3 ~> (k4 ~> (k1 ~> k_last)))) Source # | |
(forall (a1 :: k2) (a2 :: k3) (a3 :: k4) (a4 :: k5) (a5 :: k1). (SingI a1, SingI a2, SingI a3, SingI a4, SingI a5) => SingI (f a1 a2 a3 a4 a5), (ApplyTyCon :: (k1 -> k_last) -> k1 ~> k_last) ~ (ApplyTyConAux1 :: (k1 -> k_last) -> TyFun k1 k_last -> Type)) => SingI (TyCon5 f :: k2 ~> (k3 ~> (k4 ~> (k5 ~> (k1 ~> k_last))))) Source # | |
(forall (a1 :: k2) (a2 :: k3) (a3 :: k4) (a4 :: k5) (a5 :: k6) (a6 :: k1). (SingI a1, SingI a2, SingI a3, SingI a4, SingI a5, SingI a6) => SingI (f a1 a2 a3 a4 a5 a6), (ApplyTyCon :: (k1 -> k_last) -> k1 ~> k_last) ~ (ApplyTyConAux1 :: (k1 -> k_last) -> TyFun k1 k_last -> Type)) => SingI (TyCon6 f :: k2 ~> (k3 ~> (k4 ~> (k5 ~> (k6 ~> (k1 ~> k_last)))))) Source # | |
(forall (a1 :: k2) (a2 :: k3) (a3 :: k4) (a4 :: k5) (a5 :: k6) (a6 :: k7) (a7 :: k1). (SingI a1, SingI a2, SingI a3, SingI a4, SingI a5, SingI a6, SingI a7) => SingI (f a1 a2 a3 a4 a5 a6 a7), (ApplyTyCon :: (k1 -> k_last) -> k1 ~> k_last) ~ (ApplyTyConAux1 :: (k1 -> k_last) -> TyFun k1 k_last -> Type)) => SingI (TyCon7 f :: k2 ~> (k3 ~> (k4 ~> (k5 ~> (k6 ~> (k7 ~> (k1 ~> k_last))))))) Source # | |
(forall (a1 :: k2) (a2 :: k3) (a3 :: k4) (a4 :: k5) (a5 :: k6) (a6 :: k7) (a7 :: k8) (a8 :: k1). (SingI a1, SingI a2, SingI a3, SingI a4, SingI a5, SingI a6, SingI a7, SingI a8) => SingI (f a1 a2 a3 a4 a5 a6 a7 a8), (ApplyTyCon :: (k1 -> k_last) -> k1 ~> k_last) ~ (ApplyTyConAux1 :: (k1 -> k_last) -> TyFun k1 k_last -> Type)) => SingI (TyCon8 f :: k2 ~> (k3 ~> (k4 ~> (k5 ~> (k6 ~> (k7 ~> (k8 ~> (k1 ~> k_last)))))))) Source # | |