Copyright | (C) 2020 Ryan Scott |
---|---|
License | BSD-style (see LICENSE) |
Maintainer | Richard Eisenberg (rae@cs.brynmawr.edu) |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Exports promoted and singled versions of the definitions in Data.Proxy.
Synopsis
- type family Sing
- data SProxy :: forall t. Proxy t -> Type where
- type family AsProxyTypeOf a a where ...
- sAsProxyTypeOf :: forall a proxy (t :: a) (t :: proxy a). Sing t -> Sing t -> Sing (Apply (Apply AsProxyTypeOfSym0 t) t :: a)
- type ProxySym0 = 'Proxy :: Proxy (t :: k)
- data AsProxyTypeOfSym0 a6989586621680453165
- data AsProxyTypeOfSym1 a6989586621680453165 a6989586621680453166
- type AsProxyTypeOfSym2 (a6989586621680453165 :: a) (a6989586621680453166 :: proxy a) = AsProxyTypeOf a6989586621680453165 a6989586621680453166 :: a
The Proxy
singleton
The singleton kind-indexed type family.
Instances
data SProxy :: forall t. Proxy t -> Type where Source #
Instances
TestCoercion (SProxy :: Proxy t -> Type) Source # | |
Defined in Data.Singletons.Prelude.Proxy | |
TestEquality (SProxy :: Proxy t -> Type) Source # | |
Defined in Data.Singletons.Prelude.Proxy | |
Show (SProxy z) Source # | |
type family AsProxyTypeOf a a where ... Source #
AsProxyTypeOf a_6989586621680453158 a_6989586621680453160 = Apply (Apply ConstSym0 a_6989586621680453158) a_6989586621680453160 |
sAsProxyTypeOf :: forall a proxy (t :: a) (t :: proxy a). Sing t -> Sing t -> Sing (Apply (Apply AsProxyTypeOfSym0 t) t :: a) Source #
Defunctionalization symbols
data AsProxyTypeOfSym0 a6989586621680453165 Source #
Instances
SingI (AsProxyTypeOfSym0 :: TyFun a (proxy a ~> a) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Proxy | |
SuppressUnusedWarnings (AsProxyTypeOfSym0 :: TyFun a (proxy a ~> a) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Proxy suppressUnusedWarnings :: () Source # | |
type Apply (AsProxyTypeOfSym0 :: TyFun a (proxy a ~> a) -> Type) (a6989586621680453165 :: a) Source # | |
Defined in Data.Singletons.Prelude.Proxy type Apply (AsProxyTypeOfSym0 :: TyFun a (proxy a ~> a) -> Type) (a6989586621680453165 :: a) = AsProxyTypeOfSym1 a6989586621680453165 :: TyFun (proxy a) a -> Type |
data AsProxyTypeOfSym1 a6989586621680453165 a6989586621680453166 Source #
Instances
SingI d => SingI (AsProxyTypeOfSym1 d :: TyFun (proxy a) a -> Type) Source # | |
Defined in Data.Singletons.Prelude.Proxy sing :: Sing (AsProxyTypeOfSym1 d) Source # | |
SuppressUnusedWarnings (AsProxyTypeOfSym1 a6989586621680453165 :: TyFun (proxy a) a -> Type) Source # | |
Defined in Data.Singletons.Prelude.Proxy suppressUnusedWarnings :: () Source # | |
type Apply (AsProxyTypeOfSym1 a6989586621680453165 :: TyFun (proxy a) a -> Type) (a6989586621680453166 :: proxy a) Source # | |
Defined in Data.Singletons.Prelude.Proxy type Apply (AsProxyTypeOfSym1 a6989586621680453165 :: TyFun (proxy a) a -> Type) (a6989586621680453166 :: proxy a) = AsProxyTypeOfSym2 a6989586621680453165 a6989586621680453166 |
type AsProxyTypeOfSym2 (a6989586621680453165 :: a) (a6989586621680453166 :: proxy a) = AsProxyTypeOf a6989586621680453165 a6989586621680453166 :: a Source #