Comments.hs 4.9 KB

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