{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE KindSignatures #-}
#ifdef IOS
#else
{-# LANGUAGE TemplateHaskell #-}
#endif
module Miso
( miso
, startApp
, sink
, module Miso.Effect
, module Miso.Event
, module Miso.Html
, module Miso.Subscription
#ifndef ghcjs_HOST_OS
, module Miso.TypeLevel
#endif
, module Miso.Types
, module Miso.Router
, module Miso.Util
, module Miso.FFI
, module Miso.WebSocket
) where
import Control.Concurrent
import Control.Monad
import Control.Monad.IO.Class
import Data.IORef
import Data.List
import Data.Sequence ((|>))
import qualified Data.Sequence as S
import qualified JavaScript.Object.Internal as OI
import System.IO.Unsafe
import System.Mem.StableName
#ifndef ghcjs_HOST_OS
import Language.Javascript.JSaddle (eval, waitForAnimationFrame)
#ifdef IOS
import Miso.JSBits
#else
import GHCJS.Types (JSString)
import Data.FileEmbed
#endif
#else
import JavaScript.Web.AnimationFrame
#endif
import Miso.Concurrent
import Miso.Delegate
import Miso.Diff
import Miso.Effect
import Miso.Event
import Miso.FFI
import Miso.Html
import Miso.Router
import Miso.Subscription
#ifndef ghcjs_HOST_OS
import Miso.TypeLevel
#endif
import Miso.Types
import Miso.Util
import Miso.WebSocket
common
:: Eq model
=> App model action
-> model
-> (Sink action -> JSM (IORef VTree))
-> JSM ()
common App {..} m getView = do
#ifndef ghcjs_HOST_OS
#ifdef IOS
mapM_ eval [delegateJs,diffJs,isomorphicJs,utilJs]
#else
_ <- eval ($(embedStringFile "jsbits/delegate.js") :: JSString)
_ <- eval ($(embedStringFile "jsbits/diff.js") :: JSString)
_ <- eval ($(embedStringFile "jsbits/isomorphic.js") :: JSString)
_ <- eval ($(embedStringFile "jsbits/util.js") :: JSString)
#endif
#endif
Notify {..} <- liftIO newNotify
actionsRef <- liftIO (newIORef S.empty)
let writeEvent a = void . liftIO . forkIO $ do
atomicModifyIORef' actionsRef $ \as -> (as |> a, ())
notify
liftIO (writeIORef sinkRef writeEvent)
forM_ subs $ \sub ->
sub writeEvent
void . liftIO . forkIO . forever $ threadDelay (1000000 * 86400) >> notify
viewRef <- getView writeEvent
mountEl <- mountElement mountPoint
delegator mountEl viewRef events
writeEvent initialAction
let
loop !oldModel = liftIO wait >> do
actions <- liftIO $ atomicModifyIORef' actionsRef $ \actions -> (S.empty, actions)
let (Acc newModel effects) = foldl' (foldEffects writeEvent update)
(Acc oldModel (pure ())) actions
effects
oldName <- liftIO $ oldModel `seq` makeStableName oldModel
newName <- liftIO $ newModel `seq` makeStableName newModel
when (oldName /= newName && oldModel /= newModel) $ do
swapCallbacks
newVTree <- runView (view newModel) writeEvent
oldVTree <- liftIO (readIORef viewRef)
void $ waitForAnimationFrame
(diff mountPoint) (Just oldVTree) (Just newVTree)
releaseCallbacks
liftIO (atomicWriteIORef viewRef newVTree)
syncPoint
loop newModel
loop m
miso :: Eq model => (URI -> App model action) -> JSM ()
miso f = do
app@App {..} <- f <$> getCurrentURI
common app model $ \writeEvent -> do
let initialView = view model
VTree (OI.Object iv) <- flip runView writeEvent initialView
mountEl <- mountElement mountPoint
copyDOMIntoVTree (logLevel == DebugPrerender) mountEl iv
let initialVTree = VTree (OI.Object iv)
liftIO (newIORef initialVTree)
sinkRef :: IORef (Sink action)
{-# NOINLINE sinkRef #-}
sinkRef = unsafePerformIO $ newIORef (\_ -> pure ())
sink :: Sink action
sink = unsafePerformIO (readIORef sinkRef)
startApp :: Eq model => App model action -> JSM ()
startApp app@App {..} =
common app model $ \writeEvent -> do
let initialView = view model
initialVTree <- flip runView writeEvent initialView
(diff mountPoint) Nothing (Just initialVTree)
liftIO (newIORef initialVTree)
foldEffects
:: Sink action
-> (action -> model -> Effect action model)
-> Acc model -> action -> Acc model
foldEffects sink update = \(Acc model as) action ->
case update action model of
Effect newModel effs -> Acc newModel newAs
where
newAs = as >> do
forM_ effs $ \eff -> forkJSM (eff sink)
data Acc model = Acc !model !(JSM ())