summaryrefslogtreecommitdiff
path: root/libraries/base/Data/Data.hs
diff options
context:
space:
mode:
Diffstat (limited to 'libraries/base/Data/Data.hs')
-rw-r--r--libraries/base/Data/Data.hs65
1 files changed, 51 insertions, 14 deletions
diff --git a/libraries/base/Data/Data.hs b/libraries/base/Data/Data.hs
index 1b55f59b10..fa199f1117 100644
--- a/libraries/base/Data/Data.hs
+++ b/libraries/base/Data/Data.hs
@@ -4,12 +4,12 @@
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE NoImplicitPrelude #-}
+{-# LANGUAGE DataKinds #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE TypeInType #-}
{-# LANGUAGE TypeOperators #-}
-----------------------------------------------------------------------------
@@ -126,7 +126,6 @@ import Data.Version( Version(..) )
import GHC.Base hiding (Any, IntRep, FloatRep)
import GHC.List
import GHC.Num
-import GHC.Natural
import GHC.Read
import GHC.Show
import Text.Read( reads )
@@ -140,6 +139,8 @@ import GHC.Real -- So we can give Data instance for Ratio
--import GHC.IOBase -- So we can give Data instance for IO, Handle
import GHC.Ptr -- So we can give Data instance for Ptr
import GHC.ForeignPtr -- So we can give Data instance for ForeignPtr
+import Foreign.Ptr (IntPtr(..), WordPtr(..))
+ -- So we can give Data instance for IntPtr and WordPtr
--import GHC.Stable -- So we can give Data instance for StablePtr
--import GHC.ST -- So we can give Data instance for ST
--import GHC.Conc -- So we can give Data instance for MVar & Co.
@@ -277,22 +278,34 @@ class Typeable a => Data a where
------------------------------------------------------------------------------
-- | Mediate types and unary type constructors.
- -- In 'Data' instances of the form @T a@, 'dataCast1' should be defined
- -- as 'gcast1'.
+ --
+ -- In 'Data' instances of the form
+ --
+ -- @
+ -- instance (Data a, ...) => Data (T a)
+ -- @
+ --
+ -- 'dataCast1' should be defined as 'gcast1'.
--
-- The default definition is @'const' 'Nothing'@, which is appropriate
- -- for non-unary type constructors.
+ -- for instances of other forms.
dataCast1 :: Typeable t
=> (forall d. Data d => c (t d))
-> Maybe (c a)
dataCast1 _ = Nothing
-- | Mediate types and binary type constructors.
- -- In 'Data' instances of the form @T a b@, 'dataCast2' should be
- -- defined as 'gcast2'.
+ --
+ -- In 'Data' instances of the form
+ --
+ -- @
+ -- instance (Data a, Data b, ...) => Data (T a b)
+ -- @
+ --
+ -- 'dataCast2' should be defined as 'gcast2'.
--
-- The default definition is @'const' 'Nothing'@, which is appropriate
- -- for non-binary type constructors.
+ -- for instances of other forms.
dataCast2 :: Typeable t
=> (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c a)
@@ -497,7 +510,7 @@ data DataType = DataType
, datarep :: DataRep
}
- deriving Show
+ deriving Show -- ^ @since 4.0.0.0
-- | Representation of constructors. Note that equality on constructors
-- with different types may not work -- i.e. the constructors for 'False' and
@@ -529,7 +542,9 @@ data DataRep = AlgRep [Constr]
| CharRep
| NoRep
- deriving (Eq,Show)
+ deriving ( Eq -- ^ @since 4.0.0.0
+ , Show -- ^ @since 4.0.0.0
+ )
-- The list of constructors could be an array, a balanced tree, or others.
@@ -539,7 +554,9 @@ data ConstrRep = AlgConstr ConIndex
| FloatConstr Rational
| CharConstr Char
- deriving (Eq,Show)
+ deriving ( Eq -- ^ @since 4.0.0.0
+ , Show -- ^ @since 4.0.0.0
+ )
-- | Unique index for datatype constructors,
@@ -551,7 +568,9 @@ type ConIndex = Int
data Fixity = Prefix
| Infix -- Later: add associativity and precedence
- deriving (Eq,Show)
+ deriving ( Eq -- ^ @since 4.0.0.0
+ , Show -- ^ @since 4.0.0.0
+ )
------------------------------------------------------------------------------
@@ -779,7 +798,7 @@ mkRealConstr dt f = case datarep dt of
FloatRep -> mkPrimCon dt (show f) (FloatConstr (toRational f))
_ -> errorWithoutStackTrace $ "Data.Data.mkRealConstr is not supported for "
++ dataTypeName dt ++
- ", as it is not an Real data type."
+ ", as it is not a Real data type."
-- | Makes a constructor for 'Char'.
mkCharConstr :: DataType -> Char -> Constr
@@ -1137,6 +1156,9 @@ instance Data a => Data [a] where
------------------------------------------------------------------------------
+-- | @since 4.9.0.0
+deriving instance Data a => Data (NonEmpty a)
+
-- | @since 4.0.0.0
deriving instance Data a => Data (Maybe a)
@@ -1189,6 +1211,12 @@ instance Data a => Data (ForeignPtr a) where
dataTypeOf _ = mkNoRepType "GHC.ForeignPtr.ForeignPtr"
dataCast1 x = gcast1 x
+-- | @since 4.11.0.0
+deriving instance Data IntPtr
+
+-- | @since 4.11.0.0
+deriving instance Data WordPtr
+
------------------------------------------------------------------------------
-- The Data instance for Array preserves data abstraction at the cost of
-- inefficiency. We omit reflection services for the sake of data abstraction.
@@ -1254,6 +1282,9 @@ deriving instance Data a => Data (Last a)
-- | @since 4.8.0.0
deriving instance (Data (f a), Data a, Typeable f) => Data (Alt f a)
+-- | @since 4.12.0.0
+deriving instance (Data (f a), Data a, Typeable f) => Data (Ap f a)
+
----------------------------------------------------------------------------
-- Data instances for GHC.Generics representations
@@ -1278,7 +1309,7 @@ deriving instance (Typeable f, Typeable g, Data p, Data (f p), Data (g p))
=> Data ((f :+: g) p)
-- | @since 4.9.0.0
-deriving instance (Typeable (f :: * -> *), Typeable (g :: * -> *),
+deriving instance (Typeable (f :: Type -> Type), Typeable (g :: Type -> Type),
Data p, Data (f (g p)))
=> Data ((f :.: g) p)
@@ -1303,3 +1334,9 @@ deriving instance Data SourceStrictness
-- | @since 4.9.0.0
deriving instance Data DecidedStrictness
+
+----------------------------------------------------------------------------
+-- Data instances for Data.Ord
+
+-- | @since 4.12.0.0
+deriving instance Data a => Data (Down a)