bricks-0.0.0.4: Bricks is a lazy functional language based on Nix.

Safe HaskellSafe
LanguageHaskell2010

Bricks

Contents

Description

Bricks is a lazy functional language that resembles Nix.

This module serves as fairly exhaustive overview of the entire package, and should usually serve as your go-to place to start when reading the Bricks documentation if you want an in-depth understanding of how everything works. It is a fairly large module, and probably ought to be used via a qualified import.

import qualified Bricks

If you just want to use Bricks for common cases, look at the simple API in Bricks.Prelude instead. That module is much smaller and is designed to be imported unqualified.

import Bricks.Prelude

Synopsis

Module overview

Modules that are re-exported from Bricks

The following modules are re-exported from this top-level Bricks module in their entireties.

Modules related to syntax:

Modules related to evaluation:

Modules that are not re-exported from Bricks

Differences from Nix

Bricks is heavily based on the Nix language, but there are a number of significant differences. Most of the differences involve the removal of some feature for the sake of simplicity in both implementation and use.

This list is not comprehensive.

Top-level Bricks expressions may contain no free variables

There are a number of cases where variables are allowed to appear free in a top-level Nix expression: true, false, null, builtins, and anything within the body of a with expression (sort of - we'll elaborate on that complicated issue further below). None of those cases are present in Bricks: All variables must be explicitly bound.

Throughout this section we will more thoroughly address specific Nix built-in variables and how to translate Nix expressions that use them into equivalent Bricks code.

Bricks has no built-in Boolean values

Nix has built-in true and false variables, a handful of operators on them (&&, ||, !), and an if-then-else construct.

nix-repl> true && false
false
nix-repl> true || false
true
nix-repl> !true
false
nix-repl> if true then "a" else "b"
"a"

None of these features are present in Bricks.

todo: Show how we can use the standard library instead.

Bricks has no built-in null

todo: Show how we can use the standard library instead.

Bricks has no integer literals

todo: Show how we can use the standard library instead.

Bricks has no built-in builtins

todo: Show how we can use the standard library instead.

Bricks has no infix operators (+, -, //, et cetera)

todo: Show how we can use the standard library instead.

Bricks has no with expression

The Nix language has a with construct which introduces the contents of a dict into the lexical scope.

The simple reason for omitting this feature is that it can easily lead to code that is difficult to trace. When with expressions are nested, it is often unclear where a variable has come into scope from.

The more subtle reason not to include the with construct is that it introduces a significant departure from the lambda calulus. Consider the expression (with d; x). In this expression, is x free or bound? It is neither; it exists in some state of uncertainty where it may or may not be bound, depending on the value of d.

This has a practical consequence: When you use a with expression, you sacrifice referential transparency. Consider the following Nix expression:

nix-repl> let v = (with { x = "a"; }; x); in (x: v) "b"
"a"

If we attempt to reduce this expression by replacing v with its definition,

nix-repl> (x: (with { x = "a"; }; x)) "b"
"b"

then it no longer evaluates to the same value. We find this unacceptable. Bricks avoids the problem by simply not implementing this feature.

Bricks allows a list on the right-hand side of the . operator

The following example is syntactically valid Nix code, but it fails to evaluate:

nix-repl> { x = "a"; y = "b"; }.${[ "x" "y" ]}
error: value is a list while a string was expected

We expand the meaning of the . operator such that if the expression on the right-hand side evaluates to a list, then the entire expression evaluates to a list:

bricks-repl> { x = "a"; y = "b"; }.${[ "x" "y" ]}
[ "a" "b" ]

Furthermore, when the expression on the right-hand side is a list literal (an expression of the form [ ... ]), the antiquotation (wrapping the expression in ${ ... }) may be omitted:

bricks-repl> { x = "a"; y = "b"; }.[ "x" "y" ]
[ "a" "b" ]

This provides a convenient alternative to many situations in which one might use the with keyword in Nix. For example, where in Nix we might write

ghcWithPackages (p: with p; [ base containers text ]);

we may write this equivalently in Bricks as

ghcWithPackages (p: p.[ "base" "containers" "text" ]);

Bricks does not have URI literals

If a string literal is a URI, it can be written in Nix without quotes.

We have chosen not to include this feature because it provides very little convenience and steals some syntax from lambda expressions. Consider the following Nix example:

nix-repl> (let x = "a"; in y: x) "b"
"a"

If we remove the space between after the colon (:), we get something entirely different:

nix-repl> (let x = "a"; in y:x) "b"
error: attempt to call something which is not
a function but a string, at (string):1:1

Because y:x contains a colon, Nix interprets it as a URI and parses it as the string "y:x" (this is the "string" to which the error message refers), rather than as a lambda.

In Bricks, by contrast, the colon in a lambda is not required to be followed by whitespace, and the previous example works as we would like.

bricks-repl> (let x = "a"; in y:x) "b"
"a"

Bricks does not have path literals

In Nix, an unquoted string that contains a slash is interpreted as a filesystem path.

Path literals have some subtle syntax rules. A common mistake is forgetting to always include a slash in the path. For an example, ./foo.nix is a URI:

nix-repl> ./foo.nix
/home/chris/foo.nix

But foo.nix, without the leading ./, is parsed differently:

nix-repl> foo.nix
error: undefined variable ‘foo’ at (string):1:1

As with URI literals, we find that the unquoted form for paths does not provide enough convenience to compensate for its potential for confusion, so we have opted to omit it.

Bricks does not have a built-in import function

In Nix, a path literal that does not start with a slash (such as ./foo.nix) is interpreted as a relative path, and the Nix parser immediately resolves it with respect to the directory in which the Nix file resides (as we saw in the example above, where it resolved to /home/chris/foo.nix).

We love being able to use relative imports, but we don't like needing a built-in language feature to do it. Fortunately, Bricks can achieve the same effect by using an ordinary function instead.

todo: Explain how imports work in the standard library, once it is implemented.

In doing this, we buy back some purity that Nix's import lacks. By passing the path argument through a function parameter, rather than deriving it implicitly from the context of "which file did the expression come from?" we eliminate a case where an expression's meaning depends on something other than the values of the formal parameters that bind its free variables.

There is another benefit to the Bricks approach: While Nix import syntax is restricted to static paths only (the argument to import cannot contain free variables), Bricks has no such limitation.

Bricks uses Haskell-style comments

The Bricks inline comment keyword is --; in Nix it is #.

The Bricks block comment form is {- ... -}; in Nix it is /* ... */.

This decision was made merely due to the Bricks authors' aesthetic preference and affinity for Haskell.

Bricks block comments may be nested

Although Nix does have block comments,

nix-repl> /* */ "a"
"a"

Nix does not support nested block comments:

nix-repl> /* /* */ */ "a"
error: syntax error, unexpected '*', at (string):1:10

Bricks does:

bricks-repl> {- {- -} -} "a"
"a"

Bricks does not support escape sequences in indented strings

Within the indented string form ('' ... ''), Nix supports the following unorthodox escape sequences:

  • ''${${
  • '''''
  • ''\n → newline
  • ''\r → carriage return
  • ''\t → tab
nix-repl> ''ab''\ncd''
"ab\ncd"

Bricks does not support any of these. If you want to include any of these strings within an indented string, you can use antiquotation:

bricks-repl> ''ab${"\n"}cd''
"ab\ncd"

Or you can interpret escape sequences at runtime by passing your string through some function in the standard library that does this sort of thing (todo: discuss said function, once it exists).

Bricks does not allow quotes in let bindings

In Nix, the left-hand side of a let binding is allowed to be a quoted string. This lets you create variables that aren't valid as variable expressions (when you refer to a variable, it may not be quoted), which puts you in a weird sitation where there is a variable in scope which can only be referred to by inheriting it into a dict.

nix-repl> let "a b" = "c"; in { inherit "a b"; }
{ "a b" = "c"; }

This oddity does not seem to serve any real purpose, so we have omitted it.

The Nix "set" concept is renamed to "dict" in Bricks

The Nix concept of "set" is referred to as "dict" in Bricks. This is not actually a language difference; we just use a different word to talk about the same thing. We believe that "dict" is a more familiar term for this data structure, and that Nix's use of "set" conflicts unnecessarily with the more common usage of the word.

Expressions

data Expression :: * #

Constructors

Expr'Var Var

A variable, such as x

Expr'Str Str'Dynamic

A string, quoted in the traditional form using a single double-quote (" ... ")

Expr'Str'Indented InStr

A string in "indented string" form, using two single-quotes ('' ... '')

Expr'List List

A list is an ordered collection of expressions.

Expr'Dict Dict

A dict is an unordered enumerated mapping from strings.

Expr'Dot Dot

A dot expression (named after the . character it contains) looks up the value at a particular key in a dict.

Expr'Lambda Lambda

A lambda expression x: y where x is the parameter.

Expr'Apply Apply

The application of a function to a single argument.

Expr'Let Let

A let-in expression consists of a list of variable bindings followed by an expression.

Instances

Show Expression

This instance is designed for doctests and REPL experimentation. The format is designed to strike a balance in verbosity between the derived Show implementations (which are unwieldily long) and the Bricks language itself (which is quite terse but unsuitable for demonstrating the parser, as outputting a Bricks rendering of parse result wouldn't illumunate anyone's understanding of the AST that the Show instances are here to depict).

Rendering expressions

render'expression :: Render Expression #

Render an expression.

Examples

>>> :{
>>> render'expression renderContext'terse
>>> (lambda
>>> (param "a" <> pattern
>>> [ dict'param "f"
>>> , dict'param "b" & def (apply (var "g") (var "x"))
>>> ] <> ellipsis)
>>> (apply (var "f") (var "b")))
>>> :}
"a@{ f, b ? g x, ... }: f b"

render'expression'listContext :: Render Expression #

Render an expression in a list context.

render'expression'dotLeftContext :: Render Expression #

Render an expression in the context of the left-hand side of a Dot.

render'expression'applyLeftContext :: Render Expression #

Render an expression in the context of the left-hand side of an Apply.

render'expression'applyRightContext :: Render Expression #

Render an expression in the context of the right-hand side of an Apply.

Parsing expressions

parse'expression :: Parser Expression #

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 #

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

parse'expression'dictKey :: Parser Expression #

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 (${ ... })

Parsing lists of expressions

parse'expressionList :: Parser [Expression] #

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 #

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 #

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

data Var :: * #

A variable x, as in the lambda calculus sense, is in one of two positions:

  1. A binding, which may take a number of forms: - x: ... (Param'Name) - let x = ... ; in ... (LetBinding'Eq) - let inherit ( ... ) x; in ... (LetBinding'Inhherit)
  2. A contextual reference to a lambda head or let binding in which x is bound: - The expression x by itself - An inherit binding in a dict expression (DictBinding'Inherit'Var)

Syntax

Variables are always written without quotes.

Unquoted strings are used for variables (Expr'Var) and places that bind variables (Lambda and Let).

Instances

Show Var 

Methods

showsPrec :: Int -> Var -> ShowS #

show :: Var -> String #

showList :: [Var] -> ShowS #

render'var :: Render Var #

Render an unquoted string in unquoted form.

Strings

str'escape :: Text -> Text #

Insert escape sequences for rendering normal double-quoted (") strings.

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

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.

Static strings

data Str'Static :: * #

A fixed string value. We use the description "static" to mean the string may not contain antiquotation, in contrast with Str'Dynamic which can.

render'strStatic'unquotedIfPossible :: Render Str'Static #

Render a static string, in unquoted form if possible.

render'strStatic'quoted :: Render Str'Static #

Render a static string, in quoted form.

parse'strStatic :: Parser Str'Static #

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 #

Parser for a static string that is quoted.

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

Parser for an unquoted static string.

Dynamic strings

data Str'Dynamic :: * #

A dynamic string is a quoted string expression, which may be a simple string like "hello" or a more complex string containing antiquotation like "Hello, my name is ${name}!". See Expr'Str.

We use the description "dynamic" to mean the string may contain antiquotation, in contrast with Str'Static which cannot.

This is the type of string expressions (Expr'Str).

String syntax

A string may be quoted either in the traditional form using a single double-quote (" ... "):

"one\ntwo"

or in the "indented string" form using two single-quotes ('' ... ''):

''
  one
  two
''

Both of these examples reduce to the same value, because leading whitespace is stripped from indented strings.

Either may contain "antiquotation" (also known as "string interpolation") to conveniently concatenate string-valued variables into the string.

"Hello, my name is ${name}!"

Normal strings may contain the following escape sequences:

  • \\\
  • \""
  • \${${
  • \n → newline
  • \r → carriage return
  • \t → tab

The indented string form does not interpret any escape sequences.

data Str'1 :: * #

One part of a Str'Dynamic.

Instances

str'dynamic'normalize :: Str'Dynamic -> Str'Dynamic #

Simplify a dynamic string by combining consecutive pieces of static text.

Examples

>>> :{
>>> str :: Text -> Str'1
>>> str x = Str'1'Literal $ Str'Static x Nothing
>>> 
>>> var :: Text -> Str'1
>>> var x = Str'1'Antiquote . Expr'Var $
>>> Var (unquotedString'orThrow x) Nothing
>>> :}
>>> :{
>>> str'dynamic'normalize $ Str'Dynamic (Seq.fromList
>>> [str "a", str "b", var "x", var "y", str "c", str "d"]) Nothing
>>> :}
str ["ab", antiquote (var "x"), antiquote (var "y"), "cd"]

str'dynamic'to'static :: Str'Dynamic -> Maybe Str'Static #

Examples

>>> str'dynamic'to'static $ Str'Dynamic (Seq.fromList []) Nothing
Just ""
>>> a = Str'1'Literal (Str'Static "hi" Nothing)
>>> b = Str'1'Antiquote $ Expr'Var $ Var (unquotedString'orThrow "x") Nothing
>>> str'dynamic'to'static $ Str'Dynamic (Seq.fromList [ a ]) Nothing
Just "hi"
>>> str'dynamic'to'static $ Str'Dynamic (Seq.fromList [ a, b ]) Nothing
Nothing

render'strDynamic'unquotedIfPossible :: Render Str'Dynamic #

Render a dynamic string, in unquoted form if possible.

render'strDynamic'quoted :: Render Str'Dynamic #

Render a dynamic string, in quoted form.

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

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

Unquoted strings

data UnquotedString :: * #

A string that can be rendered unquoted. Unquoted strings are restricted to a conservative set of characters; see text'canBeUnquoted for the full rules.

This type does not represent a particular part of Bricks syntax, but it is a wrapper for Text that enforces the limitations of strings at various places in the Bricks syntax.

Construction

Deconstruction

See also

unquotedString'try :: Text -> Maybe UnquotedString #

Properties

unquotedString'orThrow :: Text -> UnquotedString #

Throws an exception if the string cannot render unquoted.

text'canBeUnquoted :: Text -> Bool #

Whether a string having this name can be rendered without quoting it.

Requirements for unquoted strings

We allow a string to render unquoted if all these conditions are met:

Properties

Examples

>>> text'canBeUnquoted "-ab_c"
True
>>> text'canBeUnquoted ""
False
>>> text'canBeUnquoted "a\"b"
False
>>> text'canBeUnquoted "let"
False

char'canBeUnquoted :: Char -> Bool #

Whether the character is allowed to be included in an UnquotedString. Such characters are letters, +, -, *, /, and _.

This is used in the implementation of text'canBeUnquoted.

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

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 "\""

Indented strings

data InStr :: * #

An "indented string literal," delimited by two single-quotes ''.

This type of literal is called "indented" because the parser automatically removes leading whitespace from the string (inStr'dedent), which makes it convenient to use these literals for multi-line strings within an indented expression without the whitespace from indentation ending up as part of the string.

Instances

data InStr'1 :: * #

One line of an InStr.

Constructors

InStr'1 

Fields

Instances

inStr'level :: InStr -> Natural #

Determine how many characters of whitespace to strip from an indented string.

inStr'dedent :: InStr -> InStr #

Determine the minimum indentation of any nonempty line, and remove that many space characters from the front of every line.

inStr'trim :: InStr -> InStr #

Remove any empty lines from the beginning or end of an indented string, and remove the newline from the final nonempty line.

parse'inStr :: Parser InStr #

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 #

Parser for a single line of an InStr.

Lists

data List :: * #

A list is an ordered collection.

Syntax

A list expression (Expr'List) starts with [, ends with ], and contains any number of expressions in between.

The empty list:

[ ]

A list containing three variables:

[ a b c ]

Lambdas, function applications, let-in expressions, and with expressions must be parenthesized when in a list.

[
  (x: f x y)
  (g y)
  (let a = y; in f a a)
  (with d; f x a)
]

Instances

Show List 

Methods

showsPrec :: Int -> List -> ShowS #

show :: List -> String #

showList :: [List] -> ShowS #

render'list :: Render List #

Render a list literal ([ ... ]).

parse'list :: Parser List #

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

data Dict :: * #

A dict is an unordered enumerated mapping from strings.

Syntax

A dict expression (Expr'Dict) starts with { or rec {, ends with }, and contains any number of DictBindings in between.

The empty dict (with no bindings):

{ }

A dict with two bindings:

{
  a = "one";
  b = "one two";
}

By default, dict bindings cannot refer to each other. For that, you need the rec keyword to create a recursive dict.

rec {
  a = "one";
  b = "${a} two";
}

In either case, the order of the bindings does not matter.

The left-hand side of a dict binding may be a quoted string (in the traditional " ... " style, not the indented-string '' style), which make it possible for them to be strings that otherwise couldn't be expressed unquoted, such as strings containing spaces:

{ "a b" = "c"; }

The left-hand side of a dict may even be an arbitrary expression, using the ${ ... } form:

let x = "a b"; in { ${x} = "c"; }

Dicts also support the inherit keyword:

{ inherit a; inherit (x) c d; }

The previous expression is equivalent to:

{ a = a; c = x.c; d = x.d; }

Constructors

Dict 

Fields

Instances

Show Dict 

Methods

showsPrec :: Int -> Dict -> ShowS #

show :: Dict -> String #

showList :: [Dict] -> ShowS #

render'dict :: Render Dict #

Render a dict literal ({ ... }).

parse'dict :: Parser Dict #

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 #

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 #

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 bindings

render'dictBinding :: Render DictBinding #

Render a binding within a Dict, including the trailing semicolon.

Dict lookup (dot)

data Dot :: * #

The dot function looks up a value (or a list of values) from a dict.

Syntax

A dot expression is named after the . character it contains. a.b looks up value at key b in the dict a.

The examples in this section all reduce to "Z".

{ a = "Z"; }.a
let x = { a = "Z"; }; in x.a
{ x = { a = "Z"; }; }.x.a

The right-hand side of a dot may be a quoted string (in the traditional " ... " style, not the indented-string '' style):

{ a = "Z"; }."a"

The right-hand side of a dot may even be an arbitrary expression, using the ${ ... } form:

{ a = "Z"; }.${ let b = "a"; in b }

Instances

Show Dot 

Methods

showsPrec :: Int -> Dot -> ShowS #

show :: Dot -> String #

showList :: [Dot] -> ShowS #

expression'applyDots #

Arguments

:: Expression

Dict

-> [Expression]

Lookups

-> Expression

Dot expression

render'dot :: Render Dot #

Render a dot expression (a.b).

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

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")]]

Functions

Lambdas

data Lambda :: * #

A function expressed as a lambda abstraction.

Syntax

A lambda expression (Expr'Lambda) has the form x: y where x is the function parameter to bind in the function body y.

This is a function that turns a name into a greeting:

name: "Hello, ${name}!"

The function parameter can also be a dict pattern, which looks like this:

{ a, b, c ? "another" }: "Hello, ${a}, ${b}, and ${c}!"

That function accepts a dict and looks up the keys a, b, and c from it, applying the default value "another" to c if it is not present in the dict. Dict patterns therefore give us something that resembles functions with named parameters and default arguments.

By default, a lambda defined with a dict pattern fails to evaluate if the dict argument contains keys that are not listed in the pattern. To prevent it from failing, you can end the pattern with ... :

({ a, ... }: x) { a = "1"; b = "2"; }

Every function has a single parameter. If you need multiple parameters, you have to curry:

a: b: [ a b ]

Constructors

Lambda 

Fields

Instances

render'lambda :: Render Lambda #

Render a lambda expression (x: y).

parse'lambda :: Parser Lambda #

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

data Param :: * #

A parameter to a Lambda. All functions have a single parameter, but it's more complicated than that because it may also include dict destructuring.

Constructors

Param'Name Var

A simple single-parameter function

Param'DictPattern DictPattern

Dict destructuring, which gives you something resembling multiple named parameters with default values

Param'Both Var DictPattern

Both a param name and a dict pattern, separated by the @ keyword

Instances

render'param :: Render Param #

Render a lambda parameter: everything from the beginning of a lambda, up to but not including the : that separates the head from the body of the lambda.

parse'param :: Parser Param #

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 #

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 #

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.

Dict patterns

data DictPattern :: * #

A type of function parameter (Param) that does dict destructuring.

Constructors

DictPattern 

Fields

data DictPattern'1 :: * #

One item within a DictPattern.

Constructors

DictPattern'1 

Fields

render'dictPattern :: Render DictPattern #

Render a dict pattern ({ a, b ? c, ... }).

render'dictPattern'1 :: Render DictPattern'1 #

Render a single item in a DictPattern.

parse'dictPattern :: Parser DictPattern #

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

parse'dictPattern'start :: Parser () #

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

Function application

data Apply :: * #

The application of a function to a single argument.

Syntax

An function application expression (Expr'Apply) looks like this:

f x

If a function has multiple (curried) parameters, you can chain them together like so:

f x y z

Constructors

Apply 

Fields

Instances

expression'applyArgs #

Arguments

:: Expression

Function

-> [Expression]

Args

-> Expression

Function application

render'apply :: Render Apply #

Render a function application expression (f x).

let

data Let :: * #

Syntax

A let-in expression (Expr'Let) looks like this:

let
  greet = x: "Hello, ${x}!";
  name = "Chris";
in
  greet name

Let bindings, like dict bindings, may also use the inherit keyword.

let
  d = { greet = x: "Hello, ${x}!"; name = "Chris"; }
  inherit (d) greet name;
in
  greet name

The previous example also demonstrates how the bindings in a let expression may refer to each other (much like a dict with the rec keyword). As with dicts, the order of the bindings does not matter.

Constructors

Let 

Fields

Instances

Show Let 

Methods

showsPrec :: Int -> Let -> ShowS #

show :: Let -> String #

showList :: [Let] -> ShowS #

render'let :: Render Let #

Render a let-in expression.

let bindings

data LetBinding :: * #

A semicolon-terminated binding within the binding list of a Let expression.

Constructors

LetBinding'Eq Var Expression

A binding with an equals sign, of the form x = y;

LetBinding'Inherit Expression (Seq Var)

A binding using the inherit keyword, of the form inherit (x) a b;

render'letBinding :: Render LetBinding #

Render a binding within a Let, including the trailing semicolon.

inherit

Keywords

data Keyword :: * #

keywords :: [Keyword] #

All of the keywords. This list is used when parsing and rendering because an unquoted string cannot have a name that is exactly the same as a keyword.

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

Backtracking parser for a particular keyword.

Comments and whitespace

Rendering

type Render a = RenderContext -> a -> Text #