[project @ 2005-10-13 11:09:50 by ross]
[haskell-directory.git] / Data / Generics / Text.hs
index fbea73b..5a81cc1 100644 (file)
@@ -6,16 +6,16 @@
 -- 
 -- Maintainer  :  libraries@haskell.org
 -- Stability   :  experimental
--- Portability :  non-portable
+-- Portability :  non-portable (uses Data.Generics.Basics)
 --
--- "Scrap your boilerplate" --- Generic programming in Haskell 
--- See <http://www.cs.vu.nl/boilerplate/>.
+-- \"Scrap your boilerplate\" --- Generic programming in Haskell 
+-- See <http://www.cs.vu.nl/boilerplate/>. The present module provides
+-- generic operations for text serialisation of terms.
 --
 -----------------------------------------------------------------------------
 
 module Data.Generics.Text ( 
 
-       -- * Generic operations for string representations of terms
        gshow,
        gread
 
@@ -23,15 +23,15 @@ module Data.Generics.Text (
 
 ------------------------------------------------------------------------------
 
-
+#ifdef __HADDOCK__
+import Prelude
+#endif
 import Control.Monad
 import Data.Maybe
-import Data.Typeable
 import Data.Generics.Basics
 import Data.Generics.Aliases
 import Text.ParserCombinators.ReadP
 
-
 ------------------------------------------------------------------------------
 
 
@@ -43,7 +43,7 @@ gshow :: Data a => a -> String
 -- 
 gshow = ( \t ->
                 "("
-             ++ conString (toConstr t)
+             ++ showConstr (toConstr t)
              ++ concat (gmapQ ((++) " " . gshow) t)
              ++ ")"
         ) `extQ` (show :: String -> String)
@@ -57,8 +57,8 @@ gread :: Data a => ReadS a
 
 This is a read operation which insists on prefix notation.  (The
 Haskell 98 read deals with infix operators subject to associativity
-and precedence as well.) We use gunfoldM to "parse" the input. To be
-precise, gunfoldM is used for all types except String. The
+and precedence as well.) We use fromConstrM to "parse" the input. To be
+precise, fromConstrM is used for all types except String. The
 type-specific case for String uses basic String read.
 
 -}
@@ -67,30 +67,34 @@ gread = readP_to_S gread'
 
  where
 
-  gread' :: Data a => ReadP a
-  gread' = gdefault `extB` scase
-
+  -- Helper for recursive read
+  gread' :: Data a' => ReadP a'
+  gread' = allButString `extR` stringCase
 
    where
 
     -- A specific case for strings
-    scase :: ReadP String
-    scase = readS_to_P reads
+    stringCase :: ReadP String
+    stringCase = readS_to_P reads
 
+    -- Determine result type
+    myDataType = dataTypeOf (getArg allButString)
+     where
+      getArg :: ReadP a'' -> a''
+      getArg = undefined
 
     -- The generic default for gread
-    -- gdefault :: Data a => ReadP a
-    gdefault =
+    allButString =
       do
-               -- Drop "  (  "
+               -- Drop "  (  "
          skipSpaces                    -- Discard leading space
          char '('                      -- Parse '('
          skipSpaces                    -- Discard following space
 
                -- Do the real work
-        str   <- parseConstr           -- Get a lexeme for the constructor
-         con   <- str2con str          -- Convert it to a Constr (may fail)
-         x     <- gunfoldM con gread'  -- Read the children
+        str  <- parseConstr            -- Get a lexeme for the constructor
+         con  <- str2con str           -- Convert it to a Constr (may fail)
+         x    <- fromConstrM gread' con -- Read the children
 
                -- Drop "  )  "
          skipSpaces                    -- Discard leading space
@@ -99,29 +103,22 @@ gread = readP_to_S gread'
 
          return x
 
-     where
-
-       -- Get the datatype for the type at hand;
-       -- use gdefault to provide the type at hand.
-       myDataTypeOf :: Data a => ReadP a -> DataType
-       myDataTypeOf (_::ReadP a) = dataTypeOf (undefined::a)
-
-       -- Turn string into constructor driven by gdefault's type,
-       -- failing in the monad if it isn't a constructor of this data type
-       str2con :: String -> ReadP Constr       
-       str2con = maybe mzero return
-                . stringCon (myDataTypeOf gdefault)
+    -- Turn string into constructor driven by the requested result type,
+    -- failing in the monad if it isn't a constructor of this data type
+    str2con :: String -> ReadP Constr  
+    str2con = maybe mzero return
+            . readConstr myDataType
 
-       -- Get a Constr's string at the front of an input string
-       parseConstr :: ReadP String
-       parseConstr =  
+    -- Get a Constr's string at the front of an input string
+    parseConstr :: ReadP String
+    parseConstr =  
                string "[]"     -- Compound lexeme "[]"
           <++  infixOp        -- Infix operator in parantheses
           <++  readS_to_P lex  -- Ordinary constructors and literals
 
-       -- Handle infix operators such as (:)
-       infixOp :: ReadP String
-        infixOp = do c1  <- char '('
-                     str <- munch1 (not . (==) ')')
-                    c2  <- char ')'
-                    return $ [c1] ++ str ++ [c2]
+    -- Handle infix operators such as (:)
+    infixOp :: ReadP String
+    infixOp = do c1  <- char '('
+                 str <- munch1 (not . (==) ')')
+                c2  <- char ')'
+                 return $ [c1] ++ str ++ [c2]