[commit: ghc] wip/nfs-locking: Add Haddocks to Target.hs (1b013b0)
git at git.haskell.org
git at git.haskell.org
Thu Oct 26 23:43:31 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/nfs-locking
Link : http://ghc.haskell.org/trac/ghc/changeset/1b013b0886e59cdd0ff2bd7a182e874d21899961/ghc
>---------------------------------------------------------------
commit 1b013b0886e59cdd0ff2bd7a182e874d21899961
Author: David Luposchainsky <dluposchainsky at gmail.com>
Date: Wed Jan 6 15:14:08 2016 +0100
Add Haddocks to Target.hs
>---------------------------------------------------------------
1b013b0886e59cdd0ff2bd7a182e874d21899961
src/Expression.hs | 4 +--
src/Target.hs | 75 ++++++++++++++++++++++++++++++++-----------------------
2 files changed, 46 insertions(+), 33 deletions(-)
diff --git a/src/Expression.hs b/src/Expression.hs
index a2eaea9..6e2a225 100644
--- a/src/Expression.hs
+++ b/src/Expression.hs
@@ -12,7 +12,7 @@ module Expression (
-- ** Common expressions
Args, Ways, Packages,
-- ** Targets
- Target, PartialTarget (..), fromPartial, fullTarget, fullTargetWithWay,
+ Target, PartialTarget (..), unsafeFromPartial, fullTarget, fullTargetWithWay,
-- * Convenient accessors
getStage, getPackage, getBuilder, getOutputs, getInputs, getWay,
@@ -150,7 +150,7 @@ interpret :: Target -> Expr a -> Action a
interpret = flip runReaderT
interpretPartial :: PartialTarget -> Expr a -> Action a
-interpretPartial = interpret . fromPartial
+interpretPartial = interpret . unsafeFromPartial
interpretWithStage :: Stage -> Expr a -> Action a
interpretWithStage s = interpretPartial $
diff --git a/src/Target.hs b/src/Target.hs
index cd22f48..152de3d 100644
--- a/src/Target.hs
+++ b/src/Target.hs
@@ -1,7 +1,11 @@
{-# LANGUAGE DeriveGeneric, FlexibleInstances #-}
module Target (
- Target (..), PartialTarget (..), fromPartial, fullTarget, fullTargetWithWay
- ) where
+ Target (..)
+ , PartialTarget (..)
+ , unsafeFromPartial
+ , fullTarget
+ , fullTargetWithWay
+) where
import Control.Monad.Trans.Reader
@@ -12,50 +16,53 @@ import Package
import Stage
import Way
--- Target captures all parameters relevant to the current build target:
--- * Stage and Package being built,
--- * Builder to be invoked,
--- * Way to be built (set to vanilla for most targets),
--- * source file(s) to be passed to Builder,
--- * file(s) to be produced.
+-- | Parameters relevant to the current build target.
data Target = Target
{
- stage :: Stage,
- package :: Package,
- builder :: Builder,
- way :: Way,
- inputs :: [FilePath],
- outputs :: [FilePath]
+ stage :: Stage, -- ^ Stage being built
+ package :: Package, -- ^ Package being built
+ builder :: Builder, -- ^ Builder to be invoked
+ way :: Way, -- ^ Way to build (set to vanilla for most targets)
+ inputs :: [FilePath], -- ^ Source files passed to the builder
+ outputs :: [FilePath] -- ^ Files to be produced
}
deriving (Show, Eq, Generic)
--- If values of type 'a' form a Monoid then we can also derive a Monoid instance
--- for values of type 'ReaderT Target Action a':
--- * the empty computation returns the identity element of the underlying type
+-- | If values of type @a@ form a 'Monoid' then we can also derive a 'Monoid'
+-- instance for values of type @'ReaderT' 'Target' 'Action' a@:
+--
+-- * the empty computation is the identity element of the underlying type
-- * two computations can be combined by combining their results
instance Monoid a => Monoid (ReaderT Target Action a) where
mempty = return mempty
mappend = liftM2 mappend
--- PartialTarget is a partially constructed Target with fields Stage and
--- Package only. PartialTarget's are used for generating build rules.
+-- A partially constructed Target with fields 'Stage' and 'Package' only.
+-- 'PartialTarget's are used for generating build rules.
data PartialTarget = PartialTarget Stage Package deriving (Eq, Show)
--- Convert PartialTarget to Target assuming that unknown fields won't be used.
-fromPartial :: PartialTarget -> Target
-fromPartial (PartialTarget s p) = Target
+-- | Convert 'PartialTarget' to a 'Target' assuming that unknown fields won't
+-- be used.
+unsafeFromPartial :: PartialTarget -> Target
+unsafeFromPartial (PartialTarget s p) = Target
{
stage = s,
package = p,
- builder = error "fromPartial: builder not set",
- way = error "fromPartial: way not set",
- inputs = error "fromPartial: inputs not set",
- outputs = error "fromPartial: outputs not set"
+ builder = error "unsafeFromPartial: builder not set",
+ way = error "unsafeFromPartial: way not set",
+ inputs = error "unsafeFromPartial: inputs not set",
+ outputs = error "unsafeFromPartial: outputs not set"
}
--- Construct a full target by augmenting a PartialTarget with missing fields.
--- Most targets are built only one way, vanilla, hence we set it by default.
-fullTarget :: PartialTarget -> Builder -> [FilePath] -> [FilePath] -> Target
+-- | Construct a full 'Target' by augmenting a 'PartialTarget' with missing
+-- fields. Most targets are built only one way, 'vanilla', hence it is set by
+-- default. Use 'fullTargetWithWay' otherwise.
+fullTarget ::
+ PartialTarget
+ -> Builder
+ -> [FilePath] -- ^ Source files
+ -> [FilePath] -- ^ Produced files
+ -> Target
fullTarget (PartialTarget s p) b srcs fs = Target
{
stage = s,
@@ -66,8 +73,14 @@ fullTarget (PartialTarget s p) b srcs fs = Target
outputs = map unifyPath fs
}
--- Use this function to be explicit about the build way.
-fullTargetWithWay :: PartialTarget -> Builder -> Way -> [FilePath] -> [FilePath] -> Target
+-- | Like 'fullTarget', but allows an explicit 'Way' parameter.
+fullTargetWithWay ::
+ PartialTarget
+ -> Builder
+ -> Way
+ -> [FilePath] -- ^ Source files
+ -> [FilePath] -- ^ Produced files
+ -> Target
fullTargetWithWay pt b w srcs fs = (fullTarget pt b srcs fs) { way = w }
-- Instances for storing in the Shake database
More information about the ghc-commits
mailing list