{-# LANGUAGE CPP #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TemplateHaskell #-}
{-# OPTIONS_GHC -Wno-duplicate-exports #-}
module Miso
(
miso
, (🍜)
, App
, startApp
, renderApp
, Component
, startComponent
, component
, (+>)
, mount
, mount_
, withSink
, Sink
, mail
, checkMail
, parent
, mailParent
, broadcast
, startSub
, stopSub
, Sub
, issue
, batch
, io
, io_
, sync
, sync_
, for
#ifdef WASM
, evalFile
#endif
, module Miso.Binding
, module Miso.DSL
, module Miso.Effect
, module Miso.Event
, module Miso.Fetch
, module Miso.PubSub
, module Miso.Property
, module Miso.Run
, module Miso.Subscription
, module Miso.Storage
, module Miso.Types
, module Miso.Util
, module Miso.FFI
, module Miso.State
) where
import Control.Monad (void)
import Miso.Binding
import Miso.Diff
import Miso.DSL
import Miso.Effect
import Miso.Event
import Miso.Fetch
import Miso.FFI
import qualified Miso.FFI.Internal as FFI
import Miso.Property
import Miso.PubSub
import Miso.Router
import Miso.Run
import Miso.Runtime
import Miso.State
import Miso.Storage
import Miso.Subscription
import Miso.Types
import Miso.Util
miso :: Eq model => (URI -> App model action) -> IO ()
miso :: forall model action. Eq model => (URI -> App model action) -> IO ()
miso URI -> App model action
f = IO (ComponentState model action) -> IO ()
forall a. IO a -> IO ()
withJS (IO (ComponentState model action) -> IO ())
-> IO (ComponentState model action) -> IO ()
forall a b. (a -> b) -> a -> b
$ do
vcomp <- URI -> App model action
f (URI -> App model action) -> IO URI -> IO (App model action)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO URI
getURI
body <- FFI.getBody
initialize rootComponentId Hydrate isRoot vcomp (pure body)
startApp :: Eq model => App model action -> IO ()
startApp :: forall model action. Eq model => App model action -> IO ()
startApp = Component ROOT model action -> IO ()
forall model action. Eq model => App model action -> IO ()
startComponent
(🍜) :: Eq model => (URI -> App model action) -> IO ()
🍜 :: forall model action. Eq model => (URI -> App model action) -> IO ()
(🍜) = (URI -> App model action) -> IO ()
forall model action. Eq model => (URI -> App model action) -> IO ()
miso
startComponent :: Eq model => Component ROOT model action -> IO ()
startComponent :: forall model action. Eq model => App model action -> IO ()
startComponent Component ROOT model action
vcomp = IO (ComponentState model action) -> IO ()
forall a. IO a -> IO ()
withJS (Component ROOT model action -> IO (ComponentState model action)
forall parent model action.
(Eq parent, Eq model) =>
Component parent model action -> IO (ComponentState model action)
initComponent Component ROOT model action
vcomp)
renderApp
:: Eq model
=> MisoString
-> App model action
-> IO ()
renderApp :: forall model action.
Eq model =>
MisoString -> App model action -> IO ()
renderApp MisoString
renderer App model action
vcomp =
IO (ComponentState model action) -> IO ()
forall a. IO a -> IO ()
withJS (MisoString -> IO ()
FFI.setDrawingContext MisoString
renderer IO ()
-> IO (ComponentState model action)
-> IO (ComponentState model action)
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> App model action -> IO (ComponentState model action)
forall parent model action.
(Eq parent, Eq model) =>
Component parent model action -> IO (ComponentState model action)
initComponent App model action
vcomp)
initComponent
:: (Eq parent, Eq model)
=> Component parent model action
-> IO (ComponentState model action)
initComponent :: forall parent model action.
(Eq parent, Eq model) =>
Component parent model action -> IO (ComponentState model action)
initComponent vcomp :: Component parent model action
vcomp@Component {model
Bool
[Binding parent model]
[JS]
[CSS]
[Sub action]
Maybe action
Maybe (IO model)
Maybe MisoString
Events
LogLevel
model -> View model action
action -> Effect parent model action
Mail -> Maybe action
model :: model
hydrateModel :: Maybe (IO model)
update :: action -> Effect parent model action
view :: model -> View model action
subs :: [Sub action]
events :: Events
styles :: [CSS]
scripts :: [JS]
initialAction :: Maybe action
mountPoint :: Maybe MisoString
logLevel :: LogLevel
mailbox :: Mail -> Maybe action
bindings :: [Binding parent model]
eventPropagation :: Bool
eventPropagation :: forall parent model action. Component parent model action -> Bool
bindings :: forall parent model action.
Component parent model action -> [Binding parent model]
mailbox :: forall parent model action.
Component parent model action -> Mail -> Maybe action
logLevel :: forall parent model action.
Component parent model action -> LogLevel
mountPoint :: forall parent model action.
Component parent model action -> Maybe MisoString
initialAction :: forall parent model action.
Component parent model action -> Maybe action
scripts :: forall parent model action. Component parent model action -> [JS]
styles :: forall parent model action. Component parent model action -> [CSS]
events :: forall parent model action. Component parent model action -> Events
subs :: forall parent model action.
Component parent model action -> [Sub action]
view :: forall parent model action.
Component parent model action -> model -> View model action
update :: forall parent model action.
Component parent model action
-> action -> Effect parent model action
hydrateModel :: forall parent model action.
Component parent model action -> Maybe (IO model)
model :: forall parent model action. Component parent model action -> model
..} = do
root <- MisoString -> IO JSVal
mountElement (Maybe MisoString -> MisoString
getMountPoint Maybe MisoString
mountPoint)
initialize rootComponentId Draw isRoot vcomp (pure root)
isRoot :: Bool
isRoot :: Bool
isRoot = Bool
True
#ifdef PRODUCTION
#define MISO_JS_PATH "js/miso.prod.js"
#else
#define MISO_JS_PATH "js/miso.js"
#endif
withJS :: IO a -> IO ()
withJS :: forall a. IO a -> IO ()
withJS IO a
action = IO a -> IO ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (IO a -> IO ()) -> IO a -> IO ()
forall a b. (a -> b) -> a -> b
$ do
#ifdef WASM
$(evalFile MISO_JS_PATH)
#endif
action