Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Identity transformations between different Haskell types.
Synopsis
- class CanCastTo a b where
- castDummyG :: (Generic a, Generic b, GCanCastTo (Rep a) (Rep b)) => Proxy a -> Proxy b -> ()
- checkedCoerce :: forall a b. (CanCastTo a b, Coercible a b) => a -> b
- type Castable_ a b = (MichelsonCoercible a b, CanCastTo a b)
- type Coercible_ a b = (MichelsonCoercible a b, CanCastTo a b, CanCastTo b a)
- checkedCoerce_ :: forall a b s. Castable_ a b => (a ': s) :-> (b ': s)
- checkedCoercing_ :: forall a b s. Coercible_ a b => ((b ': s) :-> (b ': s)) -> (a ': s) :-> (a ': s)
- allowCheckedCoerceTo :: forall b a. Dict (CanCastTo a b)
- allowCheckedCoerce :: forall a b. Dict (CanCastTo a b, CanCastTo b a)
- coerceUnwrap :: forall a s. Unwrappable a => (a ': s) :-> (Unwrappabled a ': s)
- unsafeCoerceWrap :: forall a s. Unwrappable a => (Unwrappabled a ': s) :-> (a ': s)
- coerceWrap :: forall a s. Wrappable a => (Unwrappabled a ': s) :-> (a ': s)
- toNamed :: Label name -> (a ': s) :-> ((name :! a) ': s)
- fromNamed :: Label name -> ((name :! a) ': s) :-> (a ': s)
- type MichelsonCoercible a b = ToT a ~ ToT b
- forcedCoerce :: Coercible a b => a -> b
- forcedCoerce_ :: MichelsonCoercible a b => (a ': s) :-> (b ': s)
- gForcedCoerce_ :: MichelsonCoercible (t a) (t b) => (t a ': s) :-> (t b ': s)
- fakeCoerce :: s1 :-> s2
- fakeCoercing :: (s1 :-> s2) -> s1' :-> s2'
- class ToT s ~ ToT (Unwrappabled s) => Unwrappable (s :: Type) where
- type Unwrappabled s :: Type
- class Unwrappable s => Wrappable (s :: Type)
Safe coercions
class CanCastTo a b where Source #
Explicitly allowed coercions.
a
proclaims that CanCastTo
ba
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
.
Nothing
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
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.
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
.
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
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
Wrappable (ParameterWrapper deriv cp) Source # | |
Defined in Lorentz.Entrypoints.Manual | |
Wrappable (NamedF Identity a name) Source # | |
Defined in Lorentz.Wrappable | |
Wrappable (NamedF Maybe a name) Source # | |
Defined in Lorentz.Wrappable |