HaskLike.hs 4.9 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139
  1. {-# LANGUAGE OverloadedStrings #-}
  2. module Data.SCargot.HaskLike ( -- $info
  3. haskLikeSpec
  4. , HaskLikeAtom(..)
  5. ) where
  6. import Control.Applicative ((<$>), (<*>), (<$))
  7. import Data.Maybe (catMaybes)
  8. import Data.String (IsString(..))
  9. import Data.Text (Text, pack)
  10. import Text.Parsec
  11. import Text.Parsec.Text (Parser)
  12. import Prelude hiding (concatMap)
  13. import Data.SCargot.Common
  14. import Data.SCargot.Repr.Basic (SExpr)
  15. import Data.SCargot.General (SExprSpec, mkSpec)
  16. {- $info
  17. This module is intended for simple, ad-hoc configuration or data formats
  18. that might not need their on rich structure but might benefit from a few
  19. various literal formats. the 'haskLikeSpec' understands identifiers as
  20. defined by R5RS as well as string, integer, and floating-point literals
  21. as defined by the Haskell spec, but won't get any Lisp-specific vector
  22. literals or other structure.
  23. -}
  24. -- | An atom type that understands Haskell-like values as well as
  25. -- Scheme-like identifiers.
  26. data HaskLikeAtom
  27. = HSIdent Text -- ^ An identifier, parsed according to the R5RS Scheme
  28. -- standard
  29. | HSString Text -- ^ A string, parsed according to the syntax for string
  30. -- literals in the Haskell report
  31. | HSInt Integer -- ^ An arbitrary-sized integer value, parsed according to
  32. -- the syntax for integer literals in the Haskell report
  33. | HSFloat Double -- ^ A double-precision floating-point value, parsed
  34. -- according to the syntax for floats in the Haskell
  35. -- report
  36. deriving (Eq, Show)
  37. instance IsString HaskLikeAtom where
  38. fromString = HSIdent . fromString
  39. pString :: Parser Text
  40. pString = pack . catMaybes <$> between (char '"') (char '"') (many (val <|> esc))
  41. where val = Just <$> satisfy (\ c -> c /= '"' && c /= '\\' && c > '\026')
  42. esc = do char '\\'
  43. Nothing <$ (gap <|> char '&') <|>
  44. Just <$> code
  45. gap = many1 space >> char '\\'
  46. code = eEsc <|> eNum <|> eCtrl <|> eAscii
  47. eCtrl = char '^' >> unCtrl <$> upper
  48. eNum = (toEnum . fromInteger) <$>
  49. (decNumber <|> (char 'o' >> octNumber)
  50. <|> (char 'x' >> hexNumber))
  51. eEsc = choice [ char a >> return b | (a, b) <- escMap ]
  52. eAscii = choice [ try (string a >> return b)
  53. | (a, b) <- asciiMap ]
  54. unCtrl c = toEnum (fromEnum c - fromEnum 'A' + 1)
  55. escMap :: [(Char, Char)]
  56. escMap = zip "abfntv\\\"\'" "\a\b\f\n\r\t\v\\\"\'"
  57. asciiMap :: [(String, Char)]
  58. asciiMap = zip
  59. ["BS","HT","LF","VT","FF","CR","SO","SI","EM"
  60. ,"FS","GS","RS","US","SP","NUL","SOH","STX","ETX"
  61. ,"EOT","ENQ","ACK","BEL","DLE","DC1","DC2","DC3"
  62. ,"DC4","NAK","SYN","ETB","CAN","SUB","ESC","DEL"]
  63. ("\BS\HT\LF\VT\FF\CR\SO\SI\EM\FS\GS\RS\US\SP\NUL\SOH" ++
  64. "\STX\ETX\EOT\ENQ\ACK\BEL\DLE\DC1\DC2\DC3\DC4\NAK" ++
  65. "\SYN\ETB\CAN\SUB\ESC\DEL")
  66. pFloat :: Parser Double
  67. pFloat = do
  68. n <- decNumber
  69. withDot n <|> noDot n
  70. where withDot n = do
  71. char '.'
  72. m <- decNumber
  73. e <- option 1.0 exponent
  74. return ((fromIntegral n + asDec m 0) * e)
  75. noDot n = do
  76. e <- exponent
  77. return (fromIntegral n * e)
  78. exponent = do
  79. oneOf "eE"
  80. s <- power
  81. x <- decNumber
  82. return (10 ** s (fromIntegral x))
  83. asDec 0 k = k
  84. asDec n k =
  85. asDec (n `div` 10) ((fromIntegral (n `rem` 10) + k) * 0.1)
  86. power :: Num a => Parser (a -> a)
  87. power = negate <$ char '-' <|> id <$ char '+' <|> return id
  88. pInt :: Parser Integer
  89. pInt = do
  90. s <- power
  91. n <- pZeroNum <|> decNumber
  92. return (fromIntegral (s n))
  93. pZeroNum :: Parser Integer
  94. pZeroNum = char '0' >>
  95. ( (oneOf "xX" >> hexNumber)
  96. <|> (oneOf "oO" >> octNumber)
  97. <|> decNumber
  98. <|> return 0
  99. )
  100. pHaskLikeAtom :: Parser HaskLikeAtom
  101. pHaskLikeAtom
  102. = HSFloat <$> (try pFloat <?> "float")
  103. <|> HSInt <$> (try pInt <?> "integer")
  104. <|> HSString <$> (pString <?> "string literal")
  105. <|> HSIdent <$> (parseR5RSIdent <?> "token")
  106. sHaskLikeAtom :: HaskLikeAtom -> Text
  107. sHaskLikeAtom (HSIdent t) = t
  108. sHaskLikeAtom (HSString s) = pack (show s)
  109. sHaskLikeAtom (HSInt i) = pack (show i)
  110. sHaskLikeAtom (HSFloat f) = pack (show f)
  111. -- | This `SExprSpec` understands s-expressions that contain
  112. -- Scheme-like tokens, as well as string literals, integer
  113. -- literals, and floating-point literals. These are read
  114. -- and shown with Haskell lexical syntax, so the same set
  115. -- of values understood by GHC should be understood by this
  116. -- spec as well. This includes string escapes, different
  117. -- number bases, and so forth.
  118. haskLikeSpec :: SExprSpec HaskLikeAtom (SExpr HaskLikeAtom)
  119. haskLikeSpec = mkSpec pHaskLikeAtom sHaskLikeAtom