Skip to content

Commit

Permalink
screened 2024-06-03 12:40:52+00:00
Browse files Browse the repository at this point in the history
  • Loading branch information
hsenag committed Jun 3, 2024
1 parent 6f54090 commit ddb7231
Show file tree
Hide file tree
Showing 10 changed files with 47 additions and 10 deletions.
2 changes: 2 additions & 0 deletions .github/workflows/build-and-test.yml
Original file line number Diff line number Diff line change
Expand Up @@ -18,6 +18,8 @@ jobs:
# - windows-2019
- windows-2022
ghc:
- 8.4.4
- 8.6.5
- 8.8.2
- 8.10.7
- 9.0.2
Expand Down
2 changes: 1 addition & 1 deletion README.md
Original file line number Diff line number Diff line change
Expand Up @@ -14,7 +14,7 @@ cabal update && cabal install darcs
```

with a recent cabal (version 3.2 or later is recommended). Any version of
ghc from 8.8 up to 9.8 should work.
ghc from 8.2 up to 9.8 should work.

From inside a clone or a source dist, use

Expand Down
4 changes: 2 additions & 2 deletions darcs.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -123,7 +123,7 @@ flag warn-as-error
-- ----------------------------------------------------------------------

custom-setup
setup-depends: base >= 4.13 && < 4.20,
setup-depends: base >= 4.10 && < 4.20,
Cabal >= 2.4 && < 3.11,
process >= 1.2.3.0 && < 1.7,
filepath >= 1.4.1 && < 1.5.0.0,
Expand Down Expand Up @@ -412,7 +412,7 @@ Library
else
build-depends: unix >= 2.7.1.0 && < 2.9

build-depends: base >= 4.13 && < 4.20,
build-depends: base >= 4.10 && < 4.20,
safe >= 0.3.20 && < 0.4,
stm >= 2.1 && < 2.6,
binary >= 0.5 && < 0.11,
Expand Down
6 changes: 6 additions & 0 deletions harness/Darcs/Test/Patch/Examples/Unwind.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,6 +8,7 @@
{-# LANGUAGE NoMonomorphismRestriction #-}
{-# LANGUAGE PartialTypeSignatures #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE CPP #-}
module Darcs.Test.Patch.Examples.Unwind where

import Darcs.Prelude
Expand Down Expand Up @@ -37,6 +38,9 @@ import Darcs.Test.Patch.V1Model
import Darcs.Test.Patch.WithState
import Darcs.Test.TestOnly.Instance ()

#if MIN_VERSION_base(4,12,0) && !MIN_VERSION_base(4,13,0)
import Control.Monad.Fail
#endif
import Data.ByteString.Char8 ( pack )
import qualified Data.ByteString.Lazy.Char8 as BLC
import Data.Constraint
Expand Down Expand Up @@ -236,7 +240,9 @@ instance Applicative ErrorFail where
liftA2 f (ErrorFail v1) (ErrorFail v2) = ErrorFail (f v1 v2)
instance Monad ErrorFail where
ErrorFail v >>= f = f v
#if MIN_VERSION_base(4,12,0)
instance MonadFail ErrorFail where
#endif
fail = error

-- For now this code isn't used, it just demonstrates how example4 is broken in V1
Expand Down
4 changes: 4 additions & 0 deletions shelly/src/Shelly.hs
Original file line number Diff line number Diff line change
Expand Up @@ -124,6 +124,10 @@ import qualified Data.Text as T
import qualified Data.ByteString as BS
import Data.ByteString (ByteString)

#if !MIN_VERSION_base(4,13,0)
import Data.Monoid (mempty, mappend, (<>))
#endif

import Filesystem.Path.CurrentOS hiding (concat, fromText, (</>), (<.>))
import Filesystem hiding (canonicalizePath)
import qualified Filesystem.Path.CurrentOS as FP
Expand Down
8 changes: 8 additions & 0 deletions shelly/src/Shelly/Base.hs
Original file line number Diff line number Diff line change
Expand Up @@ -40,12 +40,18 @@ import System.IO ( Handle, hFlush, stderr, stdout )
import Control.Monad (when, (>=>))
import Control.Monad.Base
import Control.Monad.Trans.Control
#if !MIN_VERSION_base(4,13,0)
import Control.Applicative (Applicative, (<$>))
#endif
import Filesystem (isDirectory, listDirectory)
import System.PosixCompat.Files( getSymbolicLinkStatus, isSymbolicLink )
import Filesystem.Path.CurrentOS (FilePath, encodeString, relative)
import qualified Filesystem.Path.CurrentOS as FP
import qualified Filesystem as FS
import Data.IORef (readIORef, modifyIORef, IORef)
#if !MIN_VERSION_base(4,13,0)
import Data.Monoid (mappend)
#endif
import qualified Data.Text as T
import qualified Data.Text.IO as TIO
import Control.Exception (SomeException, catch, throwIO, Exception)
Expand All @@ -65,8 +71,10 @@ newtype Sh a = Sh {
unSh :: ReaderT (IORef State) IO a
} deriving (Applicative, Monad, MonadIO, MonadReader (IORef State), Functor, Catch.MonadMask)

#if MIN_VERSION_base(4,13,0)
instance MonadFail Sh where
fail = liftIO . fail
#endif

instance MonadBase IO Sh where
liftBase = Sh . ReaderT . const
Expand Down
4 changes: 4 additions & 0 deletions shelly/src/Shelly/Find.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
-- | File finding utiliites for Shelly
-- The basic 'find' takes a dir and gives back a list of files.
Expand All @@ -11,6 +12,9 @@ module Shelly.Find
import Prelude hiding (FilePath)
import Shelly.Base
import Control.Monad (foldM)
#if !MIN_VERSION_base(4,13,0)
import Data.Monoid (mappend)
#endif
import System.PosixCompat.Files( getSymbolicLinkStatus, isSymbolicLink )
import Filesystem (isDirectory)
import Filesystem.Path.CurrentOS (encodeString)
Expand Down
7 changes: 7 additions & 0 deletions src/Darcs/Prelude.hs
Original file line number Diff line number Diff line change
Expand Up @@ -27,6 +27,7 @@ module Darcs.Prelude
( module Prelude
, module Control.Applicative
, module Data.Monoid
, Semigroup(..)
, module Data.Traversable
) where

Expand All @@ -41,6 +42,11 @@ import Prelude hiding
,
-- because it's in the new Prelude but only in Data.Monoid in older GHCs
Monoid(..)
#if MIN_VERSION_base(4,11,0)
,
-- because it's in the new Prelude but only in Data.Semigroup in older GHCs
Semigroup(..)
#endif
,
-- because it's in the new Prelude but only in Data.Traversable in older GHCs
traverse
Expand All @@ -57,4 +63,5 @@ import Prelude hiding

import Control.Applicative ( Applicative(..), (<$>), (<*>) )
import Data.Monoid ( Monoid(..) )
import Data.Semigroup ( Semigroup(..) )
import Data.Traversable ( traverse )
13 changes: 13 additions & 0 deletions src/Darcs/Util/Regex.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
-- | This module is a subset of the defunct regex-compat-tdfa.
{-# LANGUAGE CPP #-}
module Darcs.Util.Regex
( Regex
, mkRegex
Expand All @@ -9,6 +10,9 @@ module Darcs.Util.Regex
import Darcs.Prelude

import Control.Exception ( throw )
#if !MIN_VERSION_base(4,13,0)
import Control.Monad.Fail
#endif
import Text.Regex.Base
( RegexContext(matchM)
, RegexMaker(makeRegexOptsM)
Expand All @@ -23,7 +27,16 @@ newtype RegexFail a = RegexFail { runRegexFail :: Either String a }
-- The subtlety here is that only in base-4.13.0 the fail method
-- in class Monad was removed. For earlier versions, regex-tdfa
-- calls the fail from class Monad, not the one from class MonadFail.
#if MIN_VERSION_base(4,13,0)
deriving (Functor, Applicative, Monad)
#else
deriving (Functor, Applicative)

instance Monad RegexFail where
RegexFail (Left e) >>= _ = RegexFail (Left e)
RegexFail (Right r) >>= k = k r
fail = RegexFail . Left
#endif

instance MonadFail RegexFail where
fail = RegexFail . Left
Expand Down
7 changes: 0 additions & 7 deletions tests/issue2333.sh
Original file line number Diff line number Diff line change
Expand Up @@ -3,13 +3,6 @@

. lib # Load some portability helpers.

require_ghc 706

# work around issue2720 (MacOS)
if test -x /usr/bin/security; then
ln -s /usr/bin/security .
fi

darcs init --repo R # Create our test repos.
darcs init --repo S

Expand Down

0 comments on commit ddb7231

Please sign in to comment.