Rich.hs 4.1 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129
  1. {-# LANGUAGE PatternSynonyms #-}
  2. module Data.SCargot.Repr.Rich
  3. ( -- * 'RichSExpr' representation
  4. R.RichSExpr(..)
  5. , R.toRich
  6. , R.fromRich
  7. -- * Useful pattern synonyms
  8. , pattern (:::)
  9. , pattern A
  10. , pattern L
  11. , pattern DL
  12. , pattern Nil
  13. -- * Lenses
  14. , _car
  15. , _cdr
  16. -- * Useful processing functions
  17. , fromPair
  18. , fromList
  19. , fromAtom
  20. , asPair
  21. , asList
  22. , isAtom
  23. , asAtom
  24. , asAssoc
  25. ) where
  26. import Control.Applicative ((<$>), (<*>), pure)
  27. import Data.SCargot.Repr as R
  28. -- | A traversal with access to the first element of a pair.
  29. _car :: Applicative f => (RichSExpr a -> f (RichSExpr a)) -> RichSExpr a -> f (RichSExpr a)
  30. _car f (L (x:xs)) = (\ x -> L (x:xs)) `fmap` f x
  31. _car f (DL (x:xs) a) = (\ x -> DL (x:xs) a) `fmap` f x
  32. _car _ (A a) = pure (A a)
  33. _car _ Nil = pure Nil
  34. -- | A traversal with access to the second element of a pair.
  35. _cdr :: Applicative f => (RichSExpr a -> f (RichSExpr a)) -> RichSExpr a -> f (RichSExpr a)
  36. _cdr f (L (x:xs)) =
  37. let go Nil = L [x]
  38. go (A a) = DL [x] a
  39. go (L xs') = L (x:xs')
  40. in go `fmap` f (L xs)
  41. _cdr f (DL [x] a) =
  42. let go Nil = L [x]
  43. go (A a') = DL [x] a'
  44. go (L xs) = L (x:xs)
  45. in go `fmap` f (A a)
  46. _cdr f (DL (x:xs) a) =
  47. let go Nil = L [x]
  48. go (A a') = DL [x] a'
  49. go (L xs) = L (x:xs)
  50. in go `fmap` f (DL xs a)
  51. _cdr _ (A a) = pure (A a)
  52. _cdr _ Nil = pure Nil
  53. -- | A shorter infix alias to grab the head
  54. -- and tail of an `RSList`.
  55. pattern x ::: xs = R.RSList (x : xs)
  56. -- | A shorter alias for `RSAtom`
  57. pattern A a = R.RSAtom a
  58. -- | A shorter alias for `RSList`
  59. pattern L xs = R.RSList xs
  60. -- | A shorter alias for `RSDotted`
  61. pattern DL xs x = R.RSDotted xs x
  62. -- | A shorter alias for `RSList []`
  63. pattern Nil = R.RSList []
  64. -- | Utility function for parsing a pair of things.
  65. fromPair :: (RichSExpr t -> Either String a)
  66. -> (RichSExpr t -> Either String b)
  67. -> RichSExpr t -> Either String (a, b)
  68. fromPair pl pr = asPair $ \(l,r) -> (,) <$> pl l <*> pr r
  69. -- | Utility function for parsing a list of things.
  70. fromList :: (RichSExpr t -> Either String a) -> RichSExpr t -> Either String [a]
  71. fromList p = asList $ \ss -> mapM p ss
  72. -- | Utility function for parsing a single atom
  73. fromAtom :: RichSExpr t -> Either String t
  74. fromAtom (L _) = Left "Expected atom; found list"
  75. fromAtom (A a) = return a
  76. -- | RichSExpr a -> Either String two-element list (NOT a dotted pair) using the
  77. -- provided function.
  78. asPair :: ((RichSExpr t, RichSExpr t) -> Either String a)
  79. -> RichSExpr t -> Either String a
  80. asPair f (L [l, r]) = f (l, r)
  81. asPair _ sx = Left ("Expected two-element list")
  82. -- | Parse an arbitrary-length list using the provided function.
  83. asList :: ([RichSExpr t] -> Either String a)
  84. -> RichSExpr t -> Either String a
  85. asList f (L ls) = f ls
  86. asList _ sx = Left ("Expected list")
  87. -- | Match a given literal atom, failing otherwise.
  88. isAtom :: Eq t => t -> RichSExpr t -> Either String ()
  89. isAtom s (A s')
  90. | s == s' = return ()
  91. | otherwise = Left ".."
  92. isAtom _ _ = Left ".."
  93. -- | Parse an atom using the provided function.
  94. asAtom :: (t -> Either String a) -> RichSExpr t -> Either String a
  95. asAtom f (A s) = f s
  96. asAtom _ sx = Left ("Expected atom; got list")
  97. -- | Parse an assoc-list using the provided function.
  98. asAssoc :: Show t => ([(RichSExpr t, RichSExpr t)] -> Either String a)
  99. -> RichSExpr t -> Either String a
  100. asAssoc f (L ss) = gatherPairs ss >>= f
  101. where gatherPairs (L [a, b] : ss) = (:) <$> pure (a, b) <*> gatherPairs ss
  102. gatherPairs [] = pure []
  103. gatherPairs _ = Left "..."
  104. asAssoc _ sx = Left ("Expected assoc list; got " ++ show sx)
  105. car :: (RichSExpr t -> Either String t') -> [RichSExpr t] -> Either String t'
  106. car f (x:_) = f x
  107. car _ [] = Left "car: Taking car of zero-element list"
  108. cdr :: ([RichSExpr t] -> Either String t') -> [RichSExpr t] -> Either String t'
  109. cdr f (_:xs) = f xs
  110. cdr _ [] = Left "cdr: Taking cdr of zero-element list"