With some diffs from the upstream darcs repository and some less
strict dependencies on libraries bundled with ghc, this builds fine with both ghc-8.2 (in my tree, not yet committed) and ghc-8.0 (in the current tree). Tested against ghc-8.0 by jca@, thanks! It may also build again on i386, but I still have to check this.
This commit is contained in:
parent
caf0264d3e
commit
93e9a7a3eb
@ -1,4 +1,4 @@
|
||||
# $OpenBSD: Makefile,v 1.67 2017/11/20 23:43:46 kili Exp $
|
||||
# $OpenBSD: Makefile,v 1.68 2018/01/08 10:18:39 kili Exp $
|
||||
|
||||
# Needs template Haskell in Setup.lhs, which doesn't work on i386.
|
||||
NOT_FOR_ARCHS = i386
|
||||
@ -8,11 +8,12 @@ USE_WXNEEDED = Yes
|
||||
COMMENT = advanced revision control system written in Haskell
|
||||
|
||||
DISTNAME = darcs-2.12.5
|
||||
REVISION = 0
|
||||
|
||||
CATEGORIES = devel
|
||||
HOMEPAGE = http://www.darcs.net/
|
||||
|
||||
WANTLIB = c curl>=2 iconv m ncursesw pthread util z
|
||||
WANTLIB = c curl>=2 curses iconv m pthread util z
|
||||
MODULES = lang/ghc
|
||||
MODGHC_BUILD = cabal hackage nort
|
||||
MODGHC_SETUP_CONF_ARGS =-f 'curl -library' --enable-tests
|
||||
|
366
devel/darcs/patches/patch-Setup_lhs
Normal file
366
devel/darcs/patches/patch-Setup_lhs
Normal file
@ -0,0 +1,366 @@
|
||||
$OpenBSD: patch-Setup_lhs,v 1.1 2018/01/08 10:18:39 kili Exp $
|
||||
|
||||
Fix configuration with newer ghc/cabal etc.
|
||||
|
||||
From upstream commit c9fe8ac1fbffeef0be1c6e0796d798b2280a2e23, with
|
||||
the \begin{code}/\end{code} bracket left in place, so we don't have
|
||||
to rename Setup.lhs to Setup.hs.
|
||||
|
||||
Index: Setup.lhs
|
||||
--- Setup.lhs.orig
|
||||
+++ Setup.lhs
|
||||
@@ -1,72 +1,45 @@
|
||||
\begin{code}
|
||||
-{-# LANGUAGE TemplateHaskell #-}
|
||||
-- copyright (c) 2008 Duncan Coutts
|
||||
-- portions copyright (c) 2008 David Roundy
|
||||
-- portions copyright (c) 2007-2009 Judah Jacobson
|
||||
|
||||
-import qualified Distribution.InstalledPackageInfo as Installed
|
||||
import Distribution.Simple
|
||||
( defaultMainWithHooks, UserHooks(..), simpleUserHooks )
|
||||
-import Distribution.Simple.Configure
|
||||
- ( checkForeignDeps )
|
||||
import Distribution.ModuleName( toFilePath )
|
||||
import Distribution.PackageDescription
|
||||
- ( PackageDescription(executables, testSuites), Executable(buildInfo, exeName)
|
||||
- , BuildInfo(customFieldsBI), emptyBuildInfo
|
||||
+ ( PackageDescription(executables, testSuites), Executable(exeName)
|
||||
+ , emptyBuildInfo
|
||||
, TestSuite(testBuildInfo)
|
||||
- , FlagName(FlagName)
|
||||
, updatePackageDescription
|
||||
- , cppOptions, ccOptions, ldOptions
|
||||
- , library, libBuildInfo, otherModules
|
||||
- , extraLibs, extraLibDirs, includeDirs )
|
||||
+ , cppOptions, ccOptions
|
||||
+ , library, libBuildInfo, otherModules )
|
||||
import Distribution.Package
|
||||
- ( packageVersion, packageName, PackageName(..), Package )
|
||||
-import Distribution.Version
|
||||
- ( Version(Version, versionBranch) )
|
||||
-import Data.Version( showVersion )
|
||||
+ ( packageVersion )
|
||||
+import Distribution.Version( Version )
|
||||
import Distribution.Simple.LocalBuildInfo
|
||||
- ( LocalBuildInfo(..), absoluteInstallDirs, externalPackageDeps )
|
||||
+ ( LocalBuildInfo(..), absoluteInstallDirs )
|
||||
import Distribution.Simple.InstallDirs (mandir, CopyDest (NoCopyDest))
|
||||
-import Distribution.Simple.PackageIndex ( topologicalOrder )
|
||||
-import Distribution.Simple.Program ( gccProgram, rawSystemProgramStdoutConf )
|
||||
import Distribution.Simple.Setup
|
||||
(buildVerbosity, copyDest, copyVerbosity, fromFlag,
|
||||
- haddockVerbosity, installVerbosity, sDistVerbosity,
|
||||
- configVerbosity, ConfigFlags, configConfigurationsFlags)
|
||||
-import qualified Distribution.Simple.Setup as DSS -- to get replVerbosity in Cabal > 1.18
|
||||
-import Distribution.Simple.BuildPaths
|
||||
- ( autogenModulesDir, exeExtension )
|
||||
+ haddockVerbosity, installVerbosity, sDistVerbosity, replVerbosity )
|
||||
+import Distribution.Simple.BuildPaths ( autogenModulesDir )
|
||||
import Distribution.System
|
||||
( OS(Windows), buildOS )
|
||||
import Distribution.Simple.Utils
|
||||
(copyFiles, createDirectoryIfMissingVerbose, rawSystemStdout,
|
||||
- rewriteFile, withTempFile, cabalVersion)
|
||||
+ rewriteFile )
|
||||
import Distribution.Verbosity
|
||||
( Verbosity )
|
||||
import Distribution.Text
|
||||
( display )
|
||||
-import Control.Monad ( zipWithM_, when, unless, filterM )
|
||||
-import Control.Exception ( bracket, handle, IOException )
|
||||
+import Control.Monad ( unless, void )
|
||||
|
||||
-import Language.Haskell.TH ( mkName, newName, recUpdE, varE, appE, lamE, varP )
|
||||
-
|
||||
import System.Directory
|
||||
- (copyFile, createDirectory, createDirectoryIfMissing,
|
||||
- doesDirectoryExist, doesFileExist,
|
||||
- getCurrentDirectory, getDirectoryContents,
|
||||
- removeDirectoryRecursive, removeFile, setCurrentDirectory,
|
||||
- getTemporaryDirectory
|
||||
- )
|
||||
-import System.Exit ( ExitCode(ExitSuccess) )
|
||||
+ ( doesDirectoryExist, doesFileExist )
|
||||
import System.IO
|
||||
- ( openFile, IOMode (..), stdout
|
||||
- , hPutStr, hFlush, hClose
|
||||
- )
|
||||
+ ( openFile, IOMode(..) )
|
||||
import System.Process (runProcess)
|
||||
-import System.IO.Error ( isDoesNotExistError )
|
||||
-import Data.List( isPrefixOf, isSuffixOf, sort )
|
||||
-import System.Process( rawSystem )
|
||||
-import System.FilePath ( (</>), (<.>), splitDirectories, isAbsolute )
|
||||
+import System.FilePath ( (</>) )
|
||||
import Foreign.Marshal.Utils ( with )
|
||||
import Foreign.Storable ( peek )
|
||||
import Foreign.Ptr ( castPtr )
|
||||
@@ -75,33 +48,11 @@ import Data.Word ( Word8, Word32 )
|
||||
|
||||
import qualified Control.Exception as Exception
|
||||
|
||||
+catchAny :: IO a -> (Exception.SomeException -> IO a) -> IO a
|
||||
catchAny f h = Exception.catch f (\e -> h (e :: Exception.SomeException))
|
||||
|
||||
-{- Template Haskell hackery for replHook while we want to support Cabal < 1.18 -}
|
||||
-replVerbosity =
|
||||
- $(if cabalVersion >= Version [1,18,0] []
|
||||
- then varE (mkName "DSS.replVerbosity")
|
||||
- else [| error "This shouldn't be called" |]
|
||||
- )
|
||||
-
|
||||
-replHookBody replHookSel =
|
||||
- \pkg lbi hooks flags args ->
|
||||
- let verb = fromFlag $ replVerbosity flags
|
||||
- in commonBuildHook replHookSel pkg lbi hooks verb >>= (\f -> f flags args)
|
||||
-
|
||||
-addReplHook =
|
||||
- $(if cabalVersion >= Version [1,18,0] []
|
||||
- then
|
||||
- do hooks <- newName "hooks"
|
||||
- let replHook = mkName "replHook"
|
||||
- app <- appE (varE (mkName "replHookBody")) (varE replHook)
|
||||
- lamE [varP hooks] (recUpdE (varE hooks) [return (replHook, app)])
|
||||
- else [| \hooks -> hooks |]
|
||||
- )
|
||||
-{- End of Template Haskell hackery -}
|
||||
-
|
||||
main :: IO ()
|
||||
-main = defaultMainWithHooks $ addReplHook $ simpleUserHooks {
|
||||
+main = defaultMainWithHooks $ simpleUserHooks {
|
||||
|
||||
buildHook = \ pkg lbi hooks flags ->
|
||||
let verb = fromFlag $ buildVerbosity flags
|
||||
@@ -110,12 +61,9 @@ main = defaultMainWithHooks $ addReplHook $ simpleUser
|
||||
haddockHook = \ pkg lbi hooks flags ->
|
||||
let verb = fromFlag $ haddockVerbosity flags
|
||||
in commonBuildHook haddockHook pkg lbi hooks verb >>= ($ flags) ,
|
||||
-{-
|
||||
- -- this is the actual replHook code we want
|
||||
replHook = \pkg lbi hooks flags args ->
|
||||
let verb = fromFlag $ replVerbosity flags
|
||||
in commonBuildHook replHook pkg lbi hooks verb >>= (\f -> f flags args) ,
|
||||
--}
|
||||
postBuild = \ _ _ _ lbi -> buildManpage lbi,
|
||||
postCopy = \ _ flags pkg lbi ->
|
||||
installManpage pkg lbi (fromFlag $ copyVerbosity flags) (fromFlag $ copyDest flags),
|
||||
@@ -126,7 +74,7 @@ main = defaultMainWithHooks $ addReplHook $ simpleUser
|
||||
let pkgVer = packageVersion pkg
|
||||
verb = fromFlag $ sDistVerbosity flags
|
||||
x <- versionPatches verb pkgVer
|
||||
- y <- context verb pkgVer
|
||||
+ y <- context verb
|
||||
rewriteFile "release/distributed-version" $ show x
|
||||
rewriteFile "release/distributed-context" $ show y
|
||||
putStrLn "about to hand over"
|
||||
@@ -137,23 +85,6 @@ main = defaultMainWithHooks $ addReplHook $ simpleUser
|
||||
|
||||
sDistHook simpleUserHooks pkg' lbi hooks flags
|
||||
,
|
||||
- confHook =
|
||||
- if buildOS == Windows
|
||||
- then confHook simpleUserHooks
|
||||
- else
|
||||
- \genericDescript flags -> do
|
||||
- lbi <- confHook simpleUserHooks genericDescript flags
|
||||
- let pkgDescr = localPkgDescr lbi
|
||||
- let verb = fromFlag (configVerbosity flags)
|
||||
- checkForeignDeps pkgDescr lbi verb
|
||||
- let lib = maybe (error "darcs library was not configured - did it end up unbuildable?") id
|
||||
- (library pkgDescr)
|
||||
- let bi = libBuildInfo lib
|
||||
- bi' <- maybeSetLibiconv flags bi lbi
|
||||
- return lbi {localPkgDescr = pkgDescr {
|
||||
- library = Just lib {
|
||||
- libBuildInfo = bi'}}}
|
||||
- ,
|
||||
postConf = \_ _ _ _ -> return () --- Usually this checked for external C
|
||||
--- dependencies, but we already have performed such
|
||||
--- check in the confHook
|
||||
@@ -167,7 +98,7 @@ commonBuildHook runHook pkg lbi hooks verbosity = do
|
||||
(version, state) <- determineVersion verbosity pkg
|
||||
|
||||
-- Create our own context file.
|
||||
- generateVersionModule verbosity pkg lbi version state
|
||||
+ generateVersionModule verbosity lbi version state
|
||||
|
||||
-- Add custom -DFOO[=BAR] flags to the cpp (for .hs) and cc (for .c)
|
||||
-- invocations, doing a dance to make the base hook aware of them.
|
||||
@@ -184,16 +115,14 @@ commonBuildHook runHook pkg lbi hooks verbosity = do
|
||||
|
||||
-- updatePackageDescription doesn't handle test suites so we
|
||||
-- need to do this manually
|
||||
- updateTestSuiteBI bi testSuite
|
||||
- = testSuite { testBuildInfo = bi `mappend` testBuildInfo testSuite }
|
||||
+ updateTestSuiteBI bi' testSuite
|
||||
+ = testSuite { testBuildInfo = bi' `mappend` testBuildInfo testSuite }
|
||||
pkg'' = pkg' { testSuites = map (updateTestSuiteBI bi) (testSuites pkg') }
|
||||
|
||||
lbi' = lbi { localPkgDescr = pkg'' }
|
||||
return $ runHook simpleUserHooks pkg'' lbi' hooks
|
||||
|
||||
where
|
||||
- customFields = map fst . customFieldsBI . buildInfo $ darcsExe
|
||||
- darcsExe = head [e | e <- executables pkg, exeName e == "darcs"]
|
||||
show' :: String -> String -- Petr was worried that we might
|
||||
show' = show -- allow non-String arguments.
|
||||
testEndianness :: IO Bool
|
||||
@@ -209,9 +138,8 @@ buildManpage lbi = do
|
||||
let darcs = buildDir lbi </> "darcs/darcs"
|
||||
manpage = buildDir lbi </> "darcs/darcs.1"
|
||||
manpageHandle <- openFile manpage WriteMode
|
||||
- runProcess darcs ["help","manpage"]
|
||||
+ void $ runProcess darcs ["help","manpage"]
|
||||
Nothing Nothing Nothing (Just manpageHandle) Nothing
|
||||
- return ()
|
||||
|
||||
installManpage :: PackageDescription -> LocalBuildInfo
|
||||
-> Verbosity -> CopyDest -> IO ()
|
||||
@@ -228,29 +156,21 @@ determineVersion :: Verbosity -> PackageDescription ->
|
||||
determineVersion verbosity pkg = do
|
||||
let darcsVersion = packageVersion pkg
|
||||
numPatches <- versionPatches verbosity darcsVersion
|
||||
- return (display darcsVersion, versionStateString numPatches darcsVersion)
|
||||
+ return (display darcsVersion, versionStateString numPatches)
|
||||
|
||||
where
|
||||
- versionStateString :: Maybe Int -> Version -> String
|
||||
- versionStateString Nothing _ = "unknown"
|
||||
- versionStateString (Just 0) v = case versionBranch v of
|
||||
- x | 97 `elem` x -> "alpha " ++ show (after 97 x)
|
||||
- | 98 `elem` x -> "beta " ++ show (after 98 x)
|
||||
- | 99 `elem` x ->
|
||||
- "release candidate " ++ show (after 99 x)
|
||||
- _ -> "release"
|
||||
- versionStateString (Just 1) _ = "+ 1 patch"
|
||||
- versionStateString (Just n) _ = "+ " ++ show n ++ " patches"
|
||||
- after w (x:r) | w == x = head r
|
||||
- | otherwise = after w r
|
||||
- after _ [] = undefined
|
||||
+ versionStateString :: Maybe Int -> String
|
||||
+ versionStateString Nothing = "unknown"
|
||||
+ versionStateString (Just 0) = "release"
|
||||
+ versionStateString (Just 1) = "+ 1 patch"
|
||||
+ versionStateString (Just n) = "+ " ++ show n ++ " patches"
|
||||
|
||||
versionPatches :: Verbosity -> Version -> IO (Maybe Int)
|
||||
versionPatches verbosity darcsVersion = do
|
||||
numPatchesDarcs <- do
|
||||
out <- rawSystemStdout verbosity "darcs"
|
||||
["log", "-a", "--from-tag", display darcsVersion, "--count"]
|
||||
- case reads (out) of
|
||||
+ case reads out of
|
||||
((n,_):_) -> return $ Just ((n :: Int) - 1)
|
||||
_ -> return Nothing
|
||||
`catchAny` \_ -> return Nothing
|
||||
@@ -264,26 +184,23 @@ versionPatches verbosity darcsVersion = do
|
||||
where
|
||||
versionFile = "release/distributed-version"
|
||||
|
||||
-generateVersionModule :: Verbosity -> PackageDescription -> LocalBuildInfo
|
||||
+generateVersionModule :: Verbosity -> LocalBuildInfo
|
||||
-> String -> String -> IO ()
|
||||
-generateVersionModule verbosity pkg lbi version state = do
|
||||
+generateVersionModule verbosity lbi version state = do
|
||||
let dir = autogenModulesDir lbi
|
||||
createDirectoryIfMissingVerbose verbosity True dir
|
||||
- ctx <- context verbosity (packageVersion pkg)
|
||||
+ ctx <- context verbosity
|
||||
rewriteFile (dir </> "Version.hs") $ unlines
|
||||
["module Version where"
|
||||
- ,"builddeps, version, context :: String"
|
||||
+ ,"version, context :: String"
|
||||
,"version = \"" ++ version ++ " (" ++ state ++ ")\""
|
||||
- ,"builddeps = " ++ show ( formatdeps (externalPackageDeps lbi))
|
||||
,"context = " ++ case ctx of
|
||||
Just x -> show x
|
||||
Nothing -> show "context not available"
|
||||
]
|
||||
- where formatdeps = unlines . map (formatone . snd)
|
||||
- formatone p = case packageName p of PackageName n -> n ++ "-" ++ showVersion (packageVersion p)
|
||||
|
||||
-context :: Verbosity -> Version -> IO (Maybe String)
|
||||
-context verbosity version = do
|
||||
+context :: Verbosity -> IO (Maybe String)
|
||||
+context verbosity = do
|
||||
contextDarcs <- do
|
||||
inrepo <- doesDirectoryExist "_darcs"
|
||||
unless inrepo $ fail "Not a repository."
|
||||
@@ -307,76 +224,5 @@ parseFile f = do
|
||||
((s,_):_) -> return s
|
||||
_ -> return Nothing
|
||||
else return Nothing
|
||||
-
|
||||
--- Test whether compiling a c program that links against libiconv needs -liconv.
|
||||
-maybeSetLibiconv :: ConfigFlags -> BuildInfo -> LocalBuildInfo -> IO BuildInfo
|
||||
-maybeSetLibiconv flags bi lbi = do
|
||||
- let biWithIconv = addIconv bi
|
||||
- let verb = fromFlag (configVerbosity flags)
|
||||
- if hasFlagSet flags (FlagName "libiconv")
|
||||
- then do
|
||||
- putStrLn "Using -liconv."
|
||||
- return biWithIconv
|
||||
- else do
|
||||
- putStr "checking whether to use -liconv... "
|
||||
- hFlush stdout
|
||||
- worksWithout <- tryCompile iconv_prog bi lbi verb
|
||||
- if worksWithout
|
||||
- then do
|
||||
- putStrLn "not needed."
|
||||
- return bi
|
||||
- else do
|
||||
- worksWith <- tryCompile iconv_prog biWithIconv lbi verb
|
||||
- if worksWith
|
||||
- then do
|
||||
- putStrLn "using -liconv."
|
||||
- return biWithIconv
|
||||
- else error "Unable to link against the iconv library."
|
||||
-
|
||||
-hasFlagSet :: ConfigFlags -> FlagName -> Bool
|
||||
-hasFlagSet cflags flag = Just True == lookup flag (configConfigurationsFlags cflags)
|
||||
-
|
||||
-tryCompile :: String -> BuildInfo -> LocalBuildInfo -> Verbosity -> IO Bool
|
||||
-tryCompile program bi lbi verb = handle processExit $ handle processException $ do
|
||||
- tempDir <- getTemporaryDirectory
|
||||
- withTempFile tempDir ".c" $ \fname cH ->
|
||||
- withTempFile tempDir "" $ \execName oH -> do
|
||||
- hPutStr cH program
|
||||
- hClose cH
|
||||
- hClose oH
|
||||
- -- TODO take verbosity from the args.
|
||||
- rawSystemProgramStdoutConf verb gccProgram (withPrograms lbi)
|
||||
- (fname : "-o" : execName : args)
|
||||
- return True
|
||||
- where
|
||||
- processException :: IOException -> IO Bool
|
||||
- processException e = return False
|
||||
- processExit = return . (==ExitSuccess)
|
||||
- -- Mimicing Distribution.Simple.Configure
|
||||
- deps = topologicalOrder (installedPkgs lbi)
|
||||
- args = concat
|
||||
- [ ccOptions bi
|
||||
- , cppOptions bi
|
||||
- , ldOptions bi
|
||||
- -- --extra-include-dirs and --extra-lib-dirs are included
|
||||
- -- in the below fields.
|
||||
- -- Also sometimes a dependency like rts points to a nonstandard
|
||||
- -- include/lib directory where iconv can be found.
|
||||
- , map ("-I" ++) (includeDirs bi ++ concatMap Installed.includeDirs deps)
|
||||
- , map ("-L" ++) (extraLibDirs bi ++ concatMap Installed.libraryDirs deps)
|
||||
- , map ("-l" ++) (extraLibs bi)
|
||||
- ]
|
||||
-
|
||||
-addIconv :: BuildInfo -> BuildInfo
|
||||
-addIconv bi = bi {extraLibs = "iconv" : extraLibs bi}
|
||||
-
|
||||
-iconv_prog :: String
|
||||
-iconv_prog = unlines
|
||||
- [ "#include <iconv.h>"
|
||||
- , "int main(void) {"
|
||||
- , " iconv_t t = iconv_open(\"UTF-8\", \"UTF-8\");"
|
||||
- , " return 0;"
|
||||
- , "}"
|
||||
- ]
|
||||
|
||||
\end{code}
|
49
devel/darcs/patches/patch-darcs_cabal
Normal file
49
devel/darcs/patches/patch-darcs_cabal
Normal file
@ -0,0 +1,49 @@
|
||||
$OpenBSD: patch-darcs_cabal,v 1.10 2018/01/08 10:18:39 kili Exp $
|
||||
|
||||
Let it build with newer versions of libraries shipped with ghc-8.2.
|
||||
|
||||
Index: darcs.cabal
|
||||
--- darcs.cabal.orig
|
||||
+++ darcs.cabal
|
||||
@@ -388,7 +388,7 @@ Library
|
||||
c-sources: src/h_iconv.c
|
||||
build-depends: unix >= 2.6.0.1 && < 2.8
|
||||
|
||||
- build-depends: base >= 4.8 && < 4.10,
|
||||
+ build-depends: base >= 4.8 && < 4.12,
|
||||
binary >= 0.5 && < 0.9,
|
||||
containers >= 0.5 && < 0.6,
|
||||
regex-compat-tdfa >= 0.95.1 && < 0.96,
|
||||
@@ -417,12 +417,12 @@ Library
|
||||
unix-compat >= 0.1.2 && < 0.5,
|
||||
bytestring >= 0.10.0.2 && < 0.11,
|
||||
old-time >= 1.1 && < 1.2,
|
||||
- time >= 1.5 && < 1.8,
|
||||
+ time >= 1.5 && < 1.9,
|
||||
-- release notes of GHC 7.10.2 recommends to use text >= 1.2.1.3:
|
||||
-- https://mail.haskell.org/pipermail/haskell/2015-July/024641.html
|
||||
text >= 1.2.1.3 && < 1.3,
|
||||
directory >= 1.2.0.1 && < 1.4.0.0,
|
||||
- process >= 1.1.0.2 && < 1.5.0.0,
|
||||
+ process >= 1.1.0.2 && < 1.7.0.0,
|
||||
array >= 0.4.0.1 && < 0.6,
|
||||
random >= 1.0.1.1 && < 1.2,
|
||||
hashable >= 1.1.2.5 && < 1.3,
|
||||
@@ -529,7 +529,7 @@ Executable darcs
|
||||
cc-options: -D_REENTRANT
|
||||
|
||||
build-depends: darcs,
|
||||
- base >= 4.8 && < 4.10
|
||||
+ base >= 4.8 && < 4.12
|
||||
|
||||
-- if true to work around cabal bug with flag ordering
|
||||
if true
|
||||
@@ -562,7 +562,7 @@ test-suite darcs-test
|
||||
build-depends: Win32 >= 2.2 && < 2.4
|
||||
|
||||
build-depends: darcs,
|
||||
- base >= 4.8 && < 4.10,
|
||||
+ base >= 4.8 && < 4.12,
|
||||
array >= 0.4.0.1 && < 0.6,
|
||||
bytestring >= 0.10.0.2 && < 0.11,
|
||||
cmdargs >= 0.10 && < 0.11,
|
25
devel/darcs/patches/patch-darcs_darcs_hs
Normal file
25
devel/darcs/patches/patch-darcs_darcs_hs
Normal file
@ -0,0 +1,25 @@
|
||||
$OpenBSD: patch-darcs_darcs_hs,v 1.1 2018/01/08 10:18:39 kili Exp $
|
||||
|
||||
Let it build with newer versions of cabal.
|
||||
|
||||
From upstream commit 5f23ab60917a36be31d2edc7c0e0c38f3fe15de7.
|
||||
|
||||
Index: darcs/darcs.hs
|
||||
--- darcs/darcs.hs.orig
|
||||
+++ darcs/darcs.hs
|
||||
@@ -45,7 +45,7 @@ import Darcs.Util.ByteString ( decodeString )
|
||||
import Darcs.UI.External ( setDarcsEncodings )
|
||||
import Darcs.Util.Exec ( ExecException(..) )
|
||||
import Darcs.Util.Path ( getCurrentDirectory )
|
||||
-import Version ( version, context, builddeps )
|
||||
+import Version ( version, context )
|
||||
|
||||
#include "impossible.h"
|
||||
|
||||
@@ -84,6 +84,4 @@ main = withAtexit . withSignalsHandled . handleExecFai
|
||||
printExactVersion = do
|
||||
putStrLn $ "darcs compiled on " ++ __DATE__ ++ ", at " ++ __TIME__
|
||||
putStrLn context
|
||||
- putStrLn "Compiled with:\n"
|
||||
- putStr builddeps
|
||||
|
Loading…
Reference in New Issue
Block a user