[commit: ghc] master: Remove a few redundant `.hs-boot` files (ad4a713)
git at git.haskell.org
git at git.haskell.org
Sat Oct 11 07:07:50 UTC 2014
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/ad4a713964225e8e2d4e4a9579305a07a6ec2721/ghc
>---------------------------------------------------------------
commit ad4a713964225e8e2d4e4a9579305a07a6ec2721
Author: Herbert Valerio Riedel <hvr at gnu.org>
Date: Sat Oct 11 00:44:54 2014 +0200
Remove a few redundant `.hs-boot` files
There don't seem to be any corresponding `{-# SOURCE #-}` for the removed
`.hs-boot`-files anymore (if there ever was any in the first place).
This also removes a commented out `{-# SOURCE #-}` import which turns up when
grepping the source for `{-# SOURCE #-}` occurences.
>---------------------------------------------------------------
ad4a713964225e8e2d4e4a9579305a07a6ec2721
libraries/base/Data/OldTypeable/Internal.hs-boot | 28 ----------------------
libraries/base/Data/Typeable/Internal.hs-boot | 30 ------------------------
libraries/base/GHC/Show.lhs-boot | 11 ---------
libraries/base/GHC/Word.hs | 1 -
4 files changed, 70 deletions(-)
diff --git a/libraries/base/Data/OldTypeable/Internal.hs-boot b/libraries/base/Data/OldTypeable/Internal.hs-boot
deleted file mode 100644
index 4c1d636..0000000
--- a/libraries/base/Data/OldTypeable/Internal.hs-boot
+++ /dev/null
@@ -1,28 +0,0 @@
-{-# LANGUAGE Unsafe #-}
-{-# LANGUAGE CPP, NoImplicitPrelude, MagicHash #-}
-
-module Data.OldTypeable.Internal (
- Typeable(typeOf),
- TypeRep,
- TyCon,
- mkTyCon,
- mkTyConApp
- ) where
-
-import GHC.Base
-
-data TypeRep
-data TyCon
-
-#include "MachDeps.h"
-
-#if WORD_SIZE_IN_BITS < 64
-mkTyCon :: Word64# -> Word64# -> String -> String -> String -> TyCon
-#else
-mkTyCon :: Word# -> Word# -> String -> String -> String -> TyCon
-#endif
-
-mkTyConApp :: TyCon -> [TypeRep] -> TypeRep
-
-class Typeable a where
- typeOf :: a -> TypeRep
diff --git a/libraries/base/Data/Typeable/Internal.hs-boot b/libraries/base/Data/Typeable/Internal.hs-boot
deleted file mode 100644
index e2f65ee..0000000
--- a/libraries/base/Data/Typeable/Internal.hs-boot
+++ /dev/null
@@ -1,30 +0,0 @@
-{-# LANGUAGE Unsafe #-}
-{-# LANGUAGE CPP, NoImplicitPrelude, MagicHash, PolyKinds #-}
-
-module Data.Typeable.Internal (
- Proxy(..),
- Typeable(typeRep),
- TypeRep,
- TyCon,
- mkTyCon,
- mkTyConApp
- ) where
-
-import GHC.Base
-import {-# SOURCE #-} Data.Proxy
-
-data TypeRep
-data TyCon
-
-#include "MachDeps.h"
-
-#if WORD_SIZE_IN_BITS < 64
-mkTyCon :: Word64# -> Word64# -> String -> String -> String -> TyCon
-#else
-mkTyCon :: Word# -> Word# -> String -> String -> String -> TyCon
-#endif
-
-mkTyConApp :: TyCon -> [TypeRep] -> TypeRep
-
-class Typeable a where
- typeRep :: proxy a -> TypeRep
diff --git a/libraries/base/GHC/Show.lhs-boot b/libraries/base/GHC/Show.lhs-boot
deleted file mode 100644
index a2363f6..0000000
--- a/libraries/base/GHC/Show.lhs-boot
+++ /dev/null
@@ -1,11 +0,0 @@
-\begin{code}
-{-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE NoImplicitPrelude #-}
-
-module GHC.Show (showSignedInt) where
-
-import GHC.Types
-
-showSignedInt :: Int -> Int -> [Char] -> [Char]
-\end{code}
-
diff --git a/libraries/base/GHC/Word.hs b/libraries/base/GHC/Word.hs
index 6721d07..b2c70a2 100644
--- a/libraries/base/GHC/Word.hs
+++ b/libraries/base/GHC/Word.hs
@@ -35,7 +35,6 @@ import Data.Maybe
import GHC.IntWord64
#endif
--- import {-# SOURCE #-} GHC.Exception
import GHC.Base
import GHC.Enum
import GHC.Num
More information about the ghc-commits
mailing list