Repr.hs 4.6 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140
  1. {-# LANGUAGE DeriveDataTypeable #-}
  2. {-# LANGUAGE DeriveFoldable #-}
  3. {-# LANGUAGE DeriveFunctor #-}
  4. {-# LANGUAGE DeriveTraversable #-}
  5. {-# LANGUAGE TypeFamilies #-}
  6. module Data.SCargot.Repr
  7. ( -- * Elementary SExpr representation
  8. SExpr(..)
  9. -- * Rich SExpr representation
  10. , RichSExpr(..)
  11. , toRich
  12. , fromRich
  13. -- * Well-Formed SExpr representation
  14. , WellFormedSExpr(..)
  15. , toWellFormed
  16. , fromWellFormed
  17. ) where
  18. import Data.Data (Data)
  19. import Data.Foldable (Foldable(..))
  20. import Data.Monoid (Monoid(..), (<>))
  21. import Data.Traversable (Traversable(..))
  22. import Data.Typeable (Typeable)
  23. import GHC.Exts (IsList(..), IsString(..))
  24. -- | All S-Expressions can be understood as a sequence
  25. -- of @cons@ cells (represented here by 'SCons'), the
  26. -- empty list @nil@ (represented by 'SNil') or an
  27. -- @atom@.
  28. data SExpr atom
  29. = SCons (SExpr atom) (SExpr atom)
  30. | SAtom atom
  31. | SNil
  32. deriving (Eq, Show, Read, Functor, Data, Typeable, Foldable, Traversable)
  33. instance IsString atom => IsString (SExpr atom) where
  34. fromString = SAtom . fromString
  35. instance IsList (SExpr atom) where
  36. type Item (SExpr atom) = SExpr atom
  37. fromList = foldr SCons SNil
  38. toList = go
  39. where go (SCons x xs) = x : go xs
  40. go SNil = []
  41. go (SAtom {}) = error "Unable to turn atom into list"
  42. -- | Sometimes the cons-based interface is too low
  43. -- level, and we'd rather have the lists themselves
  44. -- exposed. In this case, we have 'RSList' to
  45. -- represent a well-formed cons list, and 'RSDotted'
  46. -- to represent an improper list of the form
  47. -- @(a b c . d)@. This representation is based on
  48. -- the shape of the parsed S-Expression, and not on
  49. -- how it was represented, so @(a . (b))@ is going to
  50. -- be represented as @RSList[RSAtom a, RSAtom b]@
  51. -- despite having been originally represented as a
  52. -- dotted list.
  53. data RichSExpr atom
  54. = RSList [RichSExpr atom]
  55. | RSDotted [RichSExpr atom] atom
  56. | RSAtom atom
  57. deriving (Eq, Show, Read, Functor, Data, Typeable, Foldable, Traversable)
  58. instance IsString atom => IsString (RichSExpr atom) where
  59. fromString = RSAtom . fromString
  60. instance IsList (RichSExpr atom) where
  61. type Item (RichSExpr atom) = RichSExpr atom
  62. fromList = RSList
  63. toList (RSList xs) = xs
  64. toList (RSDotted {}) = error "Unable to turn dotted list into haskell list"
  65. toList (RSAtom {}) = error "Unable to turn atom into Haskell list"
  66. -- | It should always be true that
  67. --
  68. -- > fromRich (toRich x) == x
  69. --
  70. -- and that
  71. --
  72. -- > toRich (fromRich x) == x
  73. toRich :: SExpr atom -> RichSExpr atom
  74. toRich (SAtom a) = RSAtom a
  75. toRich (SCons x xs) = go xs (toRich x:)
  76. where go (SAtom a) rs = RSDotted (rs []) a
  77. go SNil rs = RSList (rs [])
  78. go (SCons x xs) rs = go xs (rs . (toRich x:))
  79. -- | This follows the same laws as 'toRich'.
  80. fromRich :: RichSExpr atom -> SExpr atom
  81. fromRich (RSAtom a) = SAtom a
  82. fromRich (RSList xs) = foldr SCons SNil (map fromRich xs)
  83. fromRich (RSDotted xs x) = foldr SCons (SAtom x) (map fromRich xs)
  84. -- | A well-formed s-expression is one which does not
  85. -- contain any dotted lists. This means that not
  86. -- every value of @SExpr a@ can be converted to a
  87. -- @WellFormedSExpr a@, although the opposite is
  88. -- fine.
  89. data WellFormedSExpr atom
  90. = WFSList [WellFormedSExpr atom]
  91. | WFSAtom atom
  92. deriving (Eq, Show, Read, Functor, Data, Typeable, Foldable, Traversable)
  93. instance IsList (WellFormedSExpr atom) where
  94. type Item (WellFormedSExpr atom) = WellFormedSExpr atom
  95. fromList = WFSList
  96. toList (WFSList xs) = xs
  97. toList (WFSAtom {}) = error "Unable to turn atom into Haskell list"
  98. instance IsString atom => IsString (WellFormedSExpr atom) where
  99. fromString = WFSAtom . fromString
  100. -- | This will be @Nothing@ if the argument contains an
  101. -- improper list. It should hold that
  102. --
  103. -- > toWellFormed (fromWellFormed x) == Right x
  104. --
  105. -- and also (more tediously) that
  106. --
  107. -- > case toWellFormed x of
  108. -- > Left _ -> True
  109. -- > Right y -> x == fromWellFormed y
  110. toWellFormed :: SExpr atom -> Either String (WellFormedSExpr atom)
  111. toWellFormed SNil = return (WFSList [])
  112. toWellFormed (SAtom a) = return (WFSAtom a)
  113. toWellFormed (SCons x xs) = do
  114. x' <- toWellFormed x
  115. go xs (x':)
  116. where go (SAtom a) rs = Left "Found atom in cdr position"
  117. go SNil rs = return (WFSList (rs []))
  118. go (SCons x xs) rs = do
  119. x' <- toWellFormed x
  120. go xs (rs . (x':))
  121. -- | Convert a WellFormedSExpr back into a SExpr.
  122. fromWellFormed :: WellFormedSExpr atom -> SExpr atom
  123. fromWellFormed (WFSAtom a) = SAtom a
  124. fromWellFormed (WFSList xs) =
  125. foldr SCons SNil (map fromWellFormed xs)