morley-0.3.0.1: Developer tools for the Michelson Language

Safe HaskellNone
LanguageHaskell2010

Michelson.Parser

Contents

Synopsis

Main parser type

Parsers

program :: Parsec CustomParserException Text (Contract' ParsedOp) Source #

Michelson contract with let definitions

Errors

data CustomParserException Source #

Instances
Eq CustomParserException Source # 
Instance details

Defined in Michelson.Parser.Error

Data CustomParserException Source # 
Instance details

Defined in Michelson.Parser.Error

Methods

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

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

toConstr :: CustomParserException -> Constr #

dataTypeOf :: CustomParserException -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CustomParserException Source # 
Instance details

Defined in Michelson.Parser.Error

Show CustomParserException Source # 
Instance details

Defined in Michelson.Parser.Error

ShowErrorComponent CustomParserException Source # 
Instance details

Defined in Michelson.Parser.Error

Default a => Default (Parser a) Source # 
Instance details

Defined in Michelson.Parser.Types

Methods

def :: Parser a #

data ParseErrorBundle s e #

A non-empty collection of ParseErrors equipped with PosState that allows to pretty-print the errors efficiently and correctly.

Since: megaparsec-7.0.0

Instances
(Eq s, Eq (Token s), Eq e) => Eq (ParseErrorBundle s e) 
Instance details

Defined in Text.Megaparsec.Error

(Data s, Data (Token s), Ord (Token s), Data e, Ord e) => Data (ParseErrorBundle s e) 
Instance details

Defined in Text.Megaparsec.Error

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ParseErrorBundle s e -> c (ParseErrorBundle s e) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ParseErrorBundle s e) #

toConstr :: ParseErrorBundle s e -> Constr #

dataTypeOf :: ParseErrorBundle s e -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> ParseErrorBundle s e -> ParseErrorBundle s e #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ParseErrorBundle s e -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ParseErrorBundle s e -> r #

gmapQ :: (forall d. Data d => d -> u) -> ParseErrorBundle s e -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ParseErrorBundle s e -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ParseErrorBundle s e -> m (ParseErrorBundle s e) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ParseErrorBundle s e -> m (ParseErrorBundle s e) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ParseErrorBundle s e -> m (ParseErrorBundle s e) #

(Show s, Show (Token s), Show e) => Show (ParseErrorBundle s e) 
Instance details

Defined in Text.Megaparsec.Error

Generic (ParseErrorBundle s e) 
Instance details

Defined in Text.Megaparsec.Error

Associated Types

type Rep (ParseErrorBundle s e) :: Type -> Type #

(Show s, Show (Token s), Show e, ShowErrorComponent e, Stream s, Typeable s, Typeable e) => Exception (ParseErrorBundle s e) 
Instance details

Defined in Text.Megaparsec.Error

(NFData s, NFData (Token s), NFData e) => NFData (ParseErrorBundle s e) 
Instance details

Defined in Text.Megaparsec.Error

Methods

rnf :: ParseErrorBundle s e -> () #

type Rep (ParseErrorBundle s e) 
Instance details

Defined in Text.Megaparsec.Error

type Rep (ParseErrorBundle s e) = D1 (MetaData "ParseErrorBundle" "Text.Megaparsec.Error" "megaparsec-7.0.5-1qUnxTAiqclI8WUqrA8tSY" False) (C1 (MetaCons "ParseErrorBundle" PrefixI True) (S1 (MetaSel (Just "bundleErrors") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NonEmpty (ParseError s e))) :*: S1 (MetaSel (Just "bundlePosState") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (PosState s))))

data StringLiteralParserException Source #

Instances
Eq StringLiteralParserException Source # 
Instance details

Defined in Michelson.Parser.Error

Data StringLiteralParserException Source # 
Instance details

Defined in Michelson.Parser.Error

Methods

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

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

toConstr :: StringLiteralParserException -> Constr #

dataTypeOf :: StringLiteralParserException -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord StringLiteralParserException Source # 
Instance details

Defined in Michelson.Parser.Error

Show StringLiteralParserException Source # 
Instance details

Defined in Michelson.Parser.Error

ShowErrorComponent StringLiteralParserException Source # 
Instance details

Defined in Michelson.Parser.Error

Additional helpers

parseNoEnv :: Parser a -> String -> Text -> Either (ParseErrorBundle Text CustomParserException) a Source #

Parse with empty environment

For tests

codeEntry :: Parser [ParsedOp] Source #

Parses code block after "code" keyword of a contract.

This function is part of the module API, its semantics should not change.

type_ :: Parser Type Source #

Parse untyped Michelson Type (i. e. one with annotations).

explicitType :: Parser Type Source #

Parse only explicit Type, Parameter and Storage are prohibited