Correct SYB's representation of Char
[ghc-base.git] / Data / Data.hs
index 10aa17e..eaa6ae2 100644 (file)
 -- with instances for many datatypes. It corresponds to a merge between
 -- the previous "Data.Generics.Basics" and almost all of 
 -- "Data.Generics.Instances". The instances that are not present
--- in this module are available in "Data.Generics.Instances".
+-- in this module were moved to the @Data.Generics.Instances@ module
+-- in the @syb@ package.
+--
+-- For more information, please visit the new
+-- SYB wiki: <http://www.cs.uu.nl/wiki/bin/view/GenericProgramming/SYB>.
 --
 --
 -----------------------------------------------------------------------------
@@ -50,6 +54,8 @@ module Data.Data (
         mkIntType,      -- :: String -> DataType
         mkFloatType,    -- :: String -> DataType
         mkStringType,   -- :: String -> DataType
+        mkCharType,     -- :: String -> DataType
+        mkNoRepType,    -- :: String -> DataType
         mkNorepType,    -- :: String -> DataType
         -- ** Observers
         dataTypeName,   -- :: DataType -> String
@@ -72,6 +78,7 @@ module Data.Data (
         mkIntConstr,    -- :: DataType -> Integer -> Constr
         mkFloatConstr,  -- :: DataType -> Double  -> Constr
         mkStringConstr, -- :: DataType -> String  -> Constr
+        mkCharConstr,   -- :: DataType -> Char -> Constr
         -- ** Observers
         constrType,     -- :: Constr   -> DataType
         ConstrRep(..),  -- instance of: Eq, Show
@@ -121,14 +128,9 @@ import GHC.Arr               -- So we can give Data instance for Array
 # ifdef __HUGS__
 import Hugs.Prelude( Ratio(..) )
 # endif
-import System.IO
 import Foreign.Ptr
 import Foreign.ForeignPtr
-import Foreign.StablePtr
-import Control.Monad.ST
-import Control.Concurrent
 import Data.Array
-import Data.IORef
 #endif
 
 #include "Typeable.h"
@@ -433,7 +435,7 @@ newtype Mp m x = Mp { unMp :: m (x, Bool) }
 
 -- | Build a term skeleton
 fromConstr :: Data a => Constr -> a
-fromConstr = fromConstrB undefined
+fromConstr = fromConstrB (error "Data.Data.fromConstr")
 
 
 -- | Build a term and use a generic function for subterms
@@ -497,10 +499,12 @@ instance Eq Constr where
 
 
 -- | Public representation of datatypes
+{-# DEPRECATED StringRep "Use CharRep instead" #-}
 data DataRep = AlgRep [Constr]
              | IntRep
              | FloatRep
-             | StringRep
+             | StringRep -- ^ Deprecated. Please use 'CharRep' instead.
+             | CharRep
              | NoRep
 
             deriving (Eq,Show)
@@ -508,10 +512,12 @@ data DataRep = AlgRep [Constr]
 
 
 -- | Public representation of constructors
+{-# DEPRECATED StringConstr "Use CharConstr instead" #-}
 data ConstrRep = AlgConstr    ConIndex
                | IntConstr    Integer
                | FloatConstr  Double
-               | StringConstr String
+               | StringConstr String -- ^ Deprecated. Please use 'CharConstr' instead.
+               | CharConstr   Char
 
                deriving (Eq,Show)
 
@@ -564,6 +570,7 @@ repConstr dt cr =
         (IntRep,    IntConstr i)      -> mkIntConstr dt i
         (FloatRep,  FloatConstr f)    -> mkFloatConstr dt f
         (StringRep, StringConstr str) -> mkStringConstr dt str
+        (CharRep,   CharConstr c)     -> mkCharConstr dt c
         _ -> error "repConstr"
 
 
@@ -638,6 +645,7 @@ readConstr dt str =
         IntRep      -> mkReadCon (\i -> (mkPrimCon dt str (IntConstr i)))
         FloatRep    -> mkReadCon (\f -> (mkPrimCon dt str (FloatConstr f)))
         StringRep   -> Just (mkStringConstr dt str)
+        CharRep     -> mkReadCon (\c -> (mkPrimCon dt str (CharConstr c)))
         NoRep       -> Nothing
   where
 
@@ -708,10 +716,15 @@ mkFloatType :: String -> DataType
 mkFloatType = mkPrimType FloatRep
 
 
--- | Constructs the 'String' type
+-- | This function is now deprecated. Please use 'mkCharType' instead.
+{-# DEPRECATED mkStringType "Use mkCharType instead" #-}
 mkStringType :: String -> DataType
 mkStringType = mkPrimType StringRep
 
+-- | Constructs the 'Char' type
+mkCharType :: String -> DataType
+mkCharType = mkPrimType CharRep
+
 
 -- | Helper for 'mkIntType', 'mkFloatType', 'mkStringType'
 mkPrimType :: DataRep -> String -> DataType
@@ -743,12 +756,19 @@ mkFloatConstr dt f = case datarep dt of
                     FloatRep -> mkPrimCon dt (show f) (FloatConstr f)
                     _ -> error "mkFloatConstr"
 
-
+-- | This function is now deprecated. Please use 'mkCharConstr' instead.
+{-# DEPRECATED mkStringConstr "Use mkCharConstr instead" #-}
 mkStringConstr :: DataType -> String -> Constr
 mkStringConstr dt str = case datarep dt of
                        StringRep -> mkPrimCon dt str (StringConstr str)
                        _ -> error "mkStringConstr"
 
+-- | Makes a constructor for 'Char'.
+mkCharConstr :: DataType -> Char -> Constr
+mkCharConstr dt c = case datarep dt of
+                   CharRep -> mkPrimCon dt (show c) (CharConstr c)
+                   _ -> error "mkCharConstr"
+
 
 ------------------------------------------------------------------------------
 --
@@ -757,13 +777,20 @@ mkStringConstr dt str = case datarep dt of
 ------------------------------------------------------------------------------
 
 
--- | Constructs a non-representation for a non-presentable type
+-- | Deprecated version (misnamed)
+{-# DEPRECATED mkNorepType "Use mkNoRepType instead" #-}
 mkNorepType :: String -> DataType
 mkNorepType str = DataType
                         { tycon   = str
                         , datarep = NoRep
                         }
 
+-- | Constructs a non-representation for a non-presentable type
+mkNoRepType :: String -> DataType
+mkNoRepType str = DataType
+                        { tycon   = str
+                        , datarep = NoRep
+                        }
 
 -- | Test for a non-representable type
 isNorepType :: DataType -> Bool
@@ -832,12 +859,12 @@ instance Data Bool where
 ------------------------------------------------------------------------------
 
 charType :: DataType
-charType = mkStringType "Prelude.Char"
+charType = mkCharType "Prelude.Char"
 
 instance Data Char where
-  toConstr x = mkStringConstr charType [x]
+  toConstr x = mkCharConstr charType x
   gunfold _ z c = case constrRep c of
-                    (StringConstr [x]) -> z x
+                    (CharConstr x) -> z x
                     _ -> error "gunfold"
   dataTypeOf _ = charType
 
@@ -1137,20 +1164,6 @@ instance (Data a, Data b) => Data (Either a b) where
 
 ------------------------------------------------------------------------------
 
-
---
--- A last resort for functions
---
-
-instance (Data a, Data b) => Data (a -> b) where
-  toConstr _   = error "toConstr"
-  gunfold _ _  = error "gunfold"
-  dataTypeOf _ = mkNorepType "Prelude.(->)"
-  dataCast2 f  = gcast2 f
-
-
-------------------------------------------------------------------------------
-
 tuple0Constr :: Constr
 tuple0Constr = mkConstr tuple0DataType "()" [] Prefix
 
@@ -1187,7 +1200,7 @@ tuple3Constr :: Constr
 tuple3Constr = mkConstr tuple3DataType "(,,)" [] Infix
 
 tuple3DataType :: DataType
-tuple3DataType = mkDataType "Prelude.(,)" [tuple3Constr]
+tuple3DataType = mkDataType "Prelude.(,,)" [tuple3Constr]
 
 instance (Data a, Data b, Data c) => Data (a,b,c) where
   gfoldl f z (a,b,c) = z (,,) `f` a `f` b `f` c
@@ -1275,7 +1288,7 @@ instance (Data a, Data b, Data c, Data d, Data e, Data f, Data g)
 instance Typeable a => Data (Ptr a) where
   toConstr _   = error "toConstr"
   gunfold _ _  = error "gunfold"
-  dataTypeOf _ = mkNorepType "GHC.Ptr.Ptr"
+  dataTypeOf _ = mkNoRepType "GHC.Ptr.Ptr"
 
 
 ------------------------------------------------------------------------------
@@ -1283,7 +1296,7 @@ instance Typeable a => Data (Ptr a) where
 instance Typeable a => Data (ForeignPtr a) where
   toConstr _   = error "toConstr"
   gunfold _ _  = error "gunfold"
-  dataTypeOf _ = mkNorepType "GHC.ForeignPtr.ForeignPtr"
+  dataTypeOf _ = mkNoRepType "GHC.ForeignPtr.ForeignPtr"
 
 
 ------------------------------------------------------------------------------
@@ -1294,5 +1307,5 @@ instance (Typeable a, Data b, Ix a) => Data (Array a b)
   gfoldl f z a = z (listArray (bounds a)) `f` (elems a)
   toConstr _   = error "toConstr"
   gunfold _ _  = error "gunfold"
-  dataTypeOf _ = mkNorepType "Data.Array.Array"
+  dataTypeOf _ = mkNoRepType "Data.Array.Array"