Skip to content

Commit

Permalink
screened 2024-06-02 00:16:16+00:00
Browse files Browse the repository at this point in the history
  • Loading branch information
hsenag committed Jun 2, 2024
1 parent d8aa4f7 commit 7b77f32
Show file tree
Hide file tree
Showing 434 changed files with 864 additions and 927 deletions.
26 changes: 26 additions & 0 deletions CHANGELOG → CHANGELOG.md
Original file line number Diff line number Diff line change
@@ -1,3 +1,29 @@
Darcs 2.18.3, 26 May 2024

* relax upper bounds for some dependencies

* with GHC up to 9.8 all tests now succeed (including Windows and MacOS)

* resolve issue2714: cannot remove recursively

* resolve issue2715: hub.darcs.net does not support "Extended Main Secret"

We use a new addition to crypton-connection in order to change the default
setting back to old (tls < 2.0) default.

* resolve issue2721 by excluding certain versions of directory package

Versions 1.3.8 up to 1.3.8.4 of the directory package have a bug in their
implementation of copyFile on Windows.

* work around issue2720 (caused by x509-system indirect dependency, see
(see https://github.com/kazu-yamamoto/crypton-certificate/issues/9)

* make execution of release/gen-version-info.hs more robust

Using cabal run instead of runghc inside of Setup.hs ensures that we use the
same ghc version that cabal uses, avoiding dependency errors.

Darcs 2.18.2, 24 Mar 2024

* Fix deprecated head/tail warnings on GHC 9.8, making the build there
Expand Down
Empty file modified contrib/buildbot-try.sh
100755 → 100644
Empty file.
Empty file modified contrib/checkdeps.sh
100755 → 100644
Empty file.
Empty file modified contrib/cygwin-wrapper.bash
100755 → 100644
Empty file.
Empty file modified contrib/darcs-shell
100755 → 100644
Empty file.
Empty file modified contrib/darcshoogle
100755 → 100644
Empty file.
Empty file modified contrib/runHLint.sh
100755 → 100644
Empty file.
Empty file modified contrib/update_roundup.pl
100755 → 100644
Empty file.
Empty file modified contrib/upload.cgi
100755 → 100644
Empty file.
14 changes: 6 additions & 8 deletions darcs.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -84,7 +84,7 @@ extra-source-files:
GNUmakefile

extra-doc-files:
CHANGELOG
CHANGELOG.md

source-repository head
type: darcs
Expand Down Expand Up @@ -123,7 +123,7 @@ flag warn-as-error
-- ----------------------------------------------------------------------

custom-setup
setup-depends: base >= 4.10 && < 4.20,
setup-depends: base >= 4.10 && < 4.21,
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.10 && < 4.20,
build-depends: base >= 4.10 && < 4.21,
safe >= 0.3.20 && < 0.4,
stm >= 2.1 && < 2.6,
binary >= 0.5 && < 0.11,
Expand Down Expand Up @@ -619,25 +619,23 @@ test-suite darcs-test
Darcs.Test.Patch.Check
Darcs.Test.Patch.Depends
Darcs.Test.Patch.Examples.Set1
Darcs.Test.Patch.Examples.Set2Unwitnessed
Darcs.Test.Patch.Examples.Set2
Darcs.Test.Patch.Examples.Unwind
Darcs.Test.Patch.WSub
Darcs.Test.Patch.Info
Darcs.Test.Patch.Properties
Darcs.Test.Patch.Properties.V1Set1
Darcs.Test.Patch.Properties.V1Set2
Darcs.Test.Patch.Properties.Generic
Darcs.Test.Patch.Properties.GenericUnwitnessed
Darcs.Test.Patch.Properties.Check
Darcs.Test.Patch.Properties.RepoPatch
Darcs.Test.Patch.Properties.Mergeable
Darcs.Test.Patch.Properties.RepoPatchV3
Darcs.Test.Patch.Arbitrary.Generic
Darcs.Test.Patch.Arbitrary.Named
Darcs.Test.Patch.Arbitrary.NamedPrim
Darcs.Test.Patch.Arbitrary.PatchTree
Darcs.Test.Patch.Arbitrary.PrimFileUUID
Darcs.Test.Patch.Arbitrary.PrimV1
Darcs.Test.Patch.Arbitrary.RepoPatch
Darcs.Test.Patch.Arbitrary.Mergeable
Darcs.Test.Patch.Arbitrary.RepoPatchV1
Darcs.Test.Patch.Arbitrary.RepoPatchV2
Darcs.Test.Patch.Arbitrary.RepoPatchV3
Expand Down
12 changes: 10 additions & 2 deletions harness/Darcs/Test/Patch.hs
Original file line number Diff line number Diff line change
Expand Up @@ -30,11 +30,12 @@ import Darcs.Patch.V1 ( RepoPatchV1 )
import Darcs.Patch.V2.RepoPatch ( RepoPatchV2 )
import Darcs.Patch.V3 ( RepoPatchV3 )
import Darcs.Patch.Commute ( Commute(..) )
import qualified Darcs.Patch.RepoPatch as RP

import Darcs.Test.Patch.Arbitrary.Generic
import Darcs.Test.Patch.Arbitrary.Named ()
import Darcs.Test.Patch.Arbitrary.PrimFileUUID()
import Darcs.Test.Patch.Arbitrary.RepoPatch
import Darcs.Test.Patch.Arbitrary.Mergeable
import Darcs.Test.Patch.Arbitrary.RepoPatchV1 ()
import Darcs.Test.Patch.Arbitrary.RepoPatchV2 ()
import Darcs.Test.Patch.Arbitrary.RepoPatchV3 ()
Expand All @@ -58,10 +59,12 @@ type Prim2 = V2.Prim
-- tests (either QuickCheck or Unit) that should be run on any type of patch
general_patchTests
:: forall p
. ( ArbitraryRepoPatch p, CheckedMerge p
. ( ArbitraryMergeable p, CheckedMerge p
, RP.RepoPatch p
, PrimBased p, Commute (OnlyPrim p), ArbitraryPrim (OnlyPrim p)
, ShrinkModel (PrimOf p)
, Show1 (ModelOf (PrimOf p)), Show2 p
, RepoApply (PrimOf p)
)
=> [Test]
general_patchTests =
Expand All @@ -76,6 +79,7 @@ testSuite =
, repoPatchV1Tests
, repoPatchV2Tests
, repoPatchV3Tests
, namedPatchV3Tests
, Darcs.Test.Patch.Depends.testSuite
, Darcs.Test.Patch.Info.testSuite
, Darcs.Test.Patch.Selection.testSuite
Expand Down Expand Up @@ -109,3 +113,7 @@ testSuite =
qc_V3 (undefined :: FileUUID.Prim wX wY) ++
general_patchTests @(RepoPatchV3 FileUUID.Prim)
]
namedPatchV3Tests = testGroup "Named RepoPatchV3"
[ testGroup "using V2.Prim wrapper for Prim.V1" $
qc_Named_V3 (undefined :: Prim2 wX wY)
]
5 changes: 2 additions & 3 deletions harness/Darcs/Test/Patch/Arbitrary/Generic.hs
Original file line number Diff line number Diff line change
Expand Up @@ -28,7 +28,7 @@ import Darcs.Patch.Witnesses.Ordered
import Darcs.Patch.Apply ( Apply, ApplyState )
import Darcs.Patch.Effect ( Effect(..) )
import Darcs.Patch.Format ( PatchListFormat )
import Darcs.Patch.Merge ( Merge(..) )
import Darcs.Patch.Merge ( CleanMerge, Merge(..) )
import Darcs.Patch.Invert ( Invert(..) )
import Darcs.Patch.Commute ( Commute(..) )
import Darcs.Patch.FromPrim ( PrimOf )
Expand Down Expand Up @@ -125,7 +125,7 @@ type ShrinkPrim prim =
)

type TestablePrim prim =
( Apply prim, Commute prim, Invert prim, Eq2 prim
( Apply prim, CleanMerge prim, Commute prim, Invert prim, Eq2 prim, Show2 prim
, PatchListFormat prim, ShowPatchBasic prim, ReadPatch prim
, RepoModel (ModelOf prim), ApplyState prim ~ RepoState (ModelOf prim)
, ArbitraryPrim prim
Expand All @@ -147,4 +147,3 @@ instance (Commute (OnlyPrim p), PrimBased p) => PrimBased (FL p) where
type OnlyPrim (FL p) = FL (OnlyPrim p)
primEffect = concatFL . mapFL_FL (primEffect @p)
liftFromPrim = mapFL_FL liftFromPrim

Original file line number Diff line number Diff line change
@@ -1,14 +1,14 @@
{-# LANGUAGE UndecidableInstances, ViewPatterns #-}
-- | Test case generator for patch with a Merge instance
module Darcs.Test.Patch.Arbitrary.RepoPatch
module Darcs.Test.Patch.Arbitrary.Mergeable
( withSingle
, withPair
, withTriple
, withFork
, withSequence
, withAllSequenceItems
, NotRepoPatchV1(..)
, ArbitraryRepoPatch(..)
, ArbitraryMergeable(..)
) where

import Darcs.Prelude
Expand All @@ -23,7 +23,6 @@ import Darcs.Patch.Witnesses.Sealed
import Darcs.Patch.Witnesses.Ordered hiding ( Fork )
import Darcs.Patch.Apply ( Apply(..) )
import Darcs.Patch.FromPrim ( PrimOf )
import Darcs.Patch.RepoPatch ( RepoPatch )
import Darcs.Patch.V1 ( RepoPatchV1 )

import Data.Constraint
Expand All @@ -33,11 +32,10 @@ data NotRepoPatchV1 p = NotRepoPatchV1 (forall prim . Dict (p ~ RepoPatchV1 prim

-- | Class to simplify type signatures and superclass constraints.
class
( RepoPatch p
, ArbitraryPrim (PrimOf p)
( ArbitraryPrim (PrimOf p)
, ModelOf p ~ ModelOf (PrimOf p)
, ApplyState p ~ RepoState (ModelOf p)
) => ArbitraryRepoPatch p where
) => ArbitraryMergeable p where

notRepoPatchV1 :: Maybe (NotRepoPatchV1 p)

Expand Down
13 changes: 9 additions & 4 deletions harness/Darcs/Test/Patch/Arbitrary/Named.hs
Original file line number Diff line number Diff line change
Expand Up @@ -12,6 +12,7 @@ import Darcs.Test.Patch.Arbitrary.Shrink
import Darcs.Test.Patch.RepoModel
import Darcs.Test.Patch.WithState

import Darcs.Patch.Apply
import Darcs.Patch.Commute
import Darcs.Patch.Named
import Darcs.Patch.Witnesses.Maybe
Expand All @@ -21,13 +22,14 @@ import Darcs.Patch.Witnesses.Sealed
import Control.Applicative ( (<|>) )
import Test.QuickCheck

type instance ModelOf (Named prim) = ModelOf prim
type instance ModelOf (Named p) = ModelOf p

instance ArbitraryState prim => ArbitraryState (Named prim) where
instance (ArbitraryState p, RepoModel (ModelOf p)) => ArbitraryState (Named p) where
arbitraryState rm = do
info <- arbitrary
deps <- sublistOf (appliedPatchNames rm)
Sealed (WithEndState prims rm') <- arbitraryState rm
return $ Sealed $ WithEndState (NamedP info [] prims) rm'
return $ Sealed $ WithEndState (NamedP info deps prims) rm'

instance (Commute p, Shrinkable p) => Shrinkable (Named p) where
shrinkInternally (NamedP pi deps ps) =
Expand All @@ -45,8 +47,11 @@ instance PropagateShrink prim p => PropagateShrink prim (Named p) where
mps' :> mprim' <- propagateShrink (prim :> ps)
return (mapMB_MB (NamedP pi deps) mps' :> mprim')

instance (Commute (OnlyPrim p), PrimBased p) => PrimBased (Named p) where
instance (Commute (OnlyPrim p), PrimBased p, RepoModel (ModelOf (OnlyPrim p))) => PrimBased (Named p) where
type OnlyPrim (Named p) = Named (OnlyPrim p)

primEffect (NamedP _ _ ps) = primEffect @(FL p) ps
liftFromPrim (NamedP pi deps ps) = NamedP pi deps (liftFromPrim ps)

instance Apply p => RepoApply (Named p) where
patchNames p = [patch2patchinfo p]
2 changes: 2 additions & 0 deletions harness/Darcs/Test/Patch/Arbitrary/PrimFileUUID.hs
Original file line number Diff line number Diff line change
Expand Up @@ -55,6 +55,8 @@ instance ShrinkModel Prim where
-- no shrinking for now
shrinkModelPatch _ = []

instance RepoApply Prim

----------------------------------------------------------------------
-- * QuickCheck generators

Expand Down
11 changes: 9 additions & 2 deletions harness/Darcs/Test/Patch/Arbitrary/PrimV1.hs
Original file line number Diff line number Diff line change
Expand Up @@ -82,6 +82,9 @@ instance Shrinkable Prim.Prim where
deriving instance Shrinkable V1.Prim
deriving instance Shrinkable V2.Prim

instance RepoApply Prim1
instance RepoApply Prim2

----------------------------------------------------------------------
-- * QuickCheck generators

Expand Down Expand Up @@ -236,8 +239,11 @@ aModelShrinkFileContent repo = do


-- | Generates any type of 'prim' patch, except binary and setpref patches.
aPrim :: forall prim wX . (PrimPatch prim, ApplyState prim ~ RepoState V1Model)
=> V1Model wX -> Gen (Sealed (WithEndState V1Model (prim wX)))
aPrim
:: forall prim wX
. (PrimPatch prim, ApplyState prim ~ RepoState V1Model, RepoApply prim)
=> V1Model wX
-> Gen (Sealed (WithEndState V1Model (prim wX)))
aPrim repo
= do mbFile <- maybeOf repoFiles
mbEmptyFile <- maybeOf $ filter (isEmpty . snd) repoFiles
Expand Down Expand Up @@ -306,6 +312,7 @@ aPrimPair :: ( PrimPatch prim
, ArbitraryState prim
, ApplyState prim ~ RepoState V1Model
, ModelOf prim ~ V1Model
, RepoApply prim
)
=> V1Model wX
-> Gen (Sealed (WithEndState V1Model (Pair prim wX)))
Expand Down
4 changes: 2 additions & 2 deletions harness/Darcs/Test/Patch/Arbitrary/RepoPatchV1.hs
Original file line number Diff line number Diff line change
Expand Up @@ -34,7 +34,7 @@ import Darcs.Patch.Witnesses.Sealed ( Sealed(Sealed) )


import Darcs.Test.Patch.Arbitrary.Generic ( MightHaveDuplicate, ArbitraryPrim, PrimBased(..) )
import Darcs.Test.Patch.Arbitrary.RepoPatch
import Darcs.Test.Patch.Arbitrary.Mergeable
import Darcs.Test.Patch.Merge.Checked ( CheckedMerge(..) )
import Darcs.Test.Patch.RepoModel ( RepoState, ModelOf )
import Darcs.Test.Patch.Types.Pair ( Pair(..) )
Expand All @@ -47,7 +47,7 @@ type Patch = RepoPatchV1 V1.Prim

instance
(ArbitraryPrim prim, PrimPatch prim, ApplyState prim ~ RepoState (ModelOf prim))
=> ArbitraryRepoPatch (RepoPatchV1 prim)
=> ArbitraryMergeable (RepoPatchV1 prim)
where

notRepoPatchV1 = Nothing
Expand Down
4 changes: 2 additions & 2 deletions harness/Darcs/Test/Patch/Arbitrary/RepoPatchV2.hs
Original file line number Diff line number Diff line change
Expand Up @@ -12,7 +12,7 @@ import Darcs.Test.Patch.Arbitrary.Generic
, MightHaveDuplicate(..)
, PrimBased(..)
)
import Darcs.Test.Patch.Arbitrary.RepoPatch
import Darcs.Test.Patch.Arbitrary.Mergeable
import Darcs.Test.Patch.Merge.Checked ( CheckedMerge(..) )
import Darcs.Test.Patch.RepoModel ( RepoState, ModelOf )
import Darcs.Test.Patch.WithState ( PropagateShrink )
Expand All @@ -30,7 +30,7 @@ instance ( ArbitraryPrim prim
, PrimPatch prim
, ApplyState prim ~ RepoState (ModelOf prim)
) =>
ArbitraryRepoPatch (RepoPatchV2 prim) where
ArbitraryMergeable (RepoPatchV2 prim) where
notRepoPatchV1 = Just (NotRepoPatchV1 (\case {}))

instance PrimPatch prim => CheckedMerge (RepoPatchV2 prim) where
Expand Down
4 changes: 2 additions & 2 deletions harness/Darcs/Test/Patch/Arbitrary/RepoPatchV3.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@ import Darcs.Prelude

import Darcs.Test.Patch.Arbitrary.Generic ( MightHaveDuplicate(..), PrimBased(..), ArbitraryPrim )
import Darcs.Test.Patch.Arbitrary.NamedPrim ()
import Darcs.Test.Patch.Arbitrary.RepoPatch
import Darcs.Test.Patch.Arbitrary.Mergeable
import Darcs.Test.Patch.Merge.Checked ( CheckedMerge )
import Darcs.Test.Patch.RepoModel ( RepoState, ModelOf )
import Darcs.Test.Patch.WithState ( PropagateShrink )
Expand All @@ -26,7 +26,7 @@ type instance ModelOf (RepoPatchV3 prim) = ModelOf prim

instance
(ArbitraryPrim prim, PrimPatch prim, ApplyState prim ~ RepoState (ModelOf prim))
=> ArbitraryRepoPatch (RepoPatchV3 prim)
=> ArbitraryMergeable (RepoPatchV3 prim)
where

notRepoPatchV1 = Just (NotRepoPatchV1 (\case {}))
Expand Down
Loading

0 comments on commit 7b77f32

Please sign in to comment.