Repr.hs 5.9 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179
  1. {-# LANGUAGE DeriveDataTypeable #-}
  2. {-# LANGUAGE DeriveFoldable #-}
  3. {-# LANGUAGE DeriveFunctor #-}
  4. {-# LANGUAGE DeriveTraversable #-}
  5. {-# LANGUAGE TypeFamilies #-}
  6. module Data.SCargot.Repr
  7. ( -- $reprs
  8. -- * Elementary SExpr representation
  9. SExpr(..)
  10. -- * Rich SExpr representation
  11. , RichSExpr(..)
  12. , toRich
  13. , fromRich
  14. -- * Well-Formed SExpr representation
  15. , WellFormedSExpr(..)
  16. , toWellFormed
  17. , fromWellFormed
  18. ) where
  19. import Data.Data (Data)
  20. import Data.Foldable (Foldable(..))
  21. import Data.Monoid (Monoid(..), (<>))
  22. import Data.Traversable (Traversable(..))
  23. import Data.Typeable (Typeable)
  24. import GHC.Exts (IsList(..), IsString(..))
  25. -- | All S-Expressions can be understood as a sequence
  26. -- of @cons@ cells (represented here by 'SCons'), the
  27. -- empty list @nil@ (represented by 'SNil') or an
  28. -- @atom@.
  29. data SExpr atom
  30. = SCons (SExpr atom) (SExpr atom)
  31. | SAtom atom
  32. | SNil
  33. deriving (Eq, Show, Read, Functor, Data, Typeable, Foldable, Traversable)
  34. instance IsString atom => IsString (SExpr atom) where
  35. fromString = SAtom . fromString
  36. instance IsList (SExpr atom) where
  37. type Item (SExpr atom) = SExpr atom
  38. fromList = foldr SCons SNil
  39. toList = go
  40. where go (SCons x xs) = x : go xs
  41. go SNil = []
  42. go (SAtom {}) = error "Unable to turn atom into list"
  43. -- | Sometimes the cons-based interface is too low
  44. -- level, and we'd rather have the lists themselves
  45. -- exposed. In this case, we have 'RSList' to
  46. -- represent a well-formed cons list, and 'RSDotted'
  47. -- to represent an improper list of the form
  48. -- @(a b c . d)@. This representation is based on
  49. -- the structure of the parsed S-Expression, and not on
  50. -- how it was originally represented: thus, @(a . (b))@ is going to
  51. -- be represented as @RSList[RSAtom a, RSAtom b]@
  52. -- despite having been originally represented as a
  53. -- dotted list.
  54. data RichSExpr atom
  55. = RSList [RichSExpr atom]
  56. | RSDotted [RichSExpr atom] atom
  57. | RSAtom atom
  58. deriving (Eq, Show, Read, Functor, Data, Typeable, Foldable, Traversable)
  59. instance IsString atom => IsString (RichSExpr atom) where
  60. fromString = RSAtom . fromString
  61. instance IsList (RichSExpr atom) where
  62. type Item (RichSExpr atom) = RichSExpr atom
  63. fromList = RSList
  64. toList (RSList xs) = xs
  65. toList (RSDotted {}) = error "Unable to turn dotted list into haskell list"
  66. toList (RSAtom {}) = error "Unable to turn atom into Haskell list"
  67. -- | It should always be true that
  68. --
  69. -- > fromRich (toRich x) == x
  70. --
  71. -- and that
  72. --
  73. -- > toRich (fromRich x) == x
  74. toRich :: SExpr atom -> RichSExpr atom
  75. toRich (SAtom a) = RSAtom a
  76. toRich (SCons x xs) = go xs (toRich x:)
  77. where go (SAtom a) rs = RSDotted (rs []) a
  78. go SNil rs = RSList (rs [])
  79. go (SCons x xs) rs = go xs (rs . (toRich x:))
  80. -- | This follows the same laws as 'toRich'.
  81. fromRich :: RichSExpr atom -> SExpr atom
  82. fromRich (RSAtom a) = SAtom a
  83. fromRich (RSList xs) = foldr SCons SNil (map fromRich xs)
  84. fromRich (RSDotted xs x) = foldr SCons (SAtom x) (map fromRich xs)
  85. -- | A well-formed s-expression is one which does not
  86. -- contain any dotted lists. This means that not
  87. -- every value of @SExpr a@ can be converted to a
  88. -- @WellFormedSExpr a@, although the opposite is
  89. -- fine.
  90. data WellFormedSExpr atom
  91. = WFSList [WellFormedSExpr atom]
  92. | WFSAtom atom
  93. deriving (Eq, Show, Read, Functor, Data, Typeable, Foldable, Traversable)
  94. instance IsList (WellFormedSExpr atom) where
  95. type Item (WellFormedSExpr atom) = WellFormedSExpr atom
  96. fromList = WFSList
  97. toList (WFSList xs) = xs
  98. toList (WFSAtom {}) = error "Unable to turn atom into Haskell list"
  99. instance IsString atom => IsString (WellFormedSExpr atom) where
  100. fromString = WFSAtom . fromString
  101. -- | This will be @Nothing@ if the argument contains an
  102. -- improper list. It should hold that
  103. --
  104. -- > toWellFormed (fromWellFormed x) == Right x
  105. --
  106. -- and also (more tediously) that
  107. --
  108. -- > case toWellFormed x of
  109. -- > Left _ -> True
  110. -- > Right y -> x == fromWellFormed y
  111. toWellFormed :: SExpr atom -> Either String (WellFormedSExpr atom)
  112. toWellFormed SNil = return (WFSList [])
  113. toWellFormed (SAtom a) = return (WFSAtom a)
  114. toWellFormed (SCons x xs) = do
  115. x' <- toWellFormed x
  116. go xs (x':)
  117. where go (SAtom a) rs = Left "Found atom in cdr position"
  118. go SNil rs = return (WFSList (rs []))
  119. go (SCons x xs) rs = do
  120. x' <- toWellFormed x
  121. go xs (rs . (x':))
  122. -- | Convert a WellFormedSExpr back into a SExpr.
  123. fromWellFormed :: WellFormedSExpr atom -> SExpr atom
  124. fromWellFormed (WFSAtom a) = SAtom a
  125. fromWellFormed (WFSList xs) =
  126. foldr SCons SNil (map fromWellFormed xs)
  127. {- $reprs
  128. This module contains several different representations for
  129. s-expressions. The s-cargot library underlying uses the
  130. 'SExpr' type as its representation type, which is a binary
  131. tree representation with an arbitrary type for its leaves.
  132. This type is not always convenient to manipulate in Haskell
  133. code, this module defines two alternate representations
  134. which turn a sequence of nested right-branching cons pairs
  135. into Haskell lists: that is to say, they transform between
  136. @
  137. SCons a (SCons b (SCons c SNil)) \<=\> RSList [a, b, c]
  138. @
  139. These two types differ in how they handle non-well-formed
  140. lists, i.e. lists that end with an atom. The 'RichSExpr'
  141. format handles this with a special constructor for lists
  142. that end in an atom:
  143. @
  144. SCons a (SCons b (SAtom c)) \<=\> RSDotted [a, b] c
  145. @
  146. On the other hand, the 'WellFormedSExpr' type elects
  147. not to handle this case. This is unusual for Lisp source code,
  148. but is a reasonable choice for configuration or data
  149. storage formats that use s-expressions, where
  150. non-well-formed lists would be an unnecessary
  151. complication.
  152. To make working with these types less verbose, there are other
  153. modules that export pattern aliases and helper functions: these
  154. can be found at "Data.SCargot.Repr.Basic",
  155. "Data.SCargot.Repr.Rich", and "Data.SCargot.Repr.WellFormed".
  156. -}