{-# LANGUAGE DeriveDataTypeable, StandaloneDeriving, CPP #-}
-----------------------------------------------------------------------------
-- |
-- Module      :  Data.Generics.Instances
-- Copyright   :  (c) The University of Glasgow, CWI 2001--2004
-- License     :  BSD-style (see the LICENSE file)
--
-- Maintainer  :  generics@haskell.org
-- Stability   :  experimental
-- Portability :  non-portable (uses Data.Data)
--
-- \"Scrap your boilerplate\" --- Generic programming in Haskell
-- See <http://www.cs.uu.nl/wiki/GenericProgramming/SYB>. The present module
-- contains thirteen 'Data' instances which are considered dubious (either
-- because the types are abstract or just not meant to be traversed).
-- Instances in this module might change or disappear in future releases
-- of this package.
--
-- (This module does not export anything. It really just defines instances.)
--
-----------------------------------------------------------------------------

{-# OPTIONS_GHC -fno-warn-orphans #-}
module Data.Generics.Instances () where

------------------------------------------------------------------------------

import Data.Data

#ifdef __GLASGOW_HASKELL__
#if __GLASGOW_HASKELL__ >= 611
import GHC.IO.Handle         -- So we can give Data instance for Handle
#else
import GHC.IOBase            -- So we can give Data instance for IO, Handle
#endif
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 TVar
import Data.IORef            -- So we can give Data instance for IORef
import Control.Concurrent    -- So we can give Data instance for MVar
#else
# ifdef __HUGS__
import Hugs.Prelude( Ratio(..) )
# endif
import System.IO
import Foreign.Ptr
import Foreign.ForeignPtr
import Foreign.StablePtr
import Control.Monad.ST
#endif

-- Version compatibility issues caused by #2760
myMkNoRepType :: String -> DataType
#if __GLASGOW_HASKELL__ >= 611
myMkNoRepType :: String -> DataType
myMkNoRepType = String -> DataType
mkNoRepType
#else
myMkNoRepType = mkNorepType
#endif


------------------------------------------------------------------------------
--
--      Instances of the Data class for Prelude-like types.
--      We define top-level definitions for representations.
--
------------------------------------------------------------------------------


------------------------------------------------------------------------------
-- Instances of abstract datatypes (6)
------------------------------------------------------------------------------

#if __GLASGOW_HASKELL__ < 801
instance Data TypeRep where
  toConstr _   = error "toConstr"
  gunfold _ _  = error "gunfold"
  dataTypeOf _ = myMkNoRepType "Data.Typeable.TypeRep"
#endif


------------------------------------------------------------------------------

instance Data TyCon where
  toConstr :: TyCon -> Constr
toConstr TyCon
_   = forall a. HasCallStack => String -> a
error String
"toConstr"
  gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TyCon
gunfold forall b r. Data b => c (b -> r) -> c r
_ forall r. r -> c r
_  = forall a. HasCallStack => String -> a
error String
"gunfold"
  dataTypeOf :: TyCon -> DataType
dataTypeOf TyCon
_ = String -> DataType
myMkNoRepType String
"Data.Typeable.TyCon"


------------------------------------------------------------------------------
#if __GLASGOW_HASKELL__ < 709
deriving instance Typeable DataType
#endif

instance Data DataType where
  toConstr :: DataType -> Constr
toConstr DataType
_   = forall a. HasCallStack => String -> a
error String
"toConstr"
  gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c DataType
gunfold forall b r. Data b => c (b -> r) -> c r
_ forall r. r -> c r
_  = forall a. HasCallStack => String -> a
error String
"gunfold"
  dataTypeOf :: DataType -> DataType
dataTypeOf DataType
_ = String -> DataType
myMkNoRepType String
"Data.Generics.Basics.DataType"


------------------------------------------------------------------------------

instance Data Handle where
  toConstr :: Handle -> Constr
toConstr Handle
_   = forall a. HasCallStack => String -> a
error String
"toConstr"
  gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Handle
gunfold forall b r. Data b => c (b -> r) -> c r
_ forall r. r -> c r
_  = forall a. HasCallStack => String -> a
error String
"gunfold"
  dataTypeOf :: Handle -> DataType
dataTypeOf Handle
_ = String -> DataType
myMkNoRepType String
"GHC.IOBase.Handle"


------------------------------------------------------------------------------

instance Typeable a => Data (StablePtr a) where
  toConstr :: StablePtr a -> Constr
toConstr StablePtr a
_   = forall a. HasCallStack => String -> a
error String
"toConstr"
  gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (StablePtr a)
gunfold forall b r. Data b => c (b -> r) -> c r
_ forall r. r -> c r
_  = forall a. HasCallStack => String -> a
error String
"gunfold"
  dataTypeOf :: StablePtr a -> DataType
dataTypeOf StablePtr a
_ = String -> DataType
myMkNoRepType String
"GHC.Stable.StablePtr"


------------------------------------------------------------------------------

#ifdef __GLASGOW_HASKELL__
instance Data ThreadId where
  toConstr :: ThreadId -> Constr
toConstr ThreadId
_   = forall a. HasCallStack => String -> a
error String
"toConstr"
  gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ThreadId
gunfold forall b r. Data b => c (b -> r) -> c r
_ forall r. r -> c r
_  = forall a. HasCallStack => String -> a
error String
"gunfold"
  dataTypeOf :: ThreadId -> DataType
dataTypeOf ThreadId
_ = String -> DataType
myMkNoRepType String
"GHC.Conc.ThreadId"
#endif


------------------------------------------------------------------------------
-- Dubious instances (7)
------------------------------------------------------------------------------

#ifdef __GLASGOW_HASKELL__
instance Typeable a => Data (TVar a) where
  toConstr :: TVar a -> Constr
toConstr TVar a
_   = forall a. HasCallStack => String -> a
error String
"toConstr"
  gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (TVar a)
gunfold forall b r. Data b => c (b -> r) -> c r
_ forall r. r -> c r
_  = forall a. HasCallStack => String -> a
error String
"gunfold"
  dataTypeOf :: TVar a -> DataType
dataTypeOf TVar a
_ = String -> DataType
myMkNoRepType String
"GHC.Conc.TVar"
#endif


------------------------------------------------------------------------------

instance Typeable a => Data (MVar a) where
  toConstr :: MVar a -> Constr
toConstr MVar a
_   = forall a. HasCallStack => String -> a
error String
"toConstr"
  gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (MVar a)
gunfold forall b r. Data b => c (b -> r) -> c r
_ forall r. r -> c r
_  = forall a. HasCallStack => String -> a
error String
"gunfold"
  dataTypeOf :: MVar a -> DataType
dataTypeOf MVar a
_ = String -> DataType
myMkNoRepType String
"GHC.Conc.MVar"


------------------------------------------------------------------------------

#ifdef __GLASGOW_HASKELL__
instance Typeable a => Data (STM a) where
  toConstr :: STM a -> Constr
toConstr STM a
_   = forall a. HasCallStack => String -> a
error String
"toConstr"
  gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (STM a)
gunfold forall b r. Data b => c (b -> r) -> c r
_ forall r. r -> c r
_  = forall a. HasCallStack => String -> a
error String
"gunfold"
  dataTypeOf :: STM a -> DataType
dataTypeOf STM a
_ = String -> DataType
myMkNoRepType String
"GHC.Conc.STM"
#endif


------------------------------------------------------------------------------

instance (Typeable s, Typeable a) => Data (ST s a) where
  toConstr :: ST s a -> Constr
toConstr ST s a
_   = forall a. HasCallStack => String -> a
error String
"toConstr"
  gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (ST s a)
gunfold forall b r. Data b => c (b -> r) -> c r
_ forall r. r -> c r
_  = forall a. HasCallStack => String -> a
error String
"gunfold"
  dataTypeOf :: ST s a -> DataType
dataTypeOf ST s a
_ = String -> DataType
myMkNoRepType String
"GHC.ST.ST"


------------------------------------------------------------------------------

instance Typeable a => Data (IORef a) where
  toConstr :: IORef a -> Constr
toConstr IORef a
_   = forall a. HasCallStack => String -> a
error String
"toConstr"
  gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (IORef a)
gunfold forall b r. Data b => c (b -> r) -> c r
_ forall r. r -> c r
_  = forall a. HasCallStack => String -> a
error String
"gunfold"
  dataTypeOf :: IORef a -> DataType
dataTypeOf IORef a
_ = String -> DataType
myMkNoRepType String
"GHC.IOBase.IORef"


------------------------------------------------------------------------------

instance Typeable a => Data (IO a) where
  toConstr :: IO a -> Constr
toConstr IO a
_   = forall a. HasCallStack => String -> a
error String
"toConstr"
  gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (IO a)
gunfold forall b r. Data b => c (b -> r) -> c r
_ forall r. r -> c r
_  = forall a. HasCallStack => String -> a
error String
"gunfold"
  dataTypeOf :: IO a -> DataType
dataTypeOf IO a
_ = String -> DataType
myMkNoRepType String
"GHC.IOBase.IO"

------------------------------------------------------------------------------

--
-- A last resort for functions
--

instance (Data a, Data b) => Data (a -> b) where
  toConstr :: (a -> b) -> Constr
toConstr a -> b
_   = forall a. HasCallStack => String -> a
error String
"toConstr"
  gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (a -> b)
gunfold forall b r. Data b => c (b -> r) -> c r
_ forall r. r -> c r
_  = forall a. HasCallStack => String -> a
error String
"gunfold"
  dataTypeOf :: (a -> b) -> DataType
dataTypeOf a -> b
_ = String -> DataType
myMkNoRepType String
"Prelude.(->)"
  dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (a -> b))
dataCast2 forall d e. (Data d, Data e) => c (t d e)
f  = forall {k1} {k2} {k3} (c :: k1 -> *) (t :: k2 -> k3 -> k1)
       (t' :: k2 -> k3 -> k1) (a :: k2) (b :: k3).
(Typeable t, Typeable t') =>
c (t a b) -> Maybe (c (t' a b))
gcast2 forall d e. (Data d, Data e) => c (t d e)
f