Skip to content

Commit

Permalink
Removes scope depth
Browse files Browse the repository at this point in the history
  • Loading branch information
mikesol committed Aug 2, 2024
1 parent 9ccf469 commit ae99b78
Show file tree
Hide file tree
Showing 2 changed files with 29 additions and 42 deletions.
63 changes: 25 additions & 38 deletions deku-core/src/Deku/Core.purs
Original file line number Diff line number Diff line change
Expand Up @@ -26,7 +26,6 @@ module Deku.Core
, ParentId(..)
, RemoveElement
, RemoveText
, ScopeDepth(..)
, SetCb
, SetProp
, SetText
Expand Down Expand Up @@ -276,13 +275,6 @@ newtype DOMInterpret = DOMInterpret

derive instance Newtype DOMInterpret _

-- | Tracks the depths of the current dispose action. The initial level will be `ScopeDepth 0`. Every descent into an
-- | `elementify` `Nut` will increase the depth.
newtype ScopeDepth =
ScopeDepth Int

derive instance Newtype ScopeDepth _

-- | Handles an optimized `Poll` by running the effect on each emitted value. Any resulting subscription gets written to
-- | the given cleanup array.
pump'
Expand All @@ -300,15 +292,15 @@ pump' (PSR { addEffectToDisposalQueue }) p effF =
handleEvent :: Event.Event a -> Effect Unit
handleEvent y = do
uu <- runEffectFn2 Event.subscribeO y dynamicEff
void $ liftST $ runSTFn1 addEffectToDisposalQueue $ mkEffectFn1 \_ -> uu
void $ liftST $ runSTFn1 addEffectToDisposalQueue $ uu

handlePoll
:: ST.STRef Global (EffectFn1 a Unit) -> Event.Event a -> Effect Unit
handlePoll whichF y = do
uu <- runEffectFn2 Event.subscribeO y $ mkEffectFn1 \i -> do
f <- liftST $ ST.read whichF
runEffectFn1 f i
void $ liftST $ runSTFn1 addEffectToDisposalQueue $ mkEffectFn1 \_ -> uu
void $ liftST $ runSTFn1 addEffectToDisposalQueue uu

go :: Poll a -> Effect Unit
go = case _ of
Expand Down Expand Up @@ -343,31 +335,30 @@ newtype PSR = PSR
region :: StaticRegion
-- scope
-- used by an element to signal it should be removed
, signalDisposalQueueShouldBeTriggered :: Poll.Poll ScopeDepth
, addEffectToDisposalQueue :: STFn1 (EffectFn1 ScopeDepth Unit) Global Unit
, triggerDisposalQueueEffects :: EffectFn1 ScopeDepth Unit
, signalDisposalQueueShouldBeTriggered :: Poll.Poll Unit
, addEffectToDisposalQueue :: STFn1 (Effect Unit) Global Unit
, triggerDisposalQueueEffects :: Effect Unit
-- used to indicate when an element should never be statically rendered
-- it may be disqualified for other reasons, but this flag trumps them all
, ancestry :: Ancestry
}

derive instance Newtype PSR _

newPSR :: STFn3 Ancestry (Poll.Poll ScopeDepth) StaticRegion Global PSR
newPSR :: STFn3 Ancestry (Poll.Poll Unit) StaticRegion Global PSR
newPSR = mkSTFn3 \ancestry signalDisposalQueueShouldBeTriggered region -> do
unsubs <- STArray.new
let
addEffectToDisposalQueue :: STFn1 (EffectFn1 ScopeDepth Unit) Global Unit
addEffectToDisposalQueue :: STFn1 (Effect Unit) Global Unit
addEffectToDisposalQueue =
mkSTFn1 \eff -> void (STArray.push eff unsubs)

-- to correctly dispose, effect should be run in the reverse order of insertion
triggerDisposalQueueEffects :: EffectFn1 ScopeDepth Unit
triggerDisposalQueueEffects = mkEffectFn1 \d -> do
triggerDisposalQueueEffects :: Effect Unit
triggerDisposalQueueEffects = do
stack <- liftST $ STArray.unsafeFreeze unsubs
let l = Array.length stack
forE 0 l \i -> do
runEffectFn1 (unsafePartial $ Array.unsafeIndex stack (l - 1 - i)) d
forE 0 l \i -> (unsafePartial $ Array.unsafeIndex stack (l - 1 - i))

pure
( PSR
Expand All @@ -383,7 +374,7 @@ newPSR = mkSTFn3 \ancestry signalDisposalQueueShouldBeTriggered region -> do
handleScope :: EffectFn1 PSR Unit
handleScope = mkEffectFn1 \psr -> do
pump psr (un PSR psr).signalDisposalQueueShouldBeTriggered
(un PSR psr).triggerDisposalQueueEffects
$ mkEffectFn1 \_ -> (un PSR psr).triggerDisposalQueueEffects

newtype Nut =
Nut (EffectFn2 PSR DOMInterpret Unit)
Expand Down Expand Up @@ -507,7 +498,7 @@ useRef a b f = Deku.do

deferO :: EffectFn2 PSR (Effect Unit) Unit
deferO = mkEffectFn2 \psr eff -> liftST
(runSTFn1 (un PSR psr).addEffectToDisposalQueue (mkEffectFn1 \_ -> eff))
(runSTFn1 (un PSR psr).addEffectToDisposalQueue eff)

defer :: PSR -> Effect Unit -> Effect Unit
defer =
Expand Down Expand Up @@ -625,11 +616,11 @@ useDynWith elements options cont = Nut $ mkEffectFn2 \psr di' -> do

eltRemove <- liftST Poll.create
let
remove :: Poll ScopeDepth
remove :: Poll Unit
remove =
Poll.merge
[ const (ScopeDepth 0) <$> options.remove value
, const (ScopeDepth 0) <$> eltRemove.poll
[ options.remove value $> unit
, eltRemove.poll $> unit
, (un PSR psr).signalDisposalQueueShouldBeTriggered
]

Expand Down Expand Up @@ -659,16 +650,15 @@ useDynWith elements options cont = Nut $ mkEffectFn2 \psr di' -> do

-- | We need explicit ordering here, if just pass the lifecycle of the parent to the child element it is not
-- | guarantueed that the child will dispose itself before the parent.
handleRemove :: EffectFn1 ScopeDepth Unit
handleRemove = mkEffectFn1 \depth -> do
whenM (not <$> liftST (ST.read eltDisposed)) do
handleRemove :: Effect Unit
handleRemove = whenM (not <$> liftST (ST.read eltDisposed)) do
-- disable user control
void $ liftST $ ST.write true eltDisposed
eltLifecycle.push depth
eltLifecycle.push unit
liftST eltRegion.remove

pump eltPSR sendTo handleSendTo
pump eltPSR (once remove) handleRemove
pump eltPSR (once remove) $ mkEffectFn1 \_ -> handleRemove
runEffectFn2 nut eltPSR di
-- enable user control
void $ liftST $ ST.write false eltDisposed
Expand Down Expand Up @@ -756,16 +746,14 @@ elementify ns tag arrAtts nuts = Nut $ mkEffectFn2 \psr di -> do
a <- liftST $ STRef.modify (add 1) aref
scope <- liftST $ runSTFn3 newPSR
(Ancestry.element a (un PSR psr).ancestry)
( over ScopeDepth (add 1) <$>
(un PSR psr).signalDisposalQueueShouldBeTriggered
)
(un PSR psr).signalDisposalQueueShouldBeTriggered
eltRegion
runEffectFn2 nut scope di
runEffectFn2 Event.fastForeachE nuts handleNuts

let
handleRemove :: EffectFn1 ScopeDepth Unit
handleRemove = mkEffectFn1 \_ -> when
handleRemove :: Effect Unit
handleRemove = when
(not (hasElementParent (un PSR psr).ancestry))
do
runEffectFn1 (un DOMInterpret di).removeElement elt
Expand Down Expand Up @@ -844,8 +832,8 @@ text texts = Nut $ mkEffectFn2 \psr di -> do
liftST $ runSTFn1 (un StaticRegion (un PSR psr).region).element (Text txt)

let
handleRemove :: EffectFn1 ScopeDepth Unit
handleRemove = mkEffectFn1 \_ -> when
handleRemove :: Effect Unit
handleRemove = when
(not (hasElementParent (un PSR psr).ancestry))
do
runEffectFn1 (un DOMInterpret di).removeText txt
Expand Down Expand Up @@ -945,8 +933,7 @@ portaled myAncestry buffer beam beamed bumped trackBegin trackEnd =
void $ liftST $ ST.write region.begin trackBegin

-- lifecycle handling
liftST $ runSTFn1 (un PSR psr).addEffectToDisposalQueue $ mkEffectFn1 \_ ->
(unsubBeamed *> unsubBumped)
liftST $ runSTFn1 (un PSR psr).addEffectToDisposalQueue (unsubBeamed *> unsubBumped)

let
restoreBuffer :: Effect Unit
Expand Down
8 changes: 4 additions & 4 deletions deku-core/src/Deku/Toplevel.purs
Original file line number Diff line number Diff line change
Expand Up @@ -23,7 +23,7 @@ import Data.Set as Set
import Data.String as String
import Data.Traversable (traverse)
import Data.Tuple.Nested ((/\))
import Deku.Core (Nut(..), ScopeDepth(ScopeDepth), newPSR)
import Deku.Core (Nut(..), newPSR)
import Deku.FullDOMInterpret (fullDOMInterpret)
import Deku.HydratingDOMInterpret (HydrationRenderingInfo(..), hydratingDOMInterpret)
import Deku.Internal.Ancestry (Ancestry)
Expand Down Expand Up @@ -56,7 +56,7 @@ runInElement elt (Nut nut) = do
region <- liftST $ runSTFn1 Region.fromParent (DekuParent $ toDekuElement elt)
scope <- liftST $ runSTFn3 newPSR Ancestry.root lifecycle region
void $ runEffectFn2 nut scope fullDOMInterpret
pure $ dispose (ScopeDepth 0)
pure $ dispose unit

doInBody :: forall i o. (Web.DOM.Element -> i -> Effect o) -> i -> Effect o
doInBody f elt = do
Expand Down Expand Up @@ -133,7 +133,7 @@ ssrInElement elt (Nut nut) = do
)
textCache
htmlString <- innerHTML elt
dispose (ScopeDepth 0)
dispose unit
livePortals <- liftST $ ST.read portalsRef
pure $
{ html: String.replace (String.Pattern "data-deku-value")
Expand Down Expand Up @@ -197,7 +197,7 @@ hydrateInElement { cache, livePortals } ielt (Nut nut) = do
( hydratingDOMInterpret portalCtrRef (Map.fromFoldable kv) textNodes
livePortals
)
pure $ dispose (ScopeDepth 0)
pure $ dispose unit

hydrateInBody
:: forall r
Expand Down

0 comments on commit ae99b78

Please sign in to comment.