roles-0.2.1.0: Composable class-based roles
Safe HaskellNone
LanguageHaskell98

Data.Roles

Documentation

class Representational (t :: k1 -> k2) where Source #

Minimal complete definition

Nothing

Methods

rep :: Coercion a b -> Coercion (t a) (t b) Source #

An argument is representational if you can lift a coercion of the argument into one of the whole

default rep :: Phantom t => Coercion a b -> Coercion (t a) (t b) Source #

Instances

Instances details
Representational (Proxy :: k1 -> Type) Source # 
Instance details

Defined in Data.Roles

Methods

rep :: forall (a :: k10) (b :: k10). Coercion a b -> Coercion (Proxy a) (Proxy b) Source #

Representational (Coercion a :: k1 -> Type) Source # 
Instance details

Defined in Data.Roles

Methods

rep :: forall (a0 :: k10) (b :: k10). Coercion a0 b -> Coercion (Coercion a a0) (Coercion a b) Source #

Representational (Const a :: k1 -> Type) Source # 
Instance details

Defined in Data.Roles

Methods

rep :: forall (a0 :: k10) (b :: k10). Coercion a0 b -> Coercion (Const a a0) (Const a b) Source #

Representational (Coercion :: k1 -> k1 -> Type) Source # 
Instance details

Defined in Data.Roles

Methods

rep :: forall (a :: k10) (b :: k10). Coercion a b -> Coercion (Coercion a) (Coercion b) Source #

Representational [] Source # 
Instance details

Defined in Data.Roles

Methods

rep :: forall (a :: k1) (b :: k1). Coercion a b -> Coercion [a] [b] Source #

Representational Maybe Source # 
Instance details

Defined in Data.Roles

Methods

rep :: forall (a :: k1) (b :: k1). Coercion a b -> Coercion (Maybe a) (Maybe b) Source #

Representational IO Source # 
Instance details

Defined in Data.Roles

Methods

rep :: forall (a :: k1) (b :: k1). Coercion a b -> Coercion (IO a) (IO b) Source #

Representational Complex Source # 
Instance details

Defined in Data.Roles

Methods

rep :: forall (a :: k1) (b :: k1). Coercion a b -> Coercion (Complex a) (Complex b) Source #

Representational First Source # 
Instance details

Defined in Data.Roles

Methods

rep :: forall (a :: k1) (b :: k1). Coercion a b -> Coercion (First a) (First b) Source #

Representational Last Source # 
Instance details

Defined in Data.Roles

Methods

rep :: forall (a :: k1) (b :: k1). Coercion a b -> Coercion (Last a) (Last b) Source #

Representational Dual Source # 
Instance details

Defined in Data.Roles

Methods

rep :: forall (a :: k1) (b :: k1). Coercion a b -> Coercion (Dual a) (Dual b) Source #

Representational Endo Source # 
Instance details

Defined in Data.Roles

Methods

rep :: forall (a :: k1) (b :: k1). Coercion a b -> Coercion (Endo a) (Endo b) Source #

Representational Sum Source # 
Instance details

Defined in Data.Roles

Methods

rep :: forall (a :: k1) (b :: k1). Coercion a b -> Coercion (Sum a) (Sum b) Source #

Representational Product Source # 
Instance details

Defined in Data.Roles

Methods

rep :: forall (a :: k1) (b :: k1). Coercion a b -> Coercion (Product a) (Product b) Source #

Representational IntMap Source # 
Instance details

Defined in Data.Roles

Methods

rep :: forall (a :: k1) (b :: k1). Coercion a b -> Coercion (IntMap a) (IntMap b) Source #

Representational (Either a :: Type -> Type) Source # 
Instance details

Defined in Data.Roles

Methods

rep :: forall (a0 :: k1) (b :: k1). Coercion a0 b -> Coercion (Either a a0) (Either a b) Source #

Representational ((,) a :: Type -> Type) Source # 
Instance details

Defined in Data.Roles

Methods

rep :: forall (a0 :: k1) (b :: k1). Coercion a0 b -> Coercion (a, a0) (a, b) Source #

Representational (ST s :: Type -> Type) Source # 
Instance details

Defined in Data.Roles

Methods

rep :: forall (a :: k1) (b :: k1). Coercion a b -> Coercion (ST s a) (ST s b) Source #

Representational (Map k :: Type -> Type) Source # 
Instance details

Defined in Data.Roles

Methods

rep :: forall (a :: k1) (b :: k1). Coercion a b -> Coercion (Map k a) (Map k b) Source #

Representational ((,,) a b :: Type -> Type) Source # 
Instance details

Defined in Data.Roles

Methods

rep :: forall (a0 :: k1) (b0 :: k1). Coercion a0 b0 -> Coercion (a, b, a0) (a, b, b0) Source #

Representational ((->) a :: Type -> Type) Source # 
Instance details

Defined in Data.Roles

Methods

rep :: forall (a0 :: k1) (b :: k1). Coercion a0 b -> Coercion (a -> a0) (a -> b) Source #

Representational ((,,,) a b c :: Type -> Type) Source # 
Instance details

Defined in Data.Roles

Methods

rep :: forall (a0 :: k1) (b0 :: k1). Coercion a0 b0 -> Coercion (a, b, c, a0) (a, b, c, b0) Source #

Representational ((,,,,) a b c d :: Type -> Type) Source # 
Instance details

Defined in Data.Roles

Methods

rep :: forall (a0 :: k1) (b0 :: k1). Coercion a0 b0 -> Coercion (a, b, c, d, a0) (a, b, c, d, b0) Source #

Representational ((,,,,,) a b c d e :: Type -> Type) Source # 
Instance details

Defined in Data.Roles

Methods

rep :: forall (a0 :: k1) (b0 :: k1). Coercion a0 b0 -> Coercion (a, b, c, d, e, a0) (a, b, c, d, e, b0) Source #

Representational (,,,,,) Source # 
Instance details

Defined in Data.Roles

Methods

rep :: forall (a :: k1) (b :: k1). Coercion a b -> Coercion ((,,,,,) a) ((,,,,,) b) Source #

Representational (,,,,) Source # 
Instance details

Defined in Data.Roles

Methods

rep :: forall (a :: k1) (b :: k1). Coercion a b -> Coercion ((,,,,) a) ((,,,,) b) Source #

Representational (,,,) Source # 
Instance details

Defined in Data.Roles

Methods

rep :: forall (a :: k1) (b :: k1). Coercion a b -> Coercion ((,,,) a) ((,,,) b) Source #

Representational (,,) Source # 
Instance details

Defined in Data.Roles

Methods

rep :: forall (a :: k1) (b :: k1). Coercion a b -> Coercion ((,,) a) ((,,) b) Source #

Representational Either Source # 
Instance details

Defined in Data.Roles

Methods

rep :: forall (a :: k1) (b :: k1). Coercion a b -> Coercion (Either a) (Either b) Source #

Representational (,) Source # 
Instance details

Defined in Data.Roles

Methods

rep :: forall (a :: k1) (b :: k1). Coercion a b -> Coercion ((,) a) ((,) b) Source #

Representational ((,,,,,) a :: Type -> Type -> Type -> Type -> Type -> Type) Source # 
Instance details

Defined in Data.Roles

Methods

rep :: forall (a0 :: k1) (b :: k1). Coercion a0 b -> Coercion ((,,,,,) a a0) ((,,,,,) a b) Source #

Representational ((,,,,) a :: Type -> Type -> Type -> Type -> Type) Source # 
Instance details

Defined in Data.Roles

Methods

rep :: forall (a0 :: k1) (b :: k1). Coercion a0 b -> Coercion ((,,,,) a a0) ((,,,,) a b) Source #

Representational ((,,,) a :: Type -> Type -> Type -> Type) Source # 
Instance details

Defined in Data.Roles

Methods

rep :: forall (a0 :: k1) (b :: k1). Coercion a0 b -> Coercion ((,,,) a a0) ((,,,) a b) Source #

Representational ((,,) a :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Roles

Methods

rep :: forall (a0 :: k1) (b :: k1). Coercion a0 b -> Coercion ((,,) a a0) ((,,) a b) Source #

Representational (Const :: Type -> k -> Type) Source # 
Instance details

Defined in Data.Roles

Methods

rep :: forall (a :: k1) (b :: k1). Coercion a b -> Coercion (Const a) (Const b) Source #

Representational ((,,,,,) a b :: Type -> Type -> Type -> Type -> Type) Source # 
Instance details

Defined in Data.Roles

Methods

rep :: forall (a0 :: k1) (b0 :: k1). Coercion a0 b0 -> Coercion ((,,,,,) a b a0) ((,,,,,) a b b0) Source #

Representational ((,,,,) a b :: Type -> Type -> Type -> Type) Source # 
Instance details

Defined in Data.Roles

Methods

rep :: forall (a0 :: k1) (b0 :: k1). Coercion a0 b0 -> Coercion ((,,,,) a b a0) ((,,,,) a b b0) Source #

Representational ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Roles

Methods

rep :: forall (a :: k1) (b :: k1). Coercion a b -> Coercion ((->) a) ((->) b) Source #

Representational ((,,,) a b :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Roles

Methods

rep :: forall (a0 :: k1) (b0 :: k1). Coercion a0 b0 -> Coercion ((,,,) a b a0) ((,,,) a b b0) Source #

Representational ((,,,,,) a b c :: Type -> Type -> Type -> Type) Source # 
Instance details

Defined in Data.Roles

Methods

rep :: forall (a0 :: k1) (b0 :: k1). Coercion a0 b0 -> Coercion ((,,,,,) a b c a0) ((,,,,,) a b c b0) Source #

Representational ((,,,,) a b c :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Roles

Methods

rep :: forall (a0 :: k1) (b0 :: k1). Coercion a0 b0 -> Coercion ((,,,,) a b c a0) ((,,,,) a b c b0) Source #

Representational ((,,,,,) a b c d :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Roles

Methods

rep :: forall (a0 :: k1) (b0 :: k1). Coercion a0 b0 -> Coercion ((,,,,,) a b c d a0) ((,,,,,) a b c d b0) Source #

class Representational t => Phantom (t :: k1 -> k2) where Source #

Minimal complete definition

Nothing

Methods

phantom :: Coercion (t a) (t b) Source #

An argument is phantom if you can coerce the whole ignoring the argument

default phantom :: Coercible (t a) (t b) => Coercion (t a) (t b) Source #

Instances

Instances details
Phantom (Proxy :: k1 -> Type) Source # 
Instance details

Defined in Data.Roles

Methods

phantom :: forall (a :: k10) (b :: k10). Coercion (Proxy a) (Proxy b) Source #

Phantom (Const a :: k1 -> Type) Source # 
Instance details

Defined in Data.Roles

Methods

phantom :: forall (a0 :: k10) (b :: k10). Coercion (Const a a0) (Const a b) Source #