Comments.hs 5.3 KB

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