Main namespace with parsers and their combinators.
Main namespace with parsers and their combinators.
(*many p)
This parser applies the parser p
zero or more times. Returns a sequence
of the returned values or p
.
p
fails and consumes some input.p
consumes some input.Example:
(def identifier
(p/for [c char/letter?
cs (p/*many (p/alt char/letter-or-number?
(char/is "_")))]
(p/result (cons c cs))))
This parser applies the parser `p` _zero_ or more times. Returns a sequence of the returned values or `p`. - Fails: when `p` fails and consumes some input. - Consumes: when `p` consumes some input. Example: (def identifier (p/for [c char/letter? cs (p/*many (p/alt char/letter-or-number? (char/is "_")))] (p/result (cons c cs))))
(*many-till p end)
This parser applies parser p
zero or more times until parser end
succeeds. Returns a sequence of values returned by p
.
p
fails.end
does not succeed before end of input.p
or end
consumes some input.Example:
(def simple-comment
(p/after (p/word "<!--")
(p/*many-till p/any-token (p/maybe (p/word "-->")))))
Note the overlapping parsers any-token
and (p/word "-->")
, and
therefore the use of the maybe
combinator.
This parser applies parser `p` _zero_ or more times until parser `end` succeeds. Returns a sequence of values returned by `p`. - Fails: - when `p` fails. - when `end` does not succeed before end of input. - Consumes: - when `p` or `end` consumes some input. Example: (def simple-comment (p/after (p/word "<!--") (p/*many-till p/any-token (p/maybe (p/word "-->"))))) Note the overlapping parsers [[any-token]] and `(p/word "-->")`, and therefore the use of the [[maybe]] combinator.
(*sep-by p sep)
Parses zero or more occurrences of p
, separated by sep
. Returns a
sequence of values returned by p
.
(defn comma-sep [p]
(p/*sep-by p (p/after (char/is ",")
(p/*skip char/white?))))
Parses _zero_ or more occurrences of `p`, separated by `sep`. Returns a sequence of values returned by `p`. (defn comma-sep [p] (p/*sep-by p (p/after (char/is ",") (p/*skip char/white?))))
(*sep-end-by p sep)
Parses zero or more occurrences of p
, separated and ended by sep
.
Returns a sequence of values returned by p
.
Parses _zero_ or more occurrences of `p`, separated and ended by `sep`. Returns a sequence of values returned by `p`.
(*sep-opt-by p sep)
Parses zero or more occurrences of p
, separated and optionally ended by
sep
. Returns a sequence of values returned by p
.
Parses _zero_ or more occurrences of `p`, separated and optionally ended by `sep`. Returns a sequence of values returned by `p`.
(*skip p)
This parser applies the parser p
zero or more times, skipping its result.
p
fails and consumes some input.p
consumes some input.Example:
(def spaces
(p/*skip char/white?))
This parser applies the parser `p` _zero_ or more times, skipping its result. - Fails: when `p` fails and consumes some input. - Consumes: when `p` consumes some input. Example: (def spaces (p/*skip char/white?))
(+many p)
This parser applies the parser p
one or more times. Returns a sequence of
the returned values of p
.
p
does not succeed at least once.p
consumes some input.Example:
(def word
(p/+many char/letter?)
This parser applies the parser `p` _one_ or more times. Returns a sequence of the returned values of `p`. - Fails: when `p` does not succeed at least once. - Consumes: when `p` consumes some input. Example: (def word (p/+many char/letter?)
(+sep-by p sep)
Parses one or more occurrences of p
, separated by sep
. Returns a
sequence of values returned by p
.
Parses _one_ or more occurrences of `p`, separated by `sep`. Returns a sequence of values returned by `p`.
(+sep-end-by p sep)
Parses one or more occurrences of p
, separated and ended by sep
.
Returns a sequence of values returned by p
.
Parses _one_ or more occurrences of `p`, separated and ended by `sep`. Returns a sequence of values returned by `p`.
(+sep-opt-by p sep)
Parses one or more occurrences of p
, separated and optionally ended by
sep
. Returns a sequence of values returned by p
.
Parses _one_ or more occurrences of `p`, separated and optionally ended by `sep`. Returns a sequence of values returned by `p`.
(+skip p)
This parser applies the parser p
one or more times, skipping its result.
p
does not succeed at least once.p
consumes some input.This parser applies the parser `p` _one_ or more times, skipping its result. - Fails: when `p` does not succeed at least once. - Consumes: when `p` consumes some input.
(after q p)
(after q qq p)
(after q qq qqq & more)
This parser tries to apply the parsers in order, until last of them succeeds. Returns the value of the last parser, discards result of all preceding parsers.
This parser tries to apply the parsers in order, until last of them succeeds. Returns the value of the last parser, discards result of all preceding parsers. - Fails: when any of tried parsers fails. - Consumes: when any of tried parsers consumes some input.
(alt p q)
(alt p q qq)
(alt p q qq & more)
This parser tries to apply the parsers in order, until one of them succeeds. Returns the value of the succeeding parser.
The parser first applies p
. If it succeeds, the value of p
is returned. If
p
fails without consuming any input, parser q
is tried and so on.
The parser is called predictive since q
is only tried when parser p
didn't consume any input (i.e. the look ahead is 1). This non-backtracking
behaviour allows for both an efficient implementation of the parser
combinators and the generation of good error messages.
This parser tries to apply the parsers in order, until one of them succeeds. Returns the value of the succeeding parser. - Fails: - when any of tried parsers fails consuming some input. - when all tried parsers fail without consuming any input. - Consumes: - when any of tried parsers consumes some input. The parser first applies `p`. If it succeeds, the value of `p` is returned. If `p` fails _without consuming any input_, parser `q` is tried and so on. The parser is called _predictive_ since `q` is only tried when parser `p` didn't consume any input (i.e. the look ahead is 1). This non-backtracking behaviour allows for both an efficient implementation of the parser combinators and the generation of good error messages.
This parser accepts any kind of token. Returns the accepted token.
This parser accepts any kind of token. Returns the accepted token. - Fails: at the end of input. - Consumes: when succeeds.
(between p around)
(between p open close)
Parses open
, followed by p
and close
. Returns the value returned by p
.
open
fails without consuming any input.Example:
(defn braces [p]
(-> p (p/between (char/is "{")
(char/is "}"))))
Parses `open`, followed by `p` and `close`. Returns the value returned by `p`. - Fails: when any of parses fail. - Consumes: in all cases except when `open` fails without consuming any input. Example: (defn braces [p] (-> p (p/between (char/is "{") (char/is "}"))))
(bind p f)
This parser applies parser p
and then parser (f x)
where x is a return
value of the parser p
.
p
or (f x)
fails.p
or (f x)
consumes some input.This parser applies parser `p` and then parser `(f x)` where x is a return value of the parser `p`. - Fails: when any of parsers `p` or `(f x)` fails. - Consumes: when any of parsers `p` or `(f x)` consumes some input.
(do-parser & body)
Delays the evaluation of a parser that was forward (declare)d and it has not been defined yet. For use in (def)s of no-arg parsers, since the parser expression evaluates immediately.
Delays the evaluation of a parser that was forward (declare)d and it has not been defined yet. For use in (def)s of no-arg parsers, since the parser expression evaluates immediately.
(eof)
(eof x)
This parser only succeeds with value x
at the end of the input.
This parser only succeeds with value `x` at the end of the input. - Fails: when input is not completely consumed. - Consumes: never.
(expecting p msg)
This parser behaves as parser p
, but whenever the parser p
fails without
consuming any input, it replaces expect error messages with the expect error
message msg
.
This is normally used at the end of a set alternatives where we want to return
an error message in terms of a higher level construct rather than returning
all possible characters. For example, if the expr
parser from the maybe
example would fail, the error message is: '...: expecting expression'. Without
the expecting
combinator, the message would be like '...: expecting
"let" or alphabetic character', which is less friendly.
The parsers fail
, fail-unexpected
and expecting
are the three
parsers used to generate error messages. Of these, only expecting
is
commonly used.
This parser behaves as parser `p`, but whenever the parser `p` fails _without consuming any input_, it replaces expect error messages with the expect error message `msg`. This is normally used at the end of a set alternatives where we want to return an error message in terms of a higher level construct rather than returning all possible characters. For example, if the `expr` parser from the [[maybe]] example would fail, the error message is: '...: expecting expression'. Without the [[expecting]] combinator, the message would be like '...: expecting "let" or alphabetic character', which is less friendly. The parsers [[fail]], [[fail-unexpected]] and [[expecting]] are the three parsers used to generate error messages. Of these, only [[expecting]] is commonly used.
(fail)
(fail msg)
This parser always fails with message msg
without consuming any input.
This parser always fails with message `msg` without consuming any input. - Fails: always. - Consumes: never.
(fail-unexpected msg)
This parser always fails with an unexpected error message msg
without
consuming any input.
This parser always fails with an unexpected error message `msg` without consuming any input. - Fails: always. - Consumes: never.
(for [& bindings] & body)
Expands into nested bind forms and a function body.
The pattern:
(p/bind p (fn [x]
(p/bind q (fn [y]
...
(p/result (f x y ...))))))
can be more conveniently be written as:
(p/for [x p
y q
...]
(p/result (f x y ...)))
Expands into nested bind forms and a function body. The pattern: (p/bind p (fn [x] (p/bind q (fn [y] ... (p/result (f x y ...)))))) can be more conveniently be written as: (p/for [x p y q ...] (p/result (f x y ...)))
(get-state)
(get-state :input)
(get-state :pos)
(get-state :user)
This parser returns the parser state field :input
, :pos
or :user
.
Without field
it returns the parser state record itself.
This parser returns the parser state field `:input`, `:pos` or `:user`. Without `field` it returns the parser state record itself.
(group p q & ps)
This parser tries to apply parsers in order until all of them succeeds. Returns a sequence of values returned by every parser.
This parser tries to apply parsers in order until all of them succeeds. Returns a sequence of values returned by every parser. - Fails: when any of tried parsers fails. - Consumes: when any of tried parsers consumes some input.
(group* ps)
This parser tries to apply parsers of ps
in order until all of them
succeeds. Returns a sequence of values returned by every parser.
This parser tries to apply parsers of `ps` in order until all of them succeeds. Returns a sequence of values returned by every parser. - Fails: when any of tried parsers fails. - Consumes: when any of tried parsers consumes some input.
(look-ahead p)
Parses p
without consuming any input. If p
fails and consumes some input,
so does look-ahead
. Combine with maybe
if this is undesirable.
p
fails.p
fails and consumes some input.Parses `p` without consuming any input. If `p` fails and consumes some input, so does [[look-ahead]]. Combine with [[maybe]] if this is undesirable. - Fails: when `p` fails. - Consumes: when `p` fails and consumes some input.
(maybe p)
This parser behaves like parser p
, except that it pretends that it hasn't
consumed any input when an error occurs.
p
fails.p
succeeds and consumes some input.This combinator is used whenever arbitrary look ahead is needed. Since it
pretends that it hasn't consumed any input when p
fails, the alt
combinator will try its second alternative even when the first parser failed
while consuming input.
The maybe
combinator can for example be used to distinguish identifiers
and reserved words. Both reserved words and identifiers are a sequence of
letters. Whenever we expect a certain reserved word where we can also expect
an identifier we have to use the maybe
combinator. Suppose we write:
(def identifier
(p/+many char/letter?))
(def let-expr
(p/after (p/word "let")
...))
(def expr
(-> (p/alt let-expr
identifier)
(p/expecting "expression"))
If the user writes "lexical", the parser fails with: unexpected "x", expecting "t" of (word "let")
. Indeed, since the alt
combinator only
tries alternatives when the first alternative hasn't consumed input, the
identifier
parser is never tried (because the prefix "le" of the (p/word "let")
parser is already consumed). The right behaviour can be obtained by
adding the maybe
combinator:
(def let-expr
(p/after (p/maybe (p/word "let"))
...))
This parser behaves like parser `p`, except that it pretends that it hasn't consumed any input when an error occurs. - Fails: when `p` fails. - Consumes: when `p` succeeds and consumes some input. This combinator is used whenever arbitrary look ahead is needed. Since it pretends that it hasn't consumed any input when `p` fails, the [[alt]] combinator will try its second alternative even when the first parser failed while consuming input. The [[maybe]] combinator can for example be used to distinguish identifiers and reserved words. Both reserved words and identifiers are a sequence of letters. Whenever we expect a certain reserved word where we can also expect an identifier we have to use the [[maybe]] combinator. Suppose we write: (def identifier (p/+many char/letter?)) (def let-expr (p/after (p/word "let") ...)) (def expr (-> (p/alt let-expr identifier) (p/expecting "expression")) If the user writes "lexical", the parser fails with: `unexpected "x", expecting "t" of (word "let")`. Indeed, since the [[alt]] combinator only tries alternatives when the first alternative hasn't consumed input, the `identifier` parser is never tried (because the prefix "le" of the `(p/word "let")` parser is already consumed). The right behaviour can be obtained by adding the [[maybe]] combinator: (def let-expr (p/after (p/maybe (p/word "let")) ...))
(not-followed-by q)
(not-followed-by p q)
This parser behaves like parser p
, except that it only succeeds when parser
q
fails. This parser can be used to implement the 'longest match' rule. For
example, when recognizing keywords (for example let
), we want to make sure
that a keyword is not followed by a legal identifier character, in which case
the keyword is actually an identifier (for example lets
). We can write this
behaviour as follows:
(-> (p/word "let")
(p/not-followed-by char/letter-or-number?))
p
fails.q
succeeds.p
consumes some input.This parser behaves like parser `p`, except that it only succeeds when parser `q` fails. This parser can be used to implement the 'longest match' rule. For example, when recognizing keywords (for example `let`), we want to make sure that a keyword is not followed by a legal identifier character, in which case the keyword is actually an identifier (for example `lets`). We can write this behaviour as follows: (-> (p/word "let") (p/not-followed-by char/letter-or-number?)) - Fails: - when `p` fails. - when `q` succeeds. - Consumes: - when `p` consumes some input.
(option p)
(option p x)
This parser tries to apply parser p
. If p
fails without consuming input,
it returns the value x
(or nil
), otherwise the value returned by p
.
p
fails and consumes come input.p
consumes some input.This parser tries to apply parser `p`. If `p` fails without consuming input, it returns the value `x` (or `nil`), otherwise the value returned by `p`. - Fails: when `p` fails and consumes come input. - Consumes: when `p` consumes some input.
(parse p input)
(parse p input {:keys [pos user-state] :as options})
(parse p input {:keys [tab line col user-state] :as options})
Executes parser p
given input
sequence of tokens, returns result value or
throws exception on parsing error.
Options:
:pos
− The instance of InputPos or keyword for pos/init-pos
to init
parser pos. By default, pos is initialized to TextPos for string
input or first token of char type, or IndexPos otherwise.
TextPos options:
:tab
− tab size, default: 8.:line
− line number, default: 1.:col
− column number, default: 1.:user-state
− Initial value of user state.
Executes parser `p` given `input` sequence of tokens, returns result value or throws exception on parsing error. Options: - `:pos` − The instance of InputPos or keyword for `pos/init-pos` to init parser pos. By default, pos is initialized to TextPos for string input or first token of char type, or IndexPos otherwise. - TextPos options: - `:tab` − tab size, default: 8. - `:line` − line number, default: 1. - `:col` − column number, default: 1. - `:user-state` − Initial value of user state.
(parse* p input)
(parse* p input opts)
Executes parser p
given input
sequence of tokens, returns reply record.
See parse
for available opts
.
Executes parser `p` given `input` sequence of tokens, returns reply record. See [[parse]] for available `opts`.
(register-word-test k f)
Associates keyword k
with test-fn of the word
parser.
Associates keyword `k` with test-fn of the [[word]] parser.
(render obj)
Returns string representation of the obj
in parser error messages.
Returns string representation of the `obj` in parser error messages.
(result x)
This parser always succeeds with value x
without consuming any input.
This parser always succeeds with value `x` without consuming any input. - Fails: never. - Consumes: never.
(set-state state)
(set-state :input new-input)
(set-state :pos new-pos)
(set-state :user new-user-state)
This parser sets the parser state field :input
, :pos
or :user
to x
.
Without field
it sets the parser state record itself to state
.
This parser sets the parser state field `:input`, `:pos` or `:user` to `x`. Without `field` it sets the parser state record itself to `state`.
(times n p)
Parses n
occurrences of p
. If n
is smaller or equal to zero, the parser
equals to (p/result nil)
. Returns a sequence of n
values returned by p
.
Parses `n` occurrences of `p`. If `n` is smaller or equal to zero, the parser equals to `(p/result nil)`. Returns a sequence of `n` values returned by `p`.
(token pred)
(token pred msg)
This parser accepts a token when (pred token)
returns logical true, and
optional expecting msg
. 1-arity behaves as pred
and can be used in
predicate composition.
(pred token)
return logical false.This parser accepts a token when `(pred token)` returns logical true, and optional expecting `msg`. 1-arity behaves as `pred` and can be used in predicate composition. - Fails: when `(pred token)` return logical false. - Consumes: when succeeds.
(token-not pred)
(token-not pred msg)
This parser accepts a token when (pred token)
returns logical false, and
optional expecting msg
. 1-arity behaves as (complement pred)
and can be
used in predicate composition.
(pred token)
return logical true.This parser accepts a token when `(pred token)` returns logical false, and optional expecting `msg`. 1-arity behaves as `(complement pred)` and can be used in predicate composition. - Fails: when `(pred token)` return logical true. - Consumes: when succeeds.
(trace label)
(trace label p)
This parser prints the parser state (position, remaining input and user
state) at the time it is invoked. When p
is provided it then continues to
apply parser p
, and if p
fails will indicate that the label has been
backtracked. It is intended to be used for debugging parsers by inspecting
their intermediate states.
p
fails.p
consumes some input.Examples:
(p/parse (p/after (char/is "aeiou")
(p/trace "test-label"))
"atest")
> test-label: at line 1, column 2
> - input: (\t \e \s \t)
> - user: nil
(p/parse (p/after (char/is "aeiou")
(p/trace "test-label" (char/is "nope")))
"atest")
> test-label: at line 1, column 2
> - input: (\t \e \s \t)
> - user: nil
> test-label: backtracked
> error at line 1, column 2:
> unexpected "t"
> expecting character of "nope"
This parser prints the parser state (position, remaining input and user state) at the time it is invoked. When `p` is provided it then continues to apply parser `p`, and if `p` fails will indicate that the label has been backtracked. It is intended to be used for debugging parsers by inspecting their intermediate states. - Fails: when `p` fails. - Consumes: when `p` consumes some input. Examples: (p/parse (p/after (char/is "aeiou") (p/trace "test-label")) "atest") > test-label: at line 1, column 2 > - input: (\t \e \s \t) > - user: nil (p/parse (p/after (char/is "aeiou") (p/trace "test-label" (char/is "nope"))) "atest") > test-label: at line 1, column 2 > - input: (\t \e \s \t) > - user: nil > test-label: backtracked > error at line 1, column 2: > unexpected "t" > expecting character of "nope"
(update-state f)
(update-state :input f)
(update-state :pos f)
(update-state :user f)
This parser applies function f
to the parser state field :input
, :pos
or :user
and returns modified value. Without field
it applies f
to the
parser state record itself. Suppose that we want to count identifiers in a
source, we could use the user state as:
(p/for [x identifier
_ (p/update-state :user inc)]
(p/result x))
This parser applies function `f` to the parser state field `:input`, `:pos` or `:user` and returns modified value. Without `field` it applies `f` to the parser state record itself. Suppose that we want to count identifiers in a source, we could use the user state as: (p/for [x identifier _ (p/update-state :user inc)] (p/result x))
(value p f)
(value p f g)
(value p f g h)
(value p f g h & more)
This parser applies series of functions to the result value of the parser p
.
p
fails.p
consumes some input.This parser applies series of functions to the result value of the parser `p`. - Fails: when `p` fails. - Consumes: when `p` consumes some input.
(word tokens)
(word tokens test-fn)
Parses a sequence of tokens given by ts
and returns ts
. The optional
function (test-fn word-token input-token)
is used to match tokens
differently than simple equality. The test-fn
can be referred by keyword
registered using register-word-test
. There are two predefined keywords
registered: :default
for =
and :ic
for case insensitive char comparison.
Example:
(def let-keyword (p/word "let"))
(def let-keyword-ignorecase (p/word "let" :ic))
Parses a sequence of tokens given by `ts` and returns `ts`. The optional function `(test-fn word-token input-token)` is used to match tokens differently than simple equality. The `test-fn` can be referred by keyword registered using [[register-word-test]]. There are two predefined keywords registered: `:default` for `=` and `:ic` for case insensitive char comparison. - Fails: when any of tokens don't match the input. - Consumes: when at least first token matches the input. Example: (def let-keyword (p/word "let")) (def let-keyword-ignorecase (p/word "let" :ic))
cljdoc is a website building & hosting documentation for Clojure/Script libraries
× close