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

Morley.Michelson.Untyped.Contract

Description

Michelson contract in untyped model.

Synopsis

Documentation

newtype 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

EntriesOrder 

Instances

Instances details
FromJSON EntriesOrder Source # 
Instance details

Defined in Morley.Michelson.Untyped.Contract

ToJSON 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

Default EntriesOrder Source # 
Instance details

Defined in Morley.Michelson.Untyped.Contract

Methods

def :: EntriesOrder #

NFData EntriesOrder Source # 
Instance details

Defined in Morley.Michelson.Untyped.Contract

Methods

rnf :: EntriesOrder -> () #

Eq EntriesOrder Source # 
Instance details

Defined in Morley.Michelson.Untyped.Contract

Ord EntriesOrder Source # 
Instance details

Defined in Morley.Michelson.Untyped.Contract

data Entry Source #

Instances

Instances details
FromJSON Entry Source # 
Instance details

Defined in Morley.Michelson.Untyped.Contract

FromJSONKey Entry Source # 
Instance details

Defined in Morley.Michelson.Untyped.Contract

ToJSON Entry Source # 
Instance details

Defined in Morley.Michelson.Untyped.Contract

ToJSONKey Entry Source # 
Instance details

Defined in Morley.Michelson.Untyped.Contract

Data Entry 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) -> Entry -> c Entry #

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

toConstr :: Entry -> Constr #

dataTypeOf :: Entry -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Entry Source # 
Instance details

Defined in Morley.Michelson.Untyped.Contract

Associated Types

type Rep Entry :: Type -> Type #

Methods

from :: Entry -> Rep Entry x #

to :: Rep Entry x -> Entry #

Show Entry Source # 
Instance details

Defined in Morley.Michelson.Untyped.Contract

Methods

showsPrec :: Int -> Entry -> ShowS #

show :: Entry -> String #

showList :: [Entry] -> ShowS #

NFData Entry Source # 
Instance details

Defined in Morley.Michelson.Untyped.Contract

Methods

rnf :: Entry -> () #

Eq Entry Source # 
Instance details

Defined in Morley.Michelson.Untyped.Contract

Methods

(==) :: Entry -> Entry -> Bool #

(/=) :: Entry -> Entry -> Bool #

Ord Entry Source # 
Instance details

Defined in Morley.Michelson.Untyped.Contract

Methods

compare :: Entry -> Entry -> Ordering #

(<) :: Entry -> Entry -> Bool #

(<=) :: Entry -> Entry -> Bool #

(>) :: Entry -> Entry -> Bool #

(>=) :: Entry -> Entry -> Bool #

max :: Entry -> Entry -> Entry #

min :: Entry -> Entry -> Entry #

Buildable Entry Source # 
Instance details

Defined in Morley.Michelson.Untyped.Contract

Methods

build :: Entry -> Doc

buildList :: [Entry] -> Doc

type Rep Entry Source # 
Instance details

Defined in Morley.Michelson.Untyped.Contract

type Rep Entry = D1 ('MetaData "Entry" "Morley.Michelson.Untyped.Contract" "morley-1.20.0-inplace" 'False) ((C1 ('MetaCons "EntryParameter" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EntryStorage" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "EntryCode" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EntryView" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ViewName))))

canonicalEntriesOrder :: EntriesOrder Source #

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

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

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

mkEntriesOrder :: [Entry] -> EntriesOrder Source #

Helper to construct EntriesOrder from an ordered list of entires. Duplicate entires are ignored.

data ContractBlock op Source #

Contract block, convenient when parsing

Instances

Instances details
Functor ContractBlock Source # 
Instance details

Defined in Morley.Michelson.Untyped.Contract

Methods

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

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

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

Defined in Morley.Michelson.Untyped.Contract

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

Defined in Morley.Michelson.Untyped.Contract

Buildable (ContractBlock op) Source # 
Instance details

Defined in Morley.Michelson.Untyped.Contract

Methods

build :: ContractBlock op -> Doc

buildList :: [ContractBlock op] -> Doc

orderContractBlock :: forall op. [ContractBlock op] -> Either (NonEmpty ContractBlockError) (Contract' op) Source #

Construct a contract representation from the contract blocks (i.e. parameters, storage, code blocks, etc.) in arbitrary order. This makes sure that unique blocks like code do not duplicate, and 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 #

ToExpression Contract Source # 
Instance details

Defined in Morley.Micheline.Class

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

Defined in Morley.Micheline.Class

Methods

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

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

Defined in Morley.Michelson.Untyped.Contract

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

Defined in Morley.Michelson.Untyped.Contract

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) #

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 #

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 #

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

Defined in Morley.Michelson.Untyped.Contract

Methods

rnf :: Contract' op -> () #

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 #

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.20.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) :*: S1 ('MetaSel ('Just "contractViews") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (ViewsSet op))))))

data View' op Source #

Untyped view in a contract.

Constructors

View 

Fields

Instances

Instances details
Functor View' Source # 
Instance details

Defined in Morley.Michelson.Untyped.View

Methods

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

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

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

Defined in Morley.Michelson.Untyped.View

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

Defined in Morley.Michelson.Untyped.View

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

Defined in Morley.Michelson.Untyped.View

Methods

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

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

toConstr :: View' op -> Constr #

dataTypeOf :: View' op -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic (View' op) Source # 
Instance details

Defined in Morley.Michelson.Untyped.View

Associated Types

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

Methods

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

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

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

Defined in Morley.Michelson.Untyped.View

Methods

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

show :: View' op -> String #

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

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

Defined in Morley.Michelson.Untyped.View

Methods

rnf :: View' op -> () #

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

Defined in Morley.Michelson.Untyped.View

Methods

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

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

type Rep (View' op) Source # 
Instance details

Defined in Morley.Michelson.Untyped.View

type Rep (View' op) = D1 ('MetaData "View'" "Morley.Michelson.Untyped.View" "morley-1.20.0-inplace" 'False) (C1 ('MetaCons "View" 'PrefixI 'True) ((S1 ('MetaSel ('Just "viewName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ViewName) :*: S1 ('MetaSel ('Just "viewArgument") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Ty)) :*: (S1 ('MetaSel ('Just "viewReturn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Ty) :*: S1 ('MetaSel ('Just "viewCode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 op))))

type Storage = Ty Source #

Convenience synonym for Ty representing the storage type