| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Morley.Michelson.Typed.Existential
Synopsis
- data Constrained c f where
- pattern SomeConstrainedValue :: forall c. () => forall a. c a => Value a -> SomeConstrainedValue c
- pattern SomeValue :: () => SingI t => Value t -> SomeValue
- pattern SomeConstant :: () => ConstantScope t => Value t -> SomeConstant
- pattern SomeStorage :: () => StorageScope t => Value t -> SomeStorage
- pattern SomePackedVal :: () => PackedValScope t => Value t -> SomePackedVal
- type SomeConstrainedValue c = Constrained c Value
- type SomeConstant = SomeConstrainedValue ConstantScope
- type SomeValue = SomeConstrainedValue SingI
- type SomeStorage = SomeConstrainedValue StorageScope
- type SomePackedVal = SomeConstrainedValue PackedValScope
- data SomeContract where
- SomeContract :: Contract cp st -> SomeContract
- data SomeContractAndStorage where
- SomeContractAndStorage :: forall cp st. (StorageScope st, ParameterScope cp) => Contract cp st -> Value st -> SomeContractAndStorage
- data SomeIsoValue where
- SomeIsoValue :: KnownIsoT a => a -> SomeIsoValue
- data SomeVBigMap where
- SomeVBigMap :: forall k v. Value ('TBigMap k v) -> SomeVBigMap
SomeConstrainedValue and derivatives
data Constrained c f where Source #
Bundled Patterns
| pattern SomeConstrainedValue :: forall c. () => forall a. c a => Value a -> SomeConstrainedValue c | |
| pattern SomeValue :: () => SingI t => Value t -> SomeValue | |
| pattern SomeConstant :: () => ConstantScope t => Value t -> SomeConstant | |
| pattern SomeStorage :: () => StorageScope t => Value t -> SomeStorage | |
| pattern SomePackedVal :: () => PackedValScope t => Value t -> SomePackedVal |
Instances
type SomeConstrainedValue c = Constrained c Value Source #
type SomeValue = SomeConstrainedValue SingI Source #
Other existentials
data SomeContract where Source #
Constructors
| SomeContract :: Contract cp st -> SomeContract |
Instances
| Show SomeContract Source # | |
Defined in Morley.Michelson.Typed.Existential Methods showsPrec :: Int -> SomeContract -> ShowS # show :: SomeContract -> String # showList :: [SomeContract] -> ShowS # | |
| NFData SomeContract Source # | |
Defined in Morley.Michelson.Typed.Existential Methods rnf :: SomeContract -> () # | |
data SomeContractAndStorage where Source #
Represents a typed contract & a storage value of the type expected by the contract.
Constructors
| SomeContractAndStorage :: forall cp st. (StorageScope st, ParameterScope cp) => Contract cp st -> Value st -> SomeContractAndStorage |
Instances
| Show SomeContractAndStorage Source # | |
Defined in Morley.Michelson.Typed.Existential Methods showsPrec :: Int -> SomeContractAndStorage -> ShowS # show :: SomeContractAndStorage -> String # showList :: [SomeContractAndStorage] -> ShowS # | |
data SomeIsoValue where Source #
Hides some Haskell value put in line with Michelson Value.
Constructors
| SomeIsoValue :: KnownIsoT a => a -> SomeIsoValue |
data SomeVBigMap where Source #
Constructors
| SomeVBigMap :: forall k v. Value ('TBigMap k v) -> SomeVBigMap |
Orphan instances
| (forall (t :: T). cs t => HasNoOp t) => RenderDoc (SomeConstrainedValue cs) Source # | |
Methods renderDoc :: RenderContext -> SomeConstrainedValue cs -> Doc Source # isRenderable :: SomeConstrainedValue cs -> Bool Source # | |