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

Morley.Michelson.Parser

Synopsis

Main parser type

Parsers

Errors

data CustomParserException Source #

Instances

Instances details
Data CustomParserException Source # 
Instance details

Defined in Morley.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 :: forall r r'. (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 #

Generic CustomParserException Source # 
Instance details

Defined in Morley.Michelson.Parser.Error

Associated Types

type Rep CustomParserException :: Type -> Type #

Show CustomParserException Source # 
Instance details

Defined in Morley.Michelson.Parser.Error

NFData CustomParserException Source # 
Instance details

Defined in Morley.Michelson.Parser.Error

Methods

rnf :: CustomParserException -> () #

Eq CustomParserException Source # 
Instance details

Defined in Morley.Michelson.Parser.Error

Ord CustomParserException Source # 
Instance details

Defined in Morley.Michelson.Parser.Error

ShowErrorComponent CustomParserException Source # 
Instance details

Defined in Morley.Michelson.Parser.Error

type Rep CustomParserException Source # 
Instance details

Defined in Morley.Michelson.Parser.Error

type Rep CustomParserException = D1 ('MetaData "CustomParserException" "Morley.Michelson.Parser.Error" "morley-1.20.0-inplace" 'False) ((C1 ('MetaCons "StringLiteralException" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 StringLiteralParserException)) :+: C1 ('MetaCons "ViewNameException" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 BadViewNameError))) :+: (C1 ('MetaCons "OddNumberBytesException" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ExcessFieldAnnotation" 'PrefixI 'False) (U1 :: Type -> Type)))

data ParseErrorBundle s e #

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

Since: megaparsec-7.0.0

Instances

Instances details
(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 :: forall r r'. (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, ShowErrorComponent e, VisualStream s, TraversableStream s, Typeable s, Typeable e) => Exception (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) => Show (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 -> () #

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

Defined in Text.Megaparsec.Error

type Rep (ParseErrorBundle s e) 
Instance details

Defined in Text.Megaparsec.Error

type Rep (ParseErrorBundle s e) = D1 ('MetaData "ParseErrorBundle" "Text.Megaparsec.Error" "megaparsec-9.3.1-e773df4000f440651934d3dae050944cd14e2c3c96e86d1b463946aa1942fdb2" '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

Instances details
Data StringLiteralParserException Source # 
Instance details

Defined in Morley.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 :: forall r r'. (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 #

Generic StringLiteralParserException Source # 
Instance details

Defined in Morley.Michelson.Parser.Error

Associated Types

type Rep StringLiteralParserException :: Type -> Type #

Show StringLiteralParserException Source # 
Instance details

Defined in Morley.Michelson.Parser.Error

NFData StringLiteralParserException Source # 
Instance details

Defined in Morley.Michelson.Parser.Error

Eq StringLiteralParserException Source # 
Instance details

Defined in Morley.Michelson.Parser.Error

Ord StringLiteralParserException Source # 
Instance details

Defined in Morley.Michelson.Parser.Error

ShowErrorComponent StringLiteralParserException Source # 
Instance details

Defined in Morley.Michelson.Parser.Error

type Rep StringLiteralParserException Source # 
Instance details

Defined in Morley.Michelson.Parser.Error

type Rep StringLiteralParserException = D1 ('MetaData "StringLiteralParserException" "Morley.Michelson.Parser.Error" "morley-1.20.0-inplace" 'False) (C1 ('MetaCons "InvalidEscapeSequence" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Char)) :+: C1 ('MetaCons "InvalidChar" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Char)))

Additional helpers

data MichelsonSource Source #

Where a contract or value in Michelson comes from.

Constructors

MSFile FilePath

From given file.

MSName Text

Only source name is known.

MSCode SrcLoc

Defined in Haskell code.

MSUnspecified

Some unknown source.

Bundled Patterns

pattern MSStdin :: MichelsonSource

Designates stdin source.

pattern MSCli :: MichelsonSource

Designates command line input source.

codeSrc :: HasCallStack => MichelsonSource Source #

MichelsonSource that points to the current position.

parseValue :: MichelsonSource -> Text -> Either ParserException ParsedValue Source #

Parse untyped value from text which comes from something that is not a file (which is often the case). So we assume it does not need any parsing environment.

>>> parseValue MSUnspecified "{PUSH int aaa}" & either (putStrLn . displayException) (const $ pure ())
1:11:
  |
1 | {PUSH int aaa}
  |           ^^^^
unexpected "aaa}"
expecting value

rawOpsSequence :: Parser a -> Parser [ParsedOp] Source #

Michelson sequence of instructions, separated with a semicolon. Last semicolon is optional, semicolon after } is optional.

The first argument is the sequence terminator, that is to say, usually }. This might look mysterious, until one considers the alternatives. For example:

>>> let fmt = either (putStrLn . displayException . ParserException) (const $ pure ())
>>> parseNoEnv (braces (sepEndBy parsedOp semicolon)) "" "{ DIIIP CMPEQ }" & fmt
...
1 | { DIIIP CMPEQ }
  |   ^
unexpected 'D'
expecting '}'
...
>>> parseNoEnv (symbol "{" *> rawOpsSequence (symbol "}")) "" "{ DIIIP CMPEQ }" & fmt
...
1 | { DIIIP CMPEQ }
  |         ^
unexpected 'C'
...

This happens because braces . sepEndBy backtracks a bit too far.

Note that braces . sepEndBy doesn't match Michelson syntax exactly, it's used as an example only.

For tests

codeEntry :: Parser ParsedOp Source #

Parses code block after "code" keyword of a contract, or code in a view block.

type_ :: Parser Ty Source #

This parses arbitrary type expressions.

Note that this includes parenthesized ones. That is to say, int, (int), ((int)), etc will match with this parser and produce TInt.

parsedOp :: Parser ParsedOp Source #

>>> let fmt = either (putStrLn . displayException . ParserException) (const $ pure ())
>>> parseNoEnv parsedOp "" "{a}" & fmt
1:2:
  |
1 | {a}
  |  ^^
unexpected "a}"
expecting '{', '}', macro, or primitive instruction

>>> parseNoEnv parsedOp "" "{ UNIT; DIIIP CMPEQ }" & fmt
1:15:
  |
1 | { UNIT; DIIIP CMPEQ }
  |               ^
unexpected 'C'

Quoters

utypeQ :: QuasiQuoter Source #

Creates Ty by its Morley representation.

>>> [utypeQ| or (int :a) (nat :b) |]
Ty (TOr (UnsafeAnnotation @FieldTag "") (UnsafeAnnotation @FieldTag "") (Ty TInt (UnsafeAnnotation @TypeTag "a")) (Ty TNat (UnsafeAnnotation @TypeTag "b"))) (UnsafeAnnotation @TypeTag "")
>>> [utypeQ|a|]

...
  |
1 | a
  | ^
unexpected 'a'
expecting type
...

uparamTypeQ :: QuasiQuoter Source #

Creates ParameterType by its Morley representation.

notes :: QuasiQuoter Source #

Parses and typechecks a Notes.

>>> [notes|int :ty|]
NTInt (UnsafeAnnotation @TypeTag "ty")

Re-exports

errorBundlePretty #

Arguments

:: (VisualStream s, TraversableStream s, ShowErrorComponent e) 
=> ParseErrorBundle s e

Parse error bundle to display

-> String

Textual rendition of the bundle

Pretty-print a ParseErrorBundle. All ParseErrors in the bundle will be pretty-printed in order together with the corresponding offending lines by doing a single pass over the input stream. The rendered String always ends with a newline.

Since: megaparsec-7.0.0