lorentz-0.4.0: EDSL for the Michelson Language
Safe HaskellNone
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 :: Type) Source # 
Instance details

Defined in Lorentz.Coercions

Methods

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

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

Defined in Lorentz.Coercions

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

Defined in Lorentz.Coercions

Methods

castDummy :: Proxy [a] -> Proxy [b] -> () 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 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 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 #

SameUStoreTemplate template1 template2 => CanCastTo (UStore template1 :: Type) (UStore template2 :: Type) Source #

We allow casting between UStore_ and UStore freely.

Instance details

Defined in Lorentz.UStore.Migration.Base

Methods

castDummy :: Proxy (UStore template1) -> Proxy (UStore template2) -> () 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 (TAddress p :: Type) Address Source # 
Instance details

Defined in Lorentz.Coercions

Methods

castDummy :: Proxy (TAddress p) -> Proxy Address -> () 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 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 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 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 (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 (Lambda (UStore ot1) (UStore nt1)) (Lambda (UStore ot2) (UStore nt2)) => CanCastTo (MigrationScript ot1 nt1 :: Type) (MigrationScript ot2 nt2 :: Type) Source # 
Instance details

Defined in Lorentz.UStore.Migration.Base

Methods

castDummy :: Proxy (MigrationScript ot1 nt1) -> Proxy (MigrationScript ot2 nt2) -> () 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 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 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 a b, f ~ g) => 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 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 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 newtyp inner s. (inner ~ Unwrapped newtyp, MichelsonCoercible newtyp (Unwrapped newtyp)) => (newtyp ': s) :-> (inner ': s) Source #

Specialized version of coerce_ to unwrap a haskell newtype.

coerceWrap :: forall newtyp inner s. (inner ~ Unwrapped newtyp, MichelsonCoercible newtyp (Unwrapped newtyp)) => (inner ': s) :-> (newtyp ': s) Source #

Specialized version of coerce_ to wrap into a haskell newtype.

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

Lift given value to a named value.

fromNamed :: Label name -> (NamedF Identity a name ': 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 forthat 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) 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 Wrapped s where #

Wrapped provides isomorphisms to wrap and unwrap newtypes or data types with one constructor.

Minimal complete definition

Nothing

Associated Types

type Unwrapped s #

type Unwrapped s = GUnwrapped (Rep s) #

Methods

_Wrapped' :: Iso' s (Unwrapped s) #

An isomorphism between s and a.

If your type has a Generic instance, _Wrapped' will default to _GWrapped', and you can choose to not override it with your own definition.

Instances

Instances details
Wrapped PatternMatchFail 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped PatternMatchFail #

Wrapped RecSelError 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped RecSelError #

Wrapped RecConError 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped RecConError #

Wrapped RecUpdError 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped RecUpdError #

Wrapped NoMethodError 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped NoMethodError #

Wrapped TypeError 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped TypeError #

Wrapped CDev 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CDev #

Wrapped CIno 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CIno #

Wrapped CMode 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CMode #

Wrapped COff 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped COff #

Wrapped CPid 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CPid #

Wrapped CSsize 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CSsize #

Wrapped CGid 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CGid #

Wrapped CNlink 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CNlink #

Wrapped CUid 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CUid #

Wrapped CCc 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CCc #

Wrapped CSpeed 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CSpeed #

Wrapped CTcflag 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CTcflag #

Wrapped CRLim 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CRLim #

Wrapped CBlkSize 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CBlkSize #

Wrapped CBlkCnt 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CBlkCnt #

Wrapped CClockId 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CClockId #

Wrapped CFsBlkCnt 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CFsBlkCnt #

Wrapped CFsFilCnt 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CFsFilCnt #

Wrapped CId 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CId #

Wrapped CKey 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CKey #

Wrapped CTimer 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CTimer #

Wrapped Fd 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped Fd #

Wrapped Errno 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped Errno #

Wrapped CompactionFailed 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CompactionFailed #

Wrapped AssertionFailed 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped AssertionFailed #

Wrapped ErrorCall 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped ErrorCall #

Wrapped All 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped All #

Wrapped Any 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped Any #

Wrapped CChar 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CChar #

Wrapped CSChar 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CSChar #

Wrapped CUChar 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CUChar #

Wrapped CShort 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CShort #

Wrapped CUShort 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CUShort #

Wrapped CInt 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CInt #

Wrapped CUInt 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CUInt #

Wrapped CLong 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CLong #

Wrapped CULong 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CULong #

Wrapped CLLong 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CLLong #

Wrapped CULLong 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CULLong #

Wrapped CBool 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CBool #

Wrapped CFloat 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CFloat #

Wrapped CDouble 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CDouble #

Wrapped CPtrdiff 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CPtrdiff #

Wrapped CSize 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CSize #

Wrapped CWchar 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CWchar #

Wrapped CSigAtomic 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CSigAtomic #

Wrapped CClock 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CClock #

Wrapped CTime 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CTime #

Wrapped CUSeconds 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CUSeconds #

Wrapped CSUSeconds 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CSUSeconds #

Wrapped CIntPtr 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CIntPtr #

Wrapped CUIntPtr 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CUIntPtr #

Wrapped CIntMax 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CIntMax #

Wrapped CUIntMax 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped CUIntMax #

Wrapped IntSet 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped IntSet #

Wrapped (Par1 p) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Par1 p) #

Methods

_Wrapped' :: Iso' (Par1 p) (Unwrapped (Par1 p)) #

Wrapped (Predicate a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Predicate a) #

Wrapped (Comparison a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Comparison a) #

Wrapped (Equivalence a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Equivalence a) #

Wrapped (Min a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Min a) #

Methods

_Wrapped' :: Iso' (Min a) (Unwrapped (Min a)) #

Wrapped (Max a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Max a) #

Methods

_Wrapped' :: Iso' (Max a) (Unwrapped (Max a)) #

Wrapped (First a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (First a) #

Methods

_Wrapped' :: Iso' (First a) (Unwrapped (First a)) #

Wrapped (Last a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Last a) #

Methods

_Wrapped' :: Iso' (Last a) (Unwrapped (Last a)) #

Wrapped (WrappedMonoid a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (WrappedMonoid a) #

Wrapped (Option a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Option a) #

Methods

_Wrapped' :: Iso' (Option a) (Unwrapped (Option a)) #

Wrapped (ZipList a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (ZipList a) #

Methods

_Wrapped' :: Iso' (ZipList a) (Unwrapped (ZipList a)) #

Wrapped (Identity a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Identity a) #

Wrapped (First a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (First a) #

Methods

_Wrapped' :: Iso' (First a) (Unwrapped (First a)) #

Wrapped (Last a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Last a) #

Methods

_Wrapped' :: Iso' (Last a) (Unwrapped (Last a)) #

Wrapped (Dual a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Dual a) #

Methods

_Wrapped' :: Iso' (Dual a) (Unwrapped (Dual a)) #

Wrapped (Endo a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Endo a) #

Methods

_Wrapped' :: Iso' (Endo a) (Unwrapped (Endo a)) #

Wrapped (Sum a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Sum a) #

Methods

_Wrapped' :: Iso' (Sum a) (Unwrapped (Sum a)) #

Wrapped (Product a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Product a) #

Methods

_Wrapped' :: Iso' (Product a) (Unwrapped (Product a)) #

Wrapped (Down a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Down a) #

Methods

_Wrapped' :: Iso' (Down a) (Unwrapped (Down a)) #

Wrapped (NonEmpty a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (NonEmpty a) #

Wrapped (IntMap a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (IntMap a) #

Methods

_Wrapped' :: Iso' (IntMap a) (Unwrapped (IntMap a)) #

Wrapped (Seq a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Seq a) #

Methods

_Wrapped' :: Iso' (Seq a) (Unwrapped (Seq a)) #

Ord a => Wrapped (Set a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Set a) #

Methods

_Wrapped' :: Iso' (Set a) (Unwrapped (Set a)) #

Prim a => Wrapped (Vector a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Vector a) #

Methods

_Wrapped' :: Iso' (Vector a) (Unwrapped (Vector a)) #

Storable a => Wrapped (Vector a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Vector a) #

Methods

_Wrapped' :: Iso' (Vector a) (Unwrapped (Vector a)) #

Unbox a => Wrapped (Vector a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Vector a) #

Methods

_Wrapped' :: Iso' (Vector a) (Unwrapped (Vector a)) #

(Hashable a, Eq a) => Wrapped (HashSet a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (HashSet a) #

Methods

_Wrapped' :: Iso' (HashSet a) (Unwrapped (HashSet a)) #

Wrapped (Vector a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Vector a) #

Methods

_Wrapped' :: Iso' (Vector a) (Unwrapped (Vector a)) #

Wrapped (UStore a) Source # 
Instance details

Defined in Lorentz.UStore.Types

Associated Types

type Unwrapped (UStore a) #

Methods

_Wrapped' :: Iso' (UStore a) (Unwrapped (UStore a)) #

Wrapped (UParam entries) Source # 
Instance details

Defined in Lorentz.UParam

Associated Types

type Unwrapped (UParam entries) #

Methods

_Wrapped' :: Iso' (UParam entries) (Unwrapped (UParam entries)) #

Wrapped (Op a b) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Op a b) #

Methods

_Wrapped' :: Iso' (Op a b) (Unwrapped (Op a b)) #

(Hashable k, Eq k) => Wrapped (HashMap k a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (HashMap k a) #

Methods

_Wrapped' :: Iso' (HashMap k a) (Unwrapped (HashMap k a)) #

Ord k => Wrapped (Map k a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Map k a) #

Methods

_Wrapped' :: Iso' (Map k a) (Unwrapped (Map k a)) #

Wrapped (WrappedMonad m a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (WrappedMonad m a) #

Wrapped (ArrowMonad m a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (ArrowMonad m a) #

Methods

_Wrapped' :: Iso' (ArrowMonad m a) (Unwrapped (ArrowMonad m a)) #

Wrapped (MaybeT m a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (MaybeT m a) #

Methods

_Wrapped' :: Iso' (MaybeT m a) (Unwrapped (MaybeT m a)) #

Wrapped (CatchT m a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (CatchT m a) #

Methods

_Wrapped' :: Iso' (CatchT m a) (Unwrapped (CatchT m a)) #

Wrapped (CoiterT w a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (CoiterT w a) #

Methods

_Wrapped' :: Iso' (CoiterT w a) (Unwrapped (CoiterT w a)) #

Wrapped (IterT m a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (IterT m a) #

Methods

_Wrapped' :: Iso' (IterT m a) (Unwrapped (IterT m a)) #

Wrapped (Alt f a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Alt f a) #

Methods

_Wrapped' :: Iso' (Alt f a) (Unwrapped (Alt f a)) #

Wrapped (ListT m a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (ListT m a) #

Methods

_Wrapped' :: Iso' (ListT m a) (Unwrapped (ListT m a)) #

Wrapped (WrappedApplicative f a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (WrappedApplicative f a) #

Wrapped (MaybeApply f a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (MaybeApply f a) #

Methods

_Wrapped' :: Iso' (MaybeApply f a) (Unwrapped (MaybeApply f a)) #

Wrapped (ParameterWrapper deriv cp) Source # 
Instance details

Defined in Lorentz.EntryPoints.Manual

Associated Types

type Unwrapped (ParameterWrapper deriv cp) #

Methods

_Wrapped' :: Iso' (ParameterWrapper deriv cp) (Unwrapped (ParameterWrapper deriv cp)) #

Wrapped (MigrationScript oldStore newStore) Source # 
Instance details

Defined in Lorentz.UStore.Migration.Base

Associated Types

type Unwrapped (MigrationScript oldStore newStore) #

Methods

_Wrapped' :: Iso' (MigrationScript oldStore newStore) (Unwrapped (MigrationScript oldStore newStore)) #

Wrapped (Extensible x) Source # 
Instance details

Defined in Lorentz.Extensible

Associated Types

type Unwrapped (Extensible x) #

Wrapped (Rec1 f p) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Rec1 f p) #

Methods

_Wrapped' :: Iso' (Rec1 f p) (Unwrapped (Rec1 f p)) #

Wrapped (WrappedArrow a b c) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (WrappedArrow a b c) #

Methods

_Wrapped' :: Iso' (WrappedArrow a b c) (Unwrapped (WrappedArrow a b c)) #

Wrapped (Kleisli m a b) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Kleisli m a b) #

Methods

_Wrapped' :: Iso' (Kleisli m a b) (Unwrapped (Kleisli m a b)) #

Wrapped (Const a x) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Const a x) #

Methods

_Wrapped' :: Iso' (Const a x) (Unwrapped (Const a x)) #

Wrapped (Ap f a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Ap f a) #

Methods

_Wrapped' :: Iso' (Ap f a) (Unwrapped (Ap f a)) #

Wrapped (Alt f a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Alt f a) #

Methods

_Wrapped' :: Iso' (Alt f a) (Unwrapped (Alt f a)) #

Wrapped (Join p a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Join p a) #

Methods

_Wrapped' :: Iso' (Join p a) (Unwrapped (Join p a)) #

Wrapped (Fix p a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Fix p a) #

Methods

_Wrapped' :: Iso' (Fix p a) (Unwrapped (Fix p a)) #

Wrapped (TracedT m w a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (TracedT m w a) #

Methods

_Wrapped' :: Iso' (TracedT m w a) (Unwrapped (TracedT m w a)) #

Wrapped (IdentityT m a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (IdentityT m a) #

Methods

_Wrapped' :: Iso' (IdentityT m a) (Unwrapped (IdentityT m a)) #

Wrapped (Compose f g a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Compose f g a) #

Methods

_Wrapped' :: Iso' (Compose f g a) (Unwrapped (Compose f g a)) #

Wrapped (ComposeFC f g a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (ComposeFC f g a) #

Methods

_Wrapped' :: Iso' (ComposeFC f g a) (Unwrapped (ComposeFC f g a)) #

Wrapped (ComposeCF f g a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (ComposeCF f g a) #

Methods

_Wrapped' :: Iso' (ComposeCF f g a) (Unwrapped (ComposeCF f g a)) #

Wrapped (ExceptT e m a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (ExceptT e m a) #

Methods

_Wrapped' :: Iso' (ExceptT e m a) (Unwrapped (ExceptT e m a)) #

Wrapped (FreeT f m a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (FreeT f m a) #

Methods

_Wrapped' :: Iso' (FreeT f m a) (Unwrapped (FreeT f m a)) #

Wrapped (CofreeT f w a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (CofreeT f w a) #

Methods

_Wrapped' :: Iso' (CofreeT f w a) (Unwrapped (CofreeT f w a)) #

Wrapped (ApT f g a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (ApT f g a) #

Methods

_Wrapped' :: Iso' (ApT f g a) (Unwrapped (ApT f g a)) #

Wrapped (ErrorT e m a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (ErrorT e m a) #

Methods

_Wrapped' :: Iso' (ErrorT e m a) (Unwrapped (ErrorT e m a)) #

Wrapped (StateT s m a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (StateT s m a) #

Methods

_Wrapped' :: Iso' (StateT s m a) (Unwrapped (StateT s m a)) #

Wrapped (Backwards f a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Backwards f a) #

Methods

_Wrapped' :: Iso' (Backwards f a) (Unwrapped (Backwards f a)) #

Wrapped (StateT s m a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (StateT s m a) #

Methods

_Wrapped' :: Iso' (StateT s m a) (Unwrapped (StateT s m a)) #

Wrapped (ReaderT r m a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (ReaderT r m a) #

Methods

_Wrapped' :: Iso' (ReaderT r m a) (Unwrapped (ReaderT r m a)) #

Wrapped (WriterT w m a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (WriterT w m a) #

Methods

_Wrapped' :: Iso' (WriterT w m a) (Unwrapped (WriterT w m a)) #

Wrapped (WriterT w m a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (WriterT w m a) #

Methods

_Wrapped' :: Iso' (WriterT w m a) (Unwrapped (WriterT w m a)) #

Wrapped (Star f d c) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Star f d c) #

Methods

_Wrapped' :: Iso' (Star f d c) (Unwrapped (Star f d c)) #

Wrapped (Costar f d c) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Costar f d c) #

Methods

_Wrapped' :: Iso' (Costar f d c) (Unwrapped (Costar f d c)) #

Wrapped (WrappedArrow p a b) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (WrappedArrow p a b) #

Methods

_Wrapped' :: Iso' (WrappedArrow p a b) (Unwrapped (WrappedArrow p a b)) #

Wrapped (Forget r a b) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Forget r a b) #

Methods

_Wrapped' :: Iso' (Forget r a b) (Unwrapped (Forget r a b)) #

Wrapped (Static f a b) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Static f a b) #

Methods

_Wrapped' :: Iso' (Static f a b) (Unwrapped (Static f a b)) #

Wrapped (Tagged s a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Tagged s a) #

Methods

_Wrapped' :: Iso' (Tagged s a) (Unwrapped (Tagged s a)) #

Wrapped (Reverse f a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Reverse f a) #

Methods

_Wrapped' :: Iso' (Reverse f a) (Unwrapped (Reverse f a)) #

Wrapped (Constant a b) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Constant a b) #

Methods

_Wrapped' :: Iso' (Constant a b) (Unwrapped (Constant a b)) #

Wrapped (K1 i c p) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (K1 i c p) #

Methods

_Wrapped' :: Iso' (K1 i c p) (Unwrapped (K1 i c p)) #

Wrapped (ContT r m a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (ContT r m a) #

Methods

_Wrapped' :: Iso' (ContT r m a) (Unwrapped (ContT r m a)) #

Wrapped (Cayley f p a b) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Cayley f p a b) #

Methods

_Wrapped' :: Iso' (Cayley f p a b) (Unwrapped (Cayley f p a b)) #

Wrapped (M1 i c f p) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (M1 i c f p) #

Methods

_Wrapped' :: Iso' (M1 i c f p) (Unwrapped (M1 i c f p)) #

Wrapped ((f :.: g) p) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped ((f :.: g) p) #

Methods

_Wrapped' :: Iso' ((f :.: g) p) (Unwrapped ((f :.: g) p)) #

Wrapped (Compose f g a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Compose f g a) #

Methods

_Wrapped' :: Iso' (Compose f g a) (Unwrapped (Compose f g a)) #

Wrapped (WrappedBifunctor p a b) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (WrappedBifunctor p a b) #

Wrapped (Joker g a b) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Joker g a b) #

Methods

_Wrapped' :: Iso' (Joker g a b) (Unwrapped (Joker g a b)) #

Wrapped (Flip p a b) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Flip p a b) #

Methods

_Wrapped' :: Iso' (Flip p a b) (Unwrapped (Flip p a b)) #

Wrapped (Clown f a b) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Clown f a b) #

Methods

_Wrapped' :: Iso' (Clown f a b) (Unwrapped (Clown f a b)) #

Wrapped (RWST r w s m a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (RWST r w s m a) #

Methods

_Wrapped' :: Iso' (RWST r w s m a) (Unwrapped (RWST r w s m a)) #

Wrapped (RWST r w s m a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (RWST r w s m a) #

Methods

_Wrapped' :: Iso' (RWST r w s m a) (Unwrapped (RWST r w s m a)) #

Wrapped (Dual k3 a b) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Dual k3 a b) #

Methods

_Wrapped' :: Iso' (Dual k3 a b) (Unwrapped (Dual k3 a b)) #

Wrapped (WrappedCategory k3 a b) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (WrappedCategory k3 a b) #

Wrapped (Semi m a b) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Semi m a b) #

Methods

_Wrapped' :: Iso' (Semi m a b) (Unwrapped (Semi m a b)) #

Wrapped (Tannen f p a b) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Tannen f p a b) #

Methods

_Wrapped' :: Iso' (Tannen f p a b) (Unwrapped (Tannen f p a b)) #

Wrapped (Biff p f g a b) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Biff p f g a b) #

Methods

_Wrapped' :: Iso' (Biff p f g a b) (Unwrapped (Biff p f g a b)) #