Comments.hs 4.8 KB

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