Basic.hs 7.7 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234
  1. {-# LANGUAGE PatternSynonyms #-}
  2. {-# LANGUAGE ScopedTypeVariables #-}
  3. {-# LANGUAGE ViewPatterns #-}
  4. module Data.SCargot.Repr.Basic
  5. ( -- * Basic 'SExpr' representation
  6. R.SExpr(..)
  7. -- * Constructing and Deconstructing
  8. , cons
  9. , uncons
  10. -- * Shorthand Patterns
  11. , pattern (:::)
  12. , pattern A
  13. , pattern L
  14. , pattern DL
  15. , pattern Nil
  16. -- * Lenses
  17. , _car
  18. , _cdr
  19. -- * Useful processing functions
  20. , fromPair
  21. , fromList
  22. , fromAtom
  23. , asPair
  24. , asList
  25. , isAtom
  26. , asAtom
  27. , asAssoc
  28. ) where
  29. #if !MIN_VERSION_base(4,8,0)
  30. import Control.Applicative (Applicative, (<$>), (<*>), pure)
  31. #endif
  32. import Data.SCargot.Repr as R
  33. -- | A traversal with access to the first element of a pair.
  34. --
  35. -- >>> import Lens.Family
  36. -- >>> set _car (A "elephant") (A "one" ::: A "two" ::: A "three" ::: Nil)
  37. -- A "elelphant" ::: A "two" ::: A "three" ::: Nil
  38. -- >>> set _car (A "two" ::: A "three" ::: Nil) (A "one" ::: A "elephant")
  39. -- (A "two" ::: A "three" ::: Nil) ::: A "elephant"
  40. _car :: Applicative f => (SExpr a -> f (SExpr a)) -> SExpr a -> f (SExpr a)
  41. _car f (SCons x xs) = (:::) <$> f x <*> pure xs
  42. _car _ (SAtom a) = pure (A a)
  43. _car _ SNil = pure SNil
  44. -- | A traversal with access to the second element of a pair.
  45. --
  46. -- >>> import Lens.Family
  47. -- >>> set _cdr (A "elephant") (A "one" ::: A "two" ::: A "three" ::: Nil)
  48. -- A "one" ::: A "elephant"
  49. -- >>> set _cdr (A "two" ::: A "three" ::: Nil) (A "one" ::: A "elephant")
  50. -- A "one" ::: A "two" ::: A "three" ::: Nil
  51. _cdr :: Applicative f => (SExpr a -> f (SExpr a)) -> SExpr a -> f (SExpr a)
  52. _cdr f (SCons x xs) = (:::) <$> pure x <*> f xs
  53. _cdr _ (SAtom a) = pure (A a)
  54. _cdr _ SNil = pure Nil
  55. -- | Produce the head and tail of the s-expression (if possible).
  56. --
  57. -- >>> uncons (A "el" ::: A "eph" ::: A "ant" ::: Nil)
  58. -- Just (A "el",SCons (SAtom "eph") (SCons (SAtom "ant") SNil))
  59. uncons :: SExpr a -> Maybe (SExpr a, SExpr a)
  60. uncons (SCons x xs) = Just (x, xs)
  61. uncons _ = Nothing
  62. -- | Combine the two s-expressions into a new one.
  63. --
  64. -- >>> cons (A "el") (L ["eph", A "ant"])
  65. -- SCons (SAtom "el) (SCons (SAtom "eph") (SCons (SAtom "ant") SNil))
  66. cons :: SExpr a -> SExpr a -> SExpr a
  67. cons = SCons
  68. gatherDList :: SExpr a -> Maybe ([SExpr a], a)
  69. gatherDList SNil = Nothing
  70. gatherDList SAtom {} = Nothing
  71. gatherDList sx = go sx
  72. where go SNil = Nothing
  73. go (SAtom a) = return ([], a)
  74. go (SCons x xs) = do
  75. (ys, a) <- go xs
  76. return (x:ys, a)
  77. infixr 5 :::
  78. -- | A shorter infix alias for `SCons`
  79. --
  80. -- >>> A "pachy" ::: A "derm"
  81. -- SCons (SAtom "pachy") (SAtom "derm")
  82. #if MIN_VERSION_base(4,8,0)
  83. pattern (:::) :: SExpr a -> SExpr a -> SExpr a
  84. #endif
  85. pattern x ::: xs = SCons x xs
  86. -- | A shorter alias for `SAtom`
  87. --
  88. -- >>> A "elephant"
  89. -- SAtom "elephant"
  90. #if MIN_VERSION_base(4,8,0)
  91. pattern A :: a -> SExpr a
  92. #endif
  93. pattern A x = SAtom x
  94. -- | A (slightly) shorter alias for `SNil`
  95. --
  96. -- >>> Nil
  97. -- SNil
  98. #if MIN_VERSION_base(4,8,0)
  99. pattern Nil :: SExpr a
  100. #endif
  101. pattern Nil = SNil
  102. -- | An alias for matching a proper list.
  103. --
  104. -- >>> L [A "pachy", A "derm"]
  105. -- SExpr (SAtom "pachy") (SExpr (SAtom "derm") SNil)
  106. #if MIN_VERSION_base(4,8,0)
  107. pattern L :: [SExpr a] -> SExpr a
  108. #endif
  109. pattern L xs <- (gatherList -> Right xs)
  110. #if MIN_VERSION_base(4,8,0)
  111. where L [] = SNil
  112. L (x:xs) = SCons x (L xs)
  113. #endif
  114. -- | An alias for matching a dotted list.
  115. --
  116. -- >>> DL [A "pachy"] A "derm"
  117. -- SExpr (SAtom "pachy") (SAtom "derm")
  118. #if MIN_VERSION_base(4,8,0)
  119. pattern DL :: [SExpr a] -> a -> SExpr a
  120. #endif
  121. pattern DL xs x <- (gatherDList -> Just (xs, x))
  122. #if MIN_VERSION_base(4,8,0)
  123. where DL [] a = SAtom a
  124. DL (x:xs) a = SCons x (DL xs a)
  125. #endif
  126. getShape :: SExpr a -> String
  127. getShape Nil = "empty list"
  128. getShape sx = go (0 :: Int) sx
  129. where go n SNil = "list of length " ++ show n
  130. go n SAtom {} = "dotted list of length " ++ show n
  131. go n (SCons _ xs) = go (n+1) xs
  132. -- | Utility function for parsing a pair of things.
  133. --
  134. -- >>> fromPair (isAtom "pachy") (asAtom return) (A "pachy" ::: A "derm" ::: Nil)
  135. -- Right ((), "derm")
  136. -- >>> fromPair (isAtom "pachy") fromAtom (A "pachy" ::: Nil)
  137. -- Left "Expected two-element list"
  138. fromPair :: (SExpr t -> Either String a)
  139. -> (SExpr t -> Either String b)
  140. -> SExpr t -> Either String (a, b)
  141. fromPair pl pr (l ::: r ::: Nil) = (,) <$> pl l <*> pr r
  142. fromPair _ _ sx = Left ("fromPair: expected two-element list; found " ++ getShape sx)
  143. -- | Utility function for parsing a list of things.
  144. fromList :: (SExpr t -> Either String a) -> SExpr t -> Either String [a]
  145. fromList p (s ::: ss) = (:) <$> p s <*> fromList p ss
  146. fromList _ Nil = pure []
  147. fromList _ sx = Left ("fromList: expected list; found " ++ getShape sx)
  148. -- | Utility function for parsing a single atom
  149. fromAtom :: SExpr t -> Either String t
  150. fromAtom (A a) = return a
  151. fromAtom sx = Left ("fromAtom: expected atom; found list" ++ getShape sx)
  152. gatherList :: SExpr t -> Either String [SExpr t]
  153. gatherList (x ::: xs) = (:) <$> pure x <*> gatherList xs
  154. gatherList Nil = pure []
  155. gatherList sx = Left ("gatherList: expected list; found " ++ getShape sx)
  156. -- | Parse a two-element list (NOT a dotted pair) using the
  157. -- provided function.
  158. --
  159. -- >>> let go (A l) (A r) = return (l ++ r); go _ _ = Left "expected atoms"
  160. -- >>> asPair go (A "pachy" ::: A "derm" ::: Nil)
  161. -- Right "pachyderm"
  162. -- >>> asPair go (A "elephant" ::: Nil)
  163. -- Left "asPair: expected two-element list; found list of length 1"
  164. asPair :: ((SExpr t, SExpr t) -> Either String a)
  165. -> SExpr t -> Either String a
  166. asPair f (l ::: r ::: SNil) = f (l, r)
  167. asPair _ sx = Left ("asPair: expected two-element list; found " ++ getShape sx)
  168. -- | Parse an arbitrary-length list using the provided function.
  169. --
  170. -- >>> let go xs = concat <$> mapM fromAtom xs
  171. -- >>> asList go (A "el" ::: A "eph" ::: A "ant" ::: Nil)
  172. -- Right "elephant"
  173. -- >>> asList go (A "el" ::: A "eph" ::: A "ant")
  174. -- Left "asList: expected list; found dotted list of length 3"
  175. asList :: ([SExpr t] -> Either String a) -> SExpr t -> Either String a
  176. asList f ls = gatherList ls >>= f
  177. -- | Match a given literal atom, failing otherwise.
  178. --
  179. -- >>> isAtom "elephant" (A "elephant")
  180. -- Right ()
  181. -- >>> isAtom "elephant" (A "elephant" ::: Nil)
  182. -- Left "isAtom: expected atom; found list"
  183. isAtom :: Eq t => t -> SExpr t -> Either String ()
  184. isAtom s (A s')
  185. | s == s' = return ()
  186. | otherwise = Left "isAtom: failed to match atom"
  187. isAtom _ sx = Left ("isAtom: expected atom; found " ++ getShape sx)
  188. -- | Parse an atom using the provided function.
  189. --
  190. -- >>> import Data.Char (toUpper)
  191. -- >>> asAtom (return . map toUpper) (A "elephant")
  192. -- Right "ELEPHANT"
  193. -- >>> asAtom (return . map toUpper) Nil
  194. -- Left "asAtom: expected atom; found empty list"
  195. asAtom :: (t -> Either String a) -> SExpr t -> Either String a
  196. asAtom f (A s) = f s
  197. asAtom _ sx = Left ("asAtom: expected atom; found " ++ getShape sx)
  198. -- | Parse an assoc-list using the provided function.
  199. --
  200. -- >>> let def (x, y) = do { a <- fromAtom x; b <- fromAtom y; return (a ++ ": " ++ b) }
  201. -- >>> let defList xs = do { defs <- mapM def xs; return (unlines defs) }
  202. -- >>> asAssoc defList ((A "legs" ::: A "four" ::: Nil) ::: (A "trunk" ::: A "one" ::: Nil) ::: Nil)
  203. -- Right "legs: four\ntrunk: one\n"
  204. -- >>> asAssoc defList ((A "legs" ::: A "four" ::: Nil) ::: (A "elephant") ::: Nil)
  205. -- Left "asAssoc: expected pair; found list of length 1"
  206. asAssoc :: ([(SExpr t, SExpr t)] -> Either String a)
  207. -> SExpr t -> Either String a
  208. asAssoc f ss = gatherList ss >>= mapM go >>= f
  209. where go (a ::: b ::: Nil) = return (a, b)
  210. go sx = Left ("asAssoc: expected pair; found " ++ getShape sx)