summaryrefslogtreecommitdiff
path: root/libraries/base
diff options
context:
space:
mode:
authorSimon Peyton Jones <simonpj@microsoft.com>2015-05-01 15:05:11 +0100
committerSimon Peyton Jones <simonpj@microsoft.com>2015-05-01 15:06:26 +0100
commit2f6a0ac7061c59ed68a6dd5a2243e3e690acbd5f (patch)
tree3a0cca1160b5479c3ef89f3df565ab470cd62e41 /libraries/base
parentde5d022e1543283effd67c2a03598e2bcaf49930 (diff)
downloadhaskell-2f6a0ac7061c59ed68a6dd5a2243e3e690acbd5f.tar.gz
Move IP, Symbol, Nat to ghc-prim
This motivation is to declare class IP much earlier (in ghc-prim), so that implicit parameters (which depend on IP) is available to library code, notably the 'error' function. * Move class IP from base:GHC.IP to ghc-prim:GHC.Classes * Delete module GHC.IP from base * Move types Symbol and Nat from base:GHC.TypeLits to ghc-prim:GHC.Types There was a name clash in GHC.RTS.Flags, where I renamed the local type Nat to RtsNat.
Diffstat (limited to 'libraries/base')
-rw-r--r--libraries/base/GHC/IP.hs19
-rw-r--r--libraries/base/GHC/RTS/Flags.hsc26
-rw-r--r--libraries/base/GHC/TypeLits.hs10
-rw-r--r--libraries/base/base.cabal1
4 files changed, 15 insertions, 41 deletions
diff --git a/libraries/base/GHC/IP.hs b/libraries/base/GHC/IP.hs
deleted file mode 100644
index b85c382a43..0000000000
--- a/libraries/base/GHC/IP.hs
+++ /dev/null
@@ -1,19 +0,0 @@
-{-# LANGUAGE Safe #-}
-{-# LANGUAGE MultiParamTypeClasses #-}
-{-# LANGUAGE FunctionalDependencies #-}
-{-# LANGUAGE KindSignatures #-}
-{-# LANGUAGE DataKinds #-}
-{-# LANGUAGE NoImplicitPrelude #-}
-{-# LANGUAGE AllowAmbiguousTypes #-}
- -- ip :: IP x a => a is strictly speaking ambiguous, but IP is magic
-
--- | @since 4.6.0.0
-module GHC.IP (IP(..)) where
-
-import GHC.TypeLits
-
--- | The syntax @?x :: a@ is desugared into @IP "x" a@
-class IP (x :: Symbol) a | x -> a where
- ip :: a
-
-
diff --git a/libraries/base/GHC/RTS/Flags.hsc b/libraries/base/GHC/RTS/Flags.hsc
index 16764e55c1..308aafbf91 100644
--- a/libraries/base/GHC/RTS/Flags.hsc
+++ b/libraries/base/GHC/RTS/Flags.hsc
@@ -51,7 +51,7 @@ import GHC.Word
type Time = Word64
-- | @'nat'@ defined in @rts/Types.h@
-type Nat = #{type unsigned int}
+type RtsNat = #{type unsigned int}
data GiveGCStats
= NoGCStats
@@ -78,19 +78,19 @@ instance Enum GiveGCStats where
data GCFlags = GCFlags
{ statsFile :: Maybe FilePath
, giveStats :: GiveGCStats
- , maxStkSize :: Nat
- , initialStkSize :: Nat
- , stkChunkSize :: Nat
- , stkChunkBufferSize :: Nat
- , maxHeapSize :: Nat
- , minAllocAreaSize :: Nat
- , minOldGenSize :: Nat
- , heapSizeSuggestion :: Nat
+ , maxStkSize :: RtsNat
+ , initialStkSize :: RtsNat
+ , stkChunkSize :: RtsNat
+ , stkChunkBufferSize :: RtsNat
+ , maxHeapSize :: RtsNat
+ , minAllocAreaSize :: RtsNat
+ , minOldGenSize :: RtsNat
+ , heapSizeSuggestion :: RtsNat
, heapSizeSuggestionAuto :: Bool
, oldGenFactor :: Double
, pcFreeHeap :: Double
- , generations :: Nat
- , steps :: Nat
+ , generations :: RtsNat
+ , steps :: RtsNat
, squeezeUpdFrames :: Bool
, compact :: Bool -- ^ True <=> "compact all the time"
, compactThreshold :: Double
@@ -305,7 +305,7 @@ getGCFlags = do
ptr <- getGcFlagsPtr
GCFlags <$> (peekFilePath =<< #{peek GC_FLAGS, statsFile} ptr)
<*> (toEnum . fromIntegral <$>
- (#{peek GC_FLAGS, giveStats} ptr :: IO Nat))
+ (#{peek GC_FLAGS, giveStats} ptr :: IO RtsNat))
<*> #{peek GC_FLAGS, maxStkSize} ptr
<*> #{peek GC_FLAGS, initialStkSize} ptr
<*> #{peek GC_FLAGS, stkChunkSize} ptr
@@ -367,7 +367,7 @@ getCCFlags :: IO CCFlags
getCCFlags = do
ptr <- getCcFlagsPtr
CCFlags <$> (toEnum . fromIntegral
- <$> (#{peek COST_CENTRE_FLAGS, doCostCentres} ptr :: IO Nat))
+ <$> (#{peek COST_CENTRE_FLAGS, doCostCentres} ptr :: IO RtsNat))
<*> #{peek COST_CENTRE_FLAGS, profilerTicks} ptr
<*> #{peek COST_CENTRE_FLAGS, msecsPerTick} ptr
diff --git a/libraries/base/GHC/TypeLits.hs b/libraries/base/GHC/TypeLits.hs
index 6da103e73c..dafdb57c69 100644
--- a/libraries/base/GHC/TypeLits.hs
+++ b/libraries/base/GHC/TypeLits.hs
@@ -22,7 +22,7 @@ for working with type-level naturals should be defined in a separate library.
module GHC.TypeLits
( -- * Kinds
- Nat, Symbol
+ Nat, Symbol -- Both declared in GHC.Types in package ghc-prim
-- * Linking type and value level
, KnownNat, natVal, natVal'
@@ -39,6 +39,7 @@ module GHC.TypeLits
) where
import GHC.Base(Eq(..), Ord(..), Bool(True,False), Ordering(..), otherwise)
+import GHC.Types( Nat, Symbol )
import GHC.Num(Integer)
import GHC.Base(String)
import GHC.Show(Show(..))
@@ -49,13 +50,6 @@ import Data.Proxy (Proxy(..))
import Data.Type.Equality(type (==), (:~:)(Refl))
import Unsafe.Coerce(unsafeCoerce)
--- | (Kind) This is the kind of type-level natural numbers.
-data Nat
-
--- | (Kind) This is the kind of type-level symbols.
-data Symbol
-
-
--------------------------------------------------------------------------------
-- | This class gives the integer associated with a type-level natural.
diff --git a/libraries/base/base.cabal b/libraries/base/base.cabal
index ba0151af5c..21a8ae7bcb 100644
--- a/libraries/base/base.cabal
+++ b/libraries/base/base.cabal
@@ -231,7 +231,6 @@ Library
GHC.IO.IOMode
GHC.IOArray
GHC.IORef
- GHC.IP
GHC.Int
GHC.List
GHC.MVar