summaryrefslogtreecommitdiff
path: root/libraries
diff options
context:
space:
mode:
authorSylvain Henry <sylvain@haskus.fr>2020-04-05 17:39:13 +0200
committerSylvain Henry <sylvain@haskus.fr>2020-04-18 20:04:46 +0200
commit15312bbb53f247c9ed2c5cf75100a9f44c1c7227 (patch)
tree8306dcc04a5b7c82464f903044dfdd589e7fdcd7 /libraries
parent3ca52151881451ce5b3a7740d003e811b586140d (diff)
downloadhaskell-15312bbb53f247c9ed2c5cf75100a9f44c1c7227.tar.gz
Modules (#13009)
* SysTools * Parser * GHC.Builtin * GHC.Iface.Recomp * Settings Update Haddock submodule Metric Decrease: Naperian parsing001
Diffstat (limited to 'libraries')
-rw-r--r--libraries/base/Data/Type/Equality.hs2
-rw-r--r--libraries/base/GHC/IO.hs2
-rw-r--r--libraries/ghc-boot-th/GHC/Lexeme.hs2
-rw-r--r--libraries/ghc-boot/GHC/Settings/Platform.hs (renamed from libraries/ghc-boot/GHC/Settings.hs)17
-rw-r--r--libraries/ghc-boot/GHC/Settings/Utils.hs15
-rw-r--r--libraries/ghc-boot/ghc-boot.cabal.in3
-rw-r--r--libraries/ghc-prim/GHC/Tuple.hs2
-rw-r--r--libraries/ghc-prim/GHC/Types.hs12
-rw-r--r--libraries/ghc-prim/cbits/atomic.c4
-rw-r--r--libraries/template-haskell/Language/Haskell/TH/Syntax.hs4
10 files changed, 33 insertions, 30 deletions
diff --git a/libraries/base/Data/Type/Equality.hs b/libraries/base/Data/Type/Equality.hs
index e900546671..ab321ba011 100644
--- a/libraries/base/Data/Type/Equality.hs
+++ b/libraries/base/Data/Type/Equality.hs
@@ -62,7 +62,7 @@ infix 4 :~:, :~~:
-- in the body of the pattern-match, the compiler knows that @a ~ b@.
--
-- @since 4.7.0.0
-data a :~: b where -- See Note [The equality types story] in TysPrim
+data a :~: b where -- See Note [The equality types story] in GHC.Builtin.Types.Prim
Refl :: a :~: a
-- with credit to Conal Elliott for 'ty', Erik Hesselink & Martijn van
diff --git a/libraries/base/GHC/IO.hs b/libraries/base/GHC/IO.hs
index ee293112a6..df79d2a9a0 100644
--- a/libraries/base/GHC/IO.hs
+++ b/libraries/base/GHC/IO.hs
@@ -62,7 +62,7 @@ implement IO exceptions.
NOTE: The IO representation is deeply wired in to various parts of the
system. The following list may or may not be exhaustive:
-Compiler - types of various primitives in PrimOp.hs
+Compiler - types of various primitives in GHC.Builtin.PrimOps
RTS - forceIO (StgStartup.cmm)
- catchzh_fast, (un)?blockAsyncExceptionszh_fast, raisezh_fast
diff --git a/libraries/ghc-boot-th/GHC/Lexeme.hs b/libraries/ghc-boot-th/GHC/Lexeme.hs
index 5093c98f1e..09d83917d3 100644
--- a/libraries/ghc-boot-th/GHC/Lexeme.hs
+++ b/libraries/ghc-boot-th/GHC/Lexeme.hs
@@ -18,7 +18,7 @@ import Prelude -- See note [Why do we import Prelude here?]
import Data.Char
-- | Is this character acceptable in a symbol (after the first char)?
--- See alexGetByte in Lexer.x
+-- See alexGetByte in GHC.Parser.Lexer
okSymChar :: Char -> Bool
okSymChar c
| c `elem` "(),;[]`{}_\"'"
diff --git a/libraries/ghc-boot/GHC/Settings.hs b/libraries/ghc-boot/GHC/Settings/Platform.hs
index fd0a0ef3ad..f97fff6b6f 100644
--- a/libraries/ghc-boot/GHC/Settings.hs
+++ b/libraries/ghc-boot/GHC/Settings/Platform.hs
@@ -11,14 +11,14 @@
--
-- The "0" suffix is because the caller will partially apply it, and that will
-- in turn be used a few more times.
-module GHC.Settings where
+module GHC.Settings.Platform where
import Prelude -- See Note [Why do we import Prelude here?]
import GHC.BaseDir
import GHC.Platform
+import GHC.Settings.Utils
-import Data.Char (isSpace)
import Data.Map (Map)
import qualified Data.Map as Map
@@ -93,16 +93,3 @@ readSetting0 settingsFile mySettings key = case Map.lookup key mySettings of
Just v -> Right v
Nothing -> Left $ "Failed to read " ++ show key ++ " value " ++ show xs
Nothing -> Left $ "No entry for " ++ show key ++ " in " ++ show settingsFile
-
------------------------------------------------------------------------------
--- read helpers
-
-maybeRead :: Read a => String -> Maybe a
-maybeRead str = case reads str of
- [(x, "")] -> Just x
- _ -> Nothing
-
-maybeReadFuzzy :: Read a => String -> Maybe a
-maybeReadFuzzy str = case reads str of
- [(x, s)] | all isSpace s -> Just x
- _ -> Nothing
diff --git a/libraries/ghc-boot/GHC/Settings/Utils.hs b/libraries/ghc-boot/GHC/Settings/Utils.hs
new file mode 100644
index 0000000000..1f1cd67030
--- /dev/null
+++ b/libraries/ghc-boot/GHC/Settings/Utils.hs
@@ -0,0 +1,15 @@
+module GHC.Settings.Utils where
+
+import Prelude -- See Note [Why do we import Prelude here?]
+
+import Data.Char (isSpace)
+
+maybeRead :: Read a => String -> Maybe a
+maybeRead str = case reads str of
+ [(x, "")] -> Just x
+ _ -> Nothing
+
+maybeReadFuzzy :: Read a => String -> Maybe a
+maybeReadFuzzy str = case reads str of
+ [(x, s)] | all isSpace s -> Just x
+ _ -> Nothing
diff --git a/libraries/ghc-boot/ghc-boot.cabal.in b/libraries/ghc-boot/ghc-boot.cabal.in
index d837fc9875..c8ac491c59 100644
--- a/libraries/ghc-boot/ghc-boot.cabal.in
+++ b/libraries/ghc-boot/ghc-boot.cabal.in
@@ -45,7 +45,8 @@ Library
GHC.HandleEncoding
GHC.Platform
GHC.Platform.Host
- GHC.Settings
+ GHC.Settings.Platform
+ GHC.Settings.Utils
GHC.UniqueSubdir
GHC.Version
diff --git a/libraries/ghc-prim/GHC/Tuple.hs b/libraries/ghc-prim/GHC/Tuple.hs
index 05d6fbfe53..51179167bc 100644
--- a/libraries/ghc-prim/GHC/Tuple.hs
+++ b/libraries/ghc-prim/GHC/Tuple.hs
@@ -28,7 +28,7 @@ data () = ()
-- The desugarer uses 1-tuples,
-- but "()" is already used up for 0-tuples
--- See Note [One-tuples] in TysWiredIn
+-- See Note [One-tuples] in GHC.Builtin.Types
data Unit a = Unit a
data (a,b) = (a,b)
diff --git a/libraries/ghc-prim/GHC/Types.hs b/libraries/ghc-prim/GHC/Types.hs
index bdd0883a37..0a32454149 100644
--- a/libraries/ghc-prim/GHC/Types.hs
+++ b/libraries/ghc-prim/GHC/Types.hs
@@ -84,7 +84,7 @@ data Symbol
-- to @x@.
--
type family Any :: k where { }
--- See Note [Any types] in TysWiredIn. Also, for a bit of history on Any see
+-- See Note [Any types] in GHC.Builtin.Types. Also, for a bit of history on Any see
-- #10886. Note that this must be a *closed* type family: we need to ensure
-- that this can't reduce to a `data` type for the results discussed in
-- Note [Any types].
@@ -214,7 +214,7 @@ for them, e.g. to compile the constructor's info table.
Furthermore the type of MkCoercible cannot be written in Haskell
(no syntax for ~#R).
-So we define them as regular data types in GHC.Types, and do magic in TysWiredIn,
+So we define them as regular data types in GHC.Types, and do magic in GHC.Builtin.Types,
inside GHC, to change the kind and type.
-}
@@ -227,13 +227,13 @@ inside GHC, to change the kind and type.
-- homogeneous equality @~@, this is printed as @~@ unless
-- @-fprint-equality-relations@ is set.
class a ~~ b
- -- See also Note [The equality types story] in TysPrim
+ -- See also Note [The equality types story] in GHC.Builtin.Types.Prim
-- | Lifted, homogeneous equality. By lifted, we mean that it
-- can be bogus (deferred type error). By homogeneous, the two
-- types @a@ and @b@ must have the same kinds.
class a ~ b
- -- See also Note [The equality types story] in TysPrim
+ -- See also Note [The equality types story] in GHC.Builtin.Types.Prim
-- | @Coercible@ is a two-parameter class that has instances for types @a@ and @b@ if
-- the compiler can infer that they have the same representation. This class
@@ -283,7 +283,7 @@ class a ~ b
--
-- @since 4.7.0.0
class Coercible (a :: k) (b :: k)
- -- See also Note [The equality types story] in TysPrim
+ -- See also Note [The equality types story] in GHC.Builtin.Types.Prim
{- *********************************************************************
* *
@@ -409,7 +409,7 @@ data RuntimeRep = VecRep VecCount VecElem -- ^ a SIMD vector type
-- RuntimeRep is intimately tied to TyCon.RuntimeRep (in GHC proper). See
-- Note [RuntimeRep and PrimRep] in RepType.
--- See also Note [Wiring in RuntimeRep] in TysWiredIn
+-- See also Note [Wiring in RuntimeRep] in GHC.Builtin.Types
-- | Length of a SIMD vector type
data VecCount = Vec2
diff --git a/libraries/ghc-prim/cbits/atomic.c b/libraries/ghc-prim/cbits/atomic.c
index 01037d70ee..d196ef23c7 100644
--- a/libraries/ghc-prim/cbits/atomic.c
+++ b/libraries/ghc-prim/cbits/atomic.c
@@ -319,7 +319,7 @@ hs_cmpxchg64(StgWord x, StgWord64 old, StgWord64 new)
#endif
// AtomicReadByteArrayOp_Int
-// Implies a full memory barrier (see compiler/prelude/primops.txt.pp)
+// Implies a full memory barrier (see compiler/GHC/Builtin/primops.txt.pp)
// __ATOMIC_SEQ_CST: Full barrier in both directions (hoisting and sinking
// of code) and synchronizes with acquire loads and release stores in
// all threads.
@@ -375,7 +375,7 @@ hs_atomicread64(StgWord x)
#endif
// AtomicWriteByteArrayOp_Int
-// Implies a full memory barrier (see compiler/prelude/primops.txt.pp)
+// Implies a full memory barrier (see compiler/GHC/Builtin/primops.txt.pp)
// __ATOMIC_SEQ_CST: Full barrier (see hs_atomicread8 above).
extern void hs_atomicwrite8(StgWord x, StgWord val);
diff --git a/libraries/template-haskell/Language/Haskell/TH/Syntax.hs b/libraries/template-haskell/Language/Haskell/TH/Syntax.hs
index 4c8aacf97f..c14bec1f65 100644
--- a/libraries/template-haskell/Language/Haskell/TH/Syntax.hs
+++ b/libraries/template-haskell/Language/Haskell/TH/Syntax.hs
@@ -1598,7 +1598,7 @@ unboxedSumDataName alt arity
prefix = "unboxedSumDataName: "
debug_info = " (alt: " ++ show alt ++ ", arity: " ++ show arity ++ ")"
- -- Synced with the definition of mkSumDataConOcc in TysWiredIn
+ -- Synced with the definition of mkSumDataConOcc in GHC.Builtin.Types
sum_occ = '(' : '#' : bars nbars_before ++ '_' : bars nbars_after ++ "#)"
bars i = replicate i '|'
nbars_before = alt - 1
@@ -1614,7 +1614,7 @@ unboxedSumTypeName arity
(NameG TcClsName (mkPkgName "ghc-prim") (mkModName "GHC.Prim"))
where
- -- Synced with the definition of mkSumTyConOcc in TysWiredIn
+ -- Synced with the definition of mkSumTyConOcc in GHC.Builtin.Types
sum_occ = '(' : '#' : replicate (arity - 1) '|' ++ "#)"
-----------------------------------------------------