{-# LANGUAGE CPP #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
#ifdef USE_REFLEX_OPTIMIZER
{-# OPTIONS_GHC -fplugin=Reflex.Optimizer #-}
#endif
-- |
-- Module:
--   Reflex.Adjustable.Class
-- Description:
--   A class for actions that can be "adjusted" over time based on some 'Event'
--   such that, when observed after the firing of any such 'Event', the result
--   is as though the action was originally run with the 'Event's value.
module Reflex.Adjustable.Class
  (
  -- * The Adjustable typeclass
    Adjustable(..)
  , sequenceDMapWithAdjust
  , sequenceDMapWithAdjustWithMove
  , mapMapWithAdjustWithMove
  -- * Deprecated aliases
  , MonadAdjust
  ) where

import Control.Monad.Identity
import Control.Monad.Reader
import Data.Dependent.Map (DMap)
import Data.GADT.Compare (GCompare(..))
import qualified Data.Dependent.Map as DMap
import Data.Functor.Constant
import Data.Functor.Misc
import Data.IntMap.Strict (IntMap)
import qualified Data.IntMap.Strict as IntMap
import Data.Map (Map)

import Reflex.Class
import Data.Patch.DMapWithMove

-- | A 'Monad' that supports adjustment over time.  After an action has been
-- run, if the given events fire, it will adjust itself so that its net effect
-- is as though it had originally been run with the new value.  Note that there
-- is some issue here with persistent side-effects: obviously, IO (and some
-- other side-effects) cannot be undone, so it is up to the instance implementer
-- to determine what the best meaning for this class is in such cases.
class (Reflex t, Monad m) => Adjustable t m | m -> t where
  runWithReplace
    :: m a
    -> Event t (m b)
    -> m (a, Event t b)

  traverseIntMapWithKeyWithAdjust
    :: (IntMap.Key -> v -> m v')
    -> IntMap v
    -> Event t (PatchIntMap v)
    -> m (IntMap v', Event t (PatchIntMap v'))

  traverseDMapWithKeyWithAdjust
    :: GCompare k
    => (forall a. k a -> v a -> m (v' a))
    -> DMap k v
    -> Event t (PatchDMap k v)
    -> m (DMap k v', Event t (PatchDMap k v'))
  {-# INLINABLE traverseDMapWithKeyWithAdjust #-}
  traverseDMapWithKeyWithAdjust forall a. k a -> v a -> m (v' a)
f DMap k v
dm0 Event t (PatchDMap k v)
dm' = ((DMap k v', Event t (PatchDMapWithMove k v'))
 -> (DMap k v', Event t (PatchDMap k v')))
-> m (DMap k v', Event t (PatchDMapWithMove k v'))
-> m (DMap k v', Event t (PatchDMap k v'))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Event t (PatchDMapWithMove k v') -> Event t (PatchDMap k v'))
-> (DMap k v', Event t (PatchDMapWithMove k v'))
-> (DMap k v', Event t (PatchDMap k v'))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((PatchDMapWithMove k v' -> PatchDMap k v')
-> Event t (PatchDMapWithMove k v') -> Event t (PatchDMap k v')
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap PatchDMapWithMove k v' -> PatchDMap k v'
forall (k1 :: * -> *) (v :: * -> *).
PatchDMapWithMove k1 v -> PatchDMap k1 v
fromPatchWithMove)) (m (DMap k v', Event t (PatchDMapWithMove k v'))
 -> m (DMap k v', Event t (PatchDMap k v')))
-> m (DMap k v', Event t (PatchDMapWithMove k v'))
-> m (DMap k v', Event t (PatchDMap k v'))
forall a b. (a -> b) -> a -> b
$
    (forall a. k a -> v a -> m (v' a))
-> DMap k v
-> Event t (PatchDMapWithMove k v)
-> m (DMap k v', Event t (PatchDMapWithMove k v'))
forall t (m :: * -> *) (k :: * -> *) (v :: * -> *) (v' :: * -> *).
(Adjustable t m, GCompare k) =>
(forall a. k a -> v a -> m (v' a))
-> DMap k v
-> Event t (PatchDMapWithMove k v)
-> m (DMap k v', Event t (PatchDMapWithMove k v'))
traverseDMapWithKeyWithAdjustWithMove forall a. k a -> v a -> m (v' a)
f DMap k v
dm0 (Event t (PatchDMapWithMove k v)
 -> m (DMap k v', Event t (PatchDMapWithMove k v')))
-> Event t (PatchDMapWithMove k v)
-> m (DMap k v', Event t (PatchDMapWithMove k v'))
forall a b. (a -> b) -> a -> b
$ (PatchDMap k v -> PatchDMapWithMove k v)
-> Event t (PatchDMap k v) -> Event t (PatchDMapWithMove k v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap PatchDMap k v -> PatchDMapWithMove k v
forall (k1 :: * -> *) (v :: * -> *).
PatchDMap k1 v -> PatchDMapWithMove k1 v
toPatchWithMove Event t (PatchDMap k v)
dm'
   where
    toPatchWithMove :: PatchDMap k1 v -> PatchDMapWithMove k1 v
toPatchWithMove (PatchDMap DMap k1 (ComposeMaybe v)
m) = DMap k1 (NodeInfo k1 v) -> PatchDMapWithMove k1 v
forall k (k1 :: k -> *) (v :: k -> *).
DMap k1 (NodeInfo k1 v) -> PatchDMapWithMove k1 v
PatchDMapWithMove (DMap k1 (NodeInfo k1 v) -> PatchDMapWithMove k1 v)
-> DMap k1 (NodeInfo k1 v) -> PatchDMapWithMove k1 v
forall a b. (a -> b) -> a -> b
$ (forall v. ComposeMaybe v v -> NodeInfo k1 v v)
-> DMap k1 (ComposeMaybe v) -> DMap k1 (NodeInfo k1 v)
forall k1 (f :: k1 -> *) (g :: k1 -> *) (k2 :: k1 -> *).
(forall (v :: k1). f v -> g v) -> DMap k2 f -> DMap k2 g
DMap.map forall v. ComposeMaybe v v -> NodeInfo k1 v v
forall (v :: * -> *) a (k1 :: * -> *).
ComposeMaybe v a -> NodeInfo k1 v a
toNodeInfoWithMove DMap k1 (ComposeMaybe v)
m
    toNodeInfoWithMove :: ComposeMaybe v a -> NodeInfo k1 v a
toNodeInfoWithMove = \case
      ComposeMaybe (Just v a
v) -> From k1 v a -> To k1 a -> NodeInfo k1 v a
forall k (k1 :: k -> *) (v :: k -> *) (a :: k).
From k1 v a -> To k1 a -> NodeInfo k1 v a
NodeInfo (v a -> From k1 v a
forall a (v :: a -> *) (b :: a) (k :: a -> *). v b -> From k v b
From_Insert v a
v) (To k1 a -> NodeInfo k1 v a) -> To k1 a -> NodeInfo k1 v a
forall a b. (a -> b) -> a -> b
$ Maybe (k1 a) -> To k1 a
forall k (f :: k -> *) (a :: k). Maybe (f a) -> ComposeMaybe f a
ComposeMaybe Maybe (k1 a)
forall a. Maybe a
Nothing
      ComposeMaybe Maybe (v a)
Nothing -> From k1 v a -> To k1 a -> NodeInfo k1 v a
forall k (k1 :: k -> *) (v :: k -> *) (a :: k).
From k1 v a -> To k1 a -> NodeInfo k1 v a
NodeInfo From k1 v a
forall a (k :: a -> *) (v :: a -> *) (b :: a). From k v b
From_Delete (To k1 a -> NodeInfo k1 v a) -> To k1 a -> NodeInfo k1 v a
forall a b. (a -> b) -> a -> b
$ Maybe (k1 a) -> To k1 a
forall k (f :: k -> *) (a :: k). Maybe (f a) -> ComposeMaybe f a
ComposeMaybe Maybe (k1 a)
forall a. Maybe a
Nothing
    fromPatchWithMove :: PatchDMapWithMove k1 v -> PatchDMap k1 v
fromPatchWithMove (PatchDMapWithMove DMap k1 (NodeInfo k1 v)
m) = DMap k1 (ComposeMaybe v) -> PatchDMap k1 v
forall k (k1 :: k -> *) (v :: k -> *).
DMap k1 (ComposeMaybe v) -> PatchDMap k1 v
PatchDMap (DMap k1 (ComposeMaybe v) -> PatchDMap k1 v)
-> DMap k1 (ComposeMaybe v) -> PatchDMap k1 v
forall a b. (a -> b) -> a -> b
$ (forall v. NodeInfo k1 v v -> ComposeMaybe v v)
-> DMap k1 (NodeInfo k1 v) -> DMap k1 (ComposeMaybe v)
forall k1 (f :: k1 -> *) (g :: k1 -> *) (k2 :: k1 -> *).
(forall (v :: k1). f v -> g v) -> DMap k2 f -> DMap k2 g
DMap.map forall v. NodeInfo k1 v v -> ComposeMaybe v v
forall (k1 :: * -> *) (f :: * -> *) a.
NodeInfo k1 f a -> ComposeMaybe f a
fromNodeInfoWithMove DMap k1 (NodeInfo k1 v)
m
    fromNodeInfoWithMove :: NodeInfo k1 f a -> ComposeMaybe f a
fromNodeInfoWithMove (NodeInfo From k1 f a
from To k1 a
_) = Maybe (f a) -> ComposeMaybe f a
forall k (f :: k -> *) (a :: k). Maybe (f a) -> ComposeMaybe f a
ComposeMaybe (Maybe (f a) -> ComposeMaybe f a)
-> Maybe (f a) -> ComposeMaybe f a
forall a b. (a -> b) -> a -> b
$ case From k1 f a
from of
      From_Insert f a
v -> f a -> Maybe (f a)
forall a. a -> Maybe a
Just f a
v
      From k1 f a
From_Delete -> Maybe (f a)
forall a. Maybe a
Nothing
      From_Move k1 a
_ -> [Char] -> Maybe (f a)
forall a. HasCallStack => [Char] -> a
error [Char]
"traverseDMapWithKeyWithAdjust: implementation of traverseDMapWithKeyWithAdjustWithMove inserted spurious move"

  traverseDMapWithKeyWithAdjustWithMove
    :: GCompare k
    => (forall a. k a -> v a -> m (v' a))
    -> DMap k v
    -> Event t (PatchDMapWithMove k v)
    -> m (DMap k v', Event t (PatchDMapWithMove k v'))

instance Adjustable t m => Adjustable t (ReaderT r m) where
  runWithReplace :: ReaderT r m a
-> Event t (ReaderT r m b) -> ReaderT r m (a, Event t b)
runWithReplace ReaderT r m a
a0 Event t (ReaderT r m b)
a' = do
    r
r <- ReaderT r m r
forall r (m :: * -> *). MonadReader r m => m r
ask
    m (a, Event t b) -> ReaderT r m (a, Event t b)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (a, Event t b) -> ReaderT r m (a, Event t b))
-> m (a, Event t b) -> ReaderT r m (a, Event t b)
forall a b. (a -> b) -> a -> b
$ m a -> Event t (m b) -> m (a, Event t b)
forall t (m :: * -> *) a b.
Adjustable t m =>
m a -> Event t (m b) -> m (a, Event t b)
runWithReplace (ReaderT r m a -> r -> m a
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT ReaderT r m a
a0 r
r) (Event t (m b) -> m (a, Event t b))
-> Event t (m b) -> m (a, Event t b)
forall a b. (a -> b) -> a -> b
$ (ReaderT r m b -> m b) -> Event t (ReaderT r m b) -> Event t (m b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (ReaderT r m b -> r -> m b
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
`runReaderT` r
r) Event t (ReaderT r m b)
a'
  traverseIntMapWithKeyWithAdjust :: (Key -> v -> ReaderT r m v')
-> IntMap v
-> Event t (PatchIntMap v)
-> ReaderT r m (IntMap v', Event t (PatchIntMap v'))
traverseIntMapWithKeyWithAdjust Key -> v -> ReaderT r m v'
f IntMap v
dm0 Event t (PatchIntMap v)
dm' = do
    r
r <- ReaderT r m r
forall r (m :: * -> *). MonadReader r m => m r
ask
    m (IntMap v', Event t (PatchIntMap v'))
-> ReaderT r m (IntMap v', Event t (PatchIntMap v'))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (IntMap v', Event t (PatchIntMap v'))
 -> ReaderT r m (IntMap v', Event t (PatchIntMap v')))
-> m (IntMap v', Event t (PatchIntMap v'))
-> ReaderT r m (IntMap v', Event t (PatchIntMap v'))
forall a b. (a -> b) -> a -> b
$ (Key -> v -> m v')
-> IntMap v
-> Event t (PatchIntMap v)
-> m (IntMap v', Event t (PatchIntMap v'))
forall t (m :: * -> *) v v'.
Adjustable t m =>
(Key -> v -> m v')
-> IntMap v
-> Event t (PatchIntMap v)
-> m (IntMap v', Event t (PatchIntMap v'))
traverseIntMapWithKeyWithAdjust (\Key
k v
v -> ReaderT r m v' -> r -> m v'
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT (Key -> v -> ReaderT r m v'
f Key
k v
v) r
r) IntMap v
dm0 Event t (PatchIntMap v)
dm'
  traverseDMapWithKeyWithAdjust :: (forall a. k a -> v a -> ReaderT r m (v' a))
-> DMap k v
-> Event t (PatchDMap k v)
-> ReaderT r m (DMap k v', Event t (PatchDMap k v'))
traverseDMapWithKeyWithAdjust forall a. k a -> v a -> ReaderT r m (v' a)
f DMap k v
dm0 Event t (PatchDMap k v)
dm' = do
    r
r <- ReaderT r m r
forall r (m :: * -> *). MonadReader r m => m r
ask
    m (DMap k v', Event t (PatchDMap k v'))
-> ReaderT r m (DMap k v', Event t (PatchDMap k v'))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (DMap k v', Event t (PatchDMap k v'))
 -> ReaderT r m (DMap k v', Event t (PatchDMap k v')))
-> m (DMap k v', Event t (PatchDMap k v'))
-> ReaderT r m (DMap k v', Event t (PatchDMap k v'))
forall a b. (a -> b) -> a -> b
$ (forall a. k a -> v a -> m (v' a))
-> DMap k v
-> Event t (PatchDMap k v)
-> m (DMap k v', Event t (PatchDMap k v'))
forall t (m :: * -> *) (k :: * -> *) (v :: * -> *) (v' :: * -> *).
(Adjustable t m, GCompare k) =>
(forall a. k a -> v a -> m (v' a))
-> DMap k v
-> Event t (PatchDMap k v)
-> m (DMap k v', Event t (PatchDMap k v'))
traverseDMapWithKeyWithAdjust (\k a
k v a
v -> ReaderT r m (v' a) -> r -> m (v' a)
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT (k a -> v a -> ReaderT r m (v' a)
forall a. k a -> v a -> ReaderT r m (v' a)
f k a
k v a
v) r
r) DMap k v
dm0 Event t (PatchDMap k v)
dm'
  traverseDMapWithKeyWithAdjustWithMove :: (forall a. k a -> v a -> ReaderT r m (v' a))
-> DMap k v
-> Event t (PatchDMapWithMove k v)
-> ReaderT r m (DMap k v', Event t (PatchDMapWithMove k v'))
traverseDMapWithKeyWithAdjustWithMove forall a. k a -> v a -> ReaderT r m (v' a)
f DMap k v
dm0 Event t (PatchDMapWithMove k v)
dm' = do
    r
r <- ReaderT r m r
forall r (m :: * -> *). MonadReader r m => m r
ask
    m (DMap k v', Event t (PatchDMapWithMove k v'))
-> ReaderT r m (DMap k v', Event t (PatchDMapWithMove k v'))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (DMap k v', Event t (PatchDMapWithMove k v'))
 -> ReaderT r m (DMap k v', Event t (PatchDMapWithMove k v')))
-> m (DMap k v', Event t (PatchDMapWithMove k v'))
-> ReaderT r m (DMap k v', Event t (PatchDMapWithMove k v'))
forall a b. (a -> b) -> a -> b
$ (forall a. k a -> v a -> m (v' a))
-> DMap k v
-> Event t (PatchDMapWithMove k v)
-> m (DMap k v', Event t (PatchDMapWithMove k v'))
forall t (m :: * -> *) (k :: * -> *) (v :: * -> *) (v' :: * -> *).
(Adjustable t m, GCompare k) =>
(forall a. k a -> v a -> m (v' a))
-> DMap k v
-> Event t (PatchDMapWithMove k v)
-> m (DMap k v', Event t (PatchDMapWithMove k v'))
traverseDMapWithKeyWithAdjustWithMove (\k a
k v a
v -> ReaderT r m (v' a) -> r -> m (v' a)
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT (k a -> v a -> ReaderT r m (v' a)
forall a. k a -> v a -> ReaderT r m (v' a)
f k a
k v a
v) r
r) DMap k v
dm0 Event t (PatchDMapWithMove k v)
dm'

-- | Traverse a 'DMap' of 'Adjustable' actions, running each of them. The provided 'Event' of patches
-- to the 'DMap' can add, remove, or update values.
sequenceDMapWithAdjust
  :: (GCompare k, Adjustable t m)
  => DMap k m
  -> Event t (PatchDMap k m)
  -> m (DMap k Identity, Event t (PatchDMap k Identity))
sequenceDMapWithAdjust :: DMap k m
-> Event t (PatchDMap k m)
-> m (DMap k Identity, Event t (PatchDMap k Identity))
sequenceDMapWithAdjust = (forall a. k a -> m a -> m (Identity a))
-> DMap k m
-> Event t (PatchDMap k m)
-> m (DMap k Identity, Event t (PatchDMap k Identity))
forall t (m :: * -> *) (k :: * -> *) (v :: * -> *) (v' :: * -> *).
(Adjustable t m, GCompare k) =>
(forall a. k a -> v a -> m (v' a))
-> DMap k v
-> Event t (PatchDMap k v)
-> m (DMap k v', Event t (PatchDMap k v'))
traverseDMapWithKeyWithAdjust ((forall a. k a -> m a -> m (Identity a))
 -> DMap k m
 -> Event t (PatchDMap k m)
 -> m (DMap k Identity, Event t (PatchDMap k Identity)))
-> (forall a. k a -> m a -> m (Identity a))
-> DMap k m
-> Event t (PatchDMap k m)
-> m (DMap k Identity, Event t (PatchDMap k Identity))
forall a b. (a -> b) -> a -> b
$ \k a
_ -> (a -> Identity a) -> m a -> m (Identity a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> Identity a
forall a. a -> Identity a
Identity

-- | Traverses a 'DMap' of 'Adjustable' actions, running each of them. The provided 'Event' of patches
-- to the 'DMap' can add, remove, update, move, or swap values.
sequenceDMapWithAdjustWithMove
  :: (GCompare k, Adjustable t m)
  => DMap k m
  -> Event t (PatchDMapWithMove k m)
  -> m (DMap k Identity, Event t (PatchDMapWithMove k Identity))
sequenceDMapWithAdjustWithMove :: DMap k m
-> Event t (PatchDMapWithMove k m)
-> m (DMap k Identity, Event t (PatchDMapWithMove k Identity))
sequenceDMapWithAdjustWithMove = (forall a. k a -> m a -> m (Identity a))
-> DMap k m
-> Event t (PatchDMapWithMove k m)
-> m (DMap k Identity, Event t (PatchDMapWithMove k Identity))
forall t (m :: * -> *) (k :: * -> *) (v :: * -> *) (v' :: * -> *).
(Adjustable t m, GCompare k) =>
(forall a. k a -> v a -> m (v' a))
-> DMap k v
-> Event t (PatchDMapWithMove k v)
-> m (DMap k v', Event t (PatchDMapWithMove k v'))
traverseDMapWithKeyWithAdjustWithMove ((forall a. k a -> m a -> m (Identity a))
 -> DMap k m
 -> Event t (PatchDMapWithMove k m)
 -> m (DMap k Identity, Event t (PatchDMapWithMove k Identity)))
-> (forall a. k a -> m a -> m (Identity a))
-> DMap k m
-> Event t (PatchDMapWithMove k m)
-> m (DMap k Identity, Event t (PatchDMapWithMove k Identity))
forall a b. (a -> b) -> a -> b
$ \k a
_ -> (a -> Identity a) -> m a -> m (Identity a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> Identity a
forall a. a -> Identity a
Identity

-- | Traverses a 'Map', running the provided 'Adjustable' action. The provided 'Event' of patches to the 'Map'
-- can add, remove, update, move, or swap values.
mapMapWithAdjustWithMove
  :: forall t m k v v'. (Adjustable t m, Ord k)
  => (k -> v -> m v')
  -> Map k v
  -> Event t (PatchMapWithMove k v)
  -> m (Map k v', Event t (PatchMapWithMove k v'))
mapMapWithAdjustWithMove :: (k -> v -> m v')
-> Map k v
-> Event t (PatchMapWithMove k v)
-> m (Map k v', Event t (PatchMapWithMove k v'))
mapMapWithAdjustWithMove k -> v -> m v'
f Map k v
m0 Event t (PatchMapWithMove k v)
m' = do
  (DMap (Const2 k v) (Constant v')
out0 :: DMap (Const2 k v) (Constant v'), Event t (PatchDMapWithMove (Const2 k v) (Constant v'))
out') <- (forall a. Const2 k v a -> Identity a -> m (Constant v' a))
-> DMap (Const2 k v) Identity
-> Event t (PatchDMapWithMove (Const2 k v) Identity)
-> m (DMap (Const2 k v) (Constant v'),
      Event t (PatchDMapWithMove (Const2 k v) (Constant v')))
forall t (m :: * -> *) (k :: * -> *) (v :: * -> *) (v' :: * -> *).
(Adjustable t m, GCompare k) =>
(forall a. k a -> v a -> m (v' a))
-> DMap k v
-> Event t (PatchDMapWithMove k v)
-> m (DMap k v', Event t (PatchDMapWithMove k v'))
traverseDMapWithKeyWithAdjustWithMove (\(Const2 k) (Identity v) -> v' -> Constant v' a
forall k a (b :: k). a -> Constant a b
Constant (v' -> Constant v' a) -> m v' -> m (Constant v' a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> k -> v -> m v'
f k
k v
a
v) (Map k v -> DMap (Const2 k v) Identity
forall k v. Map k v -> DMap (Const2 k v) Identity
mapToDMap Map k v
m0) ((v -> Identity v)
-> PatchMapWithMove k v -> PatchDMapWithMove (Const2 k v) Identity
forall k1 k2 v (v' :: k1 -> *) (a :: k1).
(v -> v' a)
-> PatchMapWithMove k2 v -> PatchDMapWithMove (Const2 k2 a) v'
const2PatchDMapWithMoveWith v -> Identity v
forall a. a -> Identity a
Identity (PatchMapWithMove k v -> PatchDMapWithMove (Const2 k v) Identity)
-> Event t (PatchMapWithMove k v)
-> Event t (PatchDMapWithMove (Const2 k v) Identity)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Event t (PatchMapWithMove k v)
m')
  (Map k v', Event t (PatchMapWithMove k v'))
-> m (Map k v', Event t (PatchMapWithMove k v'))
forall (m :: * -> *) a. Monad m => a -> m a
return ((Constant v' v -> v')
-> DMap (Const2 k v) (Constant v') -> Map k v'
forall k1 (f :: k1 -> *) (v :: k1) v' k2.
(f v -> v') -> DMap (Const2 k2 v) f -> Map k2 v'
dmapToMapWith (\(Constant v'
v') -> v'
v') DMap (Const2 k v) (Constant v')
out0, (Constant v' v -> v')
-> PatchDMapWithMove (Const2 k v) (Constant v')
-> PatchMapWithMove k v'
forall k1 k2 (v :: k1 -> *) v' (a :: k1).
(v a -> v')
-> PatchDMapWithMove (Const2 k2 a) v -> PatchMapWithMove k2 v'
patchDMapWithMoveToPatchMapWithMoveWith (\(Constant v'
v') -> v'
v') (PatchDMapWithMove (Const2 k v) (Constant v')
 -> PatchMapWithMove k v')
-> Event t (PatchDMapWithMove (Const2 k v) (Constant v'))
-> Event t (PatchMapWithMove k v')
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Event t (PatchDMapWithMove (Const2 k v) (Constant v'))
out')

--------------------------------------------------------------------------------
-- Deprecated functions
--------------------------------------------------------------------------------

{-# DEPRECATED MonadAdjust "Use Adjustable instead" #-}
-- | Synonym for 'Adjustable'
type MonadAdjust = Adjustable