summaryrefslogtreecommitdiff
path: root/libraries/ghc-prim
diff options
context:
space:
mode:
authorBen Gamari <ben@smart-cactus.org>2015-10-29 17:41:34 +0100
committerBen Gamari <ben@smart-cactus.org>2015-10-29 17:42:26 +0100
commitbbaf76f949426c91d6abbbc5eced1f705530087b (patch)
tree3c25529a062e94493d874349d55f71cfaa3e6dea /libraries/ghc-prim
parentbef2f03e4d56d88a7e9752a7afd6a0a35616da6c (diff)
downloadhaskell-bbaf76f949426c91d6abbbc5eced1f705530087b.tar.gz
Revert "Generate Typeable info at definition sites"
This reverts commit bef2f03e4d56d88a7e9752a7afd6a0a35616da6c. This merge was botched Also reverts haddock submodule.
Diffstat (limited to 'libraries/ghc-prim')
-rw-r--r--libraries/ghc-prim/GHC/Classes.hs36
-rw-r--r--libraries/ghc-prim/GHC/Magic.hs2
-rw-r--r--libraries/ghc-prim/GHC/Tuple.hs3
-rw-r--r--libraries/ghc-prim/GHC/Types.hs60
4 files changed, 4 insertions, 97 deletions
diff --git a/libraries/ghc-prim/GHC/Classes.hs b/libraries/ghc-prim/GHC/Classes.hs
index 12fe65f322..18662ad539 100644
--- a/libraries/ghc-prim/GHC/Classes.hs
+++ b/libraries/ghc-prim/GHC/Classes.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE CPP, Trustworthy #-}
+{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE NoImplicitPrelude, MagicHash, StandaloneDeriving, BangPatterns,
KindSignatures, DataKinds, ConstraintKinds,
MultiParamTypeClasses, FunctionalDependencies #-}
@@ -28,28 +28,19 @@
-----------------------------------------------------------------------------
module GHC.Classes(
- -- * Implicit paramaters
IP(..),
-
- -- * Equality and ordering
Eq(..), eqInt, neInt,
Ord(..), gtInt, geInt, leInt, ltInt, compareInt, compareInt#,
-
- -- * Functions over Bool
(&&), (||), not,
-
- -- * Integer arithmetic
divInt#, modInt#
) where
-- GHC.Magic is used in some derived instances
import GHC.Magic ()
-import GHC.IntWord64
import GHC.Prim
import GHC.Tuple
import GHC.Types
-#include "MachDeps.h"
infix 4 ==, /=, <, <=, >=, >
infixr 3 &&
@@ -146,31 +137,6 @@ eqInt, neInt :: Int -> Int -> Bool
(I# x) `eqInt` (I# y) = isTrue# (x ==# y)
(I# x) `neInt` (I# y) = isTrue# (x /=# y)
-#if WORD_SIZE_IN_BITS < 64
-instance Eq TyCon where
- (==) (TyCon hi1 lo1 _ _) (TyCon hi2 lo2 _ _)
- = isTrue# (hi1 `eqWord64#` hi2) && isTrue# (lo1 `eqWord64#` lo2)
-instance Ord TyCon where
- compare (TyCon hi1 lo1 _ _) (TyCon hi2 lo2 _ _)
- | isTrue# (hi1 `gtWord64#` hi2) = GT
- | isTrue# (hi1 `ltWord64#` hi2) = LT
- | isTrue# (lo1 `gtWord64#` lo2) = GT
- | isTrue# (lo1 `ltWord64#` lo2) = LT
- | True = EQ
-#else
-instance Eq TyCon where
- (==) (TyCon hi1 lo1 _ _) (TyCon hi2 lo2 _ _)
- = isTrue# (hi1 `eqWord#` hi2) && isTrue# (lo1 `eqWord#` lo2)
-instance Ord TyCon where
- compare (TyCon hi1 lo1 _ _) (TyCon hi2 lo2 _ _)
- | isTrue# (hi1 `gtWord#` hi2) = GT
- | isTrue# (hi1 `ltWord#` hi2) = LT
- | isTrue# (lo1 `gtWord#` lo2) = GT
- | isTrue# (lo1 `ltWord#` lo2) = LT
- | True = EQ
-#endif
-
-
-- | The 'Ord' class is used for totally ordered datatypes.
--
-- Instances of 'Ord' can be derived for any user-defined
diff --git a/libraries/ghc-prim/GHC/Magic.hs b/libraries/ghc-prim/GHC/Magic.hs
index 740abb729e..22db69f2ae 100644
--- a/libraries/ghc-prim/GHC/Magic.hs
+++ b/libraries/ghc-prim/GHC/Magic.hs
@@ -19,8 +19,6 @@
module GHC.Magic ( inline, lazy, oneShot ) where
-import GHC.CString ()
-
-- | The call @inline f@ arranges that 'f' is inlined, regardless of
-- its size. More precisely, the call @inline f@ rewrites to the
-- right-hand side of @f@'s definition. This allows the programmer to
diff --git a/libraries/ghc-prim/GHC/Tuple.hs b/libraries/ghc-prim/GHC/Tuple.hs
index b08d0b4fee..4ebda15d84 100644
--- a/libraries/ghc-prim/GHC/Tuple.hs
+++ b/libraries/ghc-prim/GHC/Tuple.hs
@@ -16,9 +16,6 @@
module GHC.Tuple where
-import GHC.CString () -- Make sure we do it first, so that the
- -- implicit Typeable stuff can see GHC.Types.TyCon
- -- and unpackCString# etc
default () -- Double and Integer aren't available yet
diff --git a/libraries/ghc-prim/GHC/Types.hs b/libraries/ghc-prim/GHC/Types.hs
index 63b4f0508f..294f15e6e4 100644
--- a/libraries/ghc-prim/GHC/Types.hs
+++ b/libraries/ghc-prim/GHC/Types.hs
@@ -1,5 +1,5 @@
{-# LANGUAGE MagicHash, NoImplicitPrelude, TypeFamilies, UnboxedTuples,
- MultiParamTypeClasses, RoleAnnotations, CPP #-}
+ MultiParamTypeClasses, RoleAnnotations #-}
-----------------------------------------------------------------------------
-- |
-- Module : GHC.Types
@@ -29,12 +29,11 @@ module GHC.Types (
isTrue#,
SPEC(..),
Nat, Symbol,
- Coercible,
- -- * Runtime type representation
- Module(..), TrName(..), TyCon(..)
+ Coercible
) where
import GHC.Prim
+import GHC.Tuple ()
infixr 5 :
@@ -309,56 +308,3 @@ you're reading this in 2023 then things went wrong). See #8326.
-- Libraries can specify this by using 'SPEC' data type to inform which
-- loops should be aggressively specialized.
data SPEC = SPEC | SPEC2
-
-{- *********************************************************************
-* *
- Runtime represntation of TyCon
-* *
-********************************************************************* -}
-
-{- Note [Runtime representation of modules and tycons]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-We generate a binding for M.$modName and M.$tcT for every module M and
-data type T. Things to think about
-
- - We want them to be economical on space; ideally pure data with no thunks.
-
- - We do this for every module (except this module GHC.Types), so we can't
- depend on anything else (eg string unpacking code)
-
-That's why we have these terribly low-level repesentations. The TrName
-type lets us use the TrNameS constructor when allocating static data;
-but we also need TrNameD for the case where we are deserialising a TyCon
-or Module (for example when deserialising a TypeRep), in which case we
-can't conveniently come up with an Addr#.
-
-
-Note [Representations of types defined in GHC.Types]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-
-The representations for the types defined in GHC.Types are
-defined in GHC.Typeable.Internal.
-
--}
-
-#include "MachDeps.h"
-
-data Module = Module
- TrName -- Package name
- TrName -- Module name
-
-data TrName
- = TrNameS Addr# -- Static
- | TrNameD [Char] -- Dynamic
-
-#if WORD_SIZE_IN_BITS < 64
-data TyCon = TyCon
- Word64# Word64# -- Fingerprint
- Module -- Module in which this is defined
- TrName -- Type constructor name
-#else
-data TyCon = TyCon
- Word# Word#
- Module
- TrName
-#endif