lorentz-0.15.0: EDSL for the Michelson Language
Safe HaskellSafe-Inferred
LanguageHaskell2010

Lorentz.Coercions

Description

Identity transformations between different Haskell types.

Synopsis

Safe coercions

class CanCastTo a b where Source #

Explicitly allowed coercions.

a CanCastTo b proclaims that a can be casted to b without violating any invariants of b.

This relation is reflexive; it may be symmetric or not. It tends to be composable: casting complex types usually requires permission to cast their respective parts; for such types consider using castDummyG as implementation of the method of this typeclass.

For cases when a cast from a to b requires some validation, consider rather making a dedicated function which performs the necessary checks and then calls forcedCoerce.

Minimal complete definition

Nothing

Methods

castDummy :: Proxy a -> Proxy b -> () Source #

An optional method which helps passing -Wredundant-constraints check. Also, you can set specific implementation for it with specific sanity checks.

Instances

Instances details
CanCastTo (a :: k) (a :: k) Source # 
Instance details

Defined in Lorentz.Coercions

Methods

castDummy :: Proxy a -> Proxy a -> () Source #

CanCastTo Address (TAddress p vd :: Type) Source # 
Instance details

Defined in Lorentz.Coercions

Methods

castDummy :: Proxy Address -> Proxy (TAddress p vd) -> () Source #

CanCastTo (TAddress p vd :: Type) Address Source # 
Instance details

Defined in Lorentz.Coercions

Methods

castDummy :: Proxy (TAddress p vd) -> Proxy Address -> () Source #

CanCastTo (FutureContract p :: Type) EpAddress Source # 
Instance details

Defined in Lorentz.Coercions

CanCastTo (Packed a :: Type) ByteString Source # 
Instance details

Defined in Lorentz.Coercions

Methods

castDummy :: Proxy (Packed a) -> Proxy ByteString -> () Source #

CanCastTo (TSignature a :: Type) ByteString Source # 
Instance details

Defined in Lorentz.Coercions

CanCastTo k1 k2 => CanCastTo (Set k1 :: Type) (Set k2 :: Type) Source # 
Instance details

Defined in Lorentz.Coercions

Methods

castDummy :: Proxy (Set k1) -> Proxy (Set k2) -> () Source #

CanCastTo a b => CanCastTo (Packed a :: Type) (Packed b :: Type) Source # 
Instance details

Defined in Lorentz.Coercions

Methods

castDummy :: Proxy (Packed a) -> Proxy (Packed b) -> () Source #

CanCastTo a b => CanCastTo (TSignature a :: Type) (TSignature b :: Type) Source # 
Instance details

Defined in Lorentz.Coercions

Methods

castDummy :: Proxy (TSignature a) -> Proxy (TSignature b) -> () Source #

SameEntries entries1 entries2 => CanCastTo (UParam entries1 :: Type) (UParam entries2 :: Type) Source #

Allows casts only between UParam_ and UParam.

Instance details

Defined in Lorentz.UParam

Methods

castDummy :: Proxy (UParam entries1) -> Proxy (UParam entries2) -> () Source #

CanCastTo a1 a2 => CanCastTo (ContractRef a1 :: Type) (ContractRef a2 :: Type) Source # 
Instance details

Defined in Lorentz.Coercions

Methods

castDummy :: Proxy (ContractRef a1) -> Proxy (ContractRef a2) -> () Source #

CanCastTo a b => CanCastTo (Maybe a :: Type) (Maybe b :: Type) Source # 
Instance details

Defined in Lorentz.Coercions

Methods

castDummy :: Proxy (Maybe a) -> Proxy (Maybe b) -> () Source #

CanCastTo a b => CanCastTo ([a] :: Type) ([b] :: Type) Source # 
Instance details

Defined in Lorentz.Coercions

Methods

castDummy :: Proxy [a] -> Proxy [b] -> () Source #

CanCastTo (Hash alg a :: Type) ByteString Source # 
Instance details

Defined in Lorentz.Coercions

Methods

castDummy :: Proxy (Hash alg a) -> Proxy ByteString -> () Source #

(CanCastTo l1 l2, CanCastTo r1 r2) => CanCastTo (Either l1 r1 :: Type) (Either l2 r2 :: Type) Source # 
Instance details

Defined in Lorentz.Coercions

Methods

castDummy :: Proxy (Either l1 r1) -> Proxy (Either l2 r2) -> () Source #

(CanCastTo k1 k2, CanCastTo v1 v2) => CanCastTo (Map k1 v1 :: Type) (Map k2 v2 :: Type) Source # 
Instance details

Defined in Lorentz.Coercions

Methods

castDummy :: Proxy (Map k1 v1) -> Proxy (Map k2 v2) -> () Source #

(CanCastTo (ZippedStack i1) (ZippedStack i2), CanCastTo (ZippedStack o1) (ZippedStack o2)) => CanCastTo (i1 :-> o1 :: Type) (i2 :-> o2 :: Type) Source # 
Instance details

Defined in Lorentz.Coercions

Methods

castDummy :: Proxy (i1 :-> o1) -> Proxy (i2 :-> o2) -> () Source #

(CanCastTo alg1 alg2, CanCastTo a1 a2) => CanCastTo (Hash alg1 a1 :: Type) (Hash alg2 a2 :: Type) Source # 
Instance details

Defined in Lorentz.Coercions

Methods

castDummy :: Proxy (Hash alg1 a1) -> Proxy (Hash alg2 a2) -> () Source #

(CanCastTo (ZippedStack inp1) (ZippedStack inp2), CanCastTo (ZippedStack out1) (ZippedStack out2), CanCastTo (ZippedStack (inp1 ++ '[WrappedLambda inp1 out1])) (ZippedStack (inp2 ++ '[WrappedLambda inp2 out2]))) => CanCastTo (WrappedLambda inp1 out1 :: Type) (WrappedLambda inp2 out2 :: Type) Source # 
Instance details

Defined in Lorentz.Lambda

Methods

castDummy :: Proxy (WrappedLambda inp1 out1) -> Proxy (WrappedLambda inp2 out2) -> () Source #

(CanCastTo a1 a2, CanCastTo r1 r2) => CanCastTo (View_ a1 r1 :: Type) (View_ a2 r2 :: Type) Source # 
Instance details

Defined in Lorentz.Macro

Methods

castDummy :: Proxy (View_ a1 r1) -> Proxy (View_ a2 r2) -> () Source #

(CanCastTo a1 a2, CanCastTo r1 r2) => CanCastTo (Void_ a1 r1 :: Type) (Void_ a2 r2 :: Type) Source # 
Instance details

Defined in Lorentz.Macro

Methods

castDummy :: Proxy (Void_ a1 r1) -> Proxy (Void_ a2 r2) -> () Source #

(CanCastTo a1 a2, CanCastTo b1 b2) => CanCastTo (ZippedStackRepr a1 b1 :: Type) (ZippedStackRepr a2 b2 :: Type) Source # 
Instance details

Defined in Lorentz.Coercions

Methods

castDummy :: Proxy (ZippedStackRepr a1 b1) -> Proxy (ZippedStackRepr a2 b2) -> () Source #

(CanCastTo k1 k2, CanCastTo v1 v2) => CanCastTo (BigMap k1 v1 :: Type) (BigMap k2 v2 :: Type) Source # 
Instance details

Defined in Lorentz.Coercions

Methods

castDummy :: Proxy (BigMap k1 v1) -> Proxy (BigMap k2 v2) -> () Source #

(CanCastTo a1 a2, CanCastTo b1 b2) => CanCastTo ((a1, b1) :: Type) ((a2, b2) :: Type) Source # 
Instance details

Defined in Lorentz.Coercions

Methods

castDummy :: Proxy (a1, b1) -> Proxy (a2, b2) -> () Source #

(CanCastTo a a2, CanCastTo td td2) => CanCastTo (STicket a td :: Type) (STicket a2 td2 :: Type) Source # 
Instance details

Defined in Lorentz.Tickets

Methods

castDummy :: Proxy (STicket a td) -> Proxy (STicket a2 td2) -> () Source #

CanCastTo (f a) (g b) => CanCastTo (NamedF f a n :: Type) (NamedF g b m :: Type) Source # 
Instance details

Defined in Lorentz.Coercions

Methods

castDummy :: Proxy (NamedF f a n) -> Proxy (NamedF g b m) -> () Source #

(CanCastTo a1 a2, CanCastTo b1 b2, CanCastTo c1 c2) => CanCastTo ((a1, b1, c1) :: Type) ((a2, b2, c2) :: Type) Source # 
Instance details

Defined in Lorentz.Coercions

Methods

castDummy :: Proxy (a1, b1, c1) -> Proxy (a2, b2, c2) -> () Source #

(CanCastTo a1 a2, CanCastTo b1 b2, CanCastTo c1 c2, CanCastTo d1 d2) => CanCastTo ((a1, b1, c1, d1) :: Type) ((a2, b2, c2, d2) :: Type) Source # 
Instance details

Defined in Lorentz.Coercions

Methods

castDummy :: Proxy (a1, b1, c1, d1) -> Proxy (a2, b2, c2, d2) -> () Source #

(CanCastTo a1 a2, CanCastTo b1 b2, CanCastTo c1 c2, CanCastTo d1 d2, CanCastTo e1 e2) => CanCastTo ((a1, b1, c1, d1, e1) :: Type) ((a2, b2, c2, d2, e2) :: Type) Source # 
Instance details

Defined in Lorentz.Coercions

Methods

castDummy :: Proxy (a1, b1, c1, d1, e1) -> Proxy (a2, b2, c2, d2, e2) -> () Source #

(CanCastTo a1 a2, CanCastTo b1 b2, CanCastTo c1 c2, CanCastTo d1 d2, CanCastTo e1 e2, CanCastTo f1 f2) => CanCastTo ((a1, b1, c1, d1, e1, f1) :: Type) ((a2, b2, c2, d2, e2, f2) :: Type) Source # 
Instance details

Defined in Lorentz.Coercions

Methods

castDummy :: Proxy (a1, b1, c1, d1, e1, f1) -> Proxy (a2, b2, c2, d2, e2, f2) -> () Source #

castDummyG :: (Generic a, Generic b, GCanCastTo (Rep a) (Rep b)) => Proxy a -> Proxy b -> () Source #

Implementation of castDummy for types composed from smaller types. It helps to ensure that all necessary constraints are requested in instance head.

checkedCoerce :: forall a b. (CanCastTo a b, Coercible a b) => a -> b Source #

Coercion in Haskell world which respects CanCastTo.

type Castable_ a b = (MichelsonCoercible a b, CanCastTo a b) Source #

Coercion from a to b is permitted and safe.

type Coercible_ a b = (MichelsonCoercible a b, CanCastTo a b, CanCastTo b a) Source #

Coercions between a to b are permitted and safe.

checkedCoerce_ :: forall a b s. Castable_ a b => (a ': s) :-> (b ': s) Source #

Coerce between types which have an explicit permission for that in the face of CanCastTo constraint.

checkedCoercing_ :: forall a b s. Coercible_ a b => ((b ': s) :-> (b ': s)) -> (a ': s) :-> (a ': s) Source #

Pretends that the top item of the stack was coerced.

allowCheckedCoerceTo :: forall b a. Dict (CanCastTo a b) Source #

Locally provide given CanCastTo instance.

allowCheckedCoerce :: forall a b. Dict (CanCastTo a b, CanCastTo b a) Source #

Locally provide bidirectional CanCastTo instance.

coerceUnwrap :: forall a s. Unwrappable a => (a ': s) :-> (Unwrappabled a ': s) Source #

Specialized version of forcedCoerce_ to unwrap a haskell newtype.

unsafeCoerceWrap :: forall a s. Unwrappable a => (Unwrappabled a ': s) :-> (a ': s) Source #

Specialized version of forcedCoerce_ to wrap a haskell newtype.

Works under Unwrappable constraint, thus is not safe.

coerceWrap :: forall a s. Wrappable a => (Unwrappabled a ': s) :-> (a ': s) Source #

Specialized version of forcedCoerce_ to wrap into a haskell newtype.

Requires Wrappable constraint.

toNamed :: Label name -> (a ': s) :-> ((name :! a) ': s) Source #

Lift given value to a named value.

fromNamed :: Label name -> ((name :! a) ': s) :-> (a ': s) Source #

Unpack named value.

Unsafe coercions

type MichelsonCoercible a b = ToT a ~ ToT b Source #

Whether two types have the same Michelson representation.

forcedCoerce :: Coercible a b => a -> b Source #

Coercion for Haskell world.

We discourage using this function on Lorentz types, consider using coerce instead. One of the reasons for that is that in Lorentz it's common to declare types as newtypes consisting of existing primitives, and forcedCoerce tends to ignore all phantom type variables of newtypes thus violating their invariants.

forcedCoerce_ :: MichelsonCoercible a b => (a ': s) :-> (b ': s) Source #

Convert between values of types that have the same representation.

This function is not safe in a sense that this allows * breaking invariants of casted type (example: UStore from morley-upgradeable), or * may stop compile on code changes (example: coercion of pair to a datatype with two fields will break if new field is added). Still, produced Michelson code will always be valid.

Prefer using one of more specific functions from this module.

gForcedCoerce_ :: MichelsonCoercible (t a) (t b) => (t a ': s) :-> (t b ': s) Source #

fakeCoerce :: s1 :-> s2 Source #

Convert between two stacks via failing.

fakeCoercing :: (s1 :-> s2) -> s1' :-> s2' Source #

Re-exports

class ToT s ~ ToT (Unwrappabled s) => Unwrappable (s :: Type) Source #

Declares that this type is just a wrapper over some other type and it can be safely unwrapped to that inner type.

Inspired by lens Wrapped.

Associated Types

type Unwrappabled s :: Type Source #

The type we unwrap to (inner type of the newtype).

Used in constraint for Lorentz instruction wrapping into a Haskell newtype and vice versa.

type Unwrappabled s = GUnwrappabled s (Rep s)

Instances

Instances details
Unwrappable NRational Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Associated Types

type Unwrappabled NRational Source #

Unwrappable Rational Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Associated Types

type Unwrappabled Rational Source #

Unwrappable (UParam entries) Source # 
Instance details

Defined in Lorentz.UParam

Associated Types

type Unwrappabled (UParam entries) Source #

Unwrappable (Fixed a) Source # 
Instance details

Defined in Lorentz.Wrappable

Associated Types

type Unwrappabled (Fixed a) Source #

Unwrappable (NFixed a) Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Associated Types

type Unwrappabled (NFixed a) Source #

Unwrappable (ParameterWrapper deriv cp) Source # 
Instance details

Defined in Lorentz.Entrypoints.Manual

Associated Types

type Unwrappabled (ParameterWrapper deriv cp) Source #

Unwrappable (Extensible x) Source # 
Instance details

Defined in Lorentz.Extensible

Associated Types

type Unwrappabled (Extensible x) Source #

Unwrappable (STicket action td) Source # 
Instance details

Defined in Lorentz.Tickets

Associated Types

type Unwrappabled (STicket action td) Source #

Unwrappable (NamedF Identity a name) Source # 
Instance details

Defined in Lorentz.Wrappable

Associated Types

type Unwrappabled (NamedF Identity a name) Source #

Unwrappable (NamedF Maybe a name) Source # 
Instance details

Defined in Lorentz.Wrappable

Associated Types

type Unwrappabled (NamedF Maybe a name) Source #

class Unwrappable s => Wrappable (s :: Type) Source #

Declares that it is safe to wrap an inner type to the given wrapper type. Can be provided in addition to Unwrappable.

You can declare this instance when your wrapper exists just to make type system differentiate the two types. Example: newtype TokenId = TokenId Natural.

Do not define this instance for wrappers that provide some invariants. Example: UStore type from morley-upgradeable.

Wrappable is similar to lens Wrapped class without the method.

Instances

Instances details
Wrappable (ParameterWrapper deriv cp) Source # 
Instance details

Defined in Lorentz.Entrypoints.Manual

Wrappable (NamedF Identity a name) Source # 
Instance details

Defined in Lorentz.Wrappable

Wrappable (NamedF Maybe a name) Source # 
Instance details

Defined in Lorentz.Wrappable