Skip to content

Commit

Permalink
add a couple of types for working with patches
Browse files Browse the repository at this point in the history
  • Loading branch information
danbornside committed Sep 18, 2019
1 parent c477539 commit 06fc958
Show file tree
Hide file tree
Showing 3 changed files with 151 additions and 0 deletions.
2 changes: 2 additions & 0 deletions reflex.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -100,9 +100,11 @@ library
Reflex.Patch.Class,
Reflex.Patch.DMap,
Reflex.Patch.DMapWithMove,
Reflex.Patch.DMapWithReset,
Reflex.Patch.IntMap,
Reflex.Patch.Map,
Reflex.Patch.MapWithMove,
Reflex.Patch.Patchable,
Reflex.PerformEvent.Base,
Reflex.PerformEvent.Class,
Reflex.PostBuild.Base,
Expand Down
105 changes: 105 additions & 0 deletions src/Reflex/Patch/DMapWithReset.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,105 @@
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE Rank2Types #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}

{-# LANGUAGE EmptyCase #-}

{-# OPTIONS_GHC -Wall #-}

-- | 'Patch'es on 'DMap' that consist only of insertions (or overwrites) and deletions.
module Reflex.Patch.DMapWithReset where

import Reflex.Patch.Class

import Data.Dependent.Map (DMap, GCompare (..))
import qualified Data.Dependent.Map as DMap
import Data.Semigroup (Semigroup (..))
import Data.Constraint.Extras

-- | A set of changes to a 'DMap'. Any element may be inserted/updated or deleted.
-- Insertions are represented as @'ComposeMaybe' (Just value)@,
-- while deletions are represented as @'ComposeMaybe' Nothing@.
newtype PatchDMapWithReset k p v = PatchDMapWithReset { unPatchDMapWithReset :: DMap k (By p) }

-- | Holds the information about each key: where its new value should come from,
-- and where its old value should go to
data By p a
= By_Insert (PatchTarget (p a)) -- ^ Insert the given value here
| By_Delete -- ^ Delete the existing value, if any, from here
| By_Patch (p a) -- ^ Patch the value here with the given patch

instance (Semigroup (p a), Patch (p a)) => Semigroup (By p a) where
x@(By_Insert _) <> _ = x
By_Delete <> _ = By_Delete
By_Patch x <> By_Insert y = By_Insert (applyAlways x y)
By_Patch x <> By_Patch y = By_Patch (x <> y)
By_Patch _ <> By_Delete = By_Delete

instance (Monoid (p a), Patch (p a)) => Monoid (By p a) where
mappend = (<>)
mempty = By_Patch mempty

instance (GCompare k, Has' Semigroup k p, Has (Patches1Locally p v) k) => Semigroup (PatchDMapWithReset k p v) where
PatchDMapWithReset xs <> PatchDMapWithReset ys = PatchDMapWithReset $ DMap.unionWithKey (\k -> has @(Patches1Locally p v) k (has' @(Semigroup) @p k (<>))) xs ys

instance (GCompare k, Has' Semigroup k p, Has (Patches1Locally p v) k) => Monoid (PatchDMapWithReset k p v) where
mappend = (<>)
mempty = PatchDMapWithReset DMap.empty

class (Patch (p a), PatchTarget (p a) ~ v a) => Patches1Locally p v a
instance (Patch (p a), PatchTarget (p a) ~ v a) => Patches1Locally p v a

data These1 f g x
= This1 (f x)
| That1 (g x)
| These1 (f x) (g x)

mergeWithKey
:: forall k v1 v2 v.
(GCompare k)
=> (forall x. k x -> v1 x -> Maybe (v x))
-> (forall x. k x -> v2 x -> Maybe (v x))
-> (forall x. k x -> v1 x -> v2 x -> Maybe (v x))
-> DMap k v1 -> DMap k v2 -> DMap k v
mergeWithKey f g fg = \xs ys -> DMap.mapMaybeWithKey onlyThat $ DMap.unionWithKey doIt (DMap.map This1 xs) (DMap.map That1 ys)
where
doIt _ (This1 xs) (That1 ys) = These1 xs ys
doIt _ _ _ = error "mergeWithKey misalligned keys"

onlyThat :: forall x. k x -> These1 v1 v2 x -> Maybe (v x)
onlyThat k = \case
This1 xs -> f k xs
That1 ys -> g k ys
These1 xs ys -> fg k xs ys
{-# INLINE mergeWithKey #-}

-- | Apply the insertions or deletions to a given 'DMap'.
instance (GCompare k, Has (Patches1Locally p v) k) => Patch (PatchDMapWithReset k p v) where

type PatchTarget (PatchDMapWithReset k p v) = DMap k v

apply = go
where
go :: PatchDMapWithReset k p v -> DMap k v -> Maybe (DMap k v)
go (PatchDMapWithReset diff) old = Just $! mergeWithKey (\_ -> Just) inserts updates old diff
where
updates :: forall x. k x -> v x -> By p x -> Maybe (v x)
updates k ys = has @(Patches1Locally p v) k $ \case
By_Insert x -> Just x
By_Delete -> Nothing
By_Patch x -> Just $ applyAlways x ys

inserts :: forall x. k x -> By p x -> Maybe (v x)
inserts k = has @(Patches1Locally p v) k $ \case
By_Insert x -> Just x
By_Delete -> Nothing
By_Patch _ -> Nothing
44 changes: 44 additions & 0 deletions src/Reflex/Patch/Patchable.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,44 @@
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeFamilies #-}

-- The derived instances are undecidable in the case of a pathlogical instance like
-- instance Patch x where
-- type PatchTarget x = Patchable x
{-# LANGUAGE UndecidableInstances #-}

module Reflex.Patch.Patchable where

-- import Data.Aeson
import GHC.Generics
import Reflex.Patch

-- | Like SemiMap/PartialMap but for anything patchable
data Patchable p
= Patchable_Patch p
| Patchable_Complete (PatchTarget p)
deriving (Generic)

completePatchable :: Patchable p -> Maybe (PatchTarget p)
completePatchable = \case
Patchable_Complete t -> Just t
Patchable_Patch _ -> Nothing

deriving instance (Eq p, Eq (PatchTarget p)) => Eq (Patchable p)
deriving instance (Ord p, Ord (PatchTarget p)) => Ord (Patchable p)
deriving instance (Show p, Show (PatchTarget p)) => Show (Patchable p)
deriving instance (Read p, Read (PatchTarget p)) => Read (Patchable p)
-- instance (ToJSON p, ToJSON (PatchTarget p)) => ToJSON (Patchable p)
-- instance (FromJSON p, FromJSON (PatchTarget p)) => FromJSON (Patchable p)

instance (Monoid p, Patch p) => Monoid (Patchable p) where
mempty = Patchable_Patch mempty
mappend = (<>)

instance (Semigroup p, Patch p) => Semigroup (Patchable p) where
(<>) = curry $ \case
(Patchable_Patch a, Patchable_Patch b) -> Patchable_Patch $ a <> b
(Patchable_Patch a, Patchable_Complete b) -> Patchable_Complete $ applyAlways a b
(Patchable_Complete a, _) -> Patchable_Complete a

0 comments on commit 06fc958

Please sign in to comment.