| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Morley.Michelson.Typed.Haskell.LooseSum
Description
Representation of Haskell sum types via loosy typed Michelson values, useful for e.g. errors and enums.
In particular, ADT sum can be represented as constructor name + data it carries. Such expression does not have particular type because different constructors may carry different data, and we avoid lifting this data to a union in order to keep only the significant parts (and thus not to confuse the client).
Synopsis
- data ComposeResult a
- fromTaggedVal :: LooseSumC dt => (Text, SomeValue) -> ComposeResult dt
- toTaggedVal :: LooseSumC dt => dt -> (Text, SomeValue)
- type LooseSumC dt = (NiceGeneric dt, GLooseSum (GRep dt))
Documentation
data ComposeResult a Source #
Possible outcomes of an attempt to construct a Haskell ADT value from constructor name and relevant data.
Constructors
| ComposeOk a | Composed fine. |
| ComposeCtorNotFound | No constructor with such name. |
| ComposeFieldTypeMismatch T T | Found required constructor, but type of data does not correspond to provided one. |
Instances
| Functor ComposeResult Source # | |
Defined in Morley.Michelson.Typed.Haskell.LooseSum Methods fmap :: (a -> b) -> ComposeResult a -> ComposeResult b # (<$) :: a -> ComposeResult b -> ComposeResult a # | |
| Monoid (ComposeResult a) Source # | |
Defined in Morley.Michelson.Typed.Haskell.LooseSum Methods mempty :: ComposeResult a # mappend :: ComposeResult a -> ComposeResult a -> ComposeResult a # mconcat :: [ComposeResult a] -> ComposeResult a # | |
| Semigroup (ComposeResult a) Source # | |
Defined in Morley.Michelson.Typed.Haskell.LooseSum Methods (<>) :: ComposeResult a -> ComposeResult a -> ComposeResult a # sconcat :: NonEmpty (ComposeResult a) -> ComposeResult a # stimes :: Integral b => b -> ComposeResult a -> ComposeResult a # | |
| Show a => Show (ComposeResult a) Source # | |
Defined in Morley.Michelson.Typed.Haskell.LooseSum Methods showsPrec :: Int -> ComposeResult a -> ShowS # show :: ComposeResult a -> String # showList :: [ComposeResult a] -> ShowS # | |
fromTaggedVal :: LooseSumC dt => (Text, SomeValue) -> ComposeResult dt Source #
Inverse to toTaggedVal.
>>>import Morley.Michelson.Typed
>>>fromTaggedVal @(Maybe ()) ("Just", SomeValue VUnit)ComposeOk (Just ())
>>>data Foo = Foo () deriving Show>>>fromTaggedVal @Foo ("Foo", SomeValue VUnit)... ... GHC.Generics.Rep Foo ... is stuck. Likely ... Generic Foo ... instance is missing or out of scope. ...>>>data Foo = Foo () deriving (Show, Generic)>>>fromTaggedVal @Foo ("Foo", SomeValue VUnit)ComposeOk (Foo ())
toTaggedVal :: LooseSumC dt => dt -> (Text, SomeValue) Source #
Decompose Haskell type into constructor name and
data it carries, converting the latter into Michelson Value.
>>>toTaggedVal $ Just ()("Just",Constrained VUnit)
A custom TypeError is generated if a type doesn't have a Generic instance
>>>data Foo = Foo ()>>>toTaggedVal $ Foo ()... ... GHC.Generics.Rep Foo ... is stuck. Likely ... Generic Foo ... instance is missing or out of scope. ...>>>data Foo = Foo () deriving Generic>>>toTaggedVal $ Foo ()("Foo",Constrained VUnit)
type LooseSumC dt = (NiceGeneric dt, GLooseSum (GRep dt)) Source #
Constraint for toTaggedVal and fromTaggedVal.