Skip to content

Commit 2d2c32f

Browse files
committed
Merge remote-tracking branch 'origin/develop' into patch-map-inner-patch-desugar
2 parents 32a1f2f + 755886b commit 2d2c32f

File tree

3 files changed

+91
-34
lines changed

3 files changed

+91
-34
lines changed

patch.cabal

Lines changed: 13 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -65,6 +65,19 @@ library
6565
build-depends: these >= 0.4 && <0.9
6666
, monoidal-containers == 0.4.0.0
6767

68+
test-suite tests
69+
default-language: Haskell2010
70+
type: exitcode-stdio-1.0
71+
main-is: tests.hs
72+
hs-source-dirs: test
73+
build-depends: base
74+
, patch
75+
, containers
76+
, hedgehog
77+
, HUnit
78+
if impl(ghcjs)
79+
buildable: False
80+
6881
test-suite hlint
6982
default-language: Haskell2010
7083
type: exitcode-stdio-1.0

src/Data/Patch/MapWithPatchingMove.hs

Lines changed: 35 additions & 34 deletions
Original file line numberDiff line numberDiff line change
@@ -48,10 +48,10 @@ module Data.Patch.MapWithPatchingMove
4848

4949
import Data.Patch.Class
5050

51-
import Control.Arrow
51+
import Control.Lens hiding (from, to)
5252
import Control.Lens.TH (makeWrapped)
53-
import Control.Monad.Trans.State
54-
import Data.Foldable
53+
import Data.Align (align)
54+
import Data.Foldable (toList)
5555
import Data.Function
5656
import Data.List
5757
import Data.Map (Map)
@@ -61,9 +61,9 @@ import Data.Maybe
6161
import Data.Semigroup (Semigroup (..))
6262
#endif
6363
import Data.Monoid.DecidablyEmpty
64+
import Data.Set (Set)
6465
import qualified Data.Set as Set
6566
import Data.These (These (..))
66-
import Data.Tuple
6767

6868
-- | Patch a Map with additions, deletions, and moves. Invariant: If key @k1@
6969
-- is coming from @From_Move k2@, then key @k2@ should be going to @Just k1@,
@@ -229,39 +229,40 @@ patchThatChangesAndSortsMapWith cmp oldByIndex newByIndexUnsorted = patchThatCha
229229

230230
-- | Create a 'PatchMapWithPatchingMove' that, if applied to the first 'Map' provided,
231231
-- will produce the second 'Map'.
232+
-- Note: this will never produce a patch on a value.
232233
patchThatChangesMap
233-
:: (Ord k, Ord (PatchTarget p), Monoid p)
234+
:: forall k p
235+
. (Ord k, Ord (PatchTarget p), Monoid p)
234236
=> Map k (PatchTarget p) -> Map k (PatchTarget p) -> PatchMapWithPatchingMove k p
235237
patchThatChangesMap oldByIndex newByIndex = patch
236-
where oldByValue = Map.fromListWith Set.union $ swap . first Set.singleton <$> Map.toList oldByIndex
237-
(insertsAndMoves, unusedValuesByValue) = flip runState oldByValue $ do
238-
let f k v = do
239-
remainingValues <- get
240-
let putRemainingKeys remainingKeys = put $ if Set.null remainingKeys
241-
then Map.delete v remainingValues
242-
else Map.insert v remainingKeys remainingValues
243-
case Map.lookup v remainingValues of
244-
Nothing -> return $ NodeInfo (From_Insert v) $ Just undefined -- There's no existing value we can take
245-
Just fromKs ->
246-
if k `Set.member` fromKs
247-
then do
248-
putRemainingKeys $ Set.delete k fromKs
249-
return $ NodeInfo (From_Move k mempty) $ Just undefined -- There's an existing value, and it's here, so no patch necessary
250-
else do
251-
(fromK, remainingKeys) <- return $
252-
fromMaybe (error "PatchMapWithPatchingMove.patchThatChangesMap: impossible: fromKs was empty") $
253-
Set.minView fromKs -- There's an existing value, but it's not here; move it here
254-
putRemainingKeys remainingKeys
255-
return $ NodeInfo (From_Move fromK mempty) $ Just undefined
256-
Map.traverseWithKey f newByIndex
257-
unusedOldKeys = fold unusedValuesByValue
258-
pointlessMove k = \case
259-
From_Move k' _ | k == k' -> True
260-
_ -> False
261-
keyWasMoved k = if k `Map.member` oldByIndex && not (k `Set.member` unusedOldKeys)
262-
then Just undefined
263-
else Nothing
264-
patch = unsafePatchMapWithPatchingMove $ Map.filterWithKey (\k -> not . pointlessMove k . _nodeInfo_from) $ Map.mergeWithKey (\k a _ -> Just $ nodeInfoSetTo (keyWasMoved k) a) (Map.mapWithKey $ \k -> nodeInfoSetTo $ keyWasMoved k) (Map.mapWithKey $ \k _ -> NodeInfo From_Delete $ keyWasMoved k) insertsAndMoves oldByIndex
238+
where invert :: Map k (PatchTarget p) -> Map (PatchTarget p) (Set k)
239+
invert = Map.fromListWith (<>) . fmap (\(k, v) -> (v, Set.singleton k)) . Map.toList
240+
-- In the places where we use unionDistinct, a non-distinct key indicates a bug in this function
241+
unionDistinct :: forall k' v'. Ord k' => Map k' v' -> Map k' v' -> Map k' v'
242+
unionDistinct = Map.unionWith (error "patchThatChangesMap: non-distinct keys")
243+
unionPairDistinct :: (Map k (From k v), Map k (To k)) -> (Map k (From k v), Map k (To k)) -> (Map k (From k v), Map k (To k))
244+
unionPairDistinct (oldFroms, oldTos) (newFroms, newTos) = (unionDistinct oldFroms newFroms, unionDistinct oldTos newTos)
245+
-- Generate patch info for a single value
246+
-- Keys that are found in both the old and new sets will not be patched
247+
-- Keys that are found in only the old set will be moved to a new position if any are available; otherwise they will be deleted
248+
-- Keys that are found in only the new set will be populated by moving an old key if any are available; otherwise they will be inserted
249+
patchSingleValue :: PatchTarget p -> Set k -> Set k -> (Map k (From k p), Map k (To k))
250+
patchSingleValue v oldKeys newKeys = foldl' unionPairDistinct mempty $ align (toList $ oldKeys `Set.difference` newKeys) (toList $ newKeys `Set.difference` oldKeys) <&> \case
251+
This oldK -> (mempty, Map.singleton oldK Nothing) -- There's nowhere for this value to go, so we know we are deleting it
252+
That newK -> (Map.singleton newK $ From_Insert v, mempty) -- There's nowhere fo this value to come from, so we know we are inserting it
253+
These oldK newK -> (Map.singleton newK $ From_Move oldK mempty, Map.singleton oldK $ Just newK)
254+
-- Run patchSingleValue on a These. Missing old or new sets are considered empty
255+
patchSingleValueThese :: PatchTarget p -> These (Set k) (Set k) -> (Map k (From k p), Map k (To k))
256+
patchSingleValueThese v = \case
257+
This oldKeys -> patchSingleValue v oldKeys mempty
258+
That newKeys -> patchSingleValue v mempty newKeys
259+
These oldKeys newKeys -> patchSingleValue v oldKeys newKeys
260+
-- Generate froms and tos for all values, then merge them together
261+
(froms, tos) = foldl' unionPairDistinct mempty $ Map.mapWithKey patchSingleValueThese $ align (invert oldByIndex) (invert newByIndex)
262+
patch = unsafePatchMapWithPatchingMove $ align froms tos <&> \case
263+
This from -> NodeInfo from Nothing -- Since we don't have a 'to' record for this key, that must mean it isn't being moved anywhere, so it should be deleted.
264+
That to -> NodeInfo From_Delete to -- Since we don't have a 'from' record for this key, it must be getting deleted
265+
These from to -> NodeInfo from to
265266

266267
--
267268
-- NodeInfo

test/tests.hs

Lines changed: 43 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,43 @@
1+
{-# LANGUAGE TemplateHaskell #-}
2+
module Main where
3+
4+
import Test.HUnit (runTestTT, (~:), assertEqual, errors, failures, test)
5+
import Data.Patch ( Patch(apply) )
6+
import Data.Patch.MapWithMove ( patchThatChangesMap )
7+
import Data.Map as Map ( Map, fromList, singleton )
8+
import Hedgehog (checkParallel, discover, Property, property, forAll, PropertyT, (===))
9+
import Hedgehog.Gen as Gen ( int )
10+
import Hedgehog.Range as Range ( linear )
11+
import Control.Monad (replicateM)
12+
import System.Exit (exitFailure, exitSuccess)
13+
import Data.Sequence as Seq ( foldMapWithIndex, replicateM )
14+
15+
main :: IO ()
16+
main = do
17+
counts <- runTestTT $ test [
18+
"Simple Move" ~: (do
19+
let mapBefore = Map.fromList [(0,1)]
20+
mapAfter = Map.fromList [(0,0),(1,1)]
21+
patch = patchThatChangesMap mapBefore mapAfter
22+
afterPatch = apply patch mapBefore
23+
assertEqual "Patch creates the same Map" (Just mapAfter) afterPatch),
24+
"Property Checks" ~: propertyChecks
25+
]
26+
if errors counts + failures counts == 0 then exitSuccess else exitFailure
27+
28+
propertyChecks :: IO Bool
29+
propertyChecks = checkParallel $$(discover)
30+
31+
prop_patchThatChangesMap :: Property
32+
prop_patchThatChangesMap = property $ do
33+
mapBefore <- makeRandomIntMap
34+
mapAfter <- makeRandomIntMap
35+
let patch = patchThatChangesMap mapBefore mapAfter
36+
Just mapAfter === apply patch mapBefore
37+
38+
makeRandomIntMap :: Monad m => PropertyT m (Map Int Int)
39+
makeRandomIntMap = do
40+
let genNum = Gen.int (Range.linear 0 100)
41+
length <- forAll genNum
42+
listOfNumbers <- forAll $ Seq.replicateM length genNum
43+
pure $ Seq.foldMapWithIndex Map.singleton listOfNumbers

0 commit comments

Comments
 (0)