HaskLike.hs 5.6 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158
  1. {-# LANGUAGE OverloadedStrings #-}
  2. module Data.SCargot.Language.HaskLike
  3. ( -- $info
  4. HaskLikeAtom(..)
  5. , haskLikeParser
  6. , haskLikePrinter
  7. ) where
  8. #if !MIN_VERSION_base(4,8,0)
  9. import Control.Applicative ((<$>), (<$))
  10. #endif
  11. import Data.Maybe (catMaybes)
  12. import Data.String (IsString(..))
  13. import Data.Text (Text, pack)
  14. import Text.Parsec
  15. import Text.Parsec.Text (Parser)
  16. import Prelude hiding (concatMap)
  17. import Data.SCargot.Common
  18. import Data.SCargot.Repr.Basic (SExpr)
  19. import Data.SCargot (SExprParser, SExprPrinter, mkParser, flatPrint)
  20. {- $info
  21. This module is intended for simple, ad-hoc configuration or data formats
  22. that might not need their on rich structure but might benefit from a few
  23. various kinds of literals. The 'haskLikeParser' understands identifiers as
  24. defined by R5RS, as well as string, integer, and floating-point literals
  25. as defined by the Haskell spec. It does __not__ natively understand other
  26. data types, such as booleans, vectors, bitstrings.
  27. -}
  28. -- | An atom type that understands Haskell-like values as well as
  29. -- Scheme-like identifiers.
  30. data HaskLikeAtom
  31. = HSIdent Text -- ^ An identifier, parsed according to the R5RS Scheme
  32. -- standard
  33. | HSString Text -- ^ A string, parsed according to the syntax for string
  34. -- literals in the Haskell report
  35. | HSInt Integer -- ^ An arbitrary-sized integer value, parsed according to
  36. -- the syntax for integer literals in the Haskell report
  37. | HSFloat Double -- ^ A double-precision floating-point value, parsed
  38. -- according to the syntax for floats in the Haskell
  39. -- report
  40. deriving (Eq, Show)
  41. instance IsString HaskLikeAtom where
  42. fromString = HSIdent . fromString
  43. pString :: Parser Text
  44. pString = pack . catMaybes <$> between (char '"') (char '"') (many (val <|> esc))
  45. where val = Just <$> satisfy (\ c -> c /= '"' && c /= '\\' && c > '\026')
  46. esc = do _ <- char '\\'
  47. Nothing <$ (gap <|> char '&') <|>
  48. Just <$> code
  49. gap = many1 space >> char '\\'
  50. code = eEsc <|> eNum <|> eCtrl <|> eAscii
  51. eCtrl = char '^' >> unCtrl <$> upper
  52. eNum = (toEnum . fromInteger) <$>
  53. (decNumber <|> (char 'o' >> octNumber)
  54. <|> (char 'x' >> hexNumber))
  55. eEsc = choice [ char a >> return b | (a, b) <- escMap ]
  56. eAscii = choice [ try (string a >> return b)
  57. | (a, b) <- asciiMap ]
  58. unCtrl c = toEnum (fromEnum c - fromEnum 'A' + 1)
  59. escMap :: [(Char, Char)]
  60. escMap = zip "abfntv\\\"\'" "\a\b\f\n\r\t\v\\\"\'"
  61. asciiMap :: [(String, Char)]
  62. asciiMap = zip
  63. ["BS","HT","LF","VT","FF","CR","SO","SI","EM"
  64. ,"FS","GS","RS","US","SP","NUL","SOH","STX","ETX"
  65. ,"EOT","ENQ","ACK","BEL","DLE","DC1","DC2","DC3"
  66. ,"DC4","NAK","SYN","ETB","CAN","SUB","ESC","DEL"]
  67. ("\BS\HT\LF\VT\FF\CR\SO\SI\EM\FS\GS\RS\US\SP\NUL\SOH" ++
  68. "\STX\ETX\EOT\ENQ\ACK\BEL\DLE\DC1\DC2\DC3\DC4\NAK" ++
  69. "\SYN\ETB\CAN\SUB\ESC\DEL")
  70. pFloat :: Parser Double
  71. pFloat = do
  72. n <- decNumber
  73. withDot n <|> noDot n
  74. where withDot n = do
  75. _ <- char '.'
  76. m <- decNumber
  77. e <- option 1.0 expn
  78. return ((fromIntegral n + asDec m 0) * e)
  79. noDot n = do
  80. e <- expn
  81. return (fromIntegral n * e)
  82. expn = do
  83. _ <- oneOf "eE"
  84. s <- power
  85. x <- decNumber
  86. return (10 ** s (fromIntegral x))
  87. asDec 0 k = k
  88. asDec n k =
  89. asDec (n `div` 10) ((fromIntegral (n `rem` 10) + k) * 0.1)
  90. power :: Num a => Parser (a -> a)
  91. power = negate <$ char '-' <|> id <$ char '+' <|> return id
  92. pInt :: Parser Integer
  93. pInt = do
  94. s <- power
  95. n <- pZeroNum <|> decNumber
  96. return (fromIntegral (s n))
  97. pZeroNum :: Parser Integer
  98. pZeroNum = char '0' >>
  99. ( (oneOf "xX" >> hexNumber)
  100. <|> (oneOf "oO" >> octNumber)
  101. <|> decNumber
  102. <|> return 0
  103. )
  104. pHaskLikeAtom :: Parser HaskLikeAtom
  105. pHaskLikeAtom
  106. = HSFloat <$> (try pFloat <?> "float")
  107. <|> HSInt <$> (try pInt <?> "integer")
  108. <|> HSString <$> (pString <?> "string literal")
  109. <|> HSIdent <$> (parseR5RSIdent <?> "token")
  110. sHaskLikeAtom :: HaskLikeAtom -> Text
  111. sHaskLikeAtom (HSIdent t) = t
  112. sHaskLikeAtom (HSString s) = pack (show s)
  113. sHaskLikeAtom (HSInt i) = pack (show i)
  114. sHaskLikeAtom (HSFloat f) = pack (show f)
  115. -- | This `SExprParser` understands s-expressions that contain
  116. -- Scheme-like tokens, as well as string literals, integer
  117. -- literals, and floating-point literals. Each of these values
  118. -- is parsed according to the lexical rules in the Haskell
  119. -- report, so the same set of string escapes, numeric bases,
  120. -- and floating-point options are available. This spec does
  121. -- not parse comments and does not understand any reader
  122. -- macros.
  123. --
  124. -- >>> decode haskLikeParser "(0x01 \"\\x65lephant\")"
  125. -- Right [SCons (SAtom (HSInt 1)) (SCons (SAtom (HSString "elephant")) SNil)]
  126. haskLikeParser :: SExprParser HaskLikeAtom (SExpr HaskLikeAtom)
  127. haskLikeParser = mkParser pHaskLikeAtom
  128. -- | This 'SExprPrinter' emits s-expressions that contain Scheme-like
  129. -- tokens as well as string literals, integer literals, and floating-point
  130. -- literals, which will be emitted as the literals produced by Haskell's
  131. -- 'show' function. This printer will produce a flat s-expression with
  132. -- no indentation of any kind.
  133. --
  134. -- >>> encode haskLikePrinter [L [A (HSInt 1), A (HSString "elephant")]]
  135. -- "(1 \"elephant\")"
  136. haskLikePrinter :: SExprPrinter HaskLikeAtom (SExpr HaskLikeAtom)
  137. haskLikePrinter = flatPrint sHaskLikeAtom