s-cargot-0.1.3.0: A flexible, extensible s-expression library.

Safe HaskellNone
LanguageHaskell2010

Data.SCargot.Comments

Contents

Synopsis

Documentation

By default a SExprParser will not understand any kind of comment syntax. Most varieties of s-expression will, however, want some kind of commenting capability, so the below functions will produce a new SExprParser which understands various kinds of comment syntaxes.

For example:

mySpec :: SExprParser Text (SExpr Text)
mySpec = asWellFormed $ mkParser (pack <$> many1 alphaNum)

myLispySpec :: SExprParser Text (SExpr Text)
myLispySpec = withLispComments mySpec

myCLikeSpec :: SExprParser Text (SExpr Text)
myCLikeSpec = withCLikeComment mySpec

We can then use these to parse s-expressions with different kinds of comment syntaxes:

>>> decode mySpec "(foo ; a lisp comment\n  bar)\n"
Left "(line 1, column 6):\nunexpected \";\"\nexpecting space or atom"
>>> decode myLispySpec "(foo ; a lisp comment\n  bar)\n"
Right [WFSList [WFSAtom "foo", WFSAtom "bar"]]
>>> decode mySpec "(foo /* a c-like\n   comment */ bar)\n"
Left "(line 1, column 6):\nunexpected \"/\"\nexpecting space or atom"
>>> decode myCLikeSpec "(foo /* a c-like\n   comment */ bar)\n"
Right [WFSList [WFSAtom "foo", WFSAtom "bar"]]

Lisp-Style Syntax

(one   ; a comment
  two  ; another one
  three)

withLispComments :: SExprParser t a -> SExprParser t a Source #

Lisp-style line-oriented comments start with ; and last until the end of the line. This is usually the comment syntax you want.

Other Existing Comment Syntaxes

Scripting Language Syntax

(one   # a comment
  two  # another one
  three)

withOctothorpeComments :: SExprParser t a -> SExprParser t a Source #

Many scripting and shell languages use these, which begin with # and last until the end of the line.

Prolog- or Matlab-Style Syntax

withPercentComments :: SExprParser t a -> SExprParser t a Source #

MATLAB, Prolog, PostScript, and others use comments which begin with % and last until the end of the line.

withPercentBlockComments :: SExprParser t a -> SExprParser t a Source #

MATLAB block comments are started with %{ and end with %}.

C-Style Syntax

(one // a comment
  two 
  three)

withCLikeLineComments :: SExprParser t a -> SExprParser t a Source #

C++-like line-oriented comment start with // and last until the end of the line.

withCLikeBlockComments :: SExprParser t a -> SExprParser t a Source #

C-like block comments start with @@. They do not nest.

withCLikeComments :: SExprParser t a -> SExprParser t a Source #

C-like comments include both line- and block-comments, the former starting with // and the latter contained within //.

Haskell-Style Syntax

(one -- a comment
  two {- another
         one -}
  three)

withHaskellLineComments :: SExprParser t a -> SExprParser t a Source #

Haskell line-oriented comments start with -- and last until the end of the line.

withHaskellBlockComments :: SExprParser t a -> SExprParser t a Source #

Haskell block comments start with {- and end with -}. They do not nest.

withHaskellComments :: SExprParser t a -> SExprParser t a Source #

Haskell comments include both the line-oriented -- comments and the block-oriented {- ... -} comments

Comment Syntax Helper Functions

lineComment :: String -> Comment Source #

Given a string, produce a comment parser that matches that initial string and ignores everything until the end of the line.

simpleBlockComment :: String -> String -> Comment Source #

Given two strings, a begin and an end delimiter, produce a parser that matches the beginning delimiter and then ignores everything until it finds the end delimiter. This does not consider nesting, so, for example, a comment created with

curlyComment :: Comment
curlyComment = simpleBlockComment "{" "}"

will consider

{ this { comment }

to be a complete comment, despite the apparent improper nesting. This is analogous to standard C-style comments in which

is a complete comment.