morley-1.16.0: Developer tools for the Michelson Language
Safe HaskellNone
LanguageHaskell2010

Morley.Michelson.Untyped.Contract

Description

Michelson contract in untyped model.

Synopsis

Documentation

data EntriesOrder Source #

Top-level entries order of the contract. This is preserved due to the fact that it affects the output of pretty-printing and serializing contract.

Constructors

PSC 
PCS 
SPC 
SCP 
CSP 
CPS 

Instances

Instances details
Bounded EntriesOrder Source # 
Instance details

Defined in Morley.Michelson.Untyped.Contract

Enum EntriesOrder Source # 
Instance details

Defined in Morley.Michelson.Untyped.Contract

Eq EntriesOrder Source # 
Instance details

Defined in Morley.Michelson.Untyped.Contract

Data EntriesOrder Source # 
Instance details

Defined in Morley.Michelson.Untyped.Contract

Methods

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

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

toConstr :: EntriesOrder -> Constr #

dataTypeOf :: EntriesOrder -> DataType #

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

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

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

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

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

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

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

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

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

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

Show EntriesOrder Source # 
Instance details

Defined in Morley.Michelson.Untyped.Contract

Generic EntriesOrder Source # 
Instance details

Defined in Morley.Michelson.Untyped.Contract

Associated Types

type Rep EntriesOrder :: Type -> Type #

ToJSON EntriesOrder Source # 
Instance details

Defined in Morley.Michelson.Untyped.Contract

FromJSON EntriesOrder Source # 
Instance details

Defined in Morley.Michelson.Untyped.Contract

NFData EntriesOrder Source # 
Instance details

Defined in Morley.Michelson.Untyped.Contract

Methods

rnf :: EntriesOrder -> () #

Default EntriesOrder Source # 
Instance details

Defined in Morley.Michelson.Untyped.Contract

Methods

def :: EntriesOrder #

type Rep EntriesOrder Source # 
Instance details

Defined in Morley.Michelson.Untyped.Contract

type Rep EntriesOrder = D1 ('MetaData "EntriesOrder" "Morley.Michelson.Untyped.Contract" "morley-1.16.0-inplace" 'False) ((C1 ('MetaCons "PSC" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PCS" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SPC" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "SCP" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CSP" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CPS" 'PrefixI 'False) (U1 :: Type -> Type))))

canonicalEntriesOrder :: EntriesOrder Source #

The canonical entries order which is ordered as follow: parameter, storage, and code.

entriesOrderToInt :: EntriesOrder -> (Int, Int, Int) Source #

(Int, Int, Int) is the positions of parameter, storage, and code respectively.

mapEntriesOrdered :: Contract' op -> (ParameterType -> a) -> (Storage -> a) -> ([op] -> a) -> [a] Source #

Map each contract fields by the given function and sort the output based on the EntriesOrder.

data ContractBlock op Source #

Contract block, convenient when parsing

Constructors

CBParam ParameterType 
CBStorage Ty 
CBCode [op] 

Instances

Instances details
Eq op => Eq (ContractBlock op) Source # 
Instance details

Defined in Morley.Michelson.Untyped.Contract

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

Defined in Morley.Michelson.Untyped.Contract

orderContractBlock :: (ContractBlock op, ContractBlock op, ContractBlock op) -> Maybe (Contract' op) Source #

Construct a contract representation from three different contract blocks (i.e. parameters, storage and code blocks) in arbitrary order. This saves the order in the contract so that it can print the contract blocks in the same order it was parsed.

data Contract' op Source #

General untyped contract representation.

Constructors

Contract 

Fields

Instances

Instances details
Functor Contract' Source # 
Instance details

Defined in Morley.Michelson.Untyped.Contract

Methods

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

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

FromExpression Contract Source # 
Instance details

Defined in Morley.Micheline.Class

ToExpression Contract Source # 
Instance details

Defined in Morley.Micheline.Class

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

Defined in Morley.Michelson.Untyped.Contract

Methods

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

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

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

Defined in Morley.Michelson.Untyped.Contract

Methods

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

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

toConstr :: Contract' op -> Constr #

dataTypeOf :: Contract' op -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Defined in Morley.Michelson.Untyped.Contract

Methods

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

show :: Contract' op -> String #

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

Generic (Contract' op) Source # 
Instance details

Defined in Morley.Michelson.Untyped.Contract

Associated Types

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

Methods

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

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

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

Defined in Morley.Michelson.Untyped.Contract

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

Defined in Morley.Michelson.Untyped.Contract

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

Defined in Morley.Michelson.Untyped.Contract

Methods

rnf :: Contract' op -> () #

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

Defined in Morley.Michelson.Untyped.Contract

Methods

build :: Contract' op -> Builder #

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

Defined in Morley.Michelson.Untyped.Contract

type Rep (Contract' op) Source # 
Instance details

Defined in Morley.Michelson.Untyped.Contract

type Rep (Contract' op) = D1 ('MetaData "Contract'" "Morley.Michelson.Untyped.Contract" "morley-1.16.0-inplace" 'False) (C1 ('MetaCons "Contract" 'PrefixI 'True) ((S1 ('MetaSel ('Just "contractParameter") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ParameterType) :*: S1 ('MetaSel ('Just "contractStorage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Storage)) :*: (S1 ('MetaSel ('Just "contractCode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [op]) :*: S1 ('MetaSel ('Just "entriesOrder") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 EntriesOrder))))

type Storage = Ty Source #

Convenience synonym for Ty representing the storage type