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_6989586621680595863Sym0 | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings ShowsPrec_6989586621680595887Sym0 | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings ShowsNatSym0 | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings ShowsPrec_6989586621680577891Sym0 | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings ShowsPrec_6989586621680595705Sym0 | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings ShowsPrec_6989586621680595917Sym0 | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings ShowsPrec_6989586621681091253Sym0 | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings ShowsPrec_6989586621681091281Sym0 | |
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_6989586621680595863Sym1 a6989586621680595860 :: TyFun Bool (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowList_6989586621680577858Sym0 :: TyFun [a6989586621680577383] (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowListSym0 :: TyFun [a6989586621680577383] (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680595887Sym1 a6989586621680595884 :: TyFun Ordering (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680577871Sym0 :: TyFun Nat ([a6989586621680577401] ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680595739Sym0 :: TyFun Nat (Maybe a3530822107858468865 ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680577836Sym0 :: TyFun Nat (a6989586621680577383 ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrecSym0 :: TyFun Nat (a6989586621680577383 ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621681091374Sym0 :: TyFun Nat (Min a6989586621679060072 ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621681091405Sym0 :: TyFun Nat (Max a6989586621679060077 ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621681091436Sym0 :: TyFun Nat (First a6989586621679060087 ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621681091467Sym0 :: TyFun Nat (Last a6989586621679060082 ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621681091498Sym0 :: TyFun Nat (WrappedMonoid m6989586621679090734 ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621681091194Sym0 :: TyFun Nat (Option a6989586621679060067 ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680921160Sym0 :: TyFun Nat (Identity a6989586621680920941 ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Singletons.Prelude.Identity suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680637784Sym0 :: TyFun Nat (First a6989586621679087428 ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Singletons.Prelude.Monoid suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680637815Sym0 :: TyFun Nat (Last a6989586621679087421 ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Singletons.Prelude.Monoid suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621681091225Sym0 :: TyFun Nat (Dual a6989586621679087487 ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621681091312Sym0 :: TyFun Nat (Sum a6989586621679087464 ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621681091343Sym0 :: TyFun Nat (Product a6989586621679087472 ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680595837Sym0 :: TyFun Nat (NonEmpty a6989586621679060153 ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowStringSym1 a6989586621680577777 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowCharSym1 a6989586621680577787 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Show_tupleSym1 a6989586621680577725 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsNatSym1 a6989586621680595203 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (FromStringSym0 :: TyFun Symbol a6989586621681391347 -> Type) | |
Defined in Data.Singletons.Prelude.IsString suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (FromString_6989586621681391383Sym0 :: TyFun Symbol (Identity a6989586621681391352) -> Type) | |
Defined in Data.Singletons.Prelude.IsString suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680577891Sym1 a6989586621680577888 :: TyFun Symbol (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680595705Sym1 a6989586621680595702 :: TyFun () (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsSym0 :: TyFun a6989586621680577368 (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Show__6989586621680577850Sym0 :: TyFun a6989586621680577383 Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Show_Sym0 :: TyFun a6989586621680577383 Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Lambda_6989586621680577753Sym0 :: TyFun k (TyFun Symbol Symbol -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680595917Sym1 a6989586621680595914 :: TyFun Void (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621681091253Sym1 a6989586621681091250 :: TyFun All (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621681091281Sym1 a6989586621681091278 :: TyFun Any (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowParenSym1 a6989586621680577759 :: TyFun (Symbol ~> Symbol) (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowListWithSym0 :: TyFun (a6989586621680577367 ~> (Symbol ~> Symbol)) ([a6989586621680577367] ~> (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_6989586621680577871Sym1 a6989586621680577868 a6989586621680577401 :: TyFun [a6989586621680577401] (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowListWithSym1 a6989586621680577793 :: TyFun [a6989586621680577367] (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680595739Sym1 a6989586621680595736 a3530822107858468865 :: TyFun (Maybe a3530822107858468865) (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680595795Sym0 :: TyFun Nat (Either a6989586621679091042 b6989586621679091043 ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680577911Sym0 :: TyFun Nat ((a6989586621680577405, b6989586621680577406) ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621681108427Sym0 :: TyFun Nat (Arg a6989586621681107144 b6989586621681107145 ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowParenSym2 a6989586621680577760 a6989586621680577759 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsSym1 a6989586621680577813 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowListSym1 arg6989586621680577829 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621681091253Sym2 a6989586621681091251 a6989586621681091250 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621681091281Sym2 a6989586621681091279 a6989586621681091278 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowList_6989586621680577858Sym1 a6989586621680577856 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680577891Sym2 a6989586621680577889 a6989586621680577888 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680595705Sym2 a6989586621680595703 a6989586621680595702 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680595863Sym2 a6989586621680595861 a6989586621680595860 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680595887Sym2 a6989586621680595885 a6989586621680595884 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680595917Sym2 a6989586621680595915 a6989586621680595914 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Lambda_6989586621680577753Sym1 a_69895866216805777486989586621680577752 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680577836Sym1 a6989586621680577833 a6989586621680577383 :: TyFun a6989586621680577383 (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrecSym1 arg6989586621680577821 a6989586621680577383 :: TyFun a6989586621680577383 (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621680321072GoSym0 :: TyFun k1 (TyFun k2 (TyFun [Symbol] Symbol -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621681091374Sym1 a6989586621681091371 a6989586621679060072 :: TyFun (Min a6989586621679060072) (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621681091405Sym1 a6989586621681091402 a6989586621679060077 :: TyFun (Max a6989586621679060077) (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621681091436Sym1 a6989586621681091433 a6989586621679060087 :: TyFun (First a6989586621679060087) (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621681091467Sym1 a6989586621681091464 a6989586621679060082 :: TyFun (Last a6989586621679060082) (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621681091498Sym1 a6989586621681091495 m6989586621679090734 :: TyFun (WrappedMonoid m6989586621679090734) (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621681091194Sym1 a6989586621681091191 a6989586621679060067 :: TyFun (Option a6989586621679060067) (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680921160Sym1 a6989586621680921157 a6989586621680920941 :: TyFun (Identity a6989586621680920941) (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Identity suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680637784Sym1 a6989586621680637781 a6989586621679087428 :: TyFun (First a6989586621679087428) (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Monoid suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680637815Sym1 a6989586621680637812 a6989586621679087421 :: TyFun (Last a6989586621679087421) (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Monoid suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621681091225Sym1 a6989586621681091222 a6989586621679087487 :: TyFun (Dual a6989586621679087487) (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621681091312Sym1 a6989586621681091309 a6989586621679087464 :: TyFun (Sum a6989586621679087464) (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621681091343Sym1 a6989586621681091340 a6989586621679087472 :: TyFun (Product a6989586621679087472) (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680595837Sym1 a6989586621680595834 a6989586621679060153 :: TyFun (NonEmpty a6989586621679060153) (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_6989586621680595795Sym1 a6989586621680595792 a6989586621679091042 b6989586621679091043 :: TyFun (Either a6989586621679091042 b6989586621679091043) (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680577928Sym0 :: TyFun Nat ((a6989586621680577410, b6989586621680577411, c6989586621680577412) ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680953659Sym0 :: TyFun Nat (Const a6989586621680952802 b6989586621680952803 ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Singletons.Prelude.Const suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowListWithSym2 a6989586621680577794 a6989586621680577793 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrecSym2 arg6989586621680577822 arg6989586621680577821 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621681091194Sym2 a6989586621681091192 a6989586621681091191 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621681091225Sym2 a6989586621681091223 a6989586621681091222 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621681091312Sym2 a6989586621681091310 a6989586621681091309 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621681091343Sym2 a6989586621681091341 a6989586621681091340 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621681091374Sym2 a6989586621681091372 a6989586621681091371 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621681091405Sym2 a6989586621681091403 a6989586621681091402 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621681091436Sym2 a6989586621681091434 a6989586621681091433 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621681091467Sym2 a6989586621681091465 a6989586621681091464 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621681091498Sym2 a6989586621681091496 a6989586621681091495 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680921160Sym2 a6989586621680921158 a6989586621680921157 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Identity suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680637784Sym2 a6989586621680637782 a6989586621680637781 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Monoid suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680637815Sym2 a6989586621680637813 a6989586621680637812 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Monoid suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680577836Sym2 a6989586621680577834 a6989586621680577833 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680577871Sym2 a6989586621680577869 a6989586621680577868 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680595739Sym2 a6989586621680595737 a6989586621680595736 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680595837Sym2 a6989586621680595835 a6989586621680595834 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (FromString_6989586621681391376Sym0 :: TyFun Symbol (Const a6989586621681391349 b6989586621681391350) -> Type) | |
Defined in Data.Singletons.Prelude.IsString suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680577911Sym1 a6989586621680577908 a6989586621680577405 b6989586621680577406 :: TyFun (a6989586621680577405, b6989586621680577406) (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621680321072GoSym1 w6989586621680321070 :: TyFun k2 (TyFun [Symbol] Symbol -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621681108427Sym1 a6989586621681108424 a6989586621681107144 b6989586621681107145 :: TyFun (Arg a6989586621681107144 b6989586621681107145) (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621680577804ShowlSym0 :: 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 (Let6989586621680321072GoSym2 ws6989586621680321071 w6989586621680321070 :: TyFun [Symbol] Symbol -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680577946Sym0 :: TyFun Nat ((a6989586621680577417, b6989586621680577418, c6989586621680577419, d6989586621680577420) ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621681108427Sym2 a6989586621681108425 a6989586621681108424 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680577911Sym2 a6989586621680577909 a6989586621680577908 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680595795Sym2 a6989586621680595793 a6989586621680595792 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680577928Sym1 a6989586621680577925 a6989586621680577410 b6989586621680577411 c6989586621680577412 :: TyFun (a6989586621680577410, b6989586621680577411, c6989586621680577412) (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621680577804ShowlSym1 showx6989586621680577800 :: TyFun k2 (TyFun k3 (TyFun Symbol (TyFun [k1] Symbol -> Type) -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Lambda_6989586621680577733Sym0 :: TyFun k1 (TyFun k2 (TyFun (Symbol ~> c6989586621679941607) (TyFun (a6989586621679941608 ~> Symbol) (TyFun a6989586621679941608 c6989586621679941607 -> Type) -> Type) -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680953659Sym1 a6989586621680953656 a6989586621680952802 b6989586621680952803 :: TyFun (Const a6989586621680952802 b6989586621680952803) (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Const suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680577965Sym0 :: TyFun Nat ((a6989586621680577426, b6989586621680577427, c6989586621680577428, d6989586621680577429, e6989586621680577430) ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680953659Sym2 a6989586621680953657 a6989586621680953656 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Const suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680577928Sym2 a6989586621680577926 a6989586621680577925 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680577946Sym1 a6989586621680577943 a6989586621680577417 b6989586621680577418 c6989586621680577419 d6989586621680577420 :: TyFun (a6989586621680577417, b6989586621680577418, c6989586621680577419, d6989586621680577420) (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621680577804ShowlSym2 x6989586621680577801 showx6989586621680577800 :: TyFun k3 (TyFun Symbol (TyFun [k1] Symbol -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Lambda_6989586621680577733Sym1 ss6989586621680577731 :: TyFun k2 (TyFun (Symbol ~> c6989586621679941607) (TyFun (a6989586621679941608 ~> Symbol) (TyFun a6989586621679941608 c6989586621679941607 -> Type) -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680577985Sym0 :: TyFun Nat ((a6989586621680577437, b6989586621680577438, c6989586621680577439, d6989586621680577440, e6989586621680577441, f6989586621680577442) ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621680577804ShowlSym3 xs6989586621680577802 x6989586621680577801 showx6989586621680577800 :: TyFun Symbol (TyFun [k1] Symbol -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680577946Sym2 a6989586621680577944 a6989586621680577943 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680577965Sym1 a6989586621680577962 a6989586621680577426 b6989586621680577427 c6989586621680577428 d6989586621680577429 e6989586621680577430 :: TyFun (a6989586621680577426, b6989586621680577427, c6989586621680577428, d6989586621680577429, e6989586621680577430) (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Lambda_6989586621680577733Sym2 a_69895866216805777296989586621680577732 ss6989586621680577731 :: TyFun (Symbol ~> c6989586621679941607) (TyFun (a6989586621679941608 ~> Symbol) (TyFun a6989586621679941608 c6989586621679941607 -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621680577804ShowlSym4 s6989586621680577803 xs6989586621680577802 x6989586621680577801 showx6989586621680577800 :: TyFun [k1] Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680578006Sym0 :: TyFun Nat ((a6989586621680577450, b6989586621680577451, c6989586621680577452, d6989586621680577453, e6989586621680577454, f6989586621680577455, g6989586621680577456) ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680577965Sym2 a6989586621680577963 a6989586621680577962 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680577985Sym1 a6989586621680577982 a6989586621680577437 b6989586621680577438 c6989586621680577439 d6989586621680577440 e6989586621680577441 f6989586621680577442 :: TyFun (a6989586621680577437, b6989586621680577438, c6989586621680577439, d6989586621680577440, e6989586621680577441, f6989586621680577442) (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Lambda_6989586621680577733Sym3 t6989586621680577737 a_69895866216805777296989586621680577732 ss6989586621680577731 :: TyFun (a6989586621679941608 ~> Symbol) (TyFun a6989586621679941608 c6989586621679941607 -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680577985Sym2 a6989586621680577983 a6989586621680577982 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680578006Sym1 a6989586621680578003 a6989586621680577450 b6989586621680577451 c6989586621680577452 d6989586621680577453 e6989586621680577454 f6989586621680577455 g6989586621680577456 :: TyFun (a6989586621680577450, b6989586621680577451, c6989586621680577452, d6989586621680577453, e6989586621680577454, f6989586621680577455, g6989586621680577456) (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Show suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680578006Sym2 a6989586621680578004 a6989586621680578003 :: 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 (n6989586621679863488 :: Symbol) | |
Defined in Data.Singletons.TypeLits | |
type Apply ShowCommaSpaceSym0 (a6989586621680577745 :: Symbol) | |
Defined in Data.Singletons.Prelude.Show type Apply ShowCommaSpaceSym0 (a6989586621680577745 :: Symbol) = ShowCommaSpace a6989586621680577745 | |
type Apply ShowSpaceSym0 (a6989586621680577750 :: Symbol) | |
Defined in Data.Singletons.Prelude.Show | |
type Apply (ShowStringSym1 a6989586621680577777 :: TyFun Symbol Symbol -> Type) (a6989586621680577778 :: Symbol) | |
Defined in Data.Singletons.Prelude.Show type Apply (ShowStringSym1 a6989586621680577777 :: TyFun Symbol Symbol -> Type) (a6989586621680577778 :: Symbol) = ShowString a6989586621680577777 a6989586621680577778 | |
type Apply (ShowCharSym1 a6989586621680577787 :: TyFun Symbol Symbol -> Type) (a6989586621680577788 :: Symbol) | |
Defined in Data.Singletons.Prelude.Show | |
type Apply (Show_tupleSym1 a6989586621680577725 :: TyFun Symbol Symbol -> Type) (a6989586621680577726 :: Symbol) | |
type Apply (ShowsNatSym1 a6989586621680595203 :: TyFun Symbol Symbol -> Type) (a6989586621680595204 :: Symbol) | |
type Apply (FromStringSym0 :: TyFun Symbol k2 -> Type) (arg6989586621681391373 :: Symbol) | |
Defined in Data.Singletons.Prelude.IsString type Apply (FromStringSym0 :: TyFun Symbol k2 -> Type) (arg6989586621681391373 :: Symbol) = FromString arg6989586621681391373 :: k2 | |
type Apply (Show__6989586621680577850Sym0 :: TyFun a Symbol -> Type) (a6989586621680577849 :: a) | |
Defined in Data.Singletons.Prelude.Show | |
type Apply (Show_Sym0 :: TyFun a Symbol -> Type) (arg6989586621680577827 :: a) | |
type Apply (ShowParenSym2 a6989586621680577760 a6989586621680577759 :: TyFun Symbol Symbol -> Type) (a6989586621680577761 :: Symbol) | |
Defined in Data.Singletons.Prelude.Show | |
type Apply (ShowsSym1 a6989586621680577813 :: TyFun Symbol Symbol -> Type) (a6989586621680577814 :: Symbol) | |
type Apply (ShowListSym1 arg6989586621680577829 :: TyFun Symbol Symbol -> Type) (arg6989586621680577830 :: Symbol) | |
Defined in Data.Singletons.Prelude.Show | |
type Apply (ShowsPrec_6989586621681091253Sym2 a6989586621681091251 a6989586621681091250 :: TyFun Symbol Symbol -> Type) (a6989586621681091252 :: Symbol) | |
type Apply (ShowsPrec_6989586621681091281Sym2 a6989586621681091279 a6989586621681091278 :: TyFun Symbol Symbol -> Type) (a6989586621681091280 :: Symbol) | |
type Apply (Lambda_6989586621680577753Sym1 a_69895866216805777486989586621680577752 :: TyFun Symbol Symbol -> Type) (t6989586621680577756 :: Symbol) | |
type Apply (ShowList_6989586621680577858Sym1 a6989586621680577856 :: TyFun Symbol Symbol -> Type) (a6989586621680577857 :: Symbol) | |
type Apply (ShowsPrec_6989586621680577891Sym2 a6989586621680577889 a6989586621680577888 :: TyFun Symbol Symbol -> Type) (a6989586621680577890 :: Symbol) | |
type Apply (ShowsPrec_6989586621680595705Sym2 a6989586621680595703 a6989586621680595702 :: TyFun Symbol Symbol -> Type) (a6989586621680595704 :: Symbol) | |
type Apply (ShowsPrec_6989586621680595863Sym2 a6989586621680595861 a6989586621680595860 :: TyFun Symbol Symbol -> Type) (a6989586621680595862 :: Symbol) | |
type Apply (ShowsPrec_6989586621680595887Sym2 a6989586621680595885 a6989586621680595884 :: TyFun Symbol Symbol -> Type) (a6989586621680595886 :: Symbol) | |
type Apply (ShowsPrec_6989586621680595917Sym2 a6989586621680595915 a6989586621680595914 :: TyFun Symbol Symbol -> Type) (a6989586621680595916 :: Symbol) | |
type Apply (ShowListWithSym2 a6989586621680577794 a6989586621680577793 :: TyFun Symbol Symbol -> Type) (a6989586621680577795 :: Symbol) | |
Defined in Data.Singletons.Prelude.Show type Apply (ShowListWithSym2 a6989586621680577794 a6989586621680577793 :: TyFun Symbol Symbol -> Type) (a6989586621680577795 :: Symbol) = ShowListWith a6989586621680577794 a6989586621680577793 a6989586621680577795 | |
type Apply (ShowsPrecSym2 arg6989586621680577822 arg6989586621680577821 :: TyFun Symbol Symbol -> Type) (arg6989586621680577823 :: Symbol) | |
Defined in Data.Singletons.Prelude.Show | |
type Apply (ShowsPrec_6989586621681091194Sym2 a6989586621681091192 a6989586621681091191 :: TyFun Symbol Symbol -> Type) (a6989586621681091193 :: Symbol) | |
type Apply (ShowsPrec_6989586621681091225Sym2 a6989586621681091223 a6989586621681091222 :: TyFun Symbol Symbol -> Type) (a6989586621681091224 :: Symbol) | |
type Apply (ShowsPrec_6989586621681091312Sym2 a6989586621681091310 a6989586621681091309 :: TyFun Symbol Symbol -> Type) (a6989586621681091311 :: Symbol) | |
type Apply (ShowsPrec_6989586621681091343Sym2 a6989586621681091341 a6989586621681091340 :: TyFun Symbol Symbol -> Type) (a6989586621681091342 :: Symbol) | |
type Apply (ShowsPrec_6989586621681091374Sym2 a6989586621681091372 a6989586621681091371 :: TyFun Symbol Symbol -> Type) (a6989586621681091373 :: Symbol) | |
type Apply (ShowsPrec_6989586621681091405Sym2 a6989586621681091403 a6989586621681091402 :: TyFun Symbol Symbol -> Type) (a6989586621681091404 :: Symbol) | |
type Apply (ShowsPrec_6989586621681091436Sym2 a6989586621681091434 a6989586621681091433 :: TyFun Symbol Symbol -> Type) (a6989586621681091435 :: Symbol) | |
type Apply (ShowsPrec_6989586621681091467Sym2 a6989586621681091465 a6989586621681091464 :: TyFun Symbol Symbol -> Type) (a6989586621681091466 :: Symbol) | |
type Apply (ShowsPrec_6989586621681091498Sym2 a6989586621681091496 a6989586621681091495 :: TyFun Symbol Symbol -> Type) (a6989586621681091497 :: Symbol) | |
type Apply (ShowsPrec_6989586621680921160Sym2 a6989586621680921158 a6989586621680921157 :: TyFun Symbol Symbol -> Type) (a6989586621680921159 :: Symbol) | |
type Apply (ShowsPrec_6989586621680637784Sym2 a6989586621680637782 a6989586621680637781 :: TyFun Symbol Symbol -> Type) (a6989586621680637783 :: Symbol) | |
type Apply (ShowsPrec_6989586621680637815Sym2 a6989586621680637813 a6989586621680637812 :: TyFun Symbol Symbol -> Type) (a6989586621680637814 :: Symbol) | |
type Apply (ShowsPrec_6989586621680577836Sym2 a6989586621680577834 a6989586621680577833 :: TyFun Symbol Symbol -> Type) (a6989586621680577835 :: Symbol) | |
type Apply (ShowsPrec_6989586621680577871Sym2 a6989586621680577869 a6989586621680577868 :: TyFun Symbol Symbol -> Type) (a6989586621680577870 :: Symbol) | |
type Apply (ShowsPrec_6989586621680595739Sym2 a6989586621680595737 a6989586621680595736 :: TyFun Symbol Symbol -> Type) (a6989586621680595738 :: Symbol) | |
type Apply (ShowsPrec_6989586621680595837Sym2 a6989586621680595835 a6989586621680595834 :: TyFun Symbol Symbol -> Type) (a6989586621680595836 :: Symbol) | |
type Apply (ShowsPrec_6989586621681108427Sym2 a6989586621681108425 a6989586621681108424 :: TyFun Symbol Symbol -> Type) (a6989586621681108426 :: Symbol) | |
type Apply (ShowsPrec_6989586621680577911Sym2 a6989586621680577909 a6989586621680577908 :: TyFun Symbol Symbol -> Type) (a6989586621680577910 :: Symbol) | |
type Apply (ShowsPrec_6989586621680595795Sym2 a6989586621680595793 a6989586621680595792 :: TyFun Symbol Symbol -> Type) (a6989586621680595794 :: Symbol) | |
type Apply (ShowsPrec_6989586621680953659Sym2 a6989586621680953657 a6989586621680953656 :: TyFun Symbol Symbol -> Type) (a6989586621680953658 :: Symbol) | |
type Apply (ShowsPrec_6989586621680577928Sym2 a6989586621680577926 a6989586621680577925 :: TyFun Symbol Symbol -> Type) (a6989586621680577927 :: Symbol) | |
type Apply (ShowsPrec_6989586621680577946Sym2 a6989586621680577944 a6989586621680577943 :: TyFun Symbol Symbol -> Type) (a6989586621680577945 :: Symbol) | |
type Apply (ShowsPrec_6989586621680577965Sym2 a6989586621680577963 a6989586621680577962 :: TyFun Symbol Symbol -> Type) (a6989586621680577964 :: Symbol) | |
type Apply (ShowsPrec_6989586621680577985Sym2 a6989586621680577983 a6989586621680577982 :: TyFun Symbol Symbol -> Type) (a6989586621680577984 :: Symbol) | |
type Apply (ShowsPrec_6989586621680578006Sym2 a6989586621680578004 a6989586621680578003 :: TyFun Symbol Symbol -> Type) (a6989586621680578005 :: Symbol) | |
type Apply (FromString_6989586621681391383Sym0 :: TyFun Symbol (Identity a6989586621681391352) -> Type) (a6989586621681391382 :: Symbol) | |
type Apply ShowParenSym0 (a6989586621680577759 :: Bool) | |
Defined in Data.Singletons.Prelude.Show | |
type Apply ShowsPrec_6989586621680595863Sym0 (a6989586621680595860 :: Nat) | |
Defined in Data.Singletons.Prelude.Show | |
type Apply ShowsPrec_6989586621680595887Sym0 (a6989586621680595884 :: Nat) | |
Defined in Data.Singletons.Prelude.Show | |
type Apply ShowsNatSym0 (a6989586621680595203 :: Nat) | |
Defined in Data.Singletons.Prelude.Show | |
type Apply ShowsPrec_6989586621680577891Sym0 (a6989586621680577888 :: Nat) | |
Defined in Data.Singletons.Prelude.Show | |
type Apply ShowsPrec_6989586621680595705Sym0 (a6989586621680595702 :: Nat) | |
Defined in Data.Singletons.Prelude.Show | |
type Apply ShowsPrec_6989586621680595917Sym0 (a6989586621680595914 :: Nat) | |
Defined in Data.Singletons.Prelude.Show | |
type Apply ShowsPrec_6989586621681091253Sym0 (a6989586621681091250 :: Nat) | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Apply ShowsPrec_6989586621681091281Sym0 (a6989586621681091278 :: Nat) | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Apply ShowStringSym0 (a6989586621680577777 :: Symbol) | |
Defined in Data.Singletons.Prelude.Show | |
type Apply ShowCharSym0 (a6989586621680577787 :: Symbol) | |
Defined in Data.Singletons.Prelude.Show | |
type Apply (ShowsPrec_6989586621680595863Sym1 a6989586621680595860 :: TyFun Bool (Symbol ~> Symbol) -> Type) (a6989586621680595861 :: Bool) | |
type Apply (ShowsPrec_6989586621680595887Sym1 a6989586621680595884 :: TyFun Ordering (Symbol ~> Symbol) -> Type) (a6989586621680595885 :: Ordering) | |
type Apply (ShowsPrec_6989586621680577871Sym0 :: TyFun Nat ([a6989586621680577401] ~> (Symbol ~> Symbol)) -> Type) (a6989586621680577868 :: Nat) | |
Defined in Data.Singletons.Prelude.Show | |
type Apply (ShowsPrec_6989586621680595739Sym0 :: TyFun Nat (Maybe a3530822107858468865 ~> (Symbol ~> Symbol)) -> Type) (a6989586621680595736 :: Nat) | |
Defined in Data.Singletons.Prelude.Show | |
type Apply (ShowsPrec_6989586621680577836Sym0 :: TyFun Nat (a6989586621680577383 ~> (Symbol ~> Symbol)) -> Type) (a6989586621680577833 :: Nat) | |
Defined in Data.Singletons.Prelude.Show | |
type Apply (ShowsPrecSym0 :: TyFun Nat (a6989586621680577383 ~> (Symbol ~> Symbol)) -> Type) (arg6989586621680577821 :: Nat) | |
type Apply (ShowsPrec_6989586621681091374Sym0 :: TyFun Nat (Min a6989586621679060072 ~> (Symbol ~> Symbol)) -> Type) (a6989586621681091371 :: Nat) | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Apply (ShowsPrec_6989586621681091405Sym0 :: TyFun Nat (Max a6989586621679060077 ~> (Symbol ~> Symbol)) -> Type) (a6989586621681091402 :: Nat) | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Apply (ShowsPrec_6989586621681091436Sym0 :: TyFun Nat (First a6989586621679060087 ~> (Symbol ~> Symbol)) -> Type) (a6989586621681091433 :: Nat) | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Apply (ShowsPrec_6989586621681091467Sym0 :: TyFun Nat (Last a6989586621679060082 ~> (Symbol ~> Symbol)) -> Type) (a6989586621681091464 :: Nat) | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Apply (ShowsPrec_6989586621681091498Sym0 :: TyFun Nat (WrappedMonoid m6989586621679090734 ~> (Symbol ~> Symbol)) -> Type) (a6989586621681091495 :: Nat) | |
Defined in Data.Singletons.Prelude.Semigroup type Apply (ShowsPrec_6989586621681091498Sym0 :: TyFun Nat (WrappedMonoid m6989586621679090734 ~> (Symbol ~> Symbol)) -> Type) (a6989586621681091495 :: Nat) = ShowsPrec_6989586621681091498Sym1 a6989586621681091495 m6989586621679090734 :: TyFun (WrappedMonoid m6989586621679090734) (Symbol ~> Symbol) -> Type | |
type Apply (ShowsPrec_6989586621681091194Sym0 :: TyFun Nat (Option a6989586621679060067 ~> (Symbol ~> Symbol)) -> Type) (a6989586621681091191 :: Nat) | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Apply (ShowsPrec_6989586621680921160Sym0 :: TyFun Nat (Identity a6989586621680920941 ~> (Symbol ~> Symbol)) -> Type) (a6989586621680921157 :: Nat) | |
Defined in Data.Singletons.Prelude.Identity | |
type Apply (ShowsPrec_6989586621680637784Sym0 :: TyFun Nat (First a6989586621679087428 ~> (Symbol ~> Symbol)) -> Type) (a6989586621680637781 :: Nat) | |
Defined in Data.Singletons.Prelude.Monoid | |
type Apply (ShowsPrec_6989586621680637815Sym0 :: TyFun Nat (Last a6989586621679087421 ~> (Symbol ~> Symbol)) -> Type) (a6989586621680637812 :: Nat) | |
Defined in Data.Singletons.Prelude.Monoid | |
type Apply (ShowsPrec_6989586621681091225Sym0 :: TyFun Nat (Dual a6989586621679087487 ~> (Symbol ~> Symbol)) -> Type) (a6989586621681091222 :: Nat) | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Apply (ShowsPrec_6989586621681091312Sym0 :: TyFun Nat (Sum a6989586621679087464 ~> (Symbol ~> Symbol)) -> Type) (a6989586621681091309 :: Nat) | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Apply (ShowsPrec_6989586621681091343Sym0 :: TyFun Nat (Product a6989586621679087472 ~> (Symbol ~> Symbol)) -> Type) (a6989586621681091340 :: Nat) | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Apply (ShowsPrec_6989586621680595837Sym0 :: TyFun Nat (NonEmpty a6989586621679060153 ~> (Symbol ~> Symbol)) -> Type) (a6989586621680595834 :: Nat) | |
Defined in Data.Singletons.Prelude.Show | |
type Apply (ShowsPrec_6989586621680577891Sym1 a6989586621680577888 :: TyFun Symbol (Symbol ~> Symbol) -> Type) (a6989586621680577889 :: Symbol) | |
type Apply (ShowsPrec_6989586621680595705Sym1 a6989586621680595702 :: TyFun () (Symbol ~> Symbol) -> Type) (a6989586621680595703 :: ()) | |
type Apply (Lambda_6989586621680577753Sym0 :: TyFun k (TyFun Symbol Symbol -> Type) -> Type) (a_69895866216805777486989586621680577752 :: k) | |
type Apply (ShowsSym0 :: TyFun a6989586621680577368 (Symbol ~> Symbol) -> Type) (a6989586621680577813 :: a6989586621680577368) | |
type Apply (ShowsPrec_6989586621680595917Sym1 a6989586621680595914 :: TyFun Void (Symbol ~> Symbol) -> Type) (a6989586621680595915 :: Void) | |
type Apply (ShowsPrec_6989586621681091253Sym1 a6989586621681091250 :: TyFun All (Symbol ~> Symbol) -> Type) (a6989586621681091251 :: All) | |
type Apply (ShowsPrec_6989586621681091281Sym1 a6989586621681091278 :: TyFun Any (Symbol ~> Symbol) -> Type) (a6989586621681091279 :: Any) | |
type Apply (ShowsPrec_6989586621680595795Sym0 :: TyFun Nat (Either a6989586621679091042 b6989586621679091043 ~> (Symbol ~> Symbol)) -> Type) (a6989586621680595792 :: Nat) | |
Defined in Data.Singletons.Prelude.Show type Apply (ShowsPrec_6989586621680595795Sym0 :: TyFun Nat (Either a6989586621679091042 b6989586621679091043 ~> (Symbol ~> Symbol)) -> Type) (a6989586621680595792 :: Nat) = ShowsPrec_6989586621680595795Sym1 a6989586621680595792 a6989586621679091042 b6989586621679091043 :: TyFun (Either a6989586621679091042 b6989586621679091043) (Symbol ~> Symbol) -> Type | |
type Apply (ShowsPrec_6989586621680577911Sym0 :: TyFun Nat ((a6989586621680577405, b6989586621680577406) ~> (Symbol ~> Symbol)) -> Type) (a6989586621680577908 :: Nat) | |
Defined in Data.Singletons.Prelude.Show type Apply (ShowsPrec_6989586621680577911Sym0 :: TyFun Nat ((a6989586621680577405, b6989586621680577406) ~> (Symbol ~> Symbol)) -> Type) (a6989586621680577908 :: Nat) = ShowsPrec_6989586621680577911Sym1 a6989586621680577908 a6989586621680577405 b6989586621680577406 :: TyFun (a6989586621680577405, b6989586621680577406) (Symbol ~> Symbol) -> Type | |
type Apply (ShowsPrec_6989586621681108427Sym0 :: TyFun Nat (Arg a6989586621681107144 b6989586621681107145 ~> (Symbol ~> Symbol)) -> Type) (a6989586621681108424 :: Nat) | |
Defined in Data.Singletons.Prelude.Semigroup type Apply (ShowsPrec_6989586621681108427Sym0 :: TyFun Nat (Arg a6989586621681107144 b6989586621681107145 ~> (Symbol ~> Symbol)) -> Type) (a6989586621681108424 :: Nat) = ShowsPrec_6989586621681108427Sym1 a6989586621681108424 a6989586621681107144 b6989586621681107145 :: TyFun (Arg a6989586621681107144 b6989586621681107145) (Symbol ~> Symbol) -> Type | |
type Apply (ShowsPrec_6989586621680577836Sym1 a6989586621680577833 a6989586621680577383 :: TyFun a6989586621680577383 (Symbol ~> Symbol) -> Type) (a6989586621680577834 :: a6989586621680577383) | |
Defined in Data.Singletons.Prelude.Show | |
type Apply (ShowsPrecSym1 arg6989586621680577821 a6989586621680577383 :: TyFun a6989586621680577383 (Symbol ~> Symbol) -> Type) (arg6989586621680577822 :: a6989586621680577383) | |
Defined in Data.Singletons.Prelude.Show type Apply (ShowsPrecSym1 arg6989586621680577821 a6989586621680577383 :: TyFun a6989586621680577383 (Symbol ~> Symbol) -> Type) (arg6989586621680577822 :: a6989586621680577383) = ShowsPrecSym2 arg6989586621680577821 arg6989586621680577822 | |
type Apply (Let6989586621680321072GoSym0 :: TyFun k1 (TyFun k2 (TyFun [Symbol] Symbol -> Type) -> Type) -> Type) (w6989586621680321070 :: k1) | |
type Apply (ShowsPrec_6989586621680577928Sym0 :: TyFun Nat ((a6989586621680577410, b6989586621680577411, c6989586621680577412) ~> (Symbol ~> Symbol)) -> Type) (a6989586621680577925 :: Nat) | |
Defined in Data.Singletons.Prelude.Show type Apply (ShowsPrec_6989586621680577928Sym0 :: TyFun Nat ((a6989586621680577410, b6989586621680577411, c6989586621680577412) ~> (Symbol ~> Symbol)) -> Type) (a6989586621680577925 :: Nat) = ShowsPrec_6989586621680577928Sym1 a6989586621680577925 a6989586621680577410 b6989586621680577411 c6989586621680577412 :: TyFun (a6989586621680577410, b6989586621680577411, c6989586621680577412) (Symbol ~> Symbol) -> Type | |
type Apply (ShowsPrec_6989586621680953659Sym0 :: TyFun Nat (Const a6989586621680952802 b6989586621680952803 ~> (Symbol ~> Symbol)) -> Type) (a6989586621680953656 :: Nat) | |
Defined in Data.Singletons.Prelude.Const type Apply (ShowsPrec_6989586621680953659Sym0 :: TyFun Nat (Const a6989586621680952802 b6989586621680952803 ~> (Symbol ~> Symbol)) -> Type) (a6989586621680953656 :: Nat) = ShowsPrec_6989586621680953659Sym1 a6989586621680953656 a6989586621680952802 b6989586621680952803 :: TyFun (Const a6989586621680952802 b6989586621680952803) (Symbol ~> Symbol) -> Type | |
type Apply (Let6989586621680321072GoSym1 w6989586621680321070 :: TyFun k2 (TyFun [Symbol] Symbol -> Type) -> Type) (ws6989586621680321071 :: k2) | |
type Apply (ShowsPrec_6989586621680577946Sym0 :: TyFun Nat ((a6989586621680577417, b6989586621680577418, c6989586621680577419, d6989586621680577420) ~> (Symbol ~> Symbol)) -> Type) (a6989586621680577943 :: Nat) | |
Defined in Data.Singletons.Prelude.Show type Apply (ShowsPrec_6989586621680577946Sym0 :: TyFun Nat ((a6989586621680577417, b6989586621680577418, c6989586621680577419, d6989586621680577420) ~> (Symbol ~> Symbol)) -> Type) (a6989586621680577943 :: Nat) = ShowsPrec_6989586621680577946Sym1 a6989586621680577943 a6989586621680577417 b6989586621680577418 c6989586621680577419 d6989586621680577420 :: TyFun (a6989586621680577417, b6989586621680577418, c6989586621680577419, d6989586621680577420) (Symbol ~> Symbol) -> Type | |
type Apply (Let6989586621680577804ShowlSym1 showx6989586621680577800 :: TyFun k2 (TyFun k3 (TyFun Symbol (TyFun [k1] Symbol -> Type) -> Type) -> Type) -> Type) (x6989586621680577801 :: k2) | |
Defined in Data.Singletons.Prelude.Show type Apply (Let6989586621680577804ShowlSym1 showx6989586621680577800 :: TyFun k2 (TyFun k3 (TyFun Symbol (TyFun [k1] Symbol -> Type) -> Type) -> Type) -> Type) (x6989586621680577801 :: k2) = Let6989586621680577804ShowlSym2 showx6989586621680577800 x6989586621680577801 :: TyFun k3 (TyFun Symbol (TyFun [k1] Symbol -> Type) -> Type) -> Type | |
type Apply (Lambda_6989586621680577733Sym0 :: TyFun k1 (TyFun k2 (TyFun (Symbol ~> c6989586621679941607) (TyFun (a6989586621679941608 ~> Symbol) (TyFun a6989586621679941608 c6989586621679941607 -> Type) -> Type) -> Type) -> Type) -> Type) (ss6989586621680577731 :: k1) | |
Defined in Data.Singletons.Prelude.Show type Apply (Lambda_6989586621680577733Sym0 :: TyFun k1 (TyFun k2 (TyFun (Symbol ~> c6989586621679941607) (TyFun (a6989586621679941608 ~> Symbol) (TyFun a6989586621679941608 c6989586621679941607 -> Type) -> Type) -> Type) -> Type) -> Type) (ss6989586621680577731 :: k1) = Lambda_6989586621680577733Sym1 ss6989586621680577731 :: TyFun k2 (TyFun (Symbol ~> c6989586621679941607) (TyFun (a6989586621679941608 ~> Symbol) (TyFun a6989586621679941608 c6989586621679941607 -> Type) -> Type) -> Type) -> Type | |
type Apply (ShowsPrec_6989586621680577965Sym0 :: TyFun Nat ((a6989586621680577426, b6989586621680577427, c6989586621680577428, d6989586621680577429, e6989586621680577430) ~> (Symbol ~> Symbol)) -> Type) (a6989586621680577962 :: Nat) | |
Defined in Data.Singletons.Prelude.Show type Apply (ShowsPrec_6989586621680577965Sym0 :: TyFun Nat ((a6989586621680577426, b6989586621680577427, c6989586621680577428, d6989586621680577429, e6989586621680577430) ~> (Symbol ~> Symbol)) -> Type) (a6989586621680577962 :: Nat) = ShowsPrec_6989586621680577965Sym1 a6989586621680577962 a6989586621680577426 b6989586621680577427 c6989586621680577428 d6989586621680577429 e6989586621680577430 :: TyFun (a6989586621680577426, b6989586621680577427, c6989586621680577428, d6989586621680577429, e6989586621680577430) (Symbol ~> Symbol) -> Type | |
type Apply (Let6989586621680577804ShowlSym2 x6989586621680577801 showx6989586621680577800 :: TyFun k3 (TyFun Symbol (TyFun [k1] Symbol -> Type) -> Type) -> Type) (xs6989586621680577802 :: k3) | |
Defined in Data.Singletons.Prelude.Show | |
type Apply (Lambda_6989586621680577733Sym1 ss6989586621680577731 :: TyFun k2 (TyFun (Symbol ~> c6989586621679941607) (TyFun (a6989586621679941608 ~> Symbol) (TyFun a6989586621679941608 c6989586621679941607 -> Type) -> Type) -> Type) -> Type) (a_69895866216805777296989586621680577732 :: k2) | |
Defined in Data.Singletons.Prelude.Show type Apply (Lambda_6989586621680577733Sym1 ss6989586621680577731 :: TyFun k2 (TyFun (Symbol ~> c6989586621679941607) (TyFun (a6989586621679941608 ~> Symbol) (TyFun a6989586621679941608 c6989586621679941607 -> Type) -> Type) -> Type) -> Type) (a_69895866216805777296989586621680577732 :: k2) = Lambda_6989586621680577733Sym2 ss6989586621680577731 a_69895866216805777296989586621680577732 :: TyFun (Symbol ~> c6989586621679941607) (TyFun (a6989586621679941608 ~> Symbol) (TyFun a6989586621679941608 c6989586621679941607 -> Type) -> Type) -> Type | |
type Apply (ShowsPrec_6989586621680577985Sym0 :: TyFun Nat ((a6989586621680577437, b6989586621680577438, c6989586621680577439, d6989586621680577440, e6989586621680577441, f6989586621680577442) ~> (Symbol ~> Symbol)) -> Type) (a6989586621680577982 :: Nat) | |
Defined in Data.Singletons.Prelude.Show type Apply (ShowsPrec_6989586621680577985Sym0 :: TyFun Nat ((a6989586621680577437, b6989586621680577438, c6989586621680577439, d6989586621680577440, e6989586621680577441, f6989586621680577442) ~> (Symbol ~> Symbol)) -> Type) (a6989586621680577982 :: Nat) = ShowsPrec_6989586621680577985Sym1 a6989586621680577982 a6989586621680577437 b6989586621680577438 c6989586621680577439 d6989586621680577440 e6989586621680577441 f6989586621680577442 :: TyFun (a6989586621680577437, b6989586621680577438, c6989586621680577439, d6989586621680577440, e6989586621680577441, f6989586621680577442) (Symbol ~> Symbol) -> Type | |
type Apply (Let6989586621680577804ShowlSym3 xs6989586621680577802 x6989586621680577801 showx6989586621680577800 :: TyFun Symbol (TyFun [k1] Symbol -> Type) -> Type) (s6989586621680577803 :: Symbol) | |
Defined in Data.Singletons.Prelude.Show type Apply (Let6989586621680577804ShowlSym3 xs6989586621680577802 x6989586621680577801 showx6989586621680577800 :: TyFun Symbol (TyFun [k1] Symbol -> Type) -> Type) (s6989586621680577803 :: Symbol) = Let6989586621680577804ShowlSym4 xs6989586621680577802 x6989586621680577801 showx6989586621680577800 s6989586621680577803 | |
type Apply (ShowsPrec_6989586621680578006Sym0 :: TyFun Nat ((a6989586621680577450, b6989586621680577451, c6989586621680577452, d6989586621680577453, e6989586621680577454, f6989586621680577455, g6989586621680577456) ~> (Symbol ~> Symbol)) -> Type) (a6989586621680578003 :: Nat) | |
Defined in Data.Singletons.Prelude.Show type Apply (ShowsPrec_6989586621680578006Sym0 :: TyFun Nat ((a6989586621680577450, b6989586621680577451, c6989586621680577452, d6989586621680577453, e6989586621680577454, f6989586621680577455, g6989586621680577456) ~> (Symbol ~> Symbol)) -> Type) (a6989586621680578003 :: Nat) = ShowsPrec_6989586621680578006Sym1 a6989586621680578003 a6989586621680577450 b6989586621680577451 c6989586621680577452 d6989586621680577453 e6989586621680577454 f6989586621680577455 g6989586621680577456 :: TyFun (a6989586621680577450, b6989586621680577451, c6989586621680577452, d6989586621680577453, e6989586621680577454, f6989586621680577455, g6989586621680577456) (Symbol ~> Symbol) -> Type | |
type Apply (FromString_6989586621681391376Sym0 :: TyFun Symbol (Const a6989586621681391349 b6989586621681391350) -> Type) (a6989586621681391375 :: Symbol) | |
Defined in Data.Singletons.Prelude.IsString | |
type Rep (ElField '(s, a)) | |
type Apply UnwordsSym0 (a6989586621680321068 :: [Symbol]) | |
Defined in Data.Singletons.Prelude.List.Internal | |
type Apply UnlinesSym0 (a6989586621680321079 :: [Symbol]) | |
Defined in Data.Singletons.Prelude.List.Internal | |
type Apply (Let6989586621680321072GoSym2 ws6989586621680321071 w6989586621680321070 :: TyFun [Symbol] Symbol -> Type) (a6989586621680321073 :: [Symbol]) | |
type Apply (Let6989586621680577804ShowlSym4 s6989586621680577803 xs6989586621680577802 x6989586621680577801 showx6989586621680577800 :: TyFun [k1] Symbol -> Type) (a6989586621680577805 :: [k1]) | |
Defined in Data.Singletons.Prelude.Show type Apply (Let6989586621680577804ShowlSym4 s6989586621680577803 xs6989586621680577802 x6989586621680577801 showx6989586621680577800 :: TyFun [k1] Symbol -> Type) (a6989586621680577805 :: [k1]) = Let6989586621680577804Showl s6989586621680577803 xs6989586621680577802 x6989586621680577801 showx6989586621680577800 a6989586621680577805 | |
type Apply Show_tupleSym0 (a6989586621680577725 :: [Symbol ~> Symbol]) | |
Defined in Data.Singletons.Prelude.Show | |
type Apply (ShowList_6989586621680577858Sym0 :: TyFun [a6989586621680577383] (Symbol ~> Symbol) -> Type) (a6989586621680577856 :: [a6989586621680577383]) | |
type Apply (ShowListSym0 :: TyFun [a6989586621680577383] (Symbol ~> Symbol) -> Type) (arg6989586621680577829 :: [a6989586621680577383]) | |
Defined in Data.Singletons.Prelude.Show type Apply (ShowListSym0 :: TyFun [a6989586621680577383] (Symbol ~> Symbol) -> Type) (arg6989586621680577829 :: [a6989586621680577383]) = ShowListSym1 arg6989586621680577829 | |
type Apply (ShowListWithSym1 a6989586621680577793 :: TyFun [a6989586621680577367] (Symbol ~> Symbol) -> Type) (a6989586621680577794 :: [a6989586621680577367]) | |
Defined in Data.Singletons.Prelude.Show type Apply (ShowListWithSym1 a6989586621680577793 :: TyFun [a6989586621680577367] (Symbol ~> Symbol) -> Type) (a6989586621680577794 :: [a6989586621680577367]) = ShowListWithSym2 a6989586621680577793 a6989586621680577794 | |
type Apply (ShowsPrec_6989586621680577871Sym1 a6989586621680577868 a6989586621680577401 :: TyFun [a6989586621680577401] (Symbol ~> Symbol) -> Type) (a6989586621680577869 :: [a6989586621680577401]) | |
Defined in Data.Singletons.Prelude.Show | |
type Apply (ShowsPrec_6989586621680595739Sym1 a6989586621680595736 a3530822107858468865 :: TyFun (Maybe a3530822107858468865) (Symbol ~> Symbol) -> Type) (a6989586621680595737 :: Maybe a3530822107858468865) | |
Defined in Data.Singletons.Prelude.Show | |
type Apply (ShowsPrec_6989586621681091374Sym1 a6989586621681091371 a6989586621679060072 :: TyFun (Min a6989586621679060072) (Symbol ~> Symbol) -> Type) (a6989586621681091372 :: Min a6989586621679060072) | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Apply (ShowsPrec_6989586621681091405Sym1 a6989586621681091402 a6989586621679060077 :: TyFun (Max a6989586621679060077) (Symbol ~> Symbol) -> Type) (a6989586621681091403 :: Max a6989586621679060077) | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Apply (ShowsPrec_6989586621681091436Sym1 a6989586621681091433 a6989586621679060087 :: TyFun (First a6989586621679060087) (Symbol ~> Symbol) -> Type) (a6989586621681091434 :: First a6989586621679060087) | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Apply (ShowsPrec_6989586621681091467Sym1 a6989586621681091464 a6989586621679060082 :: TyFun (Last a6989586621679060082) (Symbol ~> Symbol) -> Type) (a6989586621681091465 :: Last a6989586621679060082) | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Apply (ShowsPrec_6989586621681091498Sym1 a6989586621681091495 m6989586621679090734 :: TyFun (WrappedMonoid m6989586621679090734) (Symbol ~> Symbol) -> Type) (a6989586621681091496 :: WrappedMonoid m6989586621679090734) | |
Defined in Data.Singletons.Prelude.Semigroup type Apply (ShowsPrec_6989586621681091498Sym1 a6989586621681091495 m6989586621679090734 :: TyFun (WrappedMonoid m6989586621679090734) (Symbol ~> Symbol) -> Type) (a6989586621681091496 :: WrappedMonoid m6989586621679090734) = ShowsPrec_6989586621681091498Sym2 a6989586621681091495 a6989586621681091496 | |
type Apply (ShowsPrec_6989586621681091194Sym1 a6989586621681091191 a6989586621679060067 :: TyFun (Option a6989586621679060067) (Symbol ~> Symbol) -> Type) (a6989586621681091192 :: Option a6989586621679060067) | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Apply (ShowsPrec_6989586621680921160Sym1 a6989586621680921157 a6989586621680920941 :: TyFun (Identity a6989586621680920941) (Symbol ~> Symbol) -> Type) (a6989586621680921158 :: Identity a6989586621680920941) | |
Defined in Data.Singletons.Prelude.Identity | |
type Apply (ShowsPrec_6989586621680637784Sym1 a6989586621680637781 a6989586621679087428 :: TyFun (First a6989586621679087428) (Symbol ~> Symbol) -> Type) (a6989586621680637782 :: First a6989586621679087428) | |
Defined in Data.Singletons.Prelude.Monoid | |
type Apply (ShowsPrec_6989586621680637815Sym1 a6989586621680637812 a6989586621679087421 :: TyFun (Last a6989586621679087421) (Symbol ~> Symbol) -> Type) (a6989586621680637813 :: Last a6989586621679087421) | |
Defined in Data.Singletons.Prelude.Monoid | |
type Apply (ShowsPrec_6989586621681091225Sym1 a6989586621681091222 a6989586621679087487 :: TyFun (Dual a6989586621679087487) (Symbol ~> Symbol) -> Type) (a6989586621681091223 :: Dual a6989586621679087487) | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Apply (ShowsPrec_6989586621681091312Sym1 a6989586621681091309 a6989586621679087464 :: TyFun (Sum a6989586621679087464) (Symbol ~> Symbol) -> Type) (a6989586621681091310 :: Sum a6989586621679087464) | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Apply (ShowsPrec_6989586621681091343Sym1 a6989586621681091340 a6989586621679087472 :: TyFun (Product a6989586621679087472) (Symbol ~> Symbol) -> Type) (a6989586621681091341 :: Product a6989586621679087472) | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Apply (ShowsPrec_6989586621680595837Sym1 a6989586621680595834 a6989586621679060153 :: TyFun (NonEmpty a6989586621679060153) (Symbol ~> Symbol) -> Type) (a6989586621680595835 :: NonEmpty a6989586621679060153) | |
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 a6989586621680577759 :: TyFun (Symbol ~> Symbol) (Symbol ~> Symbol) -> Type) (a6989586621680577760 :: Symbol ~> Symbol) | |
Defined in Data.Singletons.Prelude.Show | |
type Apply (ShowListWithSym0 :: TyFun (a6989586621680577367 ~> (Symbol ~> Symbol)) ([a6989586621680577367] ~> (Symbol ~> Symbol)) -> Type) (a6989586621680577793 :: a6989586621680577367 ~> (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_6989586621680595795Sym1 a6989586621680595792 a6989586621679091042 b6989586621679091043 :: TyFun (Either a6989586621679091042 b6989586621679091043) (Symbol ~> Symbol) -> Type) (a6989586621680595793 :: Either a6989586621679091042 b6989586621679091043) | |
Defined in Data.Singletons.Prelude.Show type Apply (ShowsPrec_6989586621680595795Sym1 a6989586621680595792 a6989586621679091042 b6989586621679091043 :: TyFun (Either a6989586621679091042 b6989586621679091043) (Symbol ~> Symbol) -> Type) (a6989586621680595793 :: Either a6989586621679091042 b6989586621679091043) = ShowsPrec_6989586621680595795Sym2 a6989586621680595792 a6989586621680595793 | |
type Apply (ShowsPrec_6989586621680577911Sym1 a6989586621680577908 a6989586621680577405 b6989586621680577406 :: TyFun (a6989586621680577405, b6989586621680577406) (Symbol ~> Symbol) -> Type) (a6989586621680577909 :: (a6989586621680577405, b6989586621680577406)) | |
Defined in Data.Singletons.Prelude.Show type Apply (ShowsPrec_6989586621680577911Sym1 a6989586621680577908 a6989586621680577405 b6989586621680577406 :: TyFun (a6989586621680577405, b6989586621680577406) (Symbol ~> Symbol) -> Type) (a6989586621680577909 :: (a6989586621680577405, b6989586621680577406)) = ShowsPrec_6989586621680577911Sym2 a6989586621680577908 a6989586621680577909 | |
type Apply (ShowsPrec_6989586621681108427Sym1 a6989586621681108424 a6989586621681107144 b6989586621681107145 :: TyFun (Arg a6989586621681107144 b6989586621681107145) (Symbol ~> Symbol) -> Type) (a6989586621681108425 :: Arg a6989586621681107144 b6989586621681107145) | |
Defined in Data.Singletons.Prelude.Semigroup type Apply (ShowsPrec_6989586621681108427Sym1 a6989586621681108424 a6989586621681107144 b6989586621681107145 :: TyFun (Arg a6989586621681107144 b6989586621681107145) (Symbol ~> Symbol) -> Type) (a6989586621681108425 :: Arg a6989586621681107144 b6989586621681107145) = ShowsPrec_6989586621681108427Sym2 a6989586621681108424 a6989586621681108425 | |
type Apply (Let6989586621680577804ShowlSym0 :: TyFun (k1 ~> (Symbol ~> Symbol)) (TyFun k2 (TyFun k3 (TyFun Symbol (TyFun [k1] Symbol -> Type) -> Type) -> Type) -> Type) -> Type) (showx6989586621680577800 :: k1 ~> (Symbol ~> Symbol)) | |
Defined in Data.Singletons.Prelude.Show type Apply (Let6989586621680577804ShowlSym0 :: TyFun (k1 ~> (Symbol ~> Symbol)) (TyFun k2 (TyFun k3 (TyFun Symbol (TyFun [k1] Symbol -> Type) -> Type) -> Type) -> Type) -> Type) (showx6989586621680577800 :: k1 ~> (Symbol ~> Symbol)) = Let6989586621680577804ShowlSym1 showx6989586621680577800 :: TyFun k2 (TyFun k3 (TyFun Symbol (TyFun [k1] Symbol -> Type) -> Type) -> Type) -> Type | |
type Apply (Lambda_6989586621680577733Sym2 a_69895866216805777296989586621680577732 ss6989586621680577731 :: TyFun (Symbol ~> c6989586621679941607) (TyFun (a6989586621679941608 ~> Symbol) (TyFun a6989586621679941608 c6989586621679941607 -> Type) -> Type) -> Type) (t6989586621680577737 :: Symbol ~> c6989586621679941607) | |
Defined in Data.Singletons.Prelude.Show type Apply (Lambda_6989586621680577733Sym2 a_69895866216805777296989586621680577732 ss6989586621680577731 :: TyFun (Symbol ~> c6989586621679941607) (TyFun (a6989586621679941608 ~> Symbol) (TyFun a6989586621679941608 c6989586621679941607 -> Type) -> Type) -> Type) (t6989586621680577737 :: Symbol ~> c6989586621679941607) = Lambda_6989586621680577733Sym3 a_69895866216805777296989586621680577732 ss6989586621680577731 t6989586621680577737 :: TyFun (a6989586621679941608 ~> Symbol) (TyFun a6989586621679941608 c6989586621679941607 -> Type) -> Type | |
type Apply (Lambda_6989586621680577733Sym3 t6989586621680577737 a_69895866216805777296989586621680577732 ss6989586621680577731 :: TyFun (a6989586621679941608 ~> Symbol) (TyFun a6989586621679941608 c6989586621679941607 -> Type) -> Type) (t6989586621680577738 :: a6989586621679941608 ~> Symbol) | |
Defined in Data.Singletons.Prelude.Show type Apply (Lambda_6989586621680577733Sym3 t6989586621680577737 a_69895866216805777296989586621680577732 ss6989586621680577731 :: TyFun (a6989586621679941608 ~> Symbol) (TyFun a6989586621679941608 c6989586621679941607 -> Type) -> Type) (t6989586621680577738 :: a6989586621679941608 ~> Symbol) = Lambda_6989586621680577733 t6989586621680577737 a_69895866216805777296989586621680577732 ss6989586621680577731 t6989586621680577738 | |
type Apply (ShowsPrec_6989586621680577928Sym1 a6989586621680577925 a6989586621680577410 b6989586621680577411 c6989586621680577412 :: TyFun (a6989586621680577410, b6989586621680577411, c6989586621680577412) (Symbol ~> Symbol) -> Type) (a6989586621680577926 :: (a6989586621680577410, b6989586621680577411, c6989586621680577412)) | |
Defined in Data.Singletons.Prelude.Show type Apply (ShowsPrec_6989586621680577928Sym1 a6989586621680577925 a6989586621680577410 b6989586621680577411 c6989586621680577412 :: TyFun (a6989586621680577410, b6989586621680577411, c6989586621680577412) (Symbol ~> Symbol) -> Type) (a6989586621680577926 :: (a6989586621680577410, b6989586621680577411, c6989586621680577412)) = ShowsPrec_6989586621680577928Sym2 a6989586621680577925 a6989586621680577926 | |
type Apply (ShowsPrec_6989586621680953659Sym1 a6989586621680953656 a6989586621680952802 b6989586621680952803 :: TyFun (Const a6989586621680952802 b6989586621680952803) (Symbol ~> Symbol) -> Type) (a6989586621680953657 :: Const a6989586621680952802 b6989586621680952803) | |
Defined in Data.Singletons.Prelude.Const type Apply (ShowsPrec_6989586621680953659Sym1 a6989586621680953656 a6989586621680952802 b6989586621680952803 :: TyFun (Const a6989586621680952802 b6989586621680952803) (Symbol ~> Symbol) -> Type) (a6989586621680953657 :: Const a6989586621680952802 b6989586621680952803) = ShowsPrec_6989586621680953659Sym2 a6989586621680953656 a6989586621680953657 | |
type Apply (ShowsPrec_6989586621680577946Sym1 a6989586621680577943 a6989586621680577417 b6989586621680577418 c6989586621680577419 d6989586621680577420 :: TyFun (a6989586621680577417, b6989586621680577418, c6989586621680577419, d6989586621680577420) (Symbol ~> Symbol) -> Type) (a6989586621680577944 :: (a6989586621680577417, b6989586621680577418, c6989586621680577419, d6989586621680577420)) | |
Defined in Data.Singletons.Prelude.Show type Apply (ShowsPrec_6989586621680577946Sym1 a6989586621680577943 a6989586621680577417 b6989586621680577418 c6989586621680577419 d6989586621680577420 :: TyFun (a6989586621680577417, b6989586621680577418, c6989586621680577419, d6989586621680577420) (Symbol ~> Symbol) -> Type) (a6989586621680577944 :: (a6989586621680577417, b6989586621680577418, c6989586621680577419, d6989586621680577420)) = ShowsPrec_6989586621680577946Sym2 a6989586621680577943 a6989586621680577944 | |
type Apply (ShowsPrec_6989586621680577965Sym1 a6989586621680577962 a6989586621680577426 b6989586621680577427 c6989586621680577428 d6989586621680577429 e6989586621680577430 :: TyFun (a6989586621680577426, b6989586621680577427, c6989586621680577428, d6989586621680577429, e6989586621680577430) (Symbol ~> Symbol) -> Type) (a6989586621680577963 :: (a6989586621680577426, b6989586621680577427, c6989586621680577428, d6989586621680577429, e6989586621680577430)) | |
Defined in Data.Singletons.Prelude.Show type Apply (ShowsPrec_6989586621680577965Sym1 a6989586621680577962 a6989586621680577426 b6989586621680577427 c6989586621680577428 d6989586621680577429 e6989586621680577430 :: TyFun (a6989586621680577426, b6989586621680577427, c6989586621680577428, d6989586621680577429, e6989586621680577430) (Symbol ~> Symbol) -> Type) (a6989586621680577963 :: (a6989586621680577426, b6989586621680577427, c6989586621680577428, d6989586621680577429, e6989586621680577430)) = ShowsPrec_6989586621680577965Sym2 a6989586621680577962 a6989586621680577963 | |
type Apply (ShowsPrec_6989586621680577985Sym1 a6989586621680577982 a6989586621680577437 b6989586621680577438 c6989586621680577439 d6989586621680577440 e6989586621680577441 f6989586621680577442 :: TyFun (a6989586621680577437, b6989586621680577438, c6989586621680577439, d6989586621680577440, e6989586621680577441, f6989586621680577442) (Symbol ~> Symbol) -> Type) (a6989586621680577983 :: (a6989586621680577437, b6989586621680577438, c6989586621680577439, d6989586621680577440, e6989586621680577441, f6989586621680577442)) | |
Defined in Data.Singletons.Prelude.Show type Apply (ShowsPrec_6989586621680577985Sym1 a6989586621680577982 a6989586621680577437 b6989586621680577438 c6989586621680577439 d6989586621680577440 e6989586621680577441 f6989586621680577442 :: TyFun (a6989586621680577437, b6989586621680577438, c6989586621680577439, d6989586621680577440, e6989586621680577441, f6989586621680577442) (Symbol ~> Symbol) -> Type) (a6989586621680577983 :: (a6989586621680577437, b6989586621680577438, c6989586621680577439, d6989586621680577440, e6989586621680577441, f6989586621680577442)) = ShowsPrec_6989586621680577985Sym2 a6989586621680577982 a6989586621680577983 | |
type Apply (ShowsPrec_6989586621680578006Sym1 a6989586621680578003 a6989586621680577450 b6989586621680577451 c6989586621680577452 d6989586621680577453 e6989586621680577454 f6989586621680577455 g6989586621680577456 :: TyFun (a6989586621680577450, b6989586621680577451, c6989586621680577452, d6989586621680577453, e6989586621680577454, f6989586621680577455, g6989586621680577456) (Symbol ~> Symbol) -> Type) (a6989586621680578004 :: (a6989586621680577450, b6989586621680577451, c6989586621680577452, d6989586621680577453, e6989586621680577454, f6989586621680577455, g6989586621680577456)) | |
Defined in Data.Singletons.Prelude.Show type Apply (ShowsPrec_6989586621680578006Sym1 a6989586621680578003 a6989586621680577450 b6989586621680577451 c6989586621680577452 d6989586621680577453 e6989586621680577454 f6989586621680577455 g6989586621680577456 :: TyFun (a6989586621680577450, b6989586621680577451, c6989586621680577452, d6989586621680577453, e6989586621680577454, f6989586621680577455, g6989586621680577456) (Symbol ~> Symbol) -> Type) (a6989586621680578004 :: (a6989586621680577450, b6989586621680577451, c6989586621680577452, d6989586621680577453, e6989586621680577454, f6989586621680577455, g6989586621680577456)) = ShowsPrec_6989586621680578006Sym2 a6989586621680578003 a6989586621680578004 |
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.