bricks-parsec-0.0.0.4: ...

Safe HaskellSafe
LanguageHaskell2010

Bricks.Parsec

Contents

Description

Parsec Parsers for the Bricks language.

Most parsers consume trailing whitespace, except ones that operate within quoted string environments where whitespace is significant.

Synopsis

Expressions

parse'expression :: Parser Expression Source #

The primary, top-level expression parser. This is what you use to parse a .nix file.

Examples

>>> parseTest parse'expression ""
parse error at (line 1, column 1):
unexpected end of input
expecting expression

parse'expression'paren :: Parser Expression Source #

Parser for a parenthesized expression, from opening parenthesis to closing parenthesis.

parse'expression'dictKey :: Parser Expression Source #

Parser for an expression in a context that is expecting a dict key.

One of:

  • an unquoted string
  • a quoted dynamic string
  • an arbitrary expression wrapped in antiquotes (${ ... })

Expression lists

parse'expressionList :: Parser [Expression] Source #

Parser for a list of expressions in a list literal ([ x y z ]) or in a chain of function arguments (f x y z).

Examples

>>> parseTest parse'expressionList ""
[]
>>> parseTest (length <$> parse'expressionList) "x \"one two\" (a: b) (c d)"
4
>>> parseTest (length <$> parse'expressionList) "(x \"one two\" (a: b) (c d))"
1

parse'expressionList'1 :: Parser Expression Source #

Parser for a single item within an expression list (expressionListP). This expression is not a lambda, a function application, a let-in expression, or a with expression.

Examples

>>> parseTest parse'expressionList'1 "ab.xy"
{- 1:1-1:6 -} dot ({- 1:1-1:3 -} var "ab") ({- 1:4-1:6 -} str [{- 1:4-1:6 -} "xy"])
>>> :{
>>> parseTest (expression'discardSource <$> parse'expressionList'1)
>>> "(x: f x x) y z"
>>> :}
lambda (param "x") (apply (apply (var "f") (var "x")) (var "x"))
>>> :{
>>> parseTest (expression'discardSource <$> parse'expressionList'1)
>>> "{ a = b; }.a y"
>>> :}
dot (dict [dict'eq (str ["a"]) (var "b")]) (str ["a"])

parse'expressionList'1'noDot :: Parser Expression Source #

Like parse'expressionList'1, but with the further restriction that the expression may not be a Dot.

Examples

>>> parseTest parse'expressionList'1'noDot "ab.xy"
{- 1:1-1:3 -} var "ab"
>>> :{
>>> parseTest (expression'discardSource <$> parse'expressionList'1'noDot)
>>> "(x: f x x) y z"
>>> :}
lambda (param "x") (apply (apply (var "f") (var "x")) (var "x"))
>>> :{
>>> parseTest (expression'discardSource <$> parse'expressionList'1'noDot)
>>> "{ a = b; }.a y"
>>> :}
dict [dict'eq (str ["a"]) (var "b")]

Variables

Strings

parse'strUnquoted :: Parser (UnquotedString, SourceRange) Source #

Parser for an unquoted string. Unquoted strings are restricted to a conservative set of characters, and they may not be any of the keywords. See text'canBeUnquoted for a complete description of the unquoted string rules.

Examples

>>> parseTest parse'strUnquoted "abc"
("abc",1:1-1:4)

Here the parser consumes letters up to but not including {, because that character does not satisfy char'canBeUnquoted:

>>> parseTest parse'strUnquoted "ab{c"
("ab",1:1-1:3)

"let" does not parse as an unquoted string because let is a keyword:

>>> parseTest parse'strUnquoted "let"
parse error at (line 1, column 4):
unexpected end of input

This parser does not parse quoted strings:

>>> parseTest parse'strUnquoted "\"abc\""
parse error at (line 1, column 1):
unexpected "\""

parse'strStatic :: Parser Str'Static Source #

Parser for a static string which may be either quoted or unquoted.

Examples

>>> parseTest parse'strStatic "\"hello\""
{- 1:1-1:8 -} "hello"
>>> parseTest parse'strStatic "hello"
{- 1:1-1:6 -} "hello"
>>> parseTest parse'strStatic "\"a b\""
{- 1:1-1:6 -} "a b"
>>> parseTest parse'strStatic "a b"
{- 1:1-1:2 -} "a"

By "static," we mean that the string may not contain antiquotation:

>>> parseTest parse'strStatic "\"a${x}b\" xyz"
parse error at (line 1, column 5):
antiquotation is not allowed in this context

parse'strStatic'quoted :: Parser Str'Static Source #

Parser for a static string that is quoted.

parse'strStatic'unquoted :: Parser Str'Static Source #

Parser for an unquoted static string.

parse'str'dynamic :: Parser Str'Dynamic Source #

Parser for a dynamic string enclosed in quotes (" ... ").

parse'str'within'normalQ :: Parser Str'Static Source #

Parser for at least one normal character, within a normally-quoted string context, up to but not including the end of the string or the start of an antiquotation.

parse'inStr :: Parser InStr Source #

Parser for a dynamic string enclosed in "indented string" format, delimited by two single-quotes '' ... ''.

This form of string does not have any escape sequences. Therefore the only way to express '' or ${ within an indented string is to antiquote them.

Examples

>>> x = "''${\"''\"} and ${\"\\${\"}''"
>>> putStrLn x
''${"''"} and ${"\${"}''
>>> parseTest (inStr'discardSource <$> parse'inStr) x
str'indented [indent 0 [antiquote (str ["''"]), " and ", antiquote (str ["${"])] Nothing]
>>> parseTest parse'inStr x
{- 1:1-1:25 -} str'indented [indent {- 1:3-1:3 -} 0 [antiquote ({- 1:5-1:9 -} str [{- 1:6-1:8 -} "''"]), {- 1:10-1:15 -} " and ", antiquote ({- 1:17-1:22 -} str [{- 1:18-1:21 -} "${"])] Nothing]

parse'inStr'1 :: Parser InStr'1 Source #

Parser for a single line of an InStr.

Lists

parse'list :: Parser List Source #

Parser for a list expression ([ ... ]).

Examples

>>> parseTest parse'list "[]"
{- 1:1-1:3 -} list []
>>> :{
>>> parseTest (list'discardSource <$> parse'list)
>>> "[x \"one\" (a: b) (c d)]"
>>> :}
list [var "x", str ["one"], lambda (param "a") (var "b"), apply (var "c") (var "d")]

Dicts

parse'dict :: Parser Dict Source #

Parser for a dict expression, either recursive (rec keyword) or not.

Examples

>>> parseTest parse'dict "{}"
{- 1:1-1:3 -} dict []
>>> parseTest parse'dict "rec { }"
{- 1:1-1:8 -} rec'dict []
>>> :{
>>> parseTest (dict'discardSource <$> parse'dict)
>>> "{ a = b; inherit (x) y z \"s t\"; }"
>>> :}
dict [dict'eq (str ["a"]) (var "b"), dict'inherit'from (var "x") ["y", "z", "s t"]]

parse'dict'rec :: Parser Dict Source #

Parser for a recursive (rec keyword) dict.

Examples

>>> parseTest parse'dict'rec "rec { }"
{- 1:1-1:8 -} rec'dict []
>>> :{
>>> parseTest (dict'discardSource <$> parse'dict'rec)
>>> "rec { a = \"1\"; b = \"${a}2\"; }"
>>> :}
rec'dict [dict'eq (str ["a"]) (str ["1"]), dict'eq (str ["b"]) (str [antiquote (var "a"), "2"])]

parse'dict'noRec :: Parser Dict Source #

Parser for a non-recursive (no rec keyword) dict.

Examples

>>> parseTest parse'dict'noRec "{ }"
{- 1:1-1:4 -} dict []
>>> :{
>>> parseTest (dict'discardSource <$> parse'dict'noRec)
>>> "{ a = \"1\"; b = \"${a}2\"; }"
>>> :}
dict [dict'eq (str ["a"]) (str ["1"]), dict'eq (str ["b"]) (str [antiquote (var "a"), "2"])]

Dict lookup

parse'dot'rhs'chain :: Parser [Expression] Source #

Parser for a chain of dict lookups (like .a.b.c) on the right-hand side of a Dot expression.

Examples

>>> parseTest parse'dot'rhs'chain ""
[]
>>> parseTest parse'dot'rhs'chain ".abc"
[{- 1:2-1:5 -} str [{- 1:2-1:5 -} "abc"]]
>>> :{
>>> parseTest (fmap expression'discardSource <$> parse'dot'rhs'chain)
>>> ".a.${b}.\"c\".\"d${e}\""
>>> :}
[str ["a"],var "b",str ["c"],str ["d", antiquote (var "e")]]

Lambdas

parse'lambda :: Parser Lambda Source #

Parser for a lambda expression (x: y).

Examples

>>> test = parseTest (lambda'discardSource <$> parse'lambda)
>>> test "x: [x x \"a\"]"
lambda (param "x") (list [var "x", var "x", str ["a"]])
>>> test "{a,b}:a"
lambda (pattern [dict'param "a", dict'param "b"]) (var "a")
>>> test "{ ... }: \"x\""
lambda (pattern [] <> ellipsis) (str ["x"])
>>> test "a@{ f, b ? g x, ... }: f b"
lambda (param "a" <> pattern [dict'param "f", dict'param "b" & def (apply (var "g") (var "x"))] <> ellipsis) (apply (var "f") (var "b"))
>>> test "a: b: \"x\""
lambda (param "a") (lambda (param "b") (str ["x"]))

Function parameters

parse'param :: Parser Param Source #

Parser for a function parameter (the beginning of a Lambda), including the colon. This forms part of parse'expression, so it backtracks in places where it has overlap with other types of expressions.

parse'param'var :: Parser Param Source #

Parser for a parameter that starts with a variable. This could be a simple param that consists only of only the variable, or the variable may be followed by a dict pattern.

parse'param'noVar :: Parser Param Source #

Parser for a param that has no variable, only a a dict pattern. This parser backtracks because the beginning of a dict pattern looks like the beginning of a dict expression.

parse'dictPattern :: Parser DictPattern Source #

Parser for a dict pattern (the type of lambda parameter that does dict destructuring. This parser does not backtrack.

parse'dictPattern'start :: Parser () Source #

This is used in a lookahead by parse'param to determine whether we're about to start parsing a DictPattern.

let

Comments and whitespace

Keywords

parse'keyword :: Keyword -> Parser () Source #

Backtracking parser for a particular keyword.