{-# LANGUAGE RecordWildCards #-}
module Reflex.Data.ActionStack
( ActionStack(..)
, actionStack_makeDoSelector
, actionStack_makeUndoSelector
, ActionStackConfig(..)
, holdActionStack
)
where
import Relude
import Reflex
import Reflex.Potato.Helpers
import Control.Monad.Fix
import qualified Data.Dependent.Sum as DS
import qualified Data.GADT.Compare
import Data.Wedge
data ActionStack t a = ActionStack {
_actionStack_do :: Event t a
, _actionStack_undo :: Event t a
}
actionStack_makeDoSelector
:: (Data.GADT.Compare.GCompare k, Reflex t)
=> ActionStack t (DS.DSum k Identity)
-> (k a -> Event t a)
actionStack_makeDoSelector as = select (fanDSum $ _actionStack_do as)
actionStack_makeUndoSelector
:: (Data.GADT.Compare.GCompare k, Reflex t)
=> ActionStack t (DS.DSum k Identity)
-> (k a -> Event t a)
actionStack_makeUndoSelector as = select (fanDSum $ _actionStack_undo as)
data ActionStackConfig t a = ActionStackConfig {
_actionStackConfig_do :: Event t a
, _actionStackConfig_undo :: Event t ()
, _actionStackConfig_redo :: Event t ()
, _actionStackConfig_clear :: Event t ()
}
data ASCmd a = ASCDo a | ASCUndo | ASCRedo | ASCClear
holdActionStack
:: forall t m a
. (Reflex t, MonadHold t m, MonadFix m)
=> ActionStackConfig t a
-> m (ActionStack t a)
holdActionStack (ActionStackConfig {..}) = do
let
changeEvent :: Event t (ASCmd a)
changeEvent = leftmostwarn
"ActionStack"
[ fmap ASCDo _actionStackConfig_do
, fmap (const ASCUndo) _actionStackConfig_undo
, fmap (const ASCRedo) _actionStackConfig_redo
, fmap (const ASCClear) _actionStackConfig_clear
]
foldfn
:: (ASCmd a) -> (Wedge a a, [a], [a]) -> PushM t (Wedge a a, [a], [a])
foldfn (ASCDo x) (_, xs , _ ) = return (Here x, x : xs, [])
foldfn ASCUndo (_, [] , ys ) = return (Nowhere, [], ys)
foldfn ASCUndo (_, x : xs, ys ) = return (There x, xs, x : ys)
foldfn ASCRedo (_, xs , [] ) = return (Nowhere, xs, [])
foldfn ASCRedo (_, xs , y : ys) = return (Here y, y : xs, ys)
foldfn ASCClear (_, _ , _ ) = return (Nowhere, [], [])
asdyn :: Dynamic t (Wedge a a, [a], [a]) <- foldDynM foldfn
(Nowhere, [], [])
changeEvent
let changedEv :: Event t (Wedge a a)
changedEv = fmap (\(x, _, _) -> x) (updated asdyn)
return $ ActionStack { _actionStack_do = fmapMaybe getHere changedEv
, _actionStack_undo = fmapMaybe getThere changedEv
}