Skip to content
Commits on Source (2)
pkg-haskell-tools (0.12) unstable; urgency=medium
* Port to shake 0.16. closes: #901323.
-- Clint Adams <clint@debian.org> Mon, 11 Jun 2018 13:29:32 -0400
pkg-haskell-tools (0.11.1) unstable; urgency=medium pkg-haskell-tools (0.11.1) unstable; urgency=medium
[ Joachim Breitner ] [ Joachim Breitner ]
......
...@@ -13,14 +13,13 @@ Build-Depends: debhelper (>= 9), ...@@ -13,14 +13,13 @@ Build-Depends: debhelper (>= 9),
libghc-extra-dev (>= 1.1), libghc-extra-dev (>= 1.1),
libghc-optparse-applicative-dev (>= 0.12), libghc-optparse-applicative-dev (>= 0.12),
libghc-parsec3-dev, libghc-parsec3-dev,
libghc-shake-dev (>= 0.15), libghc-shake-dev (>= 0.16),
libghc-shake-dev (<< 0.16),
libghc-split-dev (>= 0.2), libghc-split-dev (>= 0.2),
libghc-split-dev (<< 0.3), libghc-split-dev (<< 0.3),
libghc-text-dev, libghc-text-dev,
libghc-concurrent-output-dev (>= 1.7), libghc-concurrent-output-dev (>= 1.7),
libfile-slurp-perl libfile-slurp-perl
Standards-Version: 4.1.1 Standards-Version: 4.1.4
Homepage: https://wiki.debian.org/Haskell Homepage: https://wiki.debian.org/Haskell
Vcs-Browser: https://anonscm.debian.org/cgit/pkg-haskell/pkg-haskell-tools.git Vcs-Browser: https://anonscm.debian.org/cgit/pkg-haskell/pkg-haskell-tools.git
Vcs-Git: https://anonscm.debian.org/git/pkg-haskell/pkg-haskell-tools.git Vcs-Git: https://anonscm.debian.org/git/pkg-haskell/pkg-haskell-tools.git
......
...@@ -27,7 +27,7 @@ executable make-all ...@@ -27,7 +27,7 @@ executable make-all
unix, unix,
parsec, parsec,
text, text,
shake == 0.15.*, shake >= 0.16,
extra >= 1.1, extra >= 1.1,
debian >= 3.89, debian >= 3.89,
optparse-applicative >= 0.12, optparse-applicative >= 0.12,
......
{-# LANGUAGE GeneralizedNewtypeDeriving, ConstraintKinds #-} {-# LANGUAGE GeneralizedNewtypeDeriving, ConstraintKinds, TypeFamilies #-}
module Development.Shake.Fancy module Development.Shake.Fancy
( module Development.Shake ( module Development.Shake
...@@ -210,16 +210,16 @@ cmdWrap :: String -> S.Action a -> Action a ...@@ -210,16 +210,16 @@ cmdWrap :: String -> S.Action a -> Action a
cmdWrap cmd act = cmdWrap cmd act =
describe (quietly act) '!' ("running " ++ cmd) describe (quietly act) '!' ("running " ++ cmd)
askOracle :: (S.ShakeValue q, S.ShakeValue a) => q -> Action a askOracle :: (S.RuleResult q ~ a, S.ShakeValue q, S.ShakeValue a) => q -> Action a
askOracle query = askOracle query =
describe (S.askOracle query) '?' ("querying oracle " ++ show query) describe (S.askOracle query) '?' ("querying oracle " ++ show query)
addOracle :: (S.ShakeValue q, S.ShakeValue a) => (q -> Action a) -> S.Rules (q -> Action a) addOracle :: (S.RuleResult q ~ a, S.ShakeValue q, S.ShakeValue a) => (q -> Action a) -> S.Rules (q -> Action a)
addOracle action = do addOracle action = do
query <- S.addOracle (\q -> wrapAction (action q) (show q)) query <- S.addOracle (\q -> wrapAction (action q) (show q))
return $ liftAction . query return $ liftAction . query
addQuietOracle :: (S.ShakeValue q, S.ShakeValue a) => (q -> Action a) -> S.Rules (q -> Action a) addQuietOracle :: (S.RuleResult q ~ a, S.ShakeValue q, S.ShakeValue a) => (q -> Action a) -> S.Rules (q -> Action a)
addQuietOracle action = do addQuietOracle action = do
query <- S.addOracle (\q -> wrapSpuriousAction (action q) (show q)) query <- S.addOracle (\q -> wrapSpuriousAction (action q) (show q))
return $ liftAction . query return $ liftAction . query
......
{-# LANGUAGE GeneralizedNewtypeDeriving, DeriveDataTypeable, RecordWildCards #-} {-# LANGUAGE GeneralizedNewtypeDeriving, DeriveDataTypeable, RecordWildCards #-}
{-# LANGUAGE TypeFamilies #-}
import qualified Data.Map as M import qualified Data.Map as M
import qualified Data.Set as S import qualified Data.Set as S
import Control.Applicative hiding (many) import Control.Applicative hiding (many)
...@@ -269,10 +271,12 @@ defaultExcludedPackages = words "ghc ghc-testsuite haskell-devscripts haskell98- ...@@ -269,10 +271,12 @@ defaultExcludedPackages = words "ghc ghc-testsuite haskell-devscripts haskell98-
newtype GetExcludedSources = GetExcludedSources () deriving (Show,Typeable,Eq,Hashable,Binary,NFData) newtype GetExcludedSources = GetExcludedSources () deriving (Show,Typeable,Eq,Hashable,Binary,NFData)
newtype GetDebBuiltBy = GetDebBuiltBy String deriving (Show,Typeable,Eq,Hashable,Binary,NFData) newtype GetDebBuiltBy = GetDebBuiltBy String deriving (Show,Typeable,Eq,Hashable,Binary,NFData)
type instance RuleResult GetDebBuiltBy = Maybe String
newtype GetBinToDeb = GetBinToDeb String deriving (Show,Typeable,Eq,Hashable,Binary,NFData) newtype GetBinToDeb = GetBinToDeb String deriving (Show,Typeable,Eq,Hashable,Binary,NFData)
type instance RuleResult GetBinToDeb = Maybe String
newtype GetArch = GetArch () deriving (Typeable,Eq,Hashable,Binary,NFData) newtype GetArch = GetArch () deriving (Typeable,Eq,Hashable,Binary,NFData)
type instance RuleResult GetArch = String
instance Show GetArch where show (GetArch ()) = "querying architecture" instance Show GetArch where show (GetArch ()) = "querying architecture"
-- Find dependencies on binary packages we build ourselves. -- Find dependencies on binary packages we build ourselves.
......