WellFormed.hs 6.0 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167
  1. {-# LANGUAGE PatternSynonyms #-}
  2. module Data.SCargot.Repr.WellFormed
  3. ( -- * 'WellFormedSExpr' representation
  4. R.WellFormedSExpr(..)
  5. , R.toWellFormed
  6. , R.fromWellFormed
  7. -- * Useful pattern synonyms
  8. , pattern (:::)
  9. , pattern L
  10. , pattern A
  11. , pattern Nil
  12. -- * Useful processing functions
  13. , fromPair
  14. , fromList
  15. , fromAtom
  16. , asPair
  17. , asList
  18. , isAtom
  19. , asAtom
  20. , asAssoc
  21. , car
  22. , cdr
  23. ) where
  24. import Control.Applicative ((<$>), (<*>), pure)
  25. import Data.SCargot.Repr as R
  26. -- | A shorter infix alias to grab the head
  27. -- and tail of a `WFSList`
  28. pattern x ::: xs = R.WFSList (x : xs)
  29. -- | A shorter alias for `WFSList`
  30. pattern L xs = R.WFSList xs
  31. -- | A shorter alias for `WFSAtom`
  32. pattern A a = R.WFSAtom a
  33. -- | A shorter alias for `WFSList` @[]@
  34. pattern Nil = R.WFSList []
  35. getShape :: WellFormedSExpr a -> String
  36. getShape A {} = "atom"
  37. getShape Nil = "empty list"
  38. getShape (L sx) = "list of length " ++ show (length sx)
  39. -- | Utility function for parsing a pair of things.
  40. --
  41. -- >>> fromPair (isAtom "pachy") (asAtom return) (L [A "pachy", A "derm"])
  42. -- Right ((), "derm")
  43. -- >>> fromPair (isAtom "pachy") fromAtom (L [A "pachy"])
  44. -- Left "Expected two-element list"
  45. fromPair :: (WellFormedSExpr t -> Either String a)
  46. -> (WellFormedSExpr t -> Either String b)
  47. -> WellFormedSExpr t -> Either String (a, b)
  48. fromPair pl pr (L [l, r]) = (,) <$> pl l <*> pr r
  49. fromPair _ _ sx = Left ("fromPair: expected two-element list; found " ++ getShape sx)
  50. -- | Utility function for parsing a list of things.
  51. --
  52. -- >>> fromList fromAtom (L [A "this", A "that", A "the-other"])
  53. -- Right ["this","that","the-other"]
  54. -- >>> fromList fromAtom (A "pachyderm")
  55. -- Left "asList: expected proper list; found dotted list"
  56. fromList :: (WellFormedSExpr t -> Either String a)
  57. -> WellFormedSExpr t -> Either String [a]
  58. fromList p (L ss) = mapM p ss
  59. fromList _ sx = Left ("fromList: expected list; found " ++ getShape sx)
  60. -- | Utility function for parsing a single atom
  61. --
  62. -- >>> fromAtom (A "elephant")
  63. -- Right "elephant"
  64. -- >>> fromAtom (L [A "elephant"])
  65. -- Left "fromAtom: expected atom; found list"
  66. fromAtom :: WellFormedSExpr t -> Either String t
  67. fromAtom (A a) = return a
  68. fromAtom sx = Left ("fromAtom: expected atom; found " ++ getShape sx)
  69. -- | Parses a two-element list using the provided function.
  70. --
  71. -- >>> let go (A l) (A r) = return (l ++ r); go _ _ = Left "expected atoms"
  72. -- >>> asPair go (L [A "pachy", A "derm"])
  73. -- Right "pachyderm"
  74. -- >>> asPair go (L [A "elephant"])
  75. -- Left "asPair: expected two-element list; found list of length 1"
  76. asPair :: ((WellFormedSExpr t, WellFormedSExpr t) -> Either String a)
  77. -> WellFormedSExpr t -> Either String a
  78. asPair f (L [l, r]) = f (l, r)
  79. asPair _ sx = Left ("asPair: expected two-element list; found " ++ getShape sx)
  80. -- | Parse an arbitrary-length list using the provided function.
  81. --
  82. -- >>> let go xs = concat <$> mapM fromAtom xs
  83. -- >>> asList go (L [A "el", A "eph", A "ant"])
  84. -- Right "elephant"
  85. -- >>> asList go (A "pachyderm")
  86. -- Left "asList: expected list; found atom"
  87. asList :: ([WellFormedSExpr t] -> Either String a)
  88. -> WellFormedSExpr t -> Either String a
  89. asList f (L ls) = f ls
  90. asList _ sx = Left ("asList: expected list; found " ++ getShape sx)
  91. -- | Match a given literal atom, failing otherwise.
  92. --
  93. -- >>> isAtom "elephant" (A "elephant")
  94. -- Right ()
  95. -- >>> isAtom "elephant" (L [A "elephant"])
  96. -- Left "isAtom: expected atom; found list"
  97. isAtom :: Eq t => t -> WellFormedSExpr t -> Either String ()
  98. isAtom s (A s')
  99. | s == s' = return ()
  100. | otherwise = Left "isAtom: failed to match atom"
  101. isAtom _ sx = Left ("isAtom: expected atom; found " ++ getShape sx)
  102. -- | Match an empty list, failing otherwise.
  103. --
  104. -- >>> isNil (L [])
  105. -- Right ()
  106. -- >>> isNil (A "elephant")
  107. -- Left "isNil: expected nil; found atom"
  108. isNil :: WellFormedSExpr t -> Either String ()
  109. isNil Nil = return ()
  110. isNil sx = Left ("isNil: expected nil; found " ++ getShape sx)
  111. -- | Parse an atom using the provided function.
  112. --
  113. -- >>> import Data.Char (toUpper)
  114. -- >>> asAtom (return . map toUpper) (A "elephant")
  115. -- Right "ELEPHANT"
  116. -- >>> asAtom (return . map toUpper) (L [])
  117. -- Left "asAtom: expected atom; found list"
  118. asAtom :: (t -> Either String a) -> WellFormedSExpr t -> Either String a
  119. asAtom f (A s) = f s
  120. asAtom _ sx = Left ("asAtom: expected atom; found " ++ getShape sx)
  121. -- | Parse an assoc-list using the provided function.
  122. --
  123. -- >>> let def (x, y) = do { a <- fromAtom x; b <- fromAtom y; return (a ++ ": " ++ b) }
  124. -- >>> let defList xs = do { defs <- mapM def xs; return (unlines defs) }
  125. -- >>> asAssoc defList (L [ L [A "legs", A "four"], L [ A "trunk", A "one"] ])
  126. -- Right "legs: four\ntrunk: one\n"
  127. -- >>> asAssoc defList (L [ L [A "legs", A "four"], L [ A "elephant"] ])
  128. -- Left "asAssoc: expected pair; found list of length 1"
  129. asAssoc :: ([(WellFormedSExpr t, WellFormedSExpr t)] -> Either String a)
  130. -> WellFormedSExpr t -> Either String a
  131. asAssoc f (L ss) = gatherPairs ss >>= f
  132. where gatherPairs (L [a, b] : ss) = (:) <$> pure (a, b) <*> gatherPairs ss
  133. gatherPairs [] = pure []
  134. gatherPairs (sx:_) = Left ("asAssoc: expected pair; found " ++ getShape sx)
  135. asAssoc _ sx = Left ("asAssoc: expected list; found " ++ getShape sx)
  136. -- | Run the parser on the first element of a Haskell list of "WellFormedSExpr" values,
  137. -- failing if the list is empty. This is useful in conjunction with the `asList`
  138. -- function.
  139. car :: (WellFormedSExpr t -> Either String t')
  140. -> [WellFormedSExpr t] -> Either String t'
  141. car f (x:_) = f x
  142. car _ [] = Left "car: Taking car of zero-element list"
  143. -- | Run the parser on all but the first element of a Haskell list of "WellFormedSExpr" values,
  144. -- failing if the list is empty. This is useful in conjunction with the `asList`
  145. -- function.
  146. cdr :: ([WellFormedSExpr t] -> Either String t')
  147. -> [WellFormedSExpr t] -> Either String t'
  148. cdr f (_:xs) = f xs
  149. cdr _ [] = Left "cdr: Taking cdr of zero-element list"