Repr.hs 4.1 KB

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