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 | GHC2021 |
Data.Proxy.Singletons
Description
Exports promoted and singled versions of the definitions in Data.Proxy.
Synopsis
- type family Sing :: k -> Type
- data SProxy (a :: Proxy t) where
- type family AsProxyTypeOf (a1 :: a) (a2 :: proxy a) :: a where ...
- sAsProxyTypeOf :: forall a (proxy :: Type -> Type) (t1 :: a) (t2 :: proxy a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (AsProxyTypeOfSym0 :: TyFun a (proxy a ~> a) -> Type) t1) t2)
- type family ProxySym0 :: Proxy t where ...
- data AsProxyTypeOfSym0 (a1 :: TyFun a (proxy a ~> a))
- data AsProxyTypeOfSym1 (a6989586621680355908 :: a) (b :: TyFun (proxy a) a)
- type family AsProxyTypeOfSym2 (a6989586621680355908 :: a) (a6989586621680355909 :: proxy a) :: a where ...
The Proxy
singleton
type family Sing :: k -> Type #
Instances
type family AsProxyTypeOf (a1 :: a) (a2 :: proxy a) :: a where ... Source #
sAsProxyTypeOf :: forall a (proxy :: Type -> Type) (t1 :: a) (t2 :: proxy a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (AsProxyTypeOfSym0 :: TyFun a (proxy a ~> a) -> Type) t1) t2) Source #
Defunctionalization symbols
data AsProxyTypeOfSym0 (a1 :: TyFun a (proxy a ~> a)) Source #
Instances
SingI (AsProxyTypeOfSym0 :: TyFun a (proxy a ~> a) -> Type) Source # | |
Defined in Data.Proxy.Singletons | |
SuppressUnusedWarnings (AsProxyTypeOfSym0 :: TyFun a (proxy a ~> a) -> Type) Source # | |
Defined in Data.Proxy.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (AsProxyTypeOfSym0 :: TyFun a (proxy a ~> a) -> Type) (a6989586621680355908 :: a) Source # | |
Defined in Data.Proxy.Singletons type Apply (AsProxyTypeOfSym0 :: TyFun a (proxy a ~> a) -> Type) (a6989586621680355908 :: a) = AsProxyTypeOfSym1 a6989586621680355908 :: TyFun (proxy a) a -> Type |
data AsProxyTypeOfSym1 (a6989586621680355908 :: a) (b :: TyFun (proxy a) a) Source #
Instances
SingI1 (AsProxyTypeOfSym1 :: a -> TyFun (proxy a) a -> Type) Source # | |
Defined in Data.Proxy.Singletons | |
SingI d => SingI (AsProxyTypeOfSym1 d :: TyFun (proxy a) a -> Type) Source # | |
Defined in Data.Proxy.Singletons | |
SuppressUnusedWarnings (AsProxyTypeOfSym1 a6989586621680355908 :: TyFun (proxy a) a -> Type) Source # | |
Defined in Data.Proxy.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (AsProxyTypeOfSym1 a6989586621680355908 :: TyFun (proxy a) a -> Type) (a6989586621680355909 :: proxy a) Source # | |
Defined in Data.Proxy.Singletons type Apply (AsProxyTypeOfSym1 a6989586621680355908 :: TyFun (proxy a) a -> Type) (a6989586621680355909 :: proxy a) = AsProxyTypeOf a6989586621680355908 a6989586621680355909 |
type family AsProxyTypeOfSym2 (a6989586621680355908 :: a) (a6989586621680355909 :: proxy a) :: a where ... Source #
Equations
AsProxyTypeOfSym2 (a6989586621680355908 :: a) (a6989586621680355909 :: proxy a) = AsProxyTypeOf a6989586621680355908 a6989586621680355909 |
Orphan instances
PAlternative (Proxy :: k -> Type) Source # | |||||||||||||||||||||
PMonadPlus (Proxy :: k -> Type) Source # | |||||||||||||||||||||
PApplicative (Proxy :: Type -> Type) Source # | |||||||||||||||||||||
Associated Types
| |||||||||||||||||||||
PFunctor (Proxy :: Type -> Type) Source # | |||||||||||||||||||||
PMonad (Proxy :: Type -> Type) Source # | |||||||||||||||||||||
Associated Types
| |||||||||||||||||||||
SAlternative (Proxy :: Type -> Type) Source # | |||||||||||||||||||||
SApplicative (Proxy :: Type -> Type) Source # | |||||||||||||||||||||
Methods sPure :: forall a (t :: a). Sing t -> Sing (Apply (PureSym0 :: TyFun a (Proxy a) -> Type) t) Source # (%<*>) :: forall a b (t1 :: Proxy (a ~> b)) (t2 :: Proxy a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<*>@#@$) :: TyFun (Proxy (a ~> b)) (Proxy a ~> Proxy b) -> Type) t1) t2) Source # sLiftA2 :: forall a b c (t1 :: a ~> (b ~> c)) (t2 :: Proxy a) (t3 :: Proxy b). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (LiftA2Sym0 :: TyFun (a ~> (b ~> c)) (Proxy a ~> (Proxy b ~> Proxy c)) -> Type) t1) t2) t3) Source # (%*>) :: forall a b (t1 :: Proxy a) (t2 :: Proxy b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((*>@#@$) :: TyFun (Proxy a) (Proxy b ~> Proxy b) -> Type) t1) t2) Source # (%<*) :: forall a b (t1 :: Proxy a) (t2 :: Proxy b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<*@#@$) :: TyFun (Proxy a) (Proxy b ~> Proxy a) -> Type) t1) t2) Source # | |||||||||||||||||||||
SFunctor (Proxy :: Type -> Type) Source # | |||||||||||||||||||||
Methods sFmap :: forall a b (t1 :: a ~> b) (t2 :: Proxy a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (FmapSym0 :: TyFun (a ~> b) (Proxy a ~> Proxy b) -> Type) t1) t2) Source # (%<$) :: forall a b (t1 :: a) (t2 :: Proxy b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<$@#@$) :: TyFun a (Proxy b ~> Proxy a) -> Type) t1) t2) Source # | |||||||||||||||||||||
SMonad (Proxy :: Type -> Type) Source # | |||||||||||||||||||||
Methods (%>>=) :: forall a b (t1 :: Proxy a) (t2 :: a ~> Proxy b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>>=@#@$) :: TyFun (Proxy a) ((a ~> Proxy b) ~> Proxy b) -> Type) t1) t2) Source # (%>>) :: forall a b (t1 :: Proxy a) (t2 :: Proxy b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>>@#@$) :: TyFun (Proxy a) (Proxy b ~> Proxy b) -> Type) t1) t2) Source # sReturn :: forall a (t :: a). Sing t -> Sing (Apply (ReturnSym0 :: TyFun a (Proxy a) -> Type) t) Source # | |||||||||||||||||||||
SMonadPlus (Proxy :: Type -> Type) Source # | |||||||||||||||||||||
SingKind (Proxy t) Source # | |||||||||||||||||||||
SDecide (Proxy t) Source # | |||||||||||||||||||||
PEq (Proxy s) Source # | |||||||||||||||||||||
SEq (Proxy s) Source # | |||||||||||||||||||||
Methods (%==) :: forall (t1 :: Proxy s) (t2 :: Proxy s). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((==@#@$) :: TyFun (Proxy s) (Proxy s ~> Bool) -> Type) t1) t2) Source # (%/=) :: forall (t1 :: Proxy s) (t2 :: Proxy s). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((/=@#@$) :: TyFun (Proxy s) (Proxy s ~> Bool) -> Type) t1) t2) Source # | |||||||||||||||||||||
PMonoid (Proxy s) Source # | |||||||||||||||||||||
Associated Types
| |||||||||||||||||||||
SMonoid (Proxy s) Source # | |||||||||||||||||||||
Methods sMempty :: Sing (MemptySym0 :: Proxy s) Source # sMappend :: forall (t1 :: Proxy s) (t2 :: Proxy s). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MappendSym0 :: TyFun (Proxy s) (Proxy s ~> Proxy s) -> Type) t1) t2) Source # sMconcat :: forall (t :: [Proxy s]). Sing t -> Sing (Apply (MconcatSym0 :: TyFun [Proxy s] (Proxy s) -> Type) t) Source # | |||||||||||||||||||||
POrd (Proxy s) Source # | |||||||||||||||||||||
SOrd (Proxy s) Source # | |||||||||||||||||||||
Methods sCompare :: forall (t1 :: Proxy s) (t2 :: Proxy s). Sing t1 -> Sing t2 -> Sing (Apply (Apply (CompareSym0 :: TyFun (Proxy s) (Proxy s ~> Ordering) -> Type) t1) t2) Source # (%<) :: forall (t1 :: Proxy s) (t2 :: Proxy s). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<@#@$) :: TyFun (Proxy s) (Proxy s ~> Bool) -> Type) t1) t2) Source # (%<=) :: forall (t1 :: Proxy s) (t2 :: Proxy s). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<=@#@$) :: TyFun (Proxy s) (Proxy s ~> Bool) -> Type) t1) t2) Source # (%>) :: forall (t1 :: Proxy s) (t2 :: Proxy s). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>@#@$) :: TyFun (Proxy s) (Proxy s ~> Bool) -> Type) t1) t2) Source # (%>=) :: forall (t1 :: Proxy s) (t2 :: Proxy s). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>=@#@$) :: TyFun (Proxy s) (Proxy s ~> Bool) -> Type) t1) t2) Source # sMax :: forall (t1 :: Proxy s) (t2 :: Proxy s). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MaxSym0 :: TyFun (Proxy s) (Proxy s ~> Proxy s) -> Type) t1) t2) Source # sMin :: forall (t1 :: Proxy s) (t2 :: Proxy s). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MinSym0 :: TyFun (Proxy s) (Proxy s ~> Proxy s) -> Type) t1) t2) Source # | |||||||||||||||||||||
PSemigroup (Proxy s) Source # | |||||||||||||||||||||
SSemigroup (Proxy s) Source # | |||||||||||||||||||||
Methods (%<>) :: forall (t1 :: Proxy s) (t2 :: Proxy s). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<>@#@$) :: TyFun (Proxy s) (Proxy s ~> Proxy s) -> Type) t1) t2) Source # sSconcat :: forall (t :: NonEmpty (Proxy s)). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty (Proxy s)) (Proxy s) -> Type) t) Source # | |||||||||||||||||||||
PBounded (Proxy s) Source # | |||||||||||||||||||||
Associated Types
| |||||||||||||||||||||
PEnum (Proxy s) Source # | |||||||||||||||||||||
SBounded (Proxy s) Source # | |||||||||||||||||||||
SEnum (Proxy s) Source # | |||||||||||||||||||||
Methods sSucc :: forall (t :: Proxy s). Sing t -> Sing (Apply (SuccSym0 :: TyFun (Proxy s) (Proxy s) -> Type) t) Source # sPred :: forall (t :: Proxy s). Sing t -> Sing (Apply (PredSym0 :: TyFun (Proxy s) (Proxy s) -> Type) t) Source # sToEnum :: forall (t :: Natural). Sing t -> Sing (Apply (ToEnumSym0 :: TyFun Natural (Proxy s) -> Type) t) Source # sFromEnum :: forall (t :: Proxy s). Sing t -> Sing (Apply (FromEnumSym0 :: TyFun (Proxy s) Natural -> Type) t) Source # sEnumFromTo :: forall (t1 :: Proxy s) (t2 :: Proxy s). Sing t1 -> Sing t2 -> Sing (Apply (Apply (EnumFromToSym0 :: TyFun (Proxy s) (Proxy s ~> [Proxy s]) -> Type) t1) t2) Source # sEnumFromThenTo :: forall (t1 :: Proxy s) (t2 :: Proxy s) (t3 :: Proxy s). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (EnumFromThenToSym0 :: TyFun (Proxy s) (Proxy s ~> (Proxy s ~> [Proxy s])) -> Type) t1) t2) t3) Source # | |||||||||||||||||||||
PShow (Proxy s) Source # | |||||||||||||||||||||
SShow (Proxy s) Source # | |||||||||||||||||||||
Methods sShowsPrec :: forall (t1 :: Natural) (t2 :: Proxy s) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (Proxy s ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source # sShow_ :: forall (t :: Proxy s). Sing t -> Sing (Apply (Show_Sym0 :: TyFun (Proxy s) Symbol -> Type) t) Source # sShowList :: forall (t1 :: [Proxy s]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [Proxy s] (Symbol ~> Symbol) -> Type) t1) t2) Source # | |||||||||||||||||||||
SingI ('Proxy :: Proxy t) Source # | |||||||||||||||||||||