Comments.hs 5.3 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172
  1. {-# LANGUAGE OverloadedStrings #-}
  2. module Data.SCargot.Comments
  3. ( -- $intro
  4. -- * Lisp-Style Syntax
  5. -- $lisp
  6. withLispComments
  7. -- * Other Existing Comment Syntaxes
  8. -- ** Scripting Language Syntax
  9. -- $script
  10. , withOctothorpeComments
  11. -- ** C-Style Syntax
  12. -- $clike
  13. , withCLikeLineComments
  14. , withCLikeBlockComments
  15. , withCLikeComments
  16. -- ** Haskell-Style Syntax
  17. -- $haskell
  18. , withHaskellLineComments
  19. , withHaskellBlockComments
  20. , withHaskellComments
  21. -- * Comment Syntax Helper Functions
  22. , lineComment
  23. , simpleBlockComment
  24. ) where
  25. import Text.Parsec ( (<|>)
  26. , anyChar
  27. , manyTill
  28. , noneOf
  29. , skipMany
  30. , string
  31. )
  32. import Data.SCargot.Parse ( Comment
  33. , SExprParser
  34. , setComment
  35. )
  36. -- | Given a string, produce a comment parser that matches that
  37. -- initial string and ignores everything until the end of the
  38. -- line.
  39. lineComment :: String -> Comment
  40. lineComment s = string s >> skipMany (noneOf "\n") >> return ()
  41. -- | Given two strings, a begin and an end delimeter, produce a
  42. -- parser that matches the beginning delimeter and then ignores
  43. -- everything until it finds the end delimiter. This does not
  44. -- consider nesting, so, for example, a comment created with
  45. --
  46. -- > curlyComment :: Comment
  47. -- > curlyComment = simpleBlockComment "{" "}"
  48. --
  49. -- will consider
  50. --
  51. -- > { this { comment }
  52. --
  53. -- to be a complete comment, despite the apparent improper nesting.
  54. -- This is analogous to standard C-style comments in which
  55. --
  56. -- > /* this /* comment */
  57. --
  58. -- is a complete comment.
  59. simpleBlockComment :: String -> String -> Comment
  60. simpleBlockComment begin end =
  61. string begin >>
  62. manyTill anyChar (string end) >>
  63. return ()
  64. -- | Lisp-style line-oriented comments start with @;@ and last
  65. -- until the end of the line. This is usually the comment
  66. -- syntax you want.
  67. withLispComments :: SExprParser t a -> SExprParser t a
  68. withLispComments = setComment (lineComment ";")
  69. -- | C++-like line-oriented comment start with @//@ and last
  70. -- until the end of the line.
  71. withCLikeLineComments :: SExprParser t a -> SExprParser t a
  72. withCLikeLineComments = setComment (lineComment "//")
  73. -- | C-like block comments start with @/*@ and end with @*/@.
  74. -- They do not nest.
  75. withCLikeBlockComments :: SExprParser t a -> SExprParser t a
  76. withCLikeBlockComments = setComment (simpleBlockComment "/*" "*/")
  77. -- | C-like comments include both line- and block-comments, the
  78. -- former starting with @//@ and the latter contained within
  79. -- @//* ... *//@.
  80. withCLikeComments :: SExprParser t a -> SExprParser t a
  81. withCLikeComments = setComment (lineComment "//" <|>
  82. simpleBlockComment "/*" "*/")
  83. -- | Haskell line-oriented comments start with @--@ and last
  84. -- until the end of the line.
  85. withHaskellLineComments :: SExprParser t a -> SExprParser t a
  86. withHaskellLineComments = setComment (lineComment "--")
  87. -- | Haskell block comments start with @{-@ and end with @-}@.
  88. -- They do not nest.
  89. withHaskellBlockComments :: SExprParser t a -> SExprParser t a
  90. withHaskellBlockComments = setComment (simpleBlockComment "{-" "-}")
  91. -- | Haskell comments include both the line-oriented @--@ comments
  92. -- and the block-oriented @{- ... -}@ comments
  93. withHaskellComments :: SExprParser t a -> SExprParser t a
  94. withHaskellComments = setComment (lineComment "--" <|>
  95. simpleBlockComment "{-" "-}")
  96. -- | Many scripting and shell languages use these, which begin with
  97. -- @#@ and last until the end of the line.
  98. withOctothorpeComments :: SExprParser t a -> SExprParser t a
  99. withOctothorpeComments = setComment (lineComment "#")
  100. {- $intro
  101. By default a 'SExprParser' will not understand any kind of comment
  102. syntax. Most varieties of s-expression will, however, want some kind
  103. of commenting capability, so the below functions will produce a new
  104. 'SExprParser' which understands various kinds of comment syntaxes.
  105. For example:
  106. > mySpec :: SExprParser Text (SExpr Text)
  107. > mySpec = asWellFormed $ mkParser (pack <$> many1 alphaNum)
  108. >
  109. > myLispySpec :: SExprParser Text (SExpr Text)
  110. > myLispySpec = withLispComments mySpec
  111. >
  112. > myCLikeSpec :: SExprParser Text (SExpr Text)
  113. > myCLikeSpec = withCLikeComment mySpec
  114. We can then use these to parse s-expressions with different kinds of
  115. comment syntaxes:
  116. >>> decode mySpec "(foo ; a lisp comment\n bar)\n"
  117. Left "(line 1, column 6):\nunexpected \";\"\nexpecting space or atom"
  118. >>> decode myLispySpec "(foo ; a lisp comment\n bar)\n"
  119. Right [WFSList [WFSAtom "foo", WFSAtom "bar"]]
  120. >>> decode mySpec "(foo /* a c-like\n comment */ bar)\n"
  121. Left "(line 1, column 6):\nunexpected \"/\"\nexpecting space or atom"
  122. >>> decode myCLikeSpec "(foo /* a c-like\n comment */ bar)\n"
  123. Right [WFSList [WFSAtom "foo", WFSAtom "bar"]]
  124. -}
  125. {- $lisp
  126. > (one ; a comment
  127. > two ; another one
  128. > three)
  129. -}
  130. {- $script
  131. > (one # a comment
  132. > two # another one
  133. > three)
  134. -}
  135. {- $clike
  136. > (one // a comment
  137. > two /* another
  138. > one */
  139. > three)
  140. -}
  141. -- $haskell
  142. -- > (one -- a comment
  143. -- > two {- another
  144. -- > one -}
  145. -- > three)