[commit: ghc] wip/nfs-locking: Haddocks for Way.hs (997ce25)
git at git.haskell.org
git at git.haskell.org
Thu Oct 26 23:43:48 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/nfs-locking
Link : http://ghc.haskell.org/trac/ghc/changeset/997ce259b41f6e60b7d4906292b920a00c799bfd/ghc
>---------------------------------------------------------------
commit 997ce259b41f6e60b7d4906292b920a00c799bfd
Author: David Luposchainsky <dluposchainsky at gmail.com>
Date: Wed Jan 6 15:31:55 2016 +0100
Haddocks for Way.hs
>---------------------------------------------------------------
997ce259b41f6e60b7d4906292b920a00c799bfd
src/Rules.hs | 2 +-
src/Stage.hs | 2 +-
src/Way.hs | 37 +++++++++++++++++++++++++++++--------
3 files changed, 31 insertions(+), 10 deletions(-)
diff --git a/src/Rules.hs b/src/Rules.hs
index f8b2810..c24b354 100644
--- a/src/Rules.hs
+++ b/src/Rules.hs
@@ -11,7 +11,7 @@ import Rules.Resources
import Settings
allStages :: [Stage]
-allStages = [Stage0 ..]
+allStages = [minBound ..]
-- TODO: not all program targets should be needed explicitly
-- | 'need' all top-level build targets
diff --git a/src/Stage.hs b/src/Stage.hs
index 2e581c4..af6d2df 100644
--- a/src/Stage.hs
+++ b/src/Stage.hs
@@ -22,7 +22,7 @@ import GHC.Generics (Generic)
-- Since it serves no other purpose than that, the stage 3 build is usually
-- omitted in the build process.
data Stage = Stage0 | Stage1 | Stage2 | Stage3
- deriving (Show, Eq, Ord, Enum, Generic)
+ deriving (Show, Eq, Ord, Enum, Generic, Bounded)
-- | Prettyprint a 'Stage'.
stageString :: Stage -> String
diff --git a/src/Way.hs b/src/Way.hs
index 28d1365..9f7f12a 100644
--- a/src/Way.hs
+++ b/src/Way.hs
@@ -19,6 +19,8 @@ import Oracles
-- Note: order of constructors is important for compatibility with the old build
-- system, e.g. we want "thr_p", not "p_thr" (see instance Show Way).
+-- | A 'WayUnit' is a single way of building source code, for example with
+-- profiling enabled, or dynamically linked.
data WayUnit = Threaded
| Debug
| Profiling
@@ -26,7 +28,7 @@ data WayUnit = Threaded
| Dynamic
| Parallel
| GranSim
- deriving (Eq, Enum)
+ deriving (Eq, Enum, Bounded)
-- TODO: get rid of non-derived Show instances
instance Show WayUnit where
@@ -40,16 +42,22 @@ instance Show WayUnit where
GranSim -> "gm"
instance Read WayUnit where
- readsPrec _ s = [(unit, "") | unit <- [Threaded ..], show unit == s]
+ readsPrec _ s = [(unit, "") | unit <- [minBound ..], show unit == s]
+-- | Collection of 'WayUnit's that stands for the different ways source code
+-- is to be built.
newtype Way = Way IntSet
+-- | Construct a 'Way' from multiple 'WayUnit's. Inverse of 'wayToUnits'.
wayFromUnits :: [WayUnit] -> Way
wayFromUnits = Way . Set.fromList . map fromEnum
+-- | Split a 'Way' into its 'WayUnit' building blocks.
+-- Inverse of 'wayFromUnits'.
wayToUnits :: Way -> [WayUnit]
wayToUnits (Way set) = map toEnum . Set.elems $ set
+-- | Check whether a 'Way' contains a certain 'WayUnit'.
wayUnit :: WayUnit -> Way -> Bool
wayUnit unit (Way set) = fromEnum unit `Set.member` set
@@ -72,11 +80,23 @@ instance Read Way where
instance Eq Way where
Way a == Way b = a == b
-vanilla, profiling, logging, parallel, granSim :: Way
+-- | Build with no 'WayUnit's at all.
+vanilla :: Way
vanilla = wayFromUnits []
+
+-- | Build with profiling.
+profiling :: Way
profiling = wayFromUnits [Profiling]
+
+-- | Build with logging.
+logging :: Way
logging = wayFromUnits [Logging]
+
+-- | Build in parallel.
+parallel :: Way
parallel = wayFromUnits [Parallel]
+
+granSim :: Way
granSim = wayFromUnits [GranSim]
-- RTS only ways
@@ -135,11 +155,12 @@ libsuf way @ (Way set) =
-- e.g., p_ghc7.11.20141222.dll (the result)
return $ prefix ++ "ghc" ++ version ++ extension
--- Detect way from a given filename. Returns Nothing if there is no match:
--- * safeDetectWay "foo/bar.hi" == Just vanilla
--- * safeDetectWay "baz.thr_p_o" == Just threadedProfiling
--- * safeDetectWay "qwe.ph_i" == Nothing (expected "qwe.p_hi")
--- * safeDetectWay "xru.p_ghc7.11.20141222.so" == Just profiling
+-- | Detect way from a given 'FilePath'. Returns 'Nothing' if there is no match.
+--
+-- * @'safeDetectWay' "foo/bar.hi" '==' 'Just' vanilla@
+-- * @'safeDetectWay' "baz.thr_p_o" '==' 'Just' threadedProfiling@
+-- * @'safeDetectWay' "qwe.ph_i" '==' 'Nothing' (expected "qwe.p_hi")@
+-- * @'safeDetectWay' "xru.p_ghc7.11.123.so" '==' 'Just' profiling@
safeDetectWay :: FilePath -> Maybe Way
safeDetectWay file = case reads prefix of
[(way, "")] -> Just way
More information about the ghc-commits
mailing list