Comments.hs 5.8 KB

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