Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Re-exports GHC.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
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 | |
PMonoid Symbol | |
SMonoid Symbol | |
PSemigroup Symbol | |
Defined in Data.Semigroup.Singletons.Internal | |
SSemigroup Symbol | |
PShow Symbol | |
SShow Symbol | |
Defined in Text.Show.Singletons 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) # | |
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 | |
(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 () # | |
(KnownSymbol s, Monoid t) => Monoid (ElField '(s, t)) | |
Semigroup t => Semigroup (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) # | |
KnownSymbol s => Generic (ElField '(s, a)) | |
(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) # | |
(Fractional t, KnownSymbol s) => Fractional (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)) | |
Eq t => Eq (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) # | |
SingI ShowParenSym0 | |
Defined in Text.Show.Singletons sing :: Sing ShowParenSym0 # | |
SingI ShowCharSym0 | |
Defined in Text.Show.Singletons sing :: Sing ShowCharSym0 # | |
SingI ShowStringSym0 | |
Defined in Text.Show.Singletons sing :: Sing ShowStringSym0 # | |
SingI ShowCommaSpaceSym0 | |
Defined in Text.Show.Singletons | |
SingI ShowSpaceSym0 | |
Defined in Text.Show.Singletons sing :: Sing ShowSpaceSym0 # | |
SingI Show_tupleSym0 | |
Defined in Text.Show.Singletons | |
SingI UnlinesSym0 | |
Defined in Data.List.Singletons.Internal sing :: Sing UnlinesSym0 # | |
SingI UnwordsSym0 | |
Defined in Data.List.Singletons.Internal sing :: Sing UnwordsSym0 # | |
SuppressUnusedWarnings ShowParenSym0 | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings ShowsPrec_6989586621680582204Sym0 | |
Defined in Data.Semigroup.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings ShowsPrec_6989586621680582228Sym0 | |
Defined in Data.Semigroup.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings ShowsPrec_6989586621680071884Sym0 | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings ShowsPrec_6989586621680071856Sym0 | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings ShowsPrec_6989586621680071694Sym0 | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings ShowsPrec_6989586621680071834Sym0 | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings ShowsPrec_6989586621680047588Sym0 | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings ShowsNatSym0 | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings ShowCharSym0 | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings ShowStringSym0 | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings KnownSymbolSym0 | |
Defined in GHC.TypeLits.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings ShowCommaSpaceSym0 | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings ShowSpaceSym0 | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings Show_tupleSym0 | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings UnlinesSym0 | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings UnwordsSym0 | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
KnownSymbol s => IsoHKD ElField ('(s, a) :: (Symbol, Type)) | Work with values of type |
SingI d => SingI (ShowParenSym1 d :: TyFun (Symbol ~> Symbol) (Symbol ~> Symbol) -> Type) | |
Defined in Text.Show.Singletons sing :: Sing (ShowParenSym1 d) # | |
SingI (ShowListWithSym0 :: TyFun (a ~> (Symbol ~> Symbol)) ([a] ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Text.Show.Singletons | |
SShow a => SingI (ShowsPrecSym0 :: TyFun Nat (a ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Text.Show.Singletons sing :: Sing ShowsPrecSym0 # | |
SingI d => SingI (ShowCharSym1 d :: TyFun Symbol Symbol -> Type) | |
Defined in Text.Show.Singletons sing :: Sing (ShowCharSym1 d) # | |
SingI d => SingI (ShowStringSym1 d :: TyFun Symbol Symbol -> Type) | |
Defined in Text.Show.Singletons sing :: Sing (ShowStringSym1 d) # | |
SingI d => SingI (Show_tupleSym1 d :: TyFun Symbol Symbol -> Type) | |
Defined in Text.Show.Singletons | |
SShow a => SingI (ShowListSym0 :: TyFun [a] (Symbol ~> Symbol) -> Type) | |
Defined in Text.Show.Singletons sing :: Sing ShowListSym0 # | |
SShow a => SingI (ShowsSym0 :: TyFun a (Symbol ~> Symbol) -> Type) | |
Defined in Text.Show.Singletons | |
SShow a => SingI (Show_Sym0 :: TyFun a Symbol -> Type) | |
Defined in Text.Show.Singletons | |
SuppressUnusedWarnings (ShowsPrec_6989586621680582204Sym1 a6989586621680582212 :: TyFun All (Symbol ~> Symbol) -> Type) | |
Defined in Data.Semigroup.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680582228Sym1 a6989586621680582236 :: TyFun Any (Symbol ~> Symbol) -> Type) | |
Defined in Data.Semigroup.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680071884Sym1 a6989586621680071892 :: TyFun Void (Symbol ~> Symbol) -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680071856Sym1 a6989586621680071868 :: TyFun Ordering (Symbol ~> Symbol) -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowParenSym1 a6989586621680047463 :: TyFun (Symbol ~> Symbol) (Symbol ~> Symbol) -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowListWithSym0 :: TyFun (a ~> (Symbol ~> Symbol)) ([a] ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680071694Sym1 a6989586621680071702 :: TyFun () (Symbol ~> Symbol) -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680071834Sym1 a6989586621680071844 :: TyFun Bool (Symbol ~> Symbol) -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680390927Sym0 :: TyFun Nat (Identity a ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Functor.Identity.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680113533Sym0 :: TyFun Nat (First a ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Monoid.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680113571Sym0 :: TyFun Nat (Last a ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Monoid.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680582363Sym0 :: TyFun Nat (First a ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Semigroup.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680582390Sym0 :: TyFun Nat (Last a ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Semigroup.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680582336Sym0 :: TyFun Nat (Max a ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Semigroup.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680582309Sym0 :: TyFun Nat (Min a ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Semigroup.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680582417Sym0 :: TyFun Nat (WrappedMonoid m ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Semigroup.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680582180Sym0 :: TyFun Nat (Dual a ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Semigroup.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680582282Sym0 :: TyFun Nat (Product a ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Semigroup.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680582255Sym0 :: TyFun Nat (Sum a ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Semigroup.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680071810Sym0 :: TyFun Nat (NonEmpty a ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680071724Sym0 :: TyFun Nat (Maybe a ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680047570Sym0 :: TyFun Nat ([a] ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrecSym0 :: TyFun Nat (a ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680047538Sym0 :: TyFun Nat (a ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680047588Sym1 a6989586621680047598 :: TyFun Symbol (Symbol ~> Symbol) -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowCharSym1 a6989586621680047490 :: TyFun Symbol Symbol -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowStringSym1 a6989586621680047479 :: TyFun Symbol Symbol -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Show_tupleSym1 a6989586621680047430 :: TyFun Symbol Symbol -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsNatSym1 a6989586621680070274 :: TyFun Symbol Symbol -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowListSym0 :: TyFun [a] (Symbol ~> Symbol) -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowList_6989586621680047558Sym0 :: TyFun [a] (Symbol ~> Symbol) -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsSym0 :: TyFun a (Symbol ~> Symbol) -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Show_Sym0 :: TyFun a Symbol -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Show__6989586621680047550Sym0 :: TyFun a Symbol -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Lambda_6989586621680047453Sym0 :: TyFun k (TyFun Symbol Symbol -> Type) -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
(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 # | |
(SShow a, SingI d) => SingI (ShowListSym1 d :: TyFun Symbol Symbol -> Type) | |
Defined in Text.Show.Singletons sing :: Sing (ShowListSym1 d) # | |
(SingI d1, SingI d2) => SingI (ShowParenSym2 d1 d2 :: TyFun Symbol Symbol -> Type) | |
Defined in Text.Show.Singletons sing :: Sing (ShowParenSym2 d1 d2) # | |
(SShow a, SingI d) => SingI (ShowsSym1 d :: TyFun Symbol Symbol -> Type) | |
Defined in Text.Show.Singletons | |
SingI (ErrorSym0 :: TyFun Symbol a -> Type) | |
Defined in GHC.TypeLits.Singletons.Internal | |
SingI (ErrorWithoutStackTraceSym0 :: TyFun Symbol a -> Type) | |
Defined in GHC.TypeLits.Singletons.Internal | |
SingI d => SingI (ShowListWithSym1 d :: TyFun [a] (Symbol ~> Symbol) -> Type) | |
Defined in Text.Show.Singletons sing :: Sing (ShowListWithSym1 d) # | |
(SShow a, SingI d) => SingI (ShowsPrecSym1 d :: TyFun a (Symbol ~> Symbol) -> Type) | |
Defined in Text.Show.Singletons sing :: Sing (ShowsPrecSym1 d) # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680390927Sym1 a6989586621680390935 :: TyFun (Identity a) (Symbol ~> Symbol) -> Type) | |
Defined in Data.Functor.Identity.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680113533Sym1 a6989586621680113541 :: TyFun (First a) (Symbol ~> Symbol) -> Type) | |
Defined in Data.Monoid.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680113571Sym1 a6989586621680113579 :: TyFun (Last a) (Symbol ~> Symbol) -> Type) | |
Defined in Data.Monoid.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680582363Sym1 a6989586621680582371 :: TyFun (First a) (Symbol ~> Symbol) -> Type) | |
Defined in Data.Semigroup.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680582390Sym1 a6989586621680582398 :: TyFun (Last a) (Symbol ~> Symbol) -> Type) | |
Defined in Data.Semigroup.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680582336Sym1 a6989586621680582344 :: TyFun (Max a) (Symbol ~> Symbol) -> Type) | |
Defined in Data.Semigroup.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680582309Sym1 a6989586621680582317 :: TyFun (Min a) (Symbol ~> Symbol) -> Type) | |
Defined in Data.Semigroup.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680582417Sym1 a6989586621680582425 :: TyFun (WrappedMonoid m) (Symbol ~> Symbol) -> Type) | |
Defined in Data.Semigroup.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680582180Sym1 a6989586621680582188 :: TyFun (Dual a) (Symbol ~> Symbol) -> Type) | |
Defined in Data.Semigroup.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680582282Sym1 a6989586621680582290 :: TyFun (Product a) (Symbol ~> Symbol) -> Type) | |
Defined in Data.Semigroup.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680582255Sym1 a6989586621680582263 :: TyFun (Sum a) (Symbol ~> Symbol) -> Type) | |
Defined in Data.Semigroup.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680071810Sym1 a6989586621680071818 :: TyFun (NonEmpty a) (Symbol ~> Symbol) -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680071724Sym1 a6989586621680071734 :: TyFun (Maybe a) (Symbol ~> Symbol) -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680071774Sym0 :: TyFun Nat (Either a b ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680163487Sym0 :: TyFun Nat (Proxy s ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Proxy.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680605456Sym0 :: TyFun Nat (Arg a b ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Semigroup.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680047606Sym0 :: TyFun Nat ((a, b) ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Lambda_6989586621680047453Sym1 a_69895866216800474476989586621680047452 :: TyFun Symbol Symbol -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680582204Sym2 a6989586621680582212 a6989586621680582213 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Semigroup.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680582228Sym2 a6989586621680582236 a6989586621680582237 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Semigroup.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowListSym1 a6989586621680047533 :: TyFun Symbol Symbol -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowList_6989586621680047558Sym1 a6989586621680047563 :: TyFun Symbol Symbol -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowParenSym2 a6989586621680047463 a6989586621680047464 :: TyFun Symbol Symbol -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680047588Sym2 a6989586621680047598 a6989586621680047599 :: TyFun Symbol Symbol -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680071694Sym2 a6989586621680071702 a6989586621680071703 :: TyFun Symbol Symbol -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680071834Sym2 a6989586621680071844 a6989586621680071845 :: TyFun Symbol Symbol -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680071856Sym2 a6989586621680071868 a6989586621680071869 :: TyFun Symbol Symbol -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680071884Sym2 a6989586621680071892 a6989586621680071893 :: TyFun Symbol Symbol -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsSym1 a6989586621680047516 :: TyFun Symbol Symbol -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowListWithSym1 a6989586621680047498 :: TyFun [a] (Symbol ~> Symbol) -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680047570Sym1 a6989586621680047580 :: TyFun [a] (Symbol ~> Symbol) -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrecSym1 a6989586621680047524 :: TyFun a (Symbol ~> Symbol) -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680047538Sym1 a6989586621680047544 :: TyFun a (Symbol ~> Symbol) -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679731625GoSym0 :: TyFun k1 (TyFun k2 (TyFun [Symbol] Symbol -> Type) -> Type) -> Type) | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
(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 # | |
(SingI d1, SingI d2) => SingI (ShowListWithSym2 d1 d2 :: TyFun Symbol Symbol -> Type) | |
Defined in Text.Show.Singletons sing :: Sing (ShowListWithSym2 d1 d2) # | |
(SShow a, SingI d1, SingI d2) => SingI (ShowsPrecSym2 d1 d2 :: TyFun Symbol Symbol -> Type) | |
Defined in Text.Show.Singletons sing :: Sing (ShowsPrecSym2 d1 d2) # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680071774Sym1 a6989586621680071784 :: TyFun (Either a b) (Symbol ~> Symbol) -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680163487Sym1 a6989586621680163495 :: TyFun (Proxy s) (Symbol ~> Symbol) -> Type) | |
Defined in Data.Proxy.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680605456Sym1 a6989586621680605464 :: TyFun (Arg a b) (Symbol ~> Symbol) -> Type) | |
Defined in Data.Semigroup.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621680047506ShowlSym0 :: TyFun (k1 ~> (Symbol ~> Symbol)) (TyFun k2 (TyFun k3 (TyFun Symbol (TyFun [k1] Symbol -> Type) -> Type) -> Type) -> Type) -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680047606Sym1 a6989586621680047612 :: TyFun (a, b) (Symbol ~> Symbol) -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680428701Sym0 :: TyFun Nat (Const a b ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Functor.Const.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680047621Sym0 :: TyFun Nat ((a, b, c) ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680390927Sym2 a6989586621680390935 a6989586621680390936 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Functor.Identity.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680113533Sym2 a6989586621680113541 a6989586621680113542 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Monoid.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680113571Sym2 a6989586621680113579 a6989586621680113580 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Monoid.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680582180Sym2 a6989586621680582188 a6989586621680582189 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Semigroup.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680582255Sym2 a6989586621680582263 a6989586621680582264 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Semigroup.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680582282Sym2 a6989586621680582290 a6989586621680582291 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Semigroup.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680582309Sym2 a6989586621680582317 a6989586621680582318 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Semigroup.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680582336Sym2 a6989586621680582344 a6989586621680582345 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Semigroup.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680582363Sym2 a6989586621680582371 a6989586621680582372 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Semigroup.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680582390Sym2 a6989586621680582398 a6989586621680582399 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Semigroup.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680582417Sym2 a6989586621680582425 a6989586621680582426 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Semigroup.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowListWithSym2 a6989586621680047498 a6989586621680047499 :: TyFun Symbol Symbol -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrecSym2 a6989586621680047524 a6989586621680047525 :: TyFun Symbol Symbol -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680047538Sym2 a6989586621680047544 a6989586621680047545 :: TyFun Symbol Symbol -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680047570Sym2 a6989586621680047580 a6989586621680047581 :: TyFun Symbol Symbol -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680071724Sym2 a6989586621680071734 a6989586621680071735 :: TyFun Symbol Symbol -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680071810Sym2 a6989586621680071818 a6989586621680071819 :: TyFun Symbol Symbol -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679731625GoSym1 w6989586621679731623 :: TyFun k2 (TyFun [Symbol] Symbol -> Type) -> Type) | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680428701Sym1 a6989586621680428709 :: TyFun (Const a b) (Symbol ~> Symbol) -> Type) | |
Defined in Data.Functor.Const.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680047621Sym1 a6989586621680047627 :: TyFun (a, b, c) (Symbol ~> Symbol) -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680047637Sym0 :: TyFun Nat ((a, b, c, d) ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680163487Sym2 a6989586621680163495 a6989586621680163496 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Proxy.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680605456Sym2 a6989586621680605464 a6989586621680605465 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Semigroup.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680047606Sym2 a6989586621680047612 a6989586621680047613 :: TyFun Symbol Symbol -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680071774Sym2 a6989586621680071784 a6989586621680071785 :: TyFun Symbol Symbol -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679731625GoSym2 w6989586621679731623 ws6989586621679731624 :: TyFun [Symbol] Symbol -> Type) | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Lambda_6989586621680047434Sym0 :: TyFun k1 (TyFun k2 (TyFun (Symbol ~> c) (TyFun (a ~> Symbol) (a ~> c) -> Type) -> Type) -> Type) -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621680047506ShowlSym1 showx6989586621680047502 :: TyFun k2 (TyFun k3 (TyFun Symbol (TyFun [k1] Symbol -> Type) -> Type) -> Type) -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680047637Sym1 a6989586621680047643 :: TyFun (a, b, c, d) (Symbol ~> Symbol) -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680047654Sym0 :: TyFun Nat ((a, b, c, d, e) ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680428701Sym2 a6989586621680428709 a6989586621680428710 :: TyFun Symbol Symbol -> Type) | |
Defined in Data.Functor.Const.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680047621Sym2 a6989586621680047627 a6989586621680047628 :: TyFun Symbol Symbol -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Lambda_6989586621680047434Sym1 ss6989586621680047432 :: TyFun k2 (TyFun (Symbol ~> c) (TyFun (a ~> Symbol) (a ~> c) -> Type) -> Type) -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621680047506ShowlSym2 showx6989586621680047502 x6989586621680047503 :: TyFun k3 (TyFun Symbol (TyFun [k1] Symbol -> Type) -> Type) -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Lambda_6989586621680047434Sym2 ss6989586621680047432 a_69895866216800474256989586621680047433 :: TyFun (Symbol ~> c) (TyFun (a ~> Symbol) (a ~> c) -> Type) -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680047654Sym1 a6989586621680047660 :: TyFun (a, b, c, d, e) (Symbol ~> Symbol) -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680047672Sym0 :: TyFun Nat ((a, b, c, d, e, f) ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621680047506ShowlSym3 showx6989586621680047502 x6989586621680047503 xs6989586621680047504 :: TyFun Symbol (TyFun [k1] Symbol -> Type) -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680047637Sym2 a6989586621680047643 a6989586621680047644 :: TyFun Symbol Symbol -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Lambda_6989586621680047434Sym3 ss6989586621680047432 a_69895866216800474256989586621680047433 s6989586621680047436 :: TyFun (a ~> Symbol) (a ~> c) -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680047672Sym1 a6989586621680047678 :: TyFun (a, b, c, d, e, f) (Symbol ~> Symbol) -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680047691Sym0 :: TyFun Nat ((a, b, c, d, e, f, g) ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680047654Sym2 a6989586621680047660 a6989586621680047661 :: TyFun Symbol Symbol -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621680047506ShowlSym4 showx6989586621680047502 x6989586621680047503 xs6989586621680047504 s6989586621680047505 :: TyFun [k1] Symbol -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680047691Sym1 a6989586621680047697 :: TyFun (a, b, c, d, e, f, g) (Symbol ~> Symbol) -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680047672Sym2 a6989586621680047678 a6989586621680047679 :: TyFun Symbol Symbol -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680047691Sym2 a6989586621680047697 a6989586621680047698 :: TyFun Symbol Symbol -> Type) | |
Defined in Text.Show.Singletons suppressUnusedWarnings :: () # | |
(TypeHasDoc a, KnownSymbol field) => GProductHasDoc (S1 ('MetaSel ('Just field) _1 _2 _3) (Rec0 a)) Source # | |
Defined in Morley.Michelson.Typed.Haskell.Doc gProductDocHaskellRep :: [(Text, Text)] -> [FieldRep SomeTypeWithDoc] | |
TypeHasDoc a => GProductHasDoc (S1 ('MetaSel ('Nothing :: Maybe Symbol) _1 _2 _3) (Rec0 a)) Source # | |
Defined in Morley.Michelson.Typed.Haskell.Doc gProductDocHaskellRep :: [(Text, Text)] -> [FieldRep SomeTypeWithDoc] | |
type DemoteRep Symbol | |
Defined in GHC.Generics | |
data Sing (s :: Symbol) | |
Defined in GHC.Generics | |
type MEmpty | |
Defined in Fcf.Class.Monoid type MEmpty = "" | |
type Demote Symbol | |
Defined in GHC.TypeLits.Singletons.Internal | |
type Sing | |
Defined in GHC.TypeLits.Singletons.Internal | |
type Mempty | |
Defined in Data.Monoid.Singletons type Mempty = Mempty_6989586621680102646Sym0 | |
type Mconcat (arg :: [Symbol]) | |
type Sconcat (arg :: NonEmpty Symbol) | |
type Show_ (arg :: Symbol) | |
type (x :: Symbol) <> (y :: Symbol) | With base >= 4.10.0.0. |
Defined in Fcf.Class.Monoid | |
type (arg :: Symbol) /= (arg1 :: Symbol) | |
type (x :: Symbol) == (y :: Symbol) | |
Defined in GHC.TypeLits.Singletons.Internal | |
type Mappend (arg1 :: Symbol) (arg2 :: Symbol) | |
type (arg :: Symbol) < (arg1 :: Symbol) | |
type (arg :: Symbol) <= (arg1 :: Symbol) | |
type (arg :: Symbol) > (arg1 :: Symbol) | |
type (arg :: Symbol) >= (arg1 :: Symbol) | |
type Compare (a :: Symbol) (b :: Symbol) | |
Defined in GHC.TypeLits.Singletons.Internal | |
type Max (arg :: Symbol) (arg1 :: Symbol) | |
type Min (arg :: Symbol) (arg1 :: Symbol) | |
type (a :: Symbol) <> (b :: Symbol) | |
Defined in Data.Semigroup.Singletons.Internal | |
type ShowList (arg1 :: [Symbol]) arg2 | |
type Apply KnownSymbolSym0 (a6989586621679476395 :: Symbol) | |
Defined in GHC.TypeLits.Singletons | |
type Apply ShowCommaSpaceSym0 (a6989586621680047445 :: Symbol) | |
Defined in Text.Show.Singletons type Apply ShowCommaSpaceSym0 (a6989586621680047445 :: Symbol) = ShowCommaSpace a6989586621680047445 | |
type Apply ShowSpaceSym0 (a6989586621680047451 :: Symbol) | |
Defined in Text.Show.Singletons | |
type ShowsPrec a1 (a2 :: Symbol) a3 | |
type Apply (ShowCharSym1 a6989586621680047490 :: TyFun Symbol Symbol -> Type) (a6989586621680047491 :: Symbol) | |
Defined in Text.Show.Singletons | |
type Apply (ShowStringSym1 a6989586621680047479 :: TyFun Symbol Symbol -> Type) (a6989586621680047480 :: Symbol) | |
Defined in Text.Show.Singletons type Apply (ShowStringSym1 a6989586621680047479 :: TyFun Symbol Symbol -> Type) (a6989586621680047480 :: Symbol) = ShowString a6989586621680047479 a6989586621680047480 | |
type Apply (Show_tupleSym1 a6989586621680047430 :: TyFun Symbol Symbol -> Type) (a6989586621680047431 :: Symbol) | |
type Apply (ShowsNatSym1 a6989586621680070274 :: TyFun Symbol Symbol -> Type) (a6989586621680070275 :: Symbol) | |
type Apply (Show_Sym0 :: TyFun a Symbol -> Type) (a6989586621680047529 :: a) | |
type Apply (Show__6989586621680047550Sym0 :: TyFun a Symbol -> Type) (a6989586621680047554 :: a) | |
Defined in Text.Show.Singletons | |
type Apply (ShowsPrec_6989586621680582204Sym2 a6989586621680582212 a6989586621680582213 :: TyFun Symbol Symbol -> Type) (a6989586621680582214 :: Symbol) | |
type Apply (ShowsPrec_6989586621680582228Sym2 a6989586621680582236 a6989586621680582237 :: TyFun Symbol Symbol -> Type) (a6989586621680582238 :: Symbol) | |
type Apply (Lambda_6989586621680047453Sym1 a_69895866216800474476989586621680047452 :: TyFun Symbol Symbol -> Type) (xs6989586621680047455 :: Symbol) | |
type Apply (ShowListSym1 a6989586621680047533 :: TyFun Symbol Symbol -> Type) (a6989586621680047534 :: Symbol) | |
Defined in Text.Show.Singletons | |
type Apply (ShowList_6989586621680047558Sym1 a6989586621680047563 :: TyFun Symbol Symbol -> Type) (a6989586621680047564 :: Symbol) | |
type Apply (ShowParenSym2 a6989586621680047463 a6989586621680047464 :: TyFun Symbol Symbol -> Type) (a6989586621680047465 :: Symbol) | |
Defined in Text.Show.Singletons | |
type Apply (ShowsPrec_6989586621680047588Sym2 a6989586621680047598 a6989586621680047599 :: TyFun Symbol Symbol -> Type) (a6989586621680047600 :: Symbol) | |
type Apply (ShowsPrec_6989586621680071694Sym2 a6989586621680071702 a6989586621680071703 :: TyFun Symbol Symbol -> Type) (a6989586621680071704 :: Symbol) | |
type Apply (ShowsPrec_6989586621680071834Sym2 a6989586621680071844 a6989586621680071845 :: TyFun Symbol Symbol -> Type) (a6989586621680071846 :: Symbol) | |
type Apply (ShowsPrec_6989586621680071856Sym2 a6989586621680071868 a6989586621680071869 :: TyFun Symbol Symbol -> Type) (a6989586621680071870 :: Symbol) | |
type Apply (ShowsPrec_6989586621680071884Sym2 a6989586621680071892 a6989586621680071893 :: TyFun Symbol Symbol -> Type) (a6989586621680071894 :: Symbol) | |
type Apply (ShowsSym1 a6989586621680047516 :: TyFun Symbol Symbol -> Type) (a6989586621680047517 :: Symbol) | |
type Apply (ShowsPrec_6989586621680390927Sym2 a6989586621680390935 a6989586621680390936 :: TyFun Symbol Symbol -> Type) (a6989586621680390937 :: Symbol) | |
type Apply (ShowsPrec_6989586621680113533Sym2 a6989586621680113541 a6989586621680113542 :: TyFun Symbol Symbol -> Type) (a6989586621680113543 :: Symbol) | |
type Apply (ShowsPrec_6989586621680113571Sym2 a6989586621680113579 a6989586621680113580 :: TyFun Symbol Symbol -> Type) (a6989586621680113581 :: Symbol) | |
type Apply (ShowsPrec_6989586621680582180Sym2 a6989586621680582188 a6989586621680582189 :: TyFun Symbol Symbol -> Type) (a6989586621680582190 :: Symbol) | |
type Apply (ShowsPrec_6989586621680582255Sym2 a6989586621680582263 a6989586621680582264 :: TyFun Symbol Symbol -> Type) (a6989586621680582265 :: Symbol) | |
type Apply (ShowsPrec_6989586621680582282Sym2 a6989586621680582290 a6989586621680582291 :: TyFun Symbol Symbol -> Type) (a6989586621680582292 :: Symbol) | |
type Apply (ShowsPrec_6989586621680582309Sym2 a6989586621680582317 a6989586621680582318 :: TyFun Symbol Symbol -> Type) (a6989586621680582319 :: Symbol) | |
type Apply (ShowsPrec_6989586621680582336Sym2 a6989586621680582344 a6989586621680582345 :: TyFun Symbol Symbol -> Type) (a6989586621680582346 :: Symbol) | |
type Apply (ShowsPrec_6989586621680582363Sym2 a6989586621680582371 a6989586621680582372 :: TyFun Symbol Symbol -> Type) (a6989586621680582373 :: Symbol) | |
type Apply (ShowsPrec_6989586621680582390Sym2 a6989586621680582398 a6989586621680582399 :: TyFun Symbol Symbol -> Type) (a6989586621680582400 :: Symbol) | |
type Apply (ShowsPrec_6989586621680582417Sym2 a6989586621680582425 a6989586621680582426 :: TyFun Symbol Symbol -> Type) (a6989586621680582427 :: Symbol) | |
type Apply (ShowListWithSym2 a6989586621680047498 a6989586621680047499 :: TyFun Symbol Symbol -> Type) (a6989586621680047500 :: Symbol) | |
Defined in Text.Show.Singletons type Apply (ShowListWithSym2 a6989586621680047498 a6989586621680047499 :: TyFun Symbol Symbol -> Type) (a6989586621680047500 :: Symbol) = ShowListWith a6989586621680047498 a6989586621680047499 a6989586621680047500 | |
type Apply (ShowsPrecSym2 a6989586621680047524 a6989586621680047525 :: TyFun Symbol Symbol -> Type) (a6989586621680047526 :: Symbol) | |
Defined in Text.Show.Singletons | |
type Apply (ShowsPrec_6989586621680047538Sym2 a6989586621680047544 a6989586621680047545 :: TyFun Symbol Symbol -> Type) (a6989586621680047546 :: Symbol) | |
type Apply (ShowsPrec_6989586621680047570Sym2 a6989586621680047580 a6989586621680047581 :: TyFun Symbol Symbol -> Type) (a6989586621680047582 :: Symbol) | |
type Apply (ShowsPrec_6989586621680071724Sym2 a6989586621680071734 a6989586621680071735 :: TyFun Symbol Symbol -> Type) (a6989586621680071736 :: Symbol) | |
type Apply (ShowsPrec_6989586621680071810Sym2 a6989586621680071818 a6989586621680071819 :: TyFun Symbol Symbol -> Type) (a6989586621680071820 :: Symbol) | |
type Apply (ShowsPrec_6989586621680163487Sym2 a6989586621680163495 a6989586621680163496 :: TyFun Symbol Symbol -> Type) (a6989586621680163497 :: Symbol) | |
type Apply (ShowsPrec_6989586621680605456Sym2 a6989586621680605464 a6989586621680605465 :: TyFun Symbol Symbol -> Type) (a6989586621680605466 :: Symbol) | |
type Apply (ShowsPrec_6989586621680047606Sym2 a6989586621680047612 a6989586621680047613 :: TyFun Symbol Symbol -> Type) (a6989586621680047614 :: Symbol) | |
type Apply (ShowsPrec_6989586621680071774Sym2 a6989586621680071784 a6989586621680071785 :: TyFun Symbol Symbol -> Type) (a6989586621680071786 :: Symbol) | |
type Apply (ShowsPrec_6989586621680428701Sym2 a6989586621680428709 a6989586621680428710 :: TyFun Symbol Symbol -> Type) (a6989586621680428711 :: Symbol) | |
type Apply (ShowsPrec_6989586621680047621Sym2 a6989586621680047627 a6989586621680047628 :: TyFun Symbol Symbol -> Type) (a6989586621680047629 :: Symbol) | |
type Apply (ShowsPrec_6989586621680047637Sym2 a6989586621680047643 a6989586621680047644 :: TyFun Symbol Symbol -> Type) (a6989586621680047645 :: Symbol) | |
type Apply (ShowsPrec_6989586621680047654Sym2 a6989586621680047660 a6989586621680047661 :: TyFun Symbol Symbol -> Type) (a6989586621680047662 :: Symbol) | |
type Apply (ShowsPrec_6989586621680047672Sym2 a6989586621680047678 a6989586621680047679 :: TyFun Symbol Symbol -> Type) (a6989586621680047680 :: Symbol) | |
type Apply (ShowsPrec_6989586621680047691Sym2 a6989586621680047697 a6989586621680047698 :: TyFun Symbol Symbol -> Type) (a6989586621680047699 :: Symbol) | |
type Apply ShowParenSym0 (a6989586621680047463 :: Bool) | |
Defined in Text.Show.Singletons | |
type Apply ShowsPrec_6989586621680582204Sym0 (a6989586621680582212 :: Nat) | |
Defined in Data.Semigroup.Singletons | |
type Apply ShowsPrec_6989586621680582228Sym0 (a6989586621680582236 :: Nat) | |
Defined in Data.Semigroup.Singletons | |
type Apply ShowsPrec_6989586621680071884Sym0 (a6989586621680071892 :: Nat) | |
Defined in Text.Show.Singletons | |
type Apply ShowsPrec_6989586621680071856Sym0 (a6989586621680071868 :: Nat) | |
Defined in Text.Show.Singletons | |
type Apply ShowsPrec_6989586621680071694Sym0 (a6989586621680071702 :: Nat) | |
Defined in Text.Show.Singletons | |
type Apply ShowsPrec_6989586621680071834Sym0 (a6989586621680071844 :: Nat) | |
Defined in Text.Show.Singletons | |
type Apply ShowsPrec_6989586621680047588Sym0 (a6989586621680047598 :: Nat) | |
Defined in Text.Show.Singletons | |
type Apply ShowsNatSym0 (a6989586621680070274 :: Nat) | |
Defined in Text.Show.Singletons | |
type Apply ShowCharSym0 (a6989586621680047490 :: Symbol) | |
Defined in Text.Show.Singletons | |
type Apply ShowStringSym0 (a6989586621680047479 :: Symbol) | |
Defined in Text.Show.Singletons | |
type Apply (ShowsPrec_6989586621680582204Sym1 a6989586621680582212 :: TyFun All (Symbol ~> Symbol) -> Type) (a6989586621680582213 :: All) | |
type Apply (ShowsPrec_6989586621680582228Sym1 a6989586621680582236 :: TyFun Any (Symbol ~> Symbol) -> Type) (a6989586621680582237 :: Any) | |
type Apply (ShowsPrec_6989586621680071884Sym1 a6989586621680071892 :: TyFun Void (Symbol ~> Symbol) -> Type) (a6989586621680071893 :: Void) | |
type Apply (ShowsPrec_6989586621680071856Sym1 a6989586621680071868 :: TyFun Ordering (Symbol ~> Symbol) -> Type) (a6989586621680071869 :: Ordering) | |
type Apply (ShowsPrec_6989586621680071694Sym1 a6989586621680071702 :: TyFun () (Symbol ~> Symbol) -> Type) (a6989586621680071703 :: ()) | |
type Apply (ShowsPrec_6989586621680071834Sym1 a6989586621680071844 :: TyFun Bool (Symbol ~> Symbol) -> Type) (a6989586621680071845 :: Bool) | |
type Apply (ShowsPrec_6989586621680390927Sym0 :: TyFun Nat (Identity a ~> (Symbol ~> Symbol)) -> Type) (a6989586621680390935 :: Nat) | |
type Apply (ShowsPrec_6989586621680113533Sym0 :: TyFun Nat (First a ~> (Symbol ~> Symbol)) -> Type) (a6989586621680113541 :: Nat) | |
type Apply (ShowsPrec_6989586621680113571Sym0 :: TyFun Nat (Last a ~> (Symbol ~> Symbol)) -> Type) (a6989586621680113579 :: Nat) | |
type Apply (ShowsPrec_6989586621680582363Sym0 :: TyFun Nat (First a ~> (Symbol ~> Symbol)) -> Type) (a6989586621680582371 :: Nat) | |
type Apply (ShowsPrec_6989586621680582390Sym0 :: TyFun Nat (Last a ~> (Symbol ~> Symbol)) -> Type) (a6989586621680582398 :: Nat) | |
type Apply (ShowsPrec_6989586621680582336Sym0 :: TyFun Nat (Max a ~> (Symbol ~> Symbol)) -> Type) (a6989586621680582344 :: Nat) | |
type Apply (ShowsPrec_6989586621680582309Sym0 :: TyFun Nat (Min a ~> (Symbol ~> Symbol)) -> Type) (a6989586621680582317 :: Nat) | |
type Apply (ShowsPrec_6989586621680582417Sym0 :: TyFun Nat (WrappedMonoid m ~> (Symbol ~> Symbol)) -> Type) (a6989586621680582425 :: Nat) | |
type Apply (ShowsPrec_6989586621680582180Sym0 :: TyFun Nat (Dual a ~> (Symbol ~> Symbol)) -> Type) (a6989586621680582188 :: Nat) | |
type Apply (ShowsPrec_6989586621680582282Sym0 :: TyFun Nat (Product a ~> (Symbol ~> Symbol)) -> Type) (a6989586621680582290 :: Nat) | |
type Apply (ShowsPrec_6989586621680582255Sym0 :: TyFun Nat (Sum a ~> (Symbol ~> Symbol)) -> Type) (a6989586621680582263 :: Nat) | |
type Apply (ShowsPrec_6989586621680071810Sym0 :: TyFun Nat (NonEmpty a ~> (Symbol ~> Symbol)) -> Type) (a6989586621680071818 :: Nat) | |
type Apply (ShowsPrec_6989586621680071724Sym0 :: TyFun Nat (Maybe a ~> (Symbol ~> Symbol)) -> Type) (a6989586621680071734 :: Nat) | |
type Apply (ShowsPrec_6989586621680047570Sym0 :: TyFun Nat ([a] ~> (Symbol ~> Symbol)) -> Type) (a6989586621680047580 :: Nat) | |
type Apply (ShowsPrecSym0 :: TyFun Nat (a ~> (Symbol ~> Symbol)) -> Type) (a6989586621680047524 :: Nat) | |
type Apply (ShowsPrec_6989586621680047538Sym0 :: TyFun Nat (a ~> (Symbol ~> Symbol)) -> Type) (a6989586621680047544 :: Nat) | |
type Apply (ShowsPrec_6989586621680047588Sym1 a6989586621680047598 :: TyFun Symbol (Symbol ~> Symbol) -> Type) (a6989586621680047599 :: Symbol) | |
type Apply (ShowsSym0 :: TyFun a (Symbol ~> Symbol) -> Type) (a6989586621680047516 :: a) | |
type Apply (Lambda_6989586621680047453Sym0 :: TyFun k (TyFun Symbol Symbol -> Type) -> Type) (a_69895866216800474476989586621680047452 :: k) | |
type Apply (ShowsPrec_6989586621680071774Sym0 :: TyFun Nat (Either a b ~> (Symbol ~> Symbol)) -> Type) (a6989586621680071784 :: Nat) | |
type Apply (ShowsPrec_6989586621680163487Sym0 :: TyFun Nat (Proxy s ~> (Symbol ~> Symbol)) -> Type) (a6989586621680163495 :: Nat) | |
type Apply (ShowsPrec_6989586621680605456Sym0 :: TyFun Nat (Arg a b ~> (Symbol ~> Symbol)) -> Type) (a6989586621680605464 :: Nat) | |
type Apply (ShowsPrec_6989586621680047606Sym0 :: TyFun Nat ((a, b) ~> (Symbol ~> Symbol)) -> Type) (a6989586621680047612 :: Nat) | |
type Apply (ShowsPrecSym1 a6989586621680047524 :: TyFun a (Symbol ~> Symbol) -> Type) (a6989586621680047525 :: a) | |
Defined in Text.Show.Singletons type Apply (ShowsPrecSym1 a6989586621680047524 :: TyFun a (Symbol ~> Symbol) -> Type) (a6989586621680047525 :: a) = ShowsPrecSym2 a6989586621680047524 a6989586621680047525 | |
type Apply (ShowsPrec_6989586621680047538Sym1 a6989586621680047544 :: TyFun a (Symbol ~> Symbol) -> Type) (a6989586621680047545 :: a) | |
type Apply (Let6989586621679731625GoSym0 :: TyFun k1 (TyFun k2 (TyFun [Symbol] Symbol -> Type) -> Type) -> Type) (w6989586621679731623 :: k1) | |
type Apply (ShowsPrec_6989586621680428701Sym0 :: TyFun Nat (Const a b ~> (Symbol ~> Symbol)) -> Type) (a6989586621680428709 :: Nat) | |
type Apply (ShowsPrec_6989586621680047621Sym0 :: TyFun Nat ((a, b, c) ~> (Symbol ~> Symbol)) -> Type) (a6989586621680047627 :: Nat) | |
type Apply (Let6989586621679731625GoSym1 w6989586621679731623 :: TyFun k2 (TyFun [Symbol] Symbol -> Type) -> Type) (ws6989586621679731624 :: k2) | |
type Apply (ShowsPrec_6989586621680047637Sym0 :: TyFun Nat ((a, b, c, d) ~> (Symbol ~> Symbol)) -> Type) (a6989586621680047643 :: Nat) | |
type Apply (Lambda_6989586621680047434Sym0 :: TyFun k1 (TyFun k2 (TyFun (Symbol ~> c) (TyFun (a ~> Symbol) (a ~> c) -> Type) -> Type) -> Type) -> Type) (ss6989586621680047432 :: k1) | |
Defined in Text.Show.Singletons type Apply (Lambda_6989586621680047434Sym0 :: TyFun k1 (TyFun k2 (TyFun (Symbol ~> c) (TyFun (a ~> Symbol) (a ~> c) -> Type) -> Type) -> Type) -> Type) (ss6989586621680047432 :: k1) = Lambda_6989586621680047434Sym1 ss6989586621680047432 :: TyFun k2 (TyFun (Symbol ~> c) (TyFun (a ~> Symbol) (a ~> c) -> Type) -> Type) -> Type | |
type Apply (Let6989586621680047506ShowlSym1 showx6989586621680047502 :: TyFun k2 (TyFun k3 (TyFun Symbol (TyFun [k1] Symbol -> Type) -> Type) -> Type) -> Type) (x6989586621680047503 :: k2) | |
Defined in Text.Show.Singletons type Apply (Let6989586621680047506ShowlSym1 showx6989586621680047502 :: TyFun k2 (TyFun k3 (TyFun Symbol (TyFun [k1] Symbol -> Type) -> Type) -> Type) -> Type) (x6989586621680047503 :: k2) = Let6989586621680047506ShowlSym2 showx6989586621680047502 x6989586621680047503 :: TyFun k3 (TyFun Symbol (TyFun [k1] Symbol -> Type) -> Type) -> Type | |
type Apply (ShowsPrec_6989586621680047654Sym0 :: TyFun Nat ((a, b, c, d, e) ~> (Symbol ~> Symbol)) -> Type) (a6989586621680047660 :: Nat) | |
type Apply (Lambda_6989586621680047434Sym1 ss6989586621680047432 :: TyFun k2 (TyFun (Symbol ~> c) (TyFun (a ~> Symbol) (a ~> c) -> Type) -> Type) -> Type) (a_69895866216800474256989586621680047433 :: k2) | |
Defined in Text.Show.Singletons type Apply (Lambda_6989586621680047434Sym1 ss6989586621680047432 :: TyFun k2 (TyFun (Symbol ~> c) (TyFun (a ~> Symbol) (a ~> c) -> Type) -> Type) -> Type) (a_69895866216800474256989586621680047433 :: k2) = Lambda_6989586621680047434Sym2 ss6989586621680047432 a_69895866216800474256989586621680047433 :: TyFun (Symbol ~> c) (TyFun (a ~> Symbol) (a ~> c) -> Type) -> Type | |
type Apply (Let6989586621680047506ShowlSym2 showx6989586621680047502 x6989586621680047503 :: TyFun k3 (TyFun Symbol (TyFun [k1] Symbol -> Type) -> Type) -> Type) (xs6989586621680047504 :: k3) | |
Defined in Text.Show.Singletons | |
type Apply (ShowsPrec_6989586621680047672Sym0 :: TyFun Nat ((a, b, c, d, e, f) ~> (Symbol ~> Symbol)) -> Type) (a6989586621680047678 :: Nat) | |
type Apply (Let6989586621680047506ShowlSym3 showx6989586621680047502 x6989586621680047503 xs6989586621680047504 :: TyFun Symbol (TyFun [k1] Symbol -> Type) -> Type) (s6989586621680047505 :: Symbol) | |
Defined in Text.Show.Singletons type Apply (Let6989586621680047506ShowlSym3 showx6989586621680047502 x6989586621680047503 xs6989586621680047504 :: TyFun Symbol (TyFun [k1] Symbol -> Type) -> Type) (s6989586621680047505 :: Symbol) = Let6989586621680047506ShowlSym4 showx6989586621680047502 x6989586621680047503 xs6989586621680047504 s6989586621680047505 | |
type Apply (ShowsPrec_6989586621680047691Sym0 :: TyFun Nat ((a, b, c, d, e, f, g) ~> (Symbol ~> Symbol)) -> Type) (a6989586621680047697 :: Nat) | |
type Rep (ElField '(s, a)) | |
type Apply UnlinesSym0 (a6989586621679731632 :: [Symbol]) | |
Defined in Data.List.Singletons.Internal | |
type Apply UnwordsSym0 (a6989586621679731622 :: [Symbol]) | |
Defined in Data.List.Singletons.Internal | |
type Apply (Let6989586621679731625GoSym2 w6989586621679731623 ws6989586621679731624 :: TyFun [Symbol] Symbol -> Type) (a6989586621679731626 :: [Symbol]) | |
type Apply (Let6989586621680047506ShowlSym4 showx6989586621680047502 x6989586621680047503 xs6989586621680047504 s6989586621680047505 :: TyFun [k1] Symbol -> Type) (a6989586621680047507 :: [k1]) | |
Defined in Text.Show.Singletons type Apply (Let6989586621680047506ShowlSym4 showx6989586621680047502 x6989586621680047503 xs6989586621680047504 s6989586621680047505 :: TyFun [k1] Symbol -> Type) (a6989586621680047507 :: [k1]) = Let6989586621680047506Showl showx6989586621680047502 x6989586621680047503 xs6989586621680047504 s6989586621680047505 a6989586621680047507 | |
type Apply Show_tupleSym0 (a6989586621680047430 :: [Symbol ~> Symbol]) | |
Defined in Text.Show.Singletons | |
type Apply (ShowListSym0 :: TyFun [a] (Symbol ~> Symbol) -> Type) (a6989586621680047533 :: [a]) | |
Defined in Text.Show.Singletons type Apply (ShowListSym0 :: TyFun [a] (Symbol ~> Symbol) -> Type) (a6989586621680047533 :: [a]) = ShowListSym1 a6989586621680047533 | |
type Apply (ShowList_6989586621680047558Sym0 :: TyFun [a] (Symbol ~> Symbol) -> Type) (a6989586621680047563 :: [a]) | |
type Apply (ShowsPrec_6989586621680390927Sym1 a6989586621680390935 :: TyFun (Identity a) (Symbol ~> Symbol) -> Type) (a6989586621680390936 :: Identity a) | |
type Apply (ShowsPrec_6989586621680113533Sym1 a6989586621680113541 :: TyFun (First a) (Symbol ~> Symbol) -> Type) (a6989586621680113542 :: First a) | |
type Apply (ShowsPrec_6989586621680113571Sym1 a6989586621680113579 :: TyFun (Last a) (Symbol ~> Symbol) -> Type) (a6989586621680113580 :: Last a) | |
type Apply (ShowsPrec_6989586621680582363Sym1 a6989586621680582371 :: TyFun (First a) (Symbol ~> Symbol) -> Type) (a6989586621680582372 :: First a) | |
type Apply (ShowsPrec_6989586621680582390Sym1 a6989586621680582398 :: TyFun (Last a) (Symbol ~> Symbol) -> Type) (a6989586621680582399 :: Last a) | |
type Apply (ShowsPrec_6989586621680582336Sym1 a6989586621680582344 :: TyFun (Max a) (Symbol ~> Symbol) -> Type) (a6989586621680582345 :: Max a) | |
type Apply (ShowsPrec_6989586621680582309Sym1 a6989586621680582317 :: TyFun (Min a) (Symbol ~> Symbol) -> Type) (a6989586621680582318 :: Min a) | |
type Apply (ShowsPrec_6989586621680582417Sym1 a6989586621680582425 :: TyFun (WrappedMonoid m) (Symbol ~> Symbol) -> Type) (a6989586621680582426 :: WrappedMonoid m) | |
Defined in Data.Semigroup.Singletons type Apply (ShowsPrec_6989586621680582417Sym1 a6989586621680582425 :: TyFun (WrappedMonoid m) (Symbol ~> Symbol) -> Type) (a6989586621680582426 :: WrappedMonoid m) = ShowsPrec_6989586621680582417Sym2 a6989586621680582425 a6989586621680582426 | |
type Apply (ShowsPrec_6989586621680582180Sym1 a6989586621680582188 :: TyFun (Dual a) (Symbol ~> Symbol) -> Type) (a6989586621680582189 :: Dual a) | |
type Apply (ShowsPrec_6989586621680582282Sym1 a6989586621680582290 :: TyFun (Product a) (Symbol ~> Symbol) -> Type) (a6989586621680582291 :: Product a) | |
type Apply (ShowsPrec_6989586621680582255Sym1 a6989586621680582263 :: TyFun (Sum a) (Symbol ~> Symbol) -> Type) (a6989586621680582264 :: Sum a) | |
type Apply (ShowsPrec_6989586621680071810Sym1 a6989586621680071818 :: TyFun (NonEmpty a) (Symbol ~> Symbol) -> Type) (a6989586621680071819 :: NonEmpty a) | |
type Apply (ShowsPrec_6989586621680071724Sym1 a6989586621680071734 :: TyFun (Maybe a) (Symbol ~> Symbol) -> Type) (a6989586621680071735 :: Maybe a) | |
type Apply (ShowListWithSym1 a6989586621680047498 :: TyFun [a] (Symbol ~> Symbol) -> Type) (a6989586621680047499 :: [a]) | |
Defined in Text.Show.Singletons type Apply (ShowListWithSym1 a6989586621680047498 :: TyFun [a] (Symbol ~> Symbol) -> Type) (a6989586621680047499 :: [a]) = ShowListWithSym2 a6989586621680047498 a6989586621680047499 | |
type Apply (ShowsPrec_6989586621680047570Sym1 a6989586621680047580 :: TyFun [a] (Symbol ~> Symbol) -> Type) (a6989586621680047581 :: [a]) | |
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 a6989586621680047463 :: TyFun (Symbol ~> Symbol) (Symbol ~> Symbol) -> Type) (a6989586621680047464 :: Symbol ~> Symbol) | |
Defined in Text.Show.Singletons | |
type Apply (ShowListWithSym0 :: TyFun (a ~> (Symbol ~> Symbol)) ([a] ~> (Symbol ~> Symbol)) -> Type) (a6989586621680047498 :: a ~> (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_6989586621680071774Sym1 a6989586621680071784 :: TyFun (Either a b) (Symbol ~> Symbol) -> Type) (a6989586621680071785 :: Either a b) | |
type Apply (ShowsPrec_6989586621680163487Sym1 a6989586621680163495 :: TyFun (Proxy s) (Symbol ~> Symbol) -> Type) (a6989586621680163496 :: Proxy s) | |
type Apply (ShowsPrec_6989586621680605456Sym1 a6989586621680605464 :: TyFun (Arg a b) (Symbol ~> Symbol) -> Type) (a6989586621680605465 :: Arg a b) | |
type Apply (Let6989586621680047506ShowlSym0 :: TyFun (k1 ~> (Symbol ~> Symbol)) (TyFun k2 (TyFun k3 (TyFun Symbol (TyFun [k1] Symbol -> Type) -> Type) -> Type) -> Type) -> Type) (showx6989586621680047502 :: k1 ~> (Symbol ~> Symbol)) | |
Defined in Text.Show.Singletons type Apply (Let6989586621680047506ShowlSym0 :: TyFun (k1 ~> (Symbol ~> Symbol)) (TyFun k2 (TyFun k3 (TyFun Symbol (TyFun [k1] Symbol -> Type) -> Type) -> Type) -> Type) -> Type) (showx6989586621680047502 :: k1 ~> (Symbol ~> Symbol)) = Let6989586621680047506ShowlSym1 showx6989586621680047502 :: TyFun k2 (TyFun k3 (TyFun Symbol (TyFun [k1] Symbol -> Type) -> Type) -> Type) -> Type | |
type Apply (ShowsPrec_6989586621680047606Sym1 a6989586621680047612 :: TyFun (a, b) (Symbol ~> Symbol) -> Type) (a6989586621680047613 :: (a, b)) | |
type Apply (Lambda_6989586621680047434Sym2 ss6989586621680047432 a_69895866216800474256989586621680047433 :: TyFun (Symbol ~> c) (TyFun (a ~> Symbol) (a ~> c) -> Type) -> Type) (s6989586621680047436 :: Symbol ~> c) | |
Defined in Text.Show.Singletons type Apply (Lambda_6989586621680047434Sym2 ss6989586621680047432 a_69895866216800474256989586621680047433 :: TyFun (Symbol ~> c) (TyFun (a ~> Symbol) (a ~> c) -> Type) -> Type) (s6989586621680047436 :: Symbol ~> c) = Lambda_6989586621680047434Sym3 ss6989586621680047432 a_69895866216800474256989586621680047433 s6989586621680047436 :: TyFun (a ~> Symbol) (a ~> c) -> Type | |
type Apply (Lambda_6989586621680047434Sym3 ss6989586621680047432 a_69895866216800474256989586621680047433 s6989586621680047436 :: TyFun (a ~> Symbol) (a ~> c) -> Type) (r6989586621680047437 :: a ~> Symbol) | |
Defined in Text.Show.Singletons type Apply (Lambda_6989586621680047434Sym3 ss6989586621680047432 a_69895866216800474256989586621680047433 s6989586621680047436 :: TyFun (a ~> Symbol) (a ~> c) -> Type) (r6989586621680047437 :: a ~> Symbol) = Lambda_6989586621680047434 ss6989586621680047432 a_69895866216800474256989586621680047433 s6989586621680047436 r6989586621680047437 | |
type Apply (ShowsPrec_6989586621680428701Sym1 a6989586621680428709 :: TyFun (Const a b) (Symbol ~> Symbol) -> Type) (a6989586621680428710 :: Const a b) | |
type Apply (ShowsPrec_6989586621680047621Sym1 a6989586621680047627 :: TyFun (a, b, c) (Symbol ~> Symbol) -> Type) (a6989586621680047628 :: (a, b, c)) | |
type Apply (ShowsPrec_6989586621680047637Sym1 a6989586621680047643 :: TyFun (a, b, c, d) (Symbol ~> Symbol) -> Type) (a6989586621680047644 :: (a, b, c, d)) | |
type Apply (ShowsPrec_6989586621680047654Sym1 a6989586621680047660 :: TyFun (a, b, c, d, e) (Symbol ~> Symbol) -> Type) (a6989586621680047661 :: (a, b, c, d, e)) | |
type Apply (ShowsPrec_6989586621680047672Sym1 a6989586621680047678 :: TyFun (a, b, c, d, e, f) (Symbol ~> Symbol) -> Type) (a6989586621680047679 :: (a, b, c, d, e, f)) | |
type Apply (ShowsPrec_6989586621680047691Sym1 a6989586621680047697 :: TyFun (a, b, c, d, e, f, g) (Symbol ~> Symbol) -> Type) (a6989586621680047698 :: (a, b, c, d, e, f, g)) | |
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. |