morley-1.19.0: Developer tools for the Michelson Language
Safe HaskellSafe-Inferred
LanguageHaskell2010

Morley.Michelson.Untyped.Value

Description

Untyped Michelson values (i. e. type of a value is not statically known).

Synopsis

Documentation

data Value' op Source #

Constructors

ValueInt Integer 
ValueString MText 
ValueBytes InternalByteString 
ValueUnit 
ValueTrue 
ValueFalse 
ValuePair (Value' op) (Value' op) 
ValueLeft (Value' op) 
ValueRight (Value' op) 
ValueSome (Value' op) 
ValueNone 
ValueNil 
ValueSeq (NonEmpty $ Value' op)

A sequence of elements: can be a list, a set or a pair. We can't distinguish lists and sets during parsing.

ValueMap (NonEmpty $ Elt op) 
ValueLambda (NonEmpty op) 
ValueLamRec (NonEmpty op) 

Instances

Instances details
Functor Value' Source # 
Instance details

Defined in Morley.Michelson.Untyped.Value

Methods

fmap :: (a -> b) -> Value' a -> Value' b #

(<$) :: a -> Value' b -> Value' a #

ToExpression Value Source # 
Instance details

Defined in Morley.Micheline.Class

HasCLReader Value Source # 
Instance details

Defined in Morley.CLI

FromExp x op => FromExp x (Value' op) Source # 
Instance details

Defined in Morley.Micheline.Class

Methods

fromExp :: Exp x -> Either (FromExpError x) (Value' op) Source #

FromJSON op => FromJSON (Value' op) Source # 
Instance details

Defined in Morley.Michelson.Untyped.Value

ToJSON op => ToJSON (Value' op) Source # 
Instance details

Defined in Morley.Michelson.Untyped.Value

Data op => Data (Value' op) Source # 
Instance details

Defined in Morley.Michelson.Untyped.Value

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Value' op -> c (Value' op) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Value' op) #

toConstr :: Value' op -> Constr #

dataTypeOf :: Value' op -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Value' op)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Value' op)) #

gmapT :: (forall b. Data b => b -> b) -> Value' op -> Value' op #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Value' op -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Value' op -> r #

gmapQ :: (forall d. Data d => d -> u) -> Value' op -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Value' op -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Value' op -> m (Value' op) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Value' op -> m (Value' op) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Value' op -> m (Value' op) #

Generic (Value' op) Source # 
Instance details

Defined in Morley.Michelson.Untyped.Value

Associated Types

type Rep (Value' op) :: Type -> Type #

Methods

from :: Value' op -> Rep (Value' op) x #

to :: Rep (Value' op) x -> Value' op #

Show op => Show (Value' op) Source # 
Instance details

Defined in Morley.Michelson.Untyped.Value

Methods

showsPrec :: Int -> Value' op -> ShowS #

show :: Value' op -> String #

showList :: [Value' op] -> ShowS #

NFData op => NFData (Value' op) Source # 
Instance details

Defined in Morley.Michelson.Untyped.Value

Methods

rnf :: Value' op -> () #

RenderDoc op => Buildable (Value' op) Source # 
Instance details

Defined in Morley.Michelson.Untyped.Value

Methods

build :: Value' op -> Builder #

Eq op => Eq (Value' op) Source # 
Instance details

Defined in Morley.Michelson.Untyped.Value

Methods

(==) :: Value' op -> Value' op -> Bool #

(/=) :: Value' op -> Value' op -> Bool #

RenderDoc op => RenderDoc (Value' op) Source # 
Instance details

Defined in Morley.Michelson.Untyped.Value

type Rep (Value' op) Source # 
Instance details

Defined in Morley.Michelson.Untyped.Value

type Rep (Value' op) = D1 ('MetaData "Value'" "Morley.Michelson.Untyped.Value" "morley-1.19.0-inplace" 'False) ((((C1 ('MetaCons "ValueInt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Integer)) :+: C1 ('MetaCons "ValueString" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 MText))) :+: (C1 ('MetaCons "ValueBytes" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 InternalByteString)) :+: C1 ('MetaCons "ValueUnit" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "ValueTrue" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ValueFalse" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ValuePair" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Value' op)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Value' op))) :+: C1 ('MetaCons "ValueLeft" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Value' op)))))) :+: (((C1 ('MetaCons "ValueRight" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Value' op))) :+: C1 ('MetaCons "ValueSome" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Value' op)))) :+: (C1 ('MetaCons "ValueNone" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ValueNil" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "ValueSeq" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (NonEmpty $ Value' op))) :+: C1 ('MetaCons "ValueMap" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (NonEmpty $ Elt op)))) :+: (C1 ('MetaCons "ValueLambda" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (NonEmpty op))) :+: C1 ('MetaCons "ValueLamRec" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (NonEmpty op)))))))

data Elt op Source #

Constructors

Elt (Value' op) (Value' op) 

Instances

Instances details
Functor Elt Source # 
Instance details

Defined in Morley.Michelson.Untyped.Value

Methods

fmap :: (a -> b) -> Elt a -> Elt b #

(<$) :: a -> Elt b -> Elt a #

FromJSON op => FromJSON (Elt op) Source # 
Instance details

Defined in Morley.Michelson.Untyped.Value

Methods

parseJSON :: Value -> Parser (Elt op) #

parseJSONList :: Value -> Parser [Elt op] #

ToJSON op => ToJSON (Elt op) Source # 
Instance details

Defined in Morley.Michelson.Untyped.Value

Methods

toJSON :: Elt op -> Value #

toEncoding :: Elt op -> Encoding #

toJSONList :: [Elt op] -> Value #

toEncodingList :: [Elt op] -> Encoding #

Data op => Data (Elt op) Source # 
Instance details

Defined in Morley.Michelson.Untyped.Value

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Elt op -> c (Elt op) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Elt op) #

toConstr :: Elt op -> Constr #

dataTypeOf :: Elt op -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Elt op)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Elt op)) #

gmapT :: (forall b. Data b => b -> b) -> Elt op -> Elt op #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Elt op -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Elt op -> r #

gmapQ :: (forall d. Data d => d -> u) -> Elt op -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Elt op -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Elt op -> m (Elt op) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Elt op -> m (Elt op) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Elt op -> m (Elt op) #

Generic (Elt op) Source # 
Instance details

Defined in Morley.Michelson.Untyped.Value

Associated Types

type Rep (Elt op) :: Type -> Type #

Methods

from :: Elt op -> Rep (Elt op) x #

to :: Rep (Elt op) x -> Elt op #

Show op => Show (Elt op) Source # 
Instance details

Defined in Morley.Michelson.Untyped.Value

Methods

showsPrec :: Int -> Elt op -> ShowS #

show :: Elt op -> String #

showList :: [Elt op] -> ShowS #

NFData op => NFData (Elt op) Source # 
Instance details

Defined in Morley.Michelson.Untyped.Value

Methods

rnf :: Elt op -> () #

RenderDoc op => Buildable (Elt op) Source # 
Instance details

Defined in Morley.Michelson.Untyped.Value

Methods

build :: Elt op -> Builder #

Eq op => Eq (Elt op) Source # 
Instance details

Defined in Morley.Michelson.Untyped.Value

Methods

(==) :: Elt op -> Elt op -> Bool #

(/=) :: Elt op -> Elt op -> Bool #

RenderDoc op => RenderDoc (Elt op) Source # 
Instance details

Defined in Morley.Michelson.Untyped.Value

type Rep (Elt op) Source # 
Instance details

Defined in Morley.Michelson.Untyped.Value

type Rep (Elt op) = D1 ('MetaData "Elt" "Morley.Michelson.Untyped.Value" "morley-1.19.0-inplace" 'False) (C1 ('MetaCons "Elt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Value' op)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Value' op))))

newtype InternalByteString Source #

ByteString does not have an instance for ToJSON and FromJSON, to avoid orphan type class instances, make a new type wrapper around it.

Instances

Instances details
FromJSON InternalByteString Source # 
Instance details

Defined in Morley.Michelson.Untyped.Value

ToJSON InternalByteString Source # 
Instance details

Defined in Morley.Michelson.Untyped.Value

Data InternalByteString Source # 
Instance details

Defined in Morley.Michelson.Untyped.Value

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InternalByteString -> c InternalByteString #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InternalByteString #

toConstr :: InternalByteString -> Constr #

dataTypeOf :: InternalByteString -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c InternalByteString) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InternalByteString) #

gmapT :: (forall b. Data b => b -> b) -> InternalByteString -> InternalByteString #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InternalByteString -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InternalByteString -> r #

gmapQ :: (forall d. Data d => d -> u) -> InternalByteString -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InternalByteString -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InternalByteString -> m InternalByteString #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InternalByteString -> m InternalByteString #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InternalByteString -> m InternalByteString #

Generic InternalByteString Source # 
Instance details

Defined in Morley.Michelson.Untyped.Value

Associated Types

type Rep InternalByteString :: Type -> Type #

Show InternalByteString Source # 
Instance details

Defined in Morley.Michelson.Untyped.Value

NFData InternalByteString Source # 
Instance details

Defined in Morley.Michelson.Untyped.Value

Methods

rnf :: InternalByteString -> () #

Eq InternalByteString Source # 
Instance details

Defined in Morley.Michelson.Untyped.Value

type Rep InternalByteString Source # 
Instance details

Defined in Morley.Michelson.Untyped.Value

type Rep InternalByteString = D1 ('MetaData "InternalByteString" "Morley.Michelson.Untyped.Value" "morley-1.19.0-inplace" 'True) (C1 ('MetaCons "InternalByteString" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))

linearizeRightCombValuePair :: Value' op -> NonEmpty (Value' op) Source #

Converts Pair a (Pair b c) to [a, b, c].

renderValuesList :: (e -> Doc) -> NonEmpty e -> Doc Source #

A helper function that renders a NonEmpty list of items in Michelson-readable format, given a rendering function for a single item.

renderSome :: RenderContext -> (RenderContext -> Doc) -> Doc Source #

Helper functions to render Values

renderNone :: Doc Source #

Helper function to render None Value

renderLeft :: RenderContext -> (RenderContext -> Doc) -> Doc Source #

Helper functions to render Values

renderRight :: RenderContext -> (RenderContext -> Doc) -> Doc Source #

Helper functions to render Values

renderPair :: RenderContext -> (RenderContext -> Doc) -> (RenderContext -> Doc) -> Doc Source #

Helper function to render Pair Value

renderElt' :: (RenderContext -> Doc) -> (RenderContext -> Doc) -> Doc Source #

Helper function to render Elt