11module Test.Main where
22
33import Prelude
4- import Control.Monad.Eff (Eff )
4+ import Control.Monad.Eff (Eff , kind Effect )
55import Control.Monad.Eff.Ref (REF )
66import Control.Monad.Eff.Ref as Ref
77import Control.Monad.Eff.Timer as Timer
88import Data.Exists (Exists , mkExists , runExists )
99import Data.Maybe (Maybe (..), isNothing )
10- import Data.Nullable ( toMaybe )
10+ import Data.Newtype ( wrap )
1111import Data.Foldable (for_ , traverse_ )
1212import Data.Function.Uncurried as Fn
1313import Data.Tuple (Tuple )
@@ -113,15 +113,15 @@ buildWidget
113113 → V.VDomMachine (dom ∷ DOM , ref ∷ REF | eff ) (Exists Thunk ) DOM.Node
114114buildWidget spec = render
115115 where
116- render = runExists \(Thunk a render) → do
117- V.Step node m h ← V .buildVDom spec (render a)
116+ render = runExists \(Thunk a render' ) → do
117+ V.Step node m h ← V .buildVDom spec (render' a)
118118 pure (V.Step node (Fn .runFn4 patch (unsafeCoerce a) node m h) h)
119119
120- patch = Fn .mkFn4 \a node step halt → runExists \(Thunk b render) →
120+ patch = Fn .mkFn4 \a node step halt → runExists \(Thunk b render' ) →
121121 if Fn .runFn2 refEq a b
122122 then pure (V.Step node (Fn .runFn4 patch a node step halt) halt)
123123 else do
124- V.Step node' m h ← step (render b)
124+ V.Step node' m h ← step (render' b)
125125 pure (V.Step node' (Fn .runFn4 patch (unsafeCoerce b) node' m h) h)
126126
127127mkSpec
@@ -134,7 +134,7 @@ mkSpec document = V.VDomSpec
134134 , document
135135 }
136136
137- foreign import data DBMON ∷ !
137+ foreign import data DBMON ∷ Effect
138138
139139foreign import getData ∷ ∀ eff . Eff (dbmon ∷ DBMON | eff ) State
140140
@@ -153,7 +153,7 @@ mkRenderQueue
153153 → Eff (dom ∷ DOM , ref ∷ REF | eff ) (a → Eff (dom ∷ DOM , ref ∷ REF | eff ) Unit )
154154mkRenderQueue spec parent render initialValue = do
155155 initMachine ← V .buildVDom spec (render initialValue)
156- DOM .appendChild (V .extract initMachine) parent
156+ _ ← DOM .appendChild (V .extract initMachine) parent
157157 ref ← Ref .newRef initMachine
158158 val ← Ref .newRef Nothing
159159 pure \a → do
@@ -175,7 +175,7 @@ mkRenderQueue'
175175 → Eff (dom ∷ DOM , ref ∷ REF | eff ) (a → Eff (dom ∷ DOM , ref ∷ REF | eff ) Unit )
176176mkRenderQueue' spec parent render initialValue = do
177177 initMachine ← V .buildVDom spec (render initialValue)
178- DOM .appendChild (V .extract initMachine) parent
178+ _ ← DOM .appendChild (V .extract initMachine) parent
179179 ref ← Ref .newRef initMachine
180180 pure \v → do
181181 machine ← Ref .readRef ref
@@ -186,8 +186,8 @@ main :: ∀ eff. Eff (ref ∷ REF, dom ∷ DOM, dbmon ∷ DBMON, timer ∷ Timer
186186main = do
187187 win ← DOM .window
188188 doc ← DOM .document win
189- bod ← DOM .querySelector " body" (DOM .htmlDocumentToParentNode doc)
190- for_ (toMaybe bod) \body → do
189+ bod ← DOM .querySelector (wrap " body" ) (DOM .htmlDocumentToParentNode doc)
190+ for_ bod \body → do
191191 let spec = mkSpec (DOM .htmlDocumentToDocument doc)
192192 pushQueue ← mkRenderQueue' spec (DOM .elementToNode body) renderData initialState
193193 let
0 commit comments