Safe Haskell | None |
---|---|
Language | Haskell2010 |
Re-exports TypeLits
, modifying it considering our practices.
Synopsis
- data Symbol
- class KnownSymbol (n :: Symbol)
- type family AppendSymbol (a :: Symbol) (b :: Symbol) :: Symbol where ...
- symbolVal :: forall (n :: Symbol) proxy. KnownSymbol n => proxy n -> String
- symbolValT :: forall s. KnownSymbol s => Proxy s -> Text
- symbolValT' :: forall s. KnownSymbol s => Text
- type family TypeError (a :: ErrorMessage) :: b where ...
- data ErrorMessage
- type family TypeErrorUnless (cond :: Bool) (err :: ErrorMessage) :: Constraint where ...
- inTypeErrorUnless :: forall cond err a. TypeErrorUnless cond err => (cond ~ 'True => a) -> a
Documentation
(Kind) This is the kind of type-level symbols. Declared here because class IP needs it
Instances
SingKind Symbol | Since: base-4.9.0.0 |
Defined in GHC.Generics type DemoteRep Symbol | |
PIsString Symbol | |
Defined in Data.Singletons.Prelude.IsString type FromString arg0 :: a0 # | |
SIsString Symbol | |
Defined in Data.Singletons.Prelude.IsString sFromString :: forall (t :: Symbol). Sing t -> Sing (Apply FromStringSym0 t) # | |
PMonoid Symbol | |
SMonoid Symbol | |
PShow Symbol | |
SShow Symbol | |
Defined in Data.Singletons.Prelude.Show sShowsPrec :: forall (t1 :: Nat) (t2 :: Symbol) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply ShowsPrecSym0 t1) t2) t3) # sShow_ :: forall (t :: Symbol). Sing t -> Sing (Apply Show_Sym0 t) # sShowList :: forall (t1 :: [Symbol]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply ShowListSym0 t1) t2) # | |
PSemigroup Symbol | |
Defined in Data.Singletons.Prelude.Semigroup.Internal | |
SSemigroup Symbol | |
KnownSymbol a => SingI (a :: Symbol) | Since: base-4.9.0.0 |
Defined in GHC.Generics sing :: Sing a | |
KnownSymbol s => Showtype (s :: Symbol) | |
Defined in Type.Showtype | |
KnownSymbol n => Reifies (n :: Symbol) String | |
Defined in Data.Reflection | |
Eq t => Eq (ElField '(s, t)) | |
(Floating t, KnownSymbol s) => Floating (ElField '(s, t)) | |
Defined in Data.Vinyl.Functor exp :: ElField '(s, t) -> ElField '(s, t) # log :: ElField '(s, t) -> ElField '(s, t) # sqrt :: ElField '(s, t) -> ElField '(s, t) # (**) :: ElField '(s, t) -> ElField '(s, t) -> ElField '(s, t) # logBase :: ElField '(s, t) -> ElField '(s, t) -> ElField '(s, t) # sin :: ElField '(s, t) -> ElField '(s, t) # cos :: ElField '(s, t) -> ElField '(s, t) # tan :: ElField '(s, t) -> ElField '(s, t) # asin :: ElField '(s, t) -> ElField '(s, t) # acos :: ElField '(s, t) -> ElField '(s, t) # atan :: ElField '(s, t) -> ElField '(s, t) # sinh :: ElField '(s, t) -> ElField '(s, t) # cosh :: ElField '(s, t) -> ElField '(s, t) # tanh :: ElField '(s, t) -> ElField '(s, t) # asinh :: ElField '(s, t) -> ElField '(s, t) # acosh :: ElField '(s, t) -> ElField '(s, t) # atanh :: ElField '(s, t) -> ElField '(s, t) # log1p :: ElField '(s, t) -> ElField '(s, t) # expm1 :: ElField '(s, t) -> ElField '(s, t) # | |
(Fractional t, KnownSymbol s) => Fractional (ElField '(s, t)) | |
(Num t, KnownSymbol s) => Num (ElField '(s, t)) | |
Defined in Data.Vinyl.Functor (+) :: ElField '(s, t) -> ElField '(s, t) -> ElField '(s, t) # (-) :: ElField '(s, t) -> ElField '(s, t) -> ElField '(s, t) # (*) :: ElField '(s, t) -> ElField '(s, t) -> ElField '(s, t) # negate :: ElField '(s, t) -> ElField '(s, t) # abs :: ElField '(s, t) -> ElField '(s, t) # signum :: ElField '(s, t) -> ElField '(s, t) # fromInteger :: Integer -> ElField '(s, t) # | |
Ord t => Ord (ElField '(s, t)) | |
Defined in Data.Vinyl.Functor compare :: ElField '(s, t) -> ElField '(s, t) -> Ordering # (<) :: ElField '(s, t) -> ElField '(s, t) -> Bool # (<=) :: ElField '(s, t) -> ElField '(s, t) -> Bool # (>) :: ElField '(s, t) -> ElField '(s, t) -> Bool # (>=) :: ElField '(s, t) -> ElField '(s, t) -> Bool # max :: ElField '(s, t) -> ElField '(s, t) -> ElField '(s, t) # min :: ElField '(s, t) -> ElField '(s, t) -> ElField '(s, t) # | |
(Real t, KnownSymbol s) => Real (ElField '(s, t)) | |
Defined in Data.Vinyl.Functor toRational :: ElField '(s, t) -> Rational # | |
(RealFrac t, KnownSymbol s) => RealFrac (ElField '(s, t)) | |
(Show t, KnownSymbol s) => Show (ElField '(s, t)) | |
KnownSymbol s => Generic (ElField '(s, a)) | |
Semigroup t => Semigroup (ElField '(s, t)) | |
(KnownSymbol s, Monoid t) => Monoid (ElField '(s, t)) | |
(KnownSymbol s, Storable t) => Storable (ElField '(s, t)) | |
Defined in Data.Vinyl.Functor sizeOf :: ElField '(s, t) -> Int # alignment :: ElField '(s, t) -> Int # peekElemOff :: Ptr (ElField '(s, t)) -> Int -> IO (ElField '(s, t)) # pokeElemOff :: Ptr (ElField '(s, t)) -> Int -> ElField '(s, t) -> IO () # peekByteOff :: Ptr b -> Int -> IO (ElField '(s, t)) # pokeByteOff :: Ptr b -> Int -> ElField '(s, t) -> IO () # | |
SuppressUnusedWarnings ShowParenSym0 | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings UnwordsSym0 | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings UnlinesSym0 | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings Show_tupleSym0 | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings ShowsPrec_6989586621680297229Sym0 | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings ShowsPrec_6989586621680297253Sym0 | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings ShowsNatSym0 | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings ShowsPrec_6989586621680279257Sym0 | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings ShowsPrec_6989586621680297071Sym0 | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings ShowsPrec_6989586621680297283Sym0 | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings ShowsPrec_6989586621680716360Sym0 | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings ShowsPrec_6989586621680716388Sym0 | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings KnownSymbolSym0 | |
Defined in Data.Singletons.TypeLits suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings ShowCommaSpaceSym0 | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings ShowSpaceSym0 | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings ShowStringSym0 | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings ShowCharSym0 | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SingI ShowParenSym0 | |
Defined in Data.Singletons.Prelude.Show sing :: Sing ShowParenSym0 # | |
SingI UnwordsSym0 | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing UnwordsSym0 # | |
SingI UnlinesSym0 | |
Defined in Data.Singletons.Prelude.List.Internal sing :: Sing UnlinesSym0 # | |
SingI Show_tupleSym0 | |
Defined in Data.Singletons.Prelude.Show | |
SingI ShowCommaSpaceSym0 | |
Defined in Data.Singletons.Prelude.Show | |
SingI ShowSpaceSym0 | |
Defined in Data.Singletons.Prelude.Show sing :: Sing ShowSpaceSym0 # | |
SingI ShowStringSym0 | |
Defined in Data.Singletons.Prelude.Show sing :: Sing ShowStringSym0 # | |
SingI ShowCharSym0 | |
Defined in Data.Singletons.Prelude.Show sing :: Sing ShowCharSym0 # | |
KnownSymbol s => IsoHKD ElField ('(s, a) :: (Symbol, Type)) | Work with values of type |
SuppressUnusedWarnings (ShowsPrec_6989586621680297229Sym1 a6989586621680297226 :: TyFun Bool (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowList_6989586621680279224Sym0 :: TyFun [a6989586621680278749] (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowListSym0 :: TyFun [a6989586621680278749] (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680297253Sym1 a6989586621680297250 :: TyFun Ordering (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680279237Sym0 :: TyFun Nat ([a6989586621680278767] ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680297105Sym0 :: TyFun Nat (Maybe a3530822107858468865 ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680279202Sym0 :: TyFun Nat (a6989586621680278749 ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrecSym0 :: TyFun Nat (a6989586621680278749 ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680716481Sym0 :: TyFun Nat (Min a6989586621679058450 ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680716512Sym0 :: TyFun Nat (Max a6989586621679058455 ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680716543Sym0 :: TyFun Nat (First a6989586621679058465 ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680716574Sym0 :: TyFun Nat (Last a6989586621679058460 ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680716605Sym0 :: TyFun Nat (WrappedMonoid m6989586621679086385 ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680716301Sym0 :: TyFun Nat (Option a6989586621679058445 ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680570718Sym0 :: TyFun Nat (Identity a6989586621680570499 ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Singletons.Prelude.Identity suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680330696Sym0 :: TyFun Nat (First a6989586621679083079 ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Singletons.Prelude.Monoid suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680330727Sym0 :: TyFun Nat (Last a6989586621679083072 ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Singletons.Prelude.Monoid suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680716332Sym0 :: TyFun Nat (Dual a6989586621679083138 ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680716419Sym0 :: TyFun Nat (Sum a6989586621679083115 ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680716450Sym0 :: TyFun Nat (Product a6989586621679083123 ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680297203Sym0 :: TyFun Nat (NonEmpty a6989586621679058531 ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowStringSym1 a6989586621680279143 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowCharSym1 a6989586621680279153 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Show_tupleSym1 a6989586621680279091 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsNatSym1 a6989586621680296569 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (FromStringSym0 :: TyFun Symbol a6989586621680971203 -> Type) | |
Defined in Data.Singletons.Prelude.IsString suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (FromString_6989586621680971239Sym0 :: TyFun Symbol (Identity a6989586621680971208) -> Type) | |
Defined in Data.Singletons.Prelude.IsString suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680279257Sym1 a6989586621680279254 :: TyFun Symbol (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680297071Sym1 a6989586621680297068 :: TyFun () (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsSym0 :: TyFun a6989586621680278734 (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Show__6989586621680279216Sym0 :: TyFun a6989586621680278749 Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Show_Sym0 :: TyFun a6989586621680278749 Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Lambda_6989586621680279119Sym0 :: TyFun k (TyFun Symbol Symbol -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680297283Sym1 a6989586621680297280 :: TyFun Void (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680716360Sym1 a6989586621680716357 :: TyFun All (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680716388Sym1 a6989586621680716385 :: TyFun Any (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowParenSym1 a6989586621680279125 :: TyFun (Symbol ~> Symbol) (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowListWithSym0 :: TyFun (a6989586621680278733 ~> (Symbol ~> Symbol)) ([a6989586621680278733] ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SShow a => SingI (ShowListSym0 :: TyFun [a] (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Show sing :: Sing ShowListSym0 # | |
SShow a => SingI (ShowsPrecSym0 :: TyFun Nat (a ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Singletons.Prelude.Show sing :: Sing ShowsPrecSym0 # | |
SingI d => SingI (ShowStringSym1 d :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show sing :: Sing (ShowStringSym1 d) # | |
SingI d => SingI (ShowCharSym1 d :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show sing :: Sing (ShowCharSym1 d) # | |
SingI d => SingI (Show_tupleSym1 d :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show | |
SIsString a => SingI (FromStringSym0 :: TyFun Symbol a -> Type) | |
Defined in Data.Singletons.Prelude.IsString sing :: Sing FromStringSym0 # | |
SShow a => SingI (ShowsSym0 :: TyFun a (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Show | |
SShow a => SingI (Show_Sym0 :: TyFun a Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show | |
SingI d => SingI (ShowParenSym1 d :: TyFun (Symbol ~> Symbol) (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Show sing :: Sing (ShowParenSym1 d) # | |
SingI (ShowListWithSym0 :: TyFun (a ~> (Symbol ~> Symbol)) ([a] ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Singletons.Prelude.Show | |
(i ~ RIndex t ts, NatToInt i, FieldOffset ElField ts t, Storable (Rec ElField ts), AllConstrained (FieldOffset ElField ts) ts) => RecElem (SRec :: ((Symbol, Type) -> Type) -> [(Symbol, Type)] -> Type) (t :: (Symbol, Type)) (t :: (Symbol, Type)) (ts :: [(Symbol, Type)]) (ts :: [(Symbol, Type)]) i | |
Defined in Data.Vinyl.SRec type RecElemFCtx SRec f # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680279237Sym1 a6989586621680279234 a6989586621680278767 :: TyFun [a6989586621680278767] (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowListWithSym1 a6989586621680279159 :: TyFun [a6989586621680278733] (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680297105Sym1 a6989586621680297102 a3530822107858468865 :: TyFun (Maybe a3530822107858468865) (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680297161Sym0 :: TyFun Nat (Either a6989586621679086693 b6989586621679086694 ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680279277Sym0 :: TyFun Nat ((a6989586621680278771, b6989586621680278772) ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680733534Sym0 :: TyFun Nat (Arg a6989586621680732251 b6989586621680732252 ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowParenSym2 a6989586621680279126 a6989586621680279125 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsSym1 a6989586621680279179 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowListSym1 arg6989586621680279195 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680716360Sym2 a6989586621680716358 a6989586621680716357 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680716388Sym2 a6989586621680716386 a6989586621680716385 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowList_6989586621680279224Sym1 a6989586621680279222 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680279257Sym2 a6989586621680279255 a6989586621680279254 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680297071Sym2 a6989586621680297069 a6989586621680297068 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680297229Sym2 a6989586621680297227 a6989586621680297226 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680297253Sym2 a6989586621680297251 a6989586621680297250 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680297283Sym2 a6989586621680297281 a6989586621680297280 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Lambda_6989586621680279119Sym1 a_69895866216802791146989586621680279118 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680279202Sym1 a6989586621680279199 a6989586621680278749 :: TyFun a6989586621680278749 (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrecSym1 arg6989586621680279187 a6989586621680278749 :: TyFun a6989586621680278749 (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621680059392GoSym0 :: TyFun k1 (TyFun k2 (TyFun [Symbol] Symbol -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680716481Sym1 a6989586621680716478 a6989586621679058450 :: TyFun (Min a6989586621679058450) (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680716512Sym1 a6989586621680716509 a6989586621679058455 :: TyFun (Max a6989586621679058455) (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680716543Sym1 a6989586621680716540 a6989586621679058465 :: TyFun (First a6989586621679058465) (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680716574Sym1 a6989586621680716571 a6989586621679058460 :: TyFun (Last a6989586621679058460) (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680716605Sym1 a6989586621680716602 m6989586621679086385 :: TyFun (WrappedMonoid m6989586621679086385) (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680716301Sym1 a6989586621680716298 a6989586621679058445 :: TyFun (Option a6989586621679058445) (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680570718Sym1 a6989586621680570715 a6989586621680570499 :: TyFun (Identity a6989586621680570499) (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Identity suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680330696Sym1 a6989586621680330693 a6989586621679083079 :: TyFun (First a6989586621679083079) (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Monoid suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680330727Sym1 a6989586621680330724 a6989586621679083072 :: TyFun (Last a6989586621679083072) (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Monoid suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680716332Sym1 a6989586621680716329 a6989586621679083138 :: TyFun (Dual a6989586621679083138) (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680716419Sym1 a6989586621680716416 a6989586621679083115 :: TyFun (Sum a6989586621679083115) (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680716450Sym1 a6989586621680716447 a6989586621679083123 :: TyFun (Product a6989586621679083123) (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680297203Sym1 a6989586621680297200 a6989586621679058531 :: TyFun (NonEmpty a6989586621679058531) (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SingI d => SingI (ShowListWithSym1 d :: TyFun [a] (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Show sing :: Sing (ShowListWithSym1 d) # | |
(SingI d1, SingI d2) => SingI (ShowParenSym2 d1 d2 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show sing :: Sing (ShowParenSym2 d1 d2) # | |
(SShow a, SingI d) => SingI (ShowsSym1 d :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show | |
(SShow a, SingI d) => SingI (ShowListSym1 d :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show sing :: Sing (ShowListSym1 d) # | |
SingI (ErrorWithoutStackTraceSym0 :: TyFun Symbol a -> Type) | |
Defined in Data.Singletons.TypeLits.Internal | |
SingI (ErrorSym0 :: TyFun Symbol a -> Type) | |
Defined in Data.Singletons.TypeLits.Internal | |
(SShow a, SingI d) => SingI (ShowsPrecSym1 d a :: TyFun a (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Show sing :: Sing (ShowsPrecSym1 d a) # | |
(i ~ RIndex t ts, NatToInt i, FieldOffset ElField ts t, Storable (Rec ElField ts), AllConstrained (FieldOffset ElField ts) ts) => RecElem (SRec2 ElField) (t :: (Symbol, Type)) (t :: (Symbol, Type)) (ts :: [(Symbol, Type)]) (ts :: [(Symbol, Type)]) i | Field accessors for |
Defined in Data.Vinyl.SRec type RecElemFCtx (SRec2 ElField) f # | |
(is ~ RImage rs ss, RecSubset (Rec :: ((Symbol, Type) -> Type) -> [(Symbol, Type)] -> Type) rs ss is, Storable (Rec ElField rs), Storable (Rec ElField ss), RPureConstrained (FieldOffset ElField ss) rs, RPureConstrained (FieldOffset ElField rs) rs, RFoldMap rs, RMap rs, RApply rs) => RecSubset (SRec :: ((Symbol, Type) -> Type) -> [(Symbol, Type)] -> Type) (rs :: [(Symbol, Type)]) (ss :: [(Symbol, Type)]) is | |
Defined in Data.Vinyl.SRec type RecSubsetFCtx SRec f # rsubsetC :: forall g (f :: k -> Type). (Functor g, RecSubsetFCtx SRec f) => (SRec f rs -> g (SRec f rs)) -> SRec f ss -> g (SRec f ss) # rcastC :: forall (f :: k -> Type). RecSubsetFCtx SRec f => SRec f ss -> SRec f rs # rreplaceC :: forall (f :: k -> Type). RecSubsetFCtx SRec f => SRec f rs -> SRec f ss -> SRec f ss # | |
(is ~ RImage rs ss, RecSubset (Rec :: ((Symbol, Type) -> Type) -> [(Symbol, Type)] -> Type) rs ss is, Storable (Rec ElField rs), Storable (Rec ElField ss), RPureConstrained (FieldOffset ElField ss) rs, RPureConstrained (FieldOffset ElField rs) rs, RFoldMap rs, RMap rs, RApply rs) => RecSubset (SRec2 ElField) (rs :: [(Symbol, Type)]) (ss :: [(Symbol, Type)]) is | |
Defined in Data.Vinyl.SRec type RecSubsetFCtx (SRec2 ElField) f # rsubsetC :: forall g (f :: k -> Type). (Functor g, RecSubsetFCtx (SRec2 ElField) f) => (SRec2 ElField f rs -> g (SRec2 ElField f rs)) -> SRec2 ElField f ss -> g (SRec2 ElField f ss) # rcastC :: forall (f :: k -> Type). RecSubsetFCtx (SRec2 ElField) f => SRec2 ElField f ss -> SRec2 ElField f rs # rreplaceC :: forall (f :: k -> Type). RecSubsetFCtx (SRec2 ElField) f => SRec2 ElField f rs -> SRec2 ElField f ss -> SRec2 ElField f ss # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680297161Sym1 a6989586621680297158 a6989586621679086693 b6989586621679086694 :: TyFun (Either a6989586621679086693 b6989586621679086694) (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680279294Sym0 :: TyFun Nat ((a6989586621680278776, b6989586621680278777, c6989586621680278778) ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680598687Sym0 :: TyFun Nat (Const a6989586621680597830 b6989586621680597831 ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Singletons.Prelude.Const suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowListWithSym2 a6989586621680279160 a6989586621680279159 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrecSym2 arg6989586621680279188 arg6989586621680279187 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680716301Sym2 a6989586621680716299 a6989586621680716298 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680716332Sym2 a6989586621680716330 a6989586621680716329 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680716419Sym2 a6989586621680716417 a6989586621680716416 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680716450Sym2 a6989586621680716448 a6989586621680716447 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680716481Sym2 a6989586621680716479 a6989586621680716478 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680716512Sym2 a6989586621680716510 a6989586621680716509 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680716543Sym2 a6989586621680716541 a6989586621680716540 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680716574Sym2 a6989586621680716572 a6989586621680716571 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680716605Sym2 a6989586621680716603 a6989586621680716602 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680570718Sym2 a6989586621680570716 a6989586621680570715 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Identity suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680330696Sym2 a6989586621680330694 a6989586621680330693 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Monoid suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680330727Sym2 a6989586621680330725 a6989586621680330724 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Monoid suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680279202Sym2 a6989586621680279200 a6989586621680279199 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680279237Sym2 a6989586621680279235 a6989586621680279234 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680297105Sym2 a6989586621680297103 a6989586621680297102 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680297203Sym2 a6989586621680297201 a6989586621680297200 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (FromString_6989586621680971232Sym0 :: TyFun Symbol (Const a6989586621680971205 b6989586621680971206) -> Type) | |
Defined in Data.Singletons.Prelude.IsString suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680279277Sym1 a6989586621680279274 a6989586621680278771 b6989586621680278772 :: TyFun (a6989586621680278771, b6989586621680278772) (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621680059392GoSym1 w6989586621680059390 :: TyFun k2 (TyFun [Symbol] Symbol -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680733534Sym1 a6989586621680733531 a6989586621680732251 b6989586621680732252 :: TyFun (Arg a6989586621680732251 b6989586621680732252) (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621680279170ShowlSym0 :: TyFun (k1 ~> (Symbol ~> Symbol)) (TyFun k2 (TyFun k3 (TyFun Symbol (TyFun [k1] Symbol -> Type) -> Type) -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
(SingI d1, SingI d2) => SingI (ShowListWithSym2 d1 d2 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show sing :: Sing (ShowListWithSym2 d1 d2) # | |
(SShow a, SingI d1, SingI d2) => SingI (ShowsPrecSym2 d1 d2 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show sing :: Sing (ShowsPrecSym2 d1 d2) # | |
SuppressUnusedWarnings (Let6989586621680059392GoSym2 ws6989586621680059391 w6989586621680059390 :: TyFun [Symbol] Symbol -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680279312Sym0 :: TyFun Nat ((a6989586621680278783, b6989586621680278784, c6989586621680278785, d6989586621680278786) ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680733534Sym2 a6989586621680733532 a6989586621680733531 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680279277Sym2 a6989586621680279275 a6989586621680279274 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680297161Sym2 a6989586621680297159 a6989586621680297158 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680279294Sym1 a6989586621680279291 a6989586621680278776 b6989586621680278777 c6989586621680278778 :: TyFun (a6989586621680278776, b6989586621680278777, c6989586621680278778) (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621680279170ShowlSym1 showx6989586621680279166 :: TyFun k2 (TyFun k3 (TyFun Symbol (TyFun [k1] Symbol -> Type) -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Lambda_6989586621680279099Sym0 :: TyFun k1 (TyFun k2 (TyFun (Symbol ~> c6989586621679736129) (TyFun (a6989586621679736130 ~> Symbol) (TyFun a6989586621679736130 c6989586621679736129 -> Type) -> Type) -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680598687Sym1 a6989586621680598684 a6989586621680597830 b6989586621680597831 :: TyFun (Const a6989586621680597830 b6989586621680597831) (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Const suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680279331Sym0 :: TyFun Nat ((a6989586621680278792, b6989586621680278793, c6989586621680278794, d6989586621680278795, e6989586621680278796) ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680598687Sym2 a6989586621680598685 a6989586621680598684 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Const suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680279294Sym2 a6989586621680279292 a6989586621680279291 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680279312Sym1 a6989586621680279309 a6989586621680278783 b6989586621680278784 c6989586621680278785 d6989586621680278786 :: TyFun (a6989586621680278783, b6989586621680278784, c6989586621680278785, d6989586621680278786) (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621680279170ShowlSym2 x6989586621680279167 showx6989586621680279166 :: TyFun k3 (TyFun Symbol (TyFun [k1] Symbol -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Lambda_6989586621680279099Sym1 ss6989586621680279097 :: TyFun k2 (TyFun (Symbol ~> c6989586621679736129) (TyFun (a6989586621679736130 ~> Symbol) (TyFun a6989586621679736130 c6989586621679736129 -> Type) -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680279351Sym0 :: TyFun Nat ((a6989586621680278803, b6989586621680278804, c6989586621680278805, d6989586621680278806, e6989586621680278807, f6989586621680278808) ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621680279170ShowlSym3 xs6989586621680279168 x6989586621680279167 showx6989586621680279166 :: TyFun Symbol (TyFun [k1] Symbol -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680279312Sym2 a6989586621680279310 a6989586621680279309 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680279331Sym1 a6989586621680279328 a6989586621680278792 b6989586621680278793 c6989586621680278794 d6989586621680278795 e6989586621680278796 :: TyFun (a6989586621680278792, b6989586621680278793, c6989586621680278794, d6989586621680278795, e6989586621680278796) (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Lambda_6989586621680279099Sym2 a_69895866216802790956989586621680279098 ss6989586621680279097 :: TyFun (Symbol ~> c6989586621679736129) (TyFun (a6989586621679736130 ~> Symbol) (TyFun a6989586621679736130 c6989586621679736129 -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621680279170ShowlSym4 s6989586621680279169 xs6989586621680279168 x6989586621680279167 showx6989586621680279166 :: TyFun [k1] Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680279372Sym0 :: TyFun Nat ((a6989586621680278816, b6989586621680278817, c6989586621680278818, d6989586621680278819, e6989586621680278820, f6989586621680278821, g6989586621680278822) ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680279331Sym2 a6989586621680279329 a6989586621680279328 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680279351Sym1 a6989586621680279348 a6989586621680278803 b6989586621680278804 c6989586621680278805 d6989586621680278806 e6989586621680278807 f6989586621680278808 :: TyFun (a6989586621680278803, b6989586621680278804, c6989586621680278805, d6989586621680278806, e6989586621680278807, f6989586621680278808) (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Lambda_6989586621680279099Sym3 t6989586621680279103 a_69895866216802790956989586621680279098 ss6989586621680279097 :: TyFun (a6989586621679736130 ~> Symbol) (TyFun a6989586621679736130 c6989586621679736129 -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680279351Sym2 a6989586621680279349 a6989586621680279348 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680279372Sym1 a6989586621680279369 a6989586621680278816 b6989586621680278817 c6989586621680278818 d6989586621680278819 e6989586621680278820 f6989586621680278821 g6989586621680278822 :: TyFun (a6989586621680278816, b6989586621680278817, c6989586621680278818, d6989586621680278819, e6989586621680278820, f6989586621680278821, g6989586621680278822) (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680279372Sym2 a6989586621680279370 a6989586621680279369 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
TypeHasDoc a => GProductHasDoc (S1 ('MetaSel ('Nothing :: Maybe Symbol) _1 _2 _3) (Rec0 a)) Source # | |
Defined in Michelson.Typed.Haskell.Doc gProductDocHaskellRep :: [(Text, Text)] -> [FieldRep SomeTypeWithDoc] | |
(TypeHasDoc a, KnownSymbol field) => GProductHasDoc (S1 ('MetaSel ('Just field) _1 _2 _3) (Rec0 a)) Source # | |
Defined in Michelson.Typed.Haskell.Doc gProductDocHaskellRep :: [(Text, Text)] -> [FieldRep SomeTypeWithDoc] | |
data Sing (s :: Symbol) | |
Defined in GHC.Generics | |
type DemoteRep Symbol | |
Defined in GHC.Generics | |
type MEmpty | |
Defined in Fcf.Class.Monoid type MEmpty = "" | |
type Mempty | |
Defined in Data.Singletons.Prelude.Monoid | |
type Sing | |
Defined in Data.Singletons.TypeLits.Internal | |
type Demote Symbol | |
Defined in Data.Singletons.TypeLits.Internal | |
type FromString a | |
Defined in Data.Singletons.Prelude.IsString type FromString a = a | |
type Mconcat (arg0 :: [Symbol]) | |
type Show_ (arg0 :: Symbol) | |
type Sconcat (arg0 :: NonEmpty Symbol) | |
type (x :: Symbol) <> (y :: Symbol) | With base >= 4.10.0.0. |
Defined in Fcf.Class.Monoid | |
type Mappend (arg1 :: Symbol) (arg2 :: Symbol) | |
type ShowList (arg1 :: [Symbol]) arg2 | |
type (a :: Symbol) <> (b :: Symbol) | |
Defined in Data.Singletons.Prelude.Semigroup.Internal | |
type Min (arg1 :: Symbol) (arg2 :: Symbol) | |
type Max (arg1 :: Symbol) (arg2 :: Symbol) | |
type (arg1 :: Symbol) >= (arg2 :: Symbol) | |
type (arg1 :: Symbol) > (arg2 :: Symbol) | |
type (arg1 :: Symbol) <= (arg2 :: Symbol) | |
type (arg1 :: Symbol) < (arg2 :: Symbol) | |
type Compare (a :: Symbol) (b :: Symbol) | |
Defined in Data.Singletons.TypeLits.Internal | |
type (x :: Symbol) /= (y :: Symbol) | |
type (x :: Symbol) == (y :: Symbol) | |
Defined in Data.Singletons.TypeLits.Internal | |
type ShowsPrec a1 (a2 :: Symbol) a3 | |
type Apply KnownSymbolSym0 (n6989586621679675475 :: Symbol) | |
Defined in Data.Singletons.TypeLits | |
type Apply ShowCommaSpaceSym0 (a6989586621680279111 :: Symbol) | |
Defined in Data.Singletons.Prelude.Show type Apply ShowCommaSpaceSym0 (a6989586621680279111 :: Symbol) = ShowCommaSpace a6989586621680279111 | |
type Apply ShowSpaceSym0 (a6989586621680279116 :: Symbol) | |
Defined in Data.Singletons.Prelude.Show | |
type Apply (ShowStringSym1 a6989586621680279143 :: TyFun Symbol Symbol -> Type) (a6989586621680279144 :: Symbol) | |
Defined in Data.Singletons.Prelude.Show type Apply (ShowStringSym1 a6989586621680279143 :: TyFun Symbol Symbol -> Type) (a6989586621680279144 :: Symbol) = ShowString a6989586621680279143 a6989586621680279144 | |
type Apply (ShowCharSym1 a6989586621680279153 :: TyFun Symbol Symbol -> Type) (a6989586621680279154 :: Symbol) | |
Defined in Data.Singletons.Prelude.Show | |
type Apply (Show_tupleSym1 a6989586621680279091 :: TyFun Symbol Symbol -> Type) (a6989586621680279092 :: Symbol) | |
type Apply (ShowsNatSym1 a6989586621680296569 :: TyFun Symbol Symbol -> Type) (a6989586621680296570 :: Symbol) | |
type Apply (FromStringSym0 :: TyFun Symbol k2 -> Type) (arg6989586621680971229 :: Symbol) | |
Defined in Data.Singletons.Prelude.IsString type Apply (FromStringSym0 :: TyFun Symbol k2 -> Type) (arg6989586621680971229 :: Symbol) = FromString arg6989586621680971229 :: k2 | |
type Apply (Show__6989586621680279216Sym0 :: TyFun a Symbol -> Type) (a6989586621680279215 :: a) | |
Defined in Data.Singletons.Prelude.Show | |
type Apply (Show_Sym0 :: TyFun a Symbol -> Type) (arg6989586621680279193 :: a) | |
type Apply (ShowParenSym2 a6989586621680279126 a6989586621680279125 :: TyFun Symbol Symbol -> Type) (a6989586621680279127 :: Symbol) | |
Defined in Data.Singletons.Prelude.Show | |
type Apply (ShowsSym1 a6989586621680279179 :: TyFun Symbol Symbol -> Type) (a6989586621680279180 :: Symbol) | |
type Apply (ShowListSym1 arg6989586621680279195 :: TyFun Symbol Symbol -> Type) (arg6989586621680279196 :: Symbol) | |
Defined in Data.Singletons.Prelude.Show | |
type Apply (ShowsPrec_6989586621680716360Sym2 a6989586621680716358 a6989586621680716357 :: TyFun Symbol Symbol -> Type) (a6989586621680716359 :: Symbol) | |
type Apply (ShowsPrec_6989586621680716388Sym2 a6989586621680716386 a6989586621680716385 :: TyFun Symbol Symbol -> Type) (a6989586621680716387 :: Symbol) | |
type Apply (Lambda_6989586621680279119Sym1 a_69895866216802791146989586621680279118 :: TyFun Symbol Symbol -> Type) (t6989586621680279122 :: Symbol) | |
type Apply (ShowList_6989586621680279224Sym1 a6989586621680279222 :: TyFun Symbol Symbol -> Type) (a6989586621680279223 :: Symbol) | |
type Apply (ShowsPrec_6989586621680279257Sym2 a6989586621680279255 a6989586621680279254 :: TyFun Symbol Symbol -> Type) (a6989586621680279256 :: Symbol) | |
type Apply (ShowsPrec_6989586621680297071Sym2 a6989586621680297069 a6989586621680297068 :: TyFun Symbol Symbol -> Type) (a6989586621680297070 :: Symbol) | |
type Apply (ShowsPrec_6989586621680297229Sym2 a6989586621680297227 a6989586621680297226 :: TyFun Symbol Symbol -> Type) (a6989586621680297228 :: Symbol) | |
type Apply (ShowsPrec_6989586621680297253Sym2 a6989586621680297251 a6989586621680297250 :: TyFun Symbol Symbol -> Type) (a6989586621680297252 :: Symbol) | |
type Apply (ShowsPrec_6989586621680297283Sym2 a6989586621680297281 a6989586621680297280 :: TyFun Symbol Symbol -> Type) (a6989586621680297282 :: Symbol) | |
type Apply (ShowListWithSym2 a6989586621680279160 a6989586621680279159 :: TyFun Symbol Symbol -> Type) (a6989586621680279161 :: Symbol) | |
Defined in Data.Singletons.Prelude.Show type Apply (ShowListWithSym2 a6989586621680279160 a6989586621680279159 :: TyFun Symbol Symbol -> Type) (a6989586621680279161 :: Symbol) = ShowListWith a6989586621680279160 a6989586621680279159 a6989586621680279161 | |
type Apply (ShowsPrecSym2 arg6989586621680279188 arg6989586621680279187 :: TyFun Symbol Symbol -> Type) (arg6989586621680279189 :: Symbol) | |
Defined in Data.Singletons.Prelude.Show | |
type Apply (ShowsPrec_6989586621680716301Sym2 a6989586621680716299 a6989586621680716298 :: TyFun Symbol Symbol -> Type) (a6989586621680716300 :: Symbol) | |
type Apply (ShowsPrec_6989586621680716332Sym2 a6989586621680716330 a6989586621680716329 :: TyFun Symbol Symbol -> Type) (a6989586621680716331 :: Symbol) | |
type Apply (ShowsPrec_6989586621680716419Sym2 a6989586621680716417 a6989586621680716416 :: TyFun Symbol Symbol -> Type) (a6989586621680716418 :: Symbol) | |
type Apply (ShowsPrec_6989586621680716450Sym2 a6989586621680716448 a6989586621680716447 :: TyFun Symbol Symbol -> Type) (a6989586621680716449 :: Symbol) | |
type Apply (ShowsPrec_6989586621680716481Sym2 a6989586621680716479 a6989586621680716478 :: TyFun Symbol Symbol -> Type) (a6989586621680716480 :: Symbol) | |
type Apply (ShowsPrec_6989586621680716512Sym2 a6989586621680716510 a6989586621680716509 :: TyFun Symbol Symbol -> Type) (a6989586621680716511 :: Symbol) | |
type Apply (ShowsPrec_6989586621680716543Sym2 a6989586621680716541 a6989586621680716540 :: TyFun Symbol Symbol -> Type) (a6989586621680716542 :: Symbol) | |
type Apply (ShowsPrec_6989586621680716574Sym2 a6989586621680716572 a6989586621680716571 :: TyFun Symbol Symbol -> Type) (a6989586621680716573 :: Symbol) | |
type Apply (ShowsPrec_6989586621680716605Sym2 a6989586621680716603 a6989586621680716602 :: TyFun Symbol Symbol -> Type) (a6989586621680716604 :: Symbol) | |
type Apply (ShowsPrec_6989586621680570718Sym2 a6989586621680570716 a6989586621680570715 :: TyFun Symbol Symbol -> Type) (a6989586621680570717 :: Symbol) | |
type Apply (ShowsPrec_6989586621680330696Sym2 a6989586621680330694 a6989586621680330693 :: TyFun Symbol Symbol -> Type) (a6989586621680330695 :: Symbol) | |
type Apply (ShowsPrec_6989586621680330727Sym2 a6989586621680330725 a6989586621680330724 :: TyFun Symbol Symbol -> Type) (a6989586621680330726 :: Symbol) | |
type Apply (ShowsPrec_6989586621680279202Sym2 a6989586621680279200 a6989586621680279199 :: TyFun Symbol Symbol -> Type) (a6989586621680279201 :: Symbol) | |
type Apply (ShowsPrec_6989586621680279237Sym2 a6989586621680279235 a6989586621680279234 :: TyFun Symbol Symbol -> Type) (a6989586621680279236 :: Symbol) | |
type Apply (ShowsPrec_6989586621680297105Sym2 a6989586621680297103 a6989586621680297102 :: TyFun Symbol Symbol -> Type) (a6989586621680297104 :: Symbol) | |
type Apply (ShowsPrec_6989586621680297203Sym2 a6989586621680297201 a6989586621680297200 :: TyFun Symbol Symbol -> Type) (a6989586621680297202 :: Symbol) | |
type Apply (ShowsPrec_6989586621680733534Sym2 a6989586621680733532 a6989586621680733531 :: TyFun Symbol Symbol -> Type) (a6989586621680733533 :: Symbol) | |
type Apply (ShowsPrec_6989586621680279277Sym2 a6989586621680279275 a6989586621680279274 :: TyFun Symbol Symbol -> Type) (a6989586621680279276 :: Symbol) | |
type Apply (ShowsPrec_6989586621680297161Sym2 a6989586621680297159 a6989586621680297158 :: TyFun Symbol Symbol -> Type) (a6989586621680297160 :: Symbol) | |
type Apply (ShowsPrec_6989586621680598687Sym2 a6989586621680598685 a6989586621680598684 :: TyFun Symbol Symbol -> Type) (a6989586621680598686 :: Symbol) | |
type Apply (ShowsPrec_6989586621680279294Sym2 a6989586621680279292 a6989586621680279291 :: TyFun Symbol Symbol -> Type) (a6989586621680279293 :: Symbol) | |
type Apply (ShowsPrec_6989586621680279312Sym2 a6989586621680279310 a6989586621680279309 :: TyFun Symbol Symbol -> Type) (a6989586621680279311 :: Symbol) | |
type Apply (ShowsPrec_6989586621680279331Sym2 a6989586621680279329 a6989586621680279328 :: TyFun Symbol Symbol -> Type) (a6989586621680279330 :: Symbol) | |
type Apply (ShowsPrec_6989586621680279351Sym2 a6989586621680279349 a6989586621680279348 :: TyFun Symbol Symbol -> Type) (a6989586621680279350 :: Symbol) | |
type Apply (ShowsPrec_6989586621680279372Sym2 a6989586621680279370 a6989586621680279369 :: TyFun Symbol Symbol -> Type) (a6989586621680279371 :: Symbol) | |
type Apply (FromString_6989586621680971239Sym0 :: TyFun Symbol (Identity a6989586621680971208) -> Type) (a6989586621680971238 :: Symbol) | |
type Apply ShowParenSym0 (a6989586621680279125 :: Bool) | |
Defined in Data.Singletons.Prelude.Show | |
type Apply ShowsPrec_6989586621680297229Sym0 (a6989586621680297226 :: Nat) | |
Defined in Data.Singletons.Prelude.Show | |
type Apply ShowsPrec_6989586621680297253Sym0 (a6989586621680297250 :: Nat) | |
Defined in Data.Singletons.Prelude.Show | |
type Apply ShowsNatSym0 (a6989586621680296569 :: Nat) | |
Defined in Data.Singletons.Prelude.Show | |
type Apply ShowsPrec_6989586621680279257Sym0 (a6989586621680279254 :: Nat) | |
Defined in Data.Singletons.Prelude.Show | |
type Apply ShowsPrec_6989586621680297071Sym0 (a6989586621680297068 :: Nat) | |
Defined in Data.Singletons.Prelude.Show | |
type Apply ShowsPrec_6989586621680297283Sym0 (a6989586621680297280 :: Nat) | |
Defined in Data.Singletons.Prelude.Show | |
type Apply ShowsPrec_6989586621680716360Sym0 (a6989586621680716357 :: Nat) | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Apply ShowsPrec_6989586621680716388Sym0 (a6989586621680716385 :: Nat) | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Apply ShowStringSym0 (a6989586621680279143 :: Symbol) | |
Defined in Data.Singletons.Prelude.Show | |
type Apply ShowCharSym0 (a6989586621680279153 :: Symbol) | |
Defined in Data.Singletons.Prelude.Show | |
type Apply (ShowsPrec_6989586621680297229Sym1 a6989586621680297226 :: TyFun Bool (Symbol ~> Symbol) -> Type) (a6989586621680297227 :: Bool) | |
type Apply (ShowsPrec_6989586621680297253Sym1 a6989586621680297250 :: TyFun Ordering (Symbol ~> Symbol) -> Type) (a6989586621680297251 :: Ordering) | |
type Apply (ShowsPrec_6989586621680279237Sym0 :: TyFun Nat ([a6989586621680278767] ~> (Symbol ~> Symbol)) -> Type) (a6989586621680279234 :: Nat) | |
Defined in Data.Singletons.Prelude.Show | |
type Apply (ShowsPrec_6989586621680297105Sym0 :: TyFun Nat (Maybe a3530822107858468865 ~> (Symbol ~> Symbol)) -> Type) (a6989586621680297102 :: Nat) | |
Defined in Data.Singletons.Prelude.Show | |
type Apply (ShowsPrec_6989586621680279202Sym0 :: TyFun Nat (a6989586621680278749 ~> (Symbol ~> Symbol)) -> Type) (a6989586621680279199 :: Nat) | |
Defined in Data.Singletons.Prelude.Show | |
type Apply (ShowsPrecSym0 :: TyFun Nat (a6989586621680278749 ~> (Symbol ~> Symbol)) -> Type) (arg6989586621680279187 :: Nat) | |
type Apply (ShowsPrec_6989586621680716481Sym0 :: TyFun Nat (Min a6989586621679058450 ~> (Symbol ~> Symbol)) -> Type) (a6989586621680716478 :: Nat) | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Apply (ShowsPrec_6989586621680716512Sym0 :: TyFun Nat (Max a6989586621679058455 ~> (Symbol ~> Symbol)) -> Type) (a6989586621680716509 :: Nat) | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Apply (ShowsPrec_6989586621680716543Sym0 :: TyFun Nat (First a6989586621679058465 ~> (Symbol ~> Symbol)) -> Type) (a6989586621680716540 :: Nat) | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Apply (ShowsPrec_6989586621680716574Sym0 :: TyFun Nat (Last a6989586621679058460 ~> (Symbol ~> Symbol)) -> Type) (a6989586621680716571 :: Nat) | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Apply (ShowsPrec_6989586621680716605Sym0 :: TyFun Nat (WrappedMonoid m6989586621679086385 ~> (Symbol ~> Symbol)) -> Type) (a6989586621680716602 :: Nat) | |
Defined in Data.Singletons.Prelude.Semigroup type Apply (ShowsPrec_6989586621680716605Sym0 :: TyFun Nat (WrappedMonoid m6989586621679086385 ~> (Symbol ~> Symbol)) -> Type) (a6989586621680716602 :: Nat) = ShowsPrec_6989586621680716605Sym1 a6989586621680716602 m6989586621679086385 :: TyFun (WrappedMonoid m6989586621679086385) (Symbol ~> Symbol) -> Type | |
type Apply (ShowsPrec_6989586621680716301Sym0 :: TyFun Nat (Option a6989586621679058445 ~> (Symbol ~> Symbol)) -> Type) (a6989586621680716298 :: Nat) | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Apply (ShowsPrec_6989586621680570718Sym0 :: TyFun Nat (Identity a6989586621680570499 ~> (Symbol ~> Symbol)) -> Type) (a6989586621680570715 :: Nat) | |
Defined in Data.Singletons.Prelude.Identity | |
type Apply (ShowsPrec_6989586621680330696Sym0 :: TyFun Nat (First a6989586621679083079 ~> (Symbol ~> Symbol)) -> Type) (a6989586621680330693 :: Nat) | |
Defined in Data.Singletons.Prelude.Monoid | |
type Apply (ShowsPrec_6989586621680330727Sym0 :: TyFun Nat (Last a6989586621679083072 ~> (Symbol ~> Symbol)) -> Type) (a6989586621680330724 :: Nat) | |
Defined in Data.Singletons.Prelude.Monoid | |
type Apply (ShowsPrec_6989586621680716332Sym0 :: TyFun Nat (Dual a6989586621679083138 ~> (Symbol ~> Symbol)) -> Type) (a6989586621680716329 :: Nat) | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Apply (ShowsPrec_6989586621680716419Sym0 :: TyFun Nat (Sum a6989586621679083115 ~> (Symbol ~> Symbol)) -> Type) (a6989586621680716416 :: Nat) | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Apply (ShowsPrec_6989586621680716450Sym0 :: TyFun Nat (Product a6989586621679083123 ~> (Symbol ~> Symbol)) -> Type) (a6989586621680716447 :: Nat) | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Apply (ShowsPrec_6989586621680297203Sym0 :: TyFun Nat (NonEmpty a6989586621679058531 ~> (Symbol ~> Symbol)) -> Type) (a6989586621680297200 :: Nat) | |
Defined in Data.Singletons.Prelude.Show | |
type Apply (ShowsPrec_6989586621680279257Sym1 a6989586621680279254 :: TyFun Symbol (Symbol ~> Symbol) -> Type) (a6989586621680279255 :: Symbol) | |
type Apply (ShowsPrec_6989586621680297071Sym1 a6989586621680297068 :: TyFun () (Symbol ~> Symbol) -> Type) (a6989586621680297069 :: ()) | |
type Apply (Lambda_6989586621680279119Sym0 :: TyFun k (TyFun Symbol Symbol -> Type) -> Type) (a_69895866216802791146989586621680279118 :: k) | |
type Apply (ShowsSym0 :: TyFun a6989586621680278734 (Symbol ~> Symbol) -> Type) (a6989586621680279179 :: a6989586621680278734) | |
type Apply (ShowsPrec_6989586621680297283Sym1 a6989586621680297280 :: TyFun Void (Symbol ~> Symbol) -> Type) (a6989586621680297281 :: Void) | |
type Apply (ShowsPrec_6989586621680716360Sym1 a6989586621680716357 :: TyFun All (Symbol ~> Symbol) -> Type) (a6989586621680716358 :: All) | |
type Apply (ShowsPrec_6989586621680716388Sym1 a6989586621680716385 :: TyFun Any (Symbol ~> Symbol) -> Type) (a6989586621680716386 :: Any) | |
type Apply (ShowsPrec_6989586621680297161Sym0 :: TyFun Nat (Either a6989586621679086693 b6989586621679086694 ~> (Symbol ~> Symbol)) -> Type) (a6989586621680297158 :: Nat) | |
Defined in Data.Singletons.Prelude.Show type Apply (ShowsPrec_6989586621680297161Sym0 :: TyFun Nat (Either a6989586621679086693 b6989586621679086694 ~> (Symbol ~> Symbol)) -> Type) (a6989586621680297158 :: Nat) = ShowsPrec_6989586621680297161Sym1 a6989586621680297158 a6989586621679086693 b6989586621679086694 :: TyFun (Either a6989586621679086693 b6989586621679086694) (Symbol ~> Symbol) -> Type | |
type Apply (ShowsPrec_6989586621680279277Sym0 :: TyFun Nat ((a6989586621680278771, b6989586621680278772) ~> (Symbol ~> Symbol)) -> Type) (a6989586621680279274 :: Nat) | |
Defined in Data.Singletons.Prelude.Show type Apply (ShowsPrec_6989586621680279277Sym0 :: TyFun Nat ((a6989586621680278771, b6989586621680278772) ~> (Symbol ~> Symbol)) -> Type) (a6989586621680279274 :: Nat) = ShowsPrec_6989586621680279277Sym1 a6989586621680279274 a6989586621680278771 b6989586621680278772 :: TyFun (a6989586621680278771, b6989586621680278772) (Symbol ~> Symbol) -> Type | |
type Apply (ShowsPrec_6989586621680733534Sym0 :: TyFun Nat (Arg a6989586621680732251 b6989586621680732252 ~> (Symbol ~> Symbol)) -> Type) (a6989586621680733531 :: Nat) | |
Defined in Data.Singletons.Prelude.Semigroup type Apply (ShowsPrec_6989586621680733534Sym0 :: TyFun Nat (Arg a6989586621680732251 b6989586621680732252 ~> (Symbol ~> Symbol)) -> Type) (a6989586621680733531 :: Nat) = ShowsPrec_6989586621680733534Sym1 a6989586621680733531 a6989586621680732251 b6989586621680732252 :: TyFun (Arg a6989586621680732251 b6989586621680732252) (Symbol ~> Symbol) -> Type | |
type Apply (ShowsPrec_6989586621680279202Sym1 a6989586621680279199 a6989586621680278749 :: TyFun a6989586621680278749 (Symbol ~> Symbol) -> Type) (a6989586621680279200 :: a6989586621680278749) | |
Defined in Data.Singletons.Prelude.Show | |
type Apply (ShowsPrecSym1 arg6989586621680279187 a6989586621680278749 :: TyFun a6989586621680278749 (Symbol ~> Symbol) -> Type) (arg6989586621680279188 :: a6989586621680278749) | |
Defined in Data.Singletons.Prelude.Show type Apply (ShowsPrecSym1 arg6989586621680279187 a6989586621680278749 :: TyFun a6989586621680278749 (Symbol ~> Symbol) -> Type) (arg6989586621680279188 :: a6989586621680278749) = ShowsPrecSym2 arg6989586621680279187 arg6989586621680279188 | |
type Apply (Let6989586621680059392GoSym0 :: TyFun k1 (TyFun k2 (TyFun [Symbol] Symbol -> Type) -> Type) -> Type) (w6989586621680059390 :: k1) | |
type Apply (ShowsPrec_6989586621680279294Sym0 :: TyFun Nat ((a6989586621680278776, b6989586621680278777, c6989586621680278778) ~> (Symbol ~> Symbol)) -> Type) (a6989586621680279291 :: Nat) | |
Defined in Data.Singletons.Prelude.Show type Apply (ShowsPrec_6989586621680279294Sym0 :: TyFun Nat ((a6989586621680278776, b6989586621680278777, c6989586621680278778) ~> (Symbol ~> Symbol)) -> Type) (a6989586621680279291 :: Nat) = ShowsPrec_6989586621680279294Sym1 a6989586621680279291 a6989586621680278776 b6989586621680278777 c6989586621680278778 :: TyFun (a6989586621680278776, b6989586621680278777, c6989586621680278778) (Symbol ~> Symbol) -> Type | |
type Apply (ShowsPrec_6989586621680598687Sym0 :: TyFun Nat (Const a6989586621680597830 b6989586621680597831 ~> (Symbol ~> Symbol)) -> Type) (a6989586621680598684 :: Nat) | |
Defined in Data.Singletons.Prelude.Const type Apply (ShowsPrec_6989586621680598687Sym0 :: TyFun Nat (Const a6989586621680597830 b6989586621680597831 ~> (Symbol ~> Symbol)) -> Type) (a6989586621680598684 :: Nat) = ShowsPrec_6989586621680598687Sym1 a6989586621680598684 a6989586621680597830 b6989586621680597831 :: TyFun (Const a6989586621680597830 b6989586621680597831) (Symbol ~> Symbol) -> Type | |
type Apply (Let6989586621680059392GoSym1 w6989586621680059390 :: TyFun k2 (TyFun [Symbol] Symbol -> Type) -> Type) (ws6989586621680059391 :: k2) | |
type Apply (ShowsPrec_6989586621680279312Sym0 :: TyFun Nat ((a6989586621680278783, b6989586621680278784, c6989586621680278785, d6989586621680278786) ~> (Symbol ~> Symbol)) -> Type) (a6989586621680279309 :: Nat) | |
Defined in Data.Singletons.Prelude.Show type Apply (ShowsPrec_6989586621680279312Sym0 :: TyFun Nat ((a6989586621680278783, b6989586621680278784, c6989586621680278785, d6989586621680278786) ~> (Symbol ~> Symbol)) -> Type) (a6989586621680279309 :: Nat) = ShowsPrec_6989586621680279312Sym1 a6989586621680279309 a6989586621680278783 b6989586621680278784 c6989586621680278785 d6989586621680278786 :: TyFun (a6989586621680278783, b6989586621680278784, c6989586621680278785, d6989586621680278786) (Symbol ~> Symbol) -> Type | |
type Apply (Let6989586621680279170ShowlSym1 showx6989586621680279166 :: TyFun k2 (TyFun k3 (TyFun Symbol (TyFun [k1] Symbol -> Type) -> Type) -> Type) -> Type) (x6989586621680279167 :: k2) | |
Defined in Data.Singletons.Prelude.Show type Apply (Let6989586621680279170ShowlSym1 showx6989586621680279166 :: TyFun k2 (TyFun k3 (TyFun Symbol (TyFun [k1] Symbol -> Type) -> Type) -> Type) -> Type) (x6989586621680279167 :: k2) = Let6989586621680279170ShowlSym2 showx6989586621680279166 x6989586621680279167 :: TyFun k3 (TyFun Symbol (TyFun [k1] Symbol -> Type) -> Type) -> Type | |
type Apply (Lambda_6989586621680279099Sym0 :: TyFun k1 (TyFun k2 (TyFun (Symbol ~> c6989586621679736129) (TyFun (a6989586621679736130 ~> Symbol) (TyFun a6989586621679736130 c6989586621679736129 -> Type) -> Type) -> Type) -> Type) -> Type) (ss6989586621680279097 :: k1) | |
Defined in Data.Singletons.Prelude.Show type Apply (Lambda_6989586621680279099Sym0 :: TyFun k1 (TyFun k2 (TyFun (Symbol ~> c6989586621679736129) (TyFun (a6989586621679736130 ~> Symbol) (TyFun a6989586621679736130 c6989586621679736129 -> Type) -> Type) -> Type) -> Type) -> Type) (ss6989586621680279097 :: k1) = Lambda_6989586621680279099Sym1 ss6989586621680279097 :: TyFun k2 (TyFun (Symbol ~> c6989586621679736129) (TyFun (a6989586621679736130 ~> Symbol) (TyFun a6989586621679736130 c6989586621679736129 -> Type) -> Type) -> Type) -> Type | |
type Apply (ShowsPrec_6989586621680279331Sym0 :: TyFun Nat ((a6989586621680278792, b6989586621680278793, c6989586621680278794, d6989586621680278795, e6989586621680278796) ~> (Symbol ~> Symbol)) -> Type) (a6989586621680279328 :: Nat) | |
Defined in Data.Singletons.Prelude.Show type Apply (ShowsPrec_6989586621680279331Sym0 :: TyFun Nat ((a6989586621680278792, b6989586621680278793, c6989586621680278794, d6989586621680278795, e6989586621680278796) ~> (Symbol ~> Symbol)) -> Type) (a6989586621680279328 :: Nat) = ShowsPrec_6989586621680279331Sym1 a6989586621680279328 a6989586621680278792 b6989586621680278793 c6989586621680278794 d6989586621680278795 e6989586621680278796 :: TyFun (a6989586621680278792, b6989586621680278793, c6989586621680278794, d6989586621680278795, e6989586621680278796) (Symbol ~> Symbol) -> Type | |
type Apply (Let6989586621680279170ShowlSym2 x6989586621680279167 showx6989586621680279166 :: TyFun k3 (TyFun Symbol (TyFun [k1] Symbol -> Type) -> Type) -> Type) (xs6989586621680279168 :: k3) | |
Defined in Data.Singletons.Prelude.Show | |
type Apply (Lambda_6989586621680279099Sym1 ss6989586621680279097 :: TyFun k2 (TyFun (Symbol ~> c6989586621679736129) (TyFun (a6989586621679736130 ~> Symbol) (TyFun a6989586621679736130 c6989586621679736129 -> Type) -> Type) -> Type) -> Type) (a_69895866216802790956989586621680279098 :: k2) | |
Defined in Data.Singletons.Prelude.Show type Apply (Lambda_6989586621680279099Sym1 ss6989586621680279097 :: TyFun k2 (TyFun (Symbol ~> c6989586621679736129) (TyFun (a6989586621679736130 ~> Symbol) (TyFun a6989586621679736130 c6989586621679736129 -> Type) -> Type) -> Type) -> Type) (a_69895866216802790956989586621680279098 :: k2) = Lambda_6989586621680279099Sym2 ss6989586621680279097 a_69895866216802790956989586621680279098 :: TyFun (Symbol ~> c6989586621679736129) (TyFun (a6989586621679736130 ~> Symbol) (TyFun a6989586621679736130 c6989586621679736129 -> Type) -> Type) -> Type | |
type Apply (ShowsPrec_6989586621680279351Sym0 :: TyFun Nat ((a6989586621680278803, b6989586621680278804, c6989586621680278805, d6989586621680278806, e6989586621680278807, f6989586621680278808) ~> (Symbol ~> Symbol)) -> Type) (a6989586621680279348 :: Nat) | |
Defined in Data.Singletons.Prelude.Show type Apply (ShowsPrec_6989586621680279351Sym0 :: TyFun Nat ((a6989586621680278803, b6989586621680278804, c6989586621680278805, d6989586621680278806, e6989586621680278807, f6989586621680278808) ~> (Symbol ~> Symbol)) -> Type) (a6989586621680279348 :: Nat) = ShowsPrec_6989586621680279351Sym1 a6989586621680279348 a6989586621680278803 b6989586621680278804 c6989586621680278805 d6989586621680278806 e6989586621680278807 f6989586621680278808 :: TyFun (a6989586621680278803, b6989586621680278804, c6989586621680278805, d6989586621680278806, e6989586621680278807, f6989586621680278808) (Symbol ~> Symbol) -> Type | |
type Apply (Let6989586621680279170ShowlSym3 xs6989586621680279168 x6989586621680279167 showx6989586621680279166 :: TyFun Symbol (TyFun [k1] Symbol -> Type) -> Type) (s6989586621680279169 :: Symbol) | |
Defined in Data.Singletons.Prelude.Show type Apply (Let6989586621680279170ShowlSym3 xs6989586621680279168 x6989586621680279167 showx6989586621680279166 :: TyFun Symbol (TyFun [k1] Symbol -> Type) -> Type) (s6989586621680279169 :: Symbol) = Let6989586621680279170ShowlSym4 xs6989586621680279168 x6989586621680279167 showx6989586621680279166 s6989586621680279169 | |
type Apply (ShowsPrec_6989586621680279372Sym0 :: TyFun Nat ((a6989586621680278816, b6989586621680278817, c6989586621680278818, d6989586621680278819, e6989586621680278820, f6989586621680278821, g6989586621680278822) ~> (Symbol ~> Symbol)) -> Type) (a6989586621680279369 :: Nat) | |
Defined in Data.Singletons.Prelude.Show type Apply (ShowsPrec_6989586621680279372Sym0 :: TyFun Nat ((a6989586621680278816, b6989586621680278817, c6989586621680278818, d6989586621680278819, e6989586621680278820, f6989586621680278821, g6989586621680278822) ~> (Symbol ~> Symbol)) -> Type) (a6989586621680279369 :: Nat) = ShowsPrec_6989586621680279372Sym1 a6989586621680279369 a6989586621680278816 b6989586621680278817 c6989586621680278818 d6989586621680278819 e6989586621680278820 f6989586621680278821 g6989586621680278822 :: TyFun (a6989586621680278816, b6989586621680278817, c6989586621680278818, d6989586621680278819, e6989586621680278820, f6989586621680278821, g6989586621680278822) (Symbol ~> Symbol) -> Type | |
type Apply (FromString_6989586621680971232Sym0 :: TyFun Symbol (Const a6989586621680971205 b6989586621680971206) -> Type) (a6989586621680971231 :: Symbol) | |
Defined in Data.Singletons.Prelude.IsString | |
type Rep (ElField '(s, a)) | |
type Apply UnwordsSym0 (a6989586621680059388 :: [Symbol]) | |
Defined in Data.Singletons.Prelude.List.Internal | |
type Apply UnlinesSym0 (a6989586621680059399 :: [Symbol]) | |
Defined in Data.Singletons.Prelude.List.Internal | |
type Apply (Let6989586621680059392GoSym2 ws6989586621680059391 w6989586621680059390 :: TyFun [Symbol] Symbol -> Type) (a6989586621680059393 :: [Symbol]) | |
type Apply (Let6989586621680279170ShowlSym4 s6989586621680279169 xs6989586621680279168 x6989586621680279167 showx6989586621680279166 :: TyFun [k1] Symbol -> Type) (a6989586621680279171 :: [k1]) | |
Defined in Data.Singletons.Prelude.Show type Apply (Let6989586621680279170ShowlSym4 s6989586621680279169 xs6989586621680279168 x6989586621680279167 showx6989586621680279166 :: TyFun [k1] Symbol -> Type) (a6989586621680279171 :: [k1]) = Let6989586621680279170Showl s6989586621680279169 xs6989586621680279168 x6989586621680279167 showx6989586621680279166 a6989586621680279171 | |
type Apply Show_tupleSym0 (a6989586621680279091 :: [Symbol ~> Symbol]) | |
Defined in Data.Singletons.Prelude.Show | |
type Apply (ShowList_6989586621680279224Sym0 :: TyFun [a6989586621680278749] (Symbol ~> Symbol) -> Type) (a6989586621680279222 :: [a6989586621680278749]) | |
type Apply (ShowListSym0 :: TyFun [a6989586621680278749] (Symbol ~> Symbol) -> Type) (arg6989586621680279195 :: [a6989586621680278749]) | |
Defined in Data.Singletons.Prelude.Show type Apply (ShowListSym0 :: TyFun [a6989586621680278749] (Symbol ~> Symbol) -> Type) (arg6989586621680279195 :: [a6989586621680278749]) = ShowListSym1 arg6989586621680279195 | |
type Apply (ShowListWithSym1 a6989586621680279159 :: TyFun [a6989586621680278733] (Symbol ~> Symbol) -> Type) (a6989586621680279160 :: [a6989586621680278733]) | |
Defined in Data.Singletons.Prelude.Show type Apply (ShowListWithSym1 a6989586621680279159 :: TyFun [a6989586621680278733] (Symbol ~> Symbol) -> Type) (a6989586621680279160 :: [a6989586621680278733]) = ShowListWithSym2 a6989586621680279159 a6989586621680279160 | |
type Apply (ShowsPrec_6989586621680279237Sym1 a6989586621680279234 a6989586621680278767 :: TyFun [a6989586621680278767] (Symbol ~> Symbol) -> Type) (a6989586621680279235 :: [a6989586621680278767]) | |
Defined in Data.Singletons.Prelude.Show | |
type Apply (ShowsPrec_6989586621680297105Sym1 a6989586621680297102 a3530822107858468865 :: TyFun (Maybe a3530822107858468865) (Symbol ~> Symbol) -> Type) (a6989586621680297103 :: Maybe a3530822107858468865) | |
Defined in Data.Singletons.Prelude.Show | |
type Apply (ShowsPrec_6989586621680716481Sym1 a6989586621680716478 a6989586621679058450 :: TyFun (Min a6989586621679058450) (Symbol ~> Symbol) -> Type) (a6989586621680716479 :: Min a6989586621679058450) | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Apply (ShowsPrec_6989586621680716512Sym1 a6989586621680716509 a6989586621679058455 :: TyFun (Max a6989586621679058455) (Symbol ~> Symbol) -> Type) (a6989586621680716510 :: Max a6989586621679058455) | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Apply (ShowsPrec_6989586621680716543Sym1 a6989586621680716540 a6989586621679058465 :: TyFun (First a6989586621679058465) (Symbol ~> Symbol) -> Type) (a6989586621680716541 :: First a6989586621679058465) | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Apply (ShowsPrec_6989586621680716574Sym1 a6989586621680716571 a6989586621679058460 :: TyFun (Last a6989586621679058460) (Symbol ~> Symbol) -> Type) (a6989586621680716572 :: Last a6989586621679058460) | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Apply (ShowsPrec_6989586621680716605Sym1 a6989586621680716602 m6989586621679086385 :: TyFun (WrappedMonoid m6989586621679086385) (Symbol ~> Symbol) -> Type) (a6989586621680716603 :: WrappedMonoid m6989586621679086385) | |
Defined in Data.Singletons.Prelude.Semigroup type Apply (ShowsPrec_6989586621680716605Sym1 a6989586621680716602 m6989586621679086385 :: TyFun (WrappedMonoid m6989586621679086385) (Symbol ~> Symbol) -> Type) (a6989586621680716603 :: WrappedMonoid m6989586621679086385) = ShowsPrec_6989586621680716605Sym2 a6989586621680716602 a6989586621680716603 | |
type Apply (ShowsPrec_6989586621680716301Sym1 a6989586621680716298 a6989586621679058445 :: TyFun (Option a6989586621679058445) (Symbol ~> Symbol) -> Type) (a6989586621680716299 :: Option a6989586621679058445) | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Apply (ShowsPrec_6989586621680570718Sym1 a6989586621680570715 a6989586621680570499 :: TyFun (Identity a6989586621680570499) (Symbol ~> Symbol) -> Type) (a6989586621680570716 :: Identity a6989586621680570499) | |
Defined in Data.Singletons.Prelude.Identity | |
type Apply (ShowsPrec_6989586621680330696Sym1 a6989586621680330693 a6989586621679083079 :: TyFun (First a6989586621679083079) (Symbol ~> Symbol) -> Type) (a6989586621680330694 :: First a6989586621679083079) | |
Defined in Data.Singletons.Prelude.Monoid | |
type Apply (ShowsPrec_6989586621680330727Sym1 a6989586621680330724 a6989586621679083072 :: TyFun (Last a6989586621679083072) (Symbol ~> Symbol) -> Type) (a6989586621680330725 :: Last a6989586621679083072) | |
Defined in Data.Singletons.Prelude.Monoid | |
type Apply (ShowsPrec_6989586621680716332Sym1 a6989586621680716329 a6989586621679083138 :: TyFun (Dual a6989586621679083138) (Symbol ~> Symbol) -> Type) (a6989586621680716330 :: Dual a6989586621679083138) | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Apply (ShowsPrec_6989586621680716419Sym1 a6989586621680716416 a6989586621679083115 :: TyFun (Sum a6989586621679083115) (Symbol ~> Symbol) -> Type) (a6989586621680716417 :: Sum a6989586621679083115) | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Apply (ShowsPrec_6989586621680716450Sym1 a6989586621680716447 a6989586621679083123 :: TyFun (Product a6989586621679083123) (Symbol ~> Symbol) -> Type) (a6989586621680716448 :: Product a6989586621679083123) | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Apply (ShowsPrec_6989586621680297203Sym1 a6989586621680297200 a6989586621679058531 :: TyFun (NonEmpty a6989586621679058531) (Symbol ~> Symbol) -> Type) (a6989586621680297201 :: NonEmpty a6989586621679058531) | |
Defined in Data.Singletons.Prelude.Show | |
type HKD ElField ('(s, a) :: (Symbol, Type)) | |
Defined in Data.Vinyl.XRec | |
type RecElemFCtx (SRec :: ((Symbol, Type) -> Type) -> [(Symbol, Type)] -> Type) (f :: (Symbol, Type) -> Type) | |
type RecElemFCtx (SRec2 ElField) (f :: (Symbol, Type) -> Type) | |
Defined in Data.Vinyl.SRec | |
type Apply (ShowParenSym1 a6989586621680279125 :: TyFun (Symbol ~> Symbol) (Symbol ~> Symbol) -> Type) (a6989586621680279126 :: Symbol ~> Symbol) | |
Defined in Data.Singletons.Prelude.Show | |
type Apply (ShowListWithSym0 :: TyFun (a6989586621680278733 ~> (Symbol ~> Symbol)) ([a6989586621680278733] ~> (Symbol ~> Symbol)) -> Type) (a6989586621680279159 :: a6989586621680278733 ~> (Symbol ~> Symbol)) | |
type RecSubsetFCtx (SRec :: ((Symbol, Type) -> Type) -> [(Symbol, Type)] -> Type) (f :: (Symbol, Type) -> Type) | |
type RecSubsetFCtx (SRec2 ElField) (f :: (Symbol, Type) -> Type) | |
Defined in Data.Vinyl.SRec | |
type Apply (ShowsPrec_6989586621680297161Sym1 a6989586621680297158 a6989586621679086693 b6989586621679086694 :: TyFun (Either a6989586621679086693 b6989586621679086694) (Symbol ~> Symbol) -> Type) (a6989586621680297159 :: Either a6989586621679086693 b6989586621679086694) | |
Defined in Data.Singletons.Prelude.Show type Apply (ShowsPrec_6989586621680297161Sym1 a6989586621680297158 a6989586621679086693 b6989586621679086694 :: TyFun (Either a6989586621679086693 b6989586621679086694) (Symbol ~> Symbol) -> Type) (a6989586621680297159 :: Either a6989586621679086693 b6989586621679086694) = ShowsPrec_6989586621680297161Sym2 a6989586621680297158 a6989586621680297159 | |
type Apply (ShowsPrec_6989586621680279277Sym1 a6989586621680279274 a6989586621680278771 b6989586621680278772 :: TyFun (a6989586621680278771, b6989586621680278772) (Symbol ~> Symbol) -> Type) (a6989586621680279275 :: (a6989586621680278771, b6989586621680278772)) | |
Defined in Data.Singletons.Prelude.Show type Apply (ShowsPrec_6989586621680279277Sym1 a6989586621680279274 a6989586621680278771 b6989586621680278772 :: TyFun (a6989586621680278771, b6989586621680278772) (Symbol ~> Symbol) -> Type) (a6989586621680279275 :: (a6989586621680278771, b6989586621680278772)) = ShowsPrec_6989586621680279277Sym2 a6989586621680279274 a6989586621680279275 | |
type Apply (ShowsPrec_6989586621680733534Sym1 a6989586621680733531 a6989586621680732251 b6989586621680732252 :: TyFun (Arg a6989586621680732251 b6989586621680732252) (Symbol ~> Symbol) -> Type) (a6989586621680733532 :: Arg a6989586621680732251 b6989586621680732252) | |
Defined in Data.Singletons.Prelude.Semigroup type Apply (ShowsPrec_6989586621680733534Sym1 a6989586621680733531 a6989586621680732251 b6989586621680732252 :: TyFun (Arg a6989586621680732251 b6989586621680732252) (Symbol ~> Symbol) -> Type) (a6989586621680733532 :: Arg a6989586621680732251 b6989586621680732252) = ShowsPrec_6989586621680733534Sym2 a6989586621680733531 a6989586621680733532 | |
type Apply (Let6989586621680279170ShowlSym0 :: TyFun (k1 ~> (Symbol ~> Symbol)) (TyFun k2 (TyFun k3 (TyFun Symbol (TyFun [k1] Symbol -> Type) -> Type) -> Type) -> Type) -> Type) (showx6989586621680279166 :: k1 ~> (Symbol ~> Symbol)) | |
Defined in Data.Singletons.Prelude.Show type Apply (Let6989586621680279170ShowlSym0 :: TyFun (k1 ~> (Symbol ~> Symbol)) (TyFun k2 (TyFun k3 (TyFun Symbol (TyFun [k1] Symbol -> Type) -> Type) -> Type) -> Type) -> Type) (showx6989586621680279166 :: k1 ~> (Symbol ~> Symbol)) = Let6989586621680279170ShowlSym1 showx6989586621680279166 :: TyFun k2 (TyFun k3 (TyFun Symbol (TyFun [k1] Symbol -> Type) -> Type) -> Type) -> Type | |
type Apply (Lambda_6989586621680279099Sym2 a_69895866216802790956989586621680279098 ss6989586621680279097 :: TyFun (Symbol ~> c6989586621679736129) (TyFun (a6989586621679736130 ~> Symbol) (TyFun a6989586621679736130 c6989586621679736129 -> Type) -> Type) -> Type) (t6989586621680279103 :: Symbol ~> c6989586621679736129) | |
Defined in Data.Singletons.Prelude.Show type Apply (Lambda_6989586621680279099Sym2 a_69895866216802790956989586621680279098 ss6989586621680279097 :: TyFun (Symbol ~> c6989586621679736129) (TyFun (a6989586621679736130 ~> Symbol) (TyFun a6989586621679736130 c6989586621679736129 -> Type) -> Type) -> Type) (t6989586621680279103 :: Symbol ~> c6989586621679736129) = Lambda_6989586621680279099Sym3 a_69895866216802790956989586621680279098 ss6989586621680279097 t6989586621680279103 :: TyFun (a6989586621679736130 ~> Symbol) (TyFun a6989586621679736130 c6989586621679736129 -> Type) -> Type | |
type Apply (Lambda_6989586621680279099Sym3 t6989586621680279103 a_69895866216802790956989586621680279098 ss6989586621680279097 :: TyFun (a6989586621679736130 ~> Symbol) (TyFun a6989586621679736130 c6989586621679736129 -> Type) -> Type) (t6989586621680279104 :: a6989586621679736130 ~> Symbol) | |
Defined in Data.Singletons.Prelude.Show type Apply (Lambda_6989586621680279099Sym3 t6989586621680279103 a_69895866216802790956989586621680279098 ss6989586621680279097 :: TyFun (a6989586621679736130 ~> Symbol) (TyFun a6989586621679736130 c6989586621679736129 -> Type) -> Type) (t6989586621680279104 :: a6989586621679736130 ~> Symbol) = Lambda_6989586621680279099 t6989586621680279103 a_69895866216802790956989586621680279098 ss6989586621680279097 t6989586621680279104 | |
type Apply (ShowsPrec_6989586621680279294Sym1 a6989586621680279291 a6989586621680278776 b6989586621680278777 c6989586621680278778 :: TyFun (a6989586621680278776, b6989586621680278777, c6989586621680278778) (Symbol ~> Symbol) -> Type) (a6989586621680279292 :: (a6989586621680278776, b6989586621680278777, c6989586621680278778)) | |
Defined in Data.Singletons.Prelude.Show type Apply (ShowsPrec_6989586621680279294Sym1 a6989586621680279291 a6989586621680278776 b6989586621680278777 c6989586621680278778 :: TyFun (a6989586621680278776, b6989586621680278777, c6989586621680278778) (Symbol ~> Symbol) -> Type) (a6989586621680279292 :: (a6989586621680278776, b6989586621680278777, c6989586621680278778)) = ShowsPrec_6989586621680279294Sym2 a6989586621680279291 a6989586621680279292 | |
type Apply (ShowsPrec_6989586621680598687Sym1 a6989586621680598684 a6989586621680597830 b6989586621680597831 :: TyFun (Const a6989586621680597830 b6989586621680597831) (Symbol ~> Symbol) -> Type) (a6989586621680598685 :: Const a6989586621680597830 b6989586621680597831) | |
Defined in Data.Singletons.Prelude.Const type Apply (ShowsPrec_6989586621680598687Sym1 a6989586621680598684 a6989586621680597830 b6989586621680597831 :: TyFun (Const a6989586621680597830 b6989586621680597831) (Symbol ~> Symbol) -> Type) (a6989586621680598685 :: Const a6989586621680597830 b6989586621680597831) = ShowsPrec_6989586621680598687Sym2 a6989586621680598684 a6989586621680598685 | |
type Apply (ShowsPrec_6989586621680279312Sym1 a6989586621680279309 a6989586621680278783 b6989586621680278784 c6989586621680278785 d6989586621680278786 :: TyFun (a6989586621680278783, b6989586621680278784, c6989586621680278785, d6989586621680278786) (Symbol ~> Symbol) -> Type) (a6989586621680279310 :: (a6989586621680278783, b6989586621680278784, c6989586621680278785, d6989586621680278786)) | |
Defined in Data.Singletons.Prelude.Show type Apply (ShowsPrec_6989586621680279312Sym1 a6989586621680279309 a6989586621680278783 b6989586621680278784 c6989586621680278785 d6989586621680278786 :: TyFun (a6989586621680278783, b6989586621680278784, c6989586621680278785, d6989586621680278786) (Symbol ~> Symbol) -> Type) (a6989586621680279310 :: (a6989586621680278783, b6989586621680278784, c6989586621680278785, d6989586621680278786)) = ShowsPrec_6989586621680279312Sym2 a6989586621680279309 a6989586621680279310 | |
type Apply (ShowsPrec_6989586621680279331Sym1 a6989586621680279328 a6989586621680278792 b6989586621680278793 c6989586621680278794 d6989586621680278795 e6989586621680278796 :: TyFun (a6989586621680278792, b6989586621680278793, c6989586621680278794, d6989586621680278795, e6989586621680278796) (Symbol ~> Symbol) -> Type) (a6989586621680279329 :: (a6989586621680278792, b6989586621680278793, c6989586621680278794, d6989586621680278795, e6989586621680278796)) | |
Defined in Data.Singletons.Prelude.Show type Apply (ShowsPrec_6989586621680279331Sym1 a6989586621680279328 a6989586621680278792 b6989586621680278793 c6989586621680278794 d6989586621680278795 e6989586621680278796 :: TyFun (a6989586621680278792, b6989586621680278793, c6989586621680278794, d6989586621680278795, e6989586621680278796) (Symbol ~> Symbol) -> Type) (a6989586621680279329 :: (a6989586621680278792, b6989586621680278793, c6989586621680278794, d6989586621680278795, e6989586621680278796)) = ShowsPrec_6989586621680279331Sym2 a6989586621680279328 a6989586621680279329 | |
type Apply (ShowsPrec_6989586621680279351Sym1 a6989586621680279348 a6989586621680278803 b6989586621680278804 c6989586621680278805 d6989586621680278806 e6989586621680278807 f6989586621680278808 :: TyFun (a6989586621680278803, b6989586621680278804, c6989586621680278805, d6989586621680278806, e6989586621680278807, f6989586621680278808) (Symbol ~> Symbol) -> Type) (a6989586621680279349 :: (a6989586621680278803, b6989586621680278804, c6989586621680278805, d6989586621680278806, e6989586621680278807, f6989586621680278808)) | |
Defined in Data.Singletons.Prelude.Show type Apply (ShowsPrec_6989586621680279351Sym1 a6989586621680279348 a6989586621680278803 b6989586621680278804 c6989586621680278805 d6989586621680278806 e6989586621680278807 f6989586621680278808 :: TyFun (a6989586621680278803, b6989586621680278804, c6989586621680278805, d6989586621680278806, e6989586621680278807, f6989586621680278808) (Symbol ~> Symbol) -> Type) (a6989586621680279349 :: (a6989586621680278803, b6989586621680278804, c6989586621680278805, d6989586621680278806, e6989586621680278807, f6989586621680278808)) = ShowsPrec_6989586621680279351Sym2 a6989586621680279348 a6989586621680279349 | |
type Apply (ShowsPrec_6989586621680279372Sym1 a6989586621680279369 a6989586621680278816 b6989586621680278817 c6989586621680278818 d6989586621680278819 e6989586621680278820 f6989586621680278821 g6989586621680278822 :: TyFun (a6989586621680278816, b6989586621680278817, c6989586621680278818, d6989586621680278819, e6989586621680278820, f6989586621680278821, g6989586621680278822) (Symbol ~> Symbol) -> Type) (a6989586621680279370 :: (a6989586621680278816, b6989586621680278817, c6989586621680278818, d6989586621680278819, e6989586621680278820, f6989586621680278821, g6989586621680278822)) | |
Defined in Data.Singletons.Prelude.Show type Apply (ShowsPrec_6989586621680279372Sym1 a6989586621680279369 a6989586621680278816 b6989586621680278817 c6989586621680278818 d6989586621680278819 e6989586621680278820 f6989586621680278821 g6989586621680278822 :: TyFun (a6989586621680278816, b6989586621680278817, c6989586621680278818, d6989586621680278819, e6989586621680278820, f6989586621680278821, g6989586621680278822) (Symbol ~> Symbol) -> Type) (a6989586621680279370 :: (a6989586621680278816, b6989586621680278817, c6989586621680278818, d6989586621680278819, e6989586621680278820, f6989586621680278821, g6989586621680278822)) = ShowsPrec_6989586621680279372Sym2 a6989586621680279369 a6989586621680279370 |
class KnownSymbol (n :: Symbol) #
This class gives the string associated with a type-level symbol. There are instances of the class for every concrete literal: "hello", etc.
Since: base-4.7.0.0
symbolSing
type family AppendSymbol (a :: Symbol) (b :: Symbol) :: Symbol where ... #
Concatenation of type-level symbols.
Since: base-4.10.0.0
symbolVal :: forall (n :: Symbol) proxy. KnownSymbol n => proxy n -> String #
Since: base-4.7.0.0
symbolValT :: forall s. KnownSymbol s => Proxy s -> Text Source #
symbolValT' :: forall s. KnownSymbol s => Text Source #
type family TypeError (a :: ErrorMessage) :: b where ... #
The type-level equivalent of error
.
The polymorphic kind of this type allows it to be used in several settings. For instance, it can be used as a constraint, e.g. to provide a better error message for a non-existent instance,
-- in a context
instance TypeError (Text "Cannot Show
functions." :$$:
Text "Perhaps there is a missing argument?")
=> Show (a -> b) where
showsPrec = error "unreachable"
It can also be placed on the right-hand side of a type-level function to provide an error for an invalid case,
type family ByteSize x where ByteSize Word16 = 2 ByteSize Word8 = 1 ByteSize a = TypeError (Text "The type " :<>: ShowType a :<>: Text " is not exportable.")
Since: base-4.9.0.0
data ErrorMessage #
A description of a custom type error.
Text Symbol | Show the text as is. |
ShowType t | Pretty print the type.
|
ErrorMessage :<>: ErrorMessage infixl 6 | Put two pieces of error message next to each other. |
ErrorMessage :$$: ErrorMessage infixl 5 | Stack two pieces of error message on top of each other. |
type family TypeErrorUnless (cond :: Bool) (err :: ErrorMessage) :: Constraint where ... Source #
Conditional type error.
Note that TypeErrorUnless cond err
is the same as
If cond () (TypeError err)
, but does not produce type-level error when
one of its arguments cannot be deduced.
TypeErrorUnless 'True _ = () | |
TypeErrorUnless 'False err = TypeError err |
inTypeErrorUnless :: forall cond err a. TypeErrorUnless cond err => (cond ~ 'True => a) -> a Source #
Reify the fact that condition under TypeErrorUnless
constraint can be
assumed to always hold.