miso-1.8.1.0: A tasty Haskell front-end framework
Copyright(C) 2016-2018 David M. Johnson
LicenseBSD3-style (see the file LICENSE)
MaintainerDavid M. Johnson <djohnson.m@gmail.com>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Miso.Types

Description

 
Synopsis

Documentation

data App model action Source #

Application entry point

Constructors

App 

Fields

  • model :: model

    initial model

  • update :: action -> model -> Effect action model

    Function to update model, optionally providing effects. See the Transition monad for succinctly expressing model transitions.

  • view :: model -> View action

    Function to draw View

  • subs :: [Sub action]

    List of subscriptions to run during application lifetime

  • events :: Map MisoString Bool

    List of delegated events that the body element will listen for. You can start with defaultEvents and modify as needed.

  • initialAction :: action

    Initial action that is run after the application has loaded

  • mountPoint :: Maybe MisoString

    Id of the root element for DOM diff. If Nothing is provided, the entire document body is used as a mount point.

  • logLevel :: LogLevel

    Display warning messages when prerendering if the DOM and VDOM are not in sync.

data LogLevel Source #

Optional Logging for debugging miso internals (useful to see if prerendering is successful)

Constructors

Off 
DebugPrerender 

Instances

Instances details
Eq LogLevel Source # 
Instance details

Defined in Miso.Types

Show LogLevel Source # 
Instance details

Defined in Miso.Types

data Effect action model Source #

An effect represents the results of an update action.

It consists of the updated model and a list of subscriptions. Each Sub is run in a new thread so there is no risk of accidentally blocking the application.

Instances

Instances details
Bifunctor Effect Source # 
Instance details

Defined in Miso.Effect

Methods

bimap :: (a -> b) -> (c -> d) -> Effect a c -> Effect b d #

first :: (a -> b) -> Effect a c -> Effect b c #

second :: (b -> c) -> Effect a b -> Effect a c #

Monad (Effect action) Source # 
Instance details

Defined in Miso.Effect

Methods

(>>=) :: Effect action a -> (a -> Effect action b) -> Effect action b #

(>>) :: Effect action a -> Effect action b -> Effect action b #

return :: a -> Effect action a #

Functor (Effect action) Source # 
Instance details

Defined in Miso.Effect

Methods

fmap :: (a -> b) -> Effect action a -> Effect action b #

(<$) :: a -> Effect action b -> Effect action a #

Applicative (Effect action) Source # 
Instance details

Defined in Miso.Effect

Methods

pure :: a -> Effect action a #

(<*>) :: Effect action (a -> b) -> Effect action a -> Effect action b #

liftA2 :: (a -> b -> c) -> Effect action a -> Effect action b -> Effect action c #

(*>) :: Effect action a -> Effect action b -> Effect action b #

(<*) :: Effect action a -> Effect action b -> Effect action a #

type Sub action = Sink action -> JSM () Source #

Type synonym for constructing event subscriptions.

The Sink callback is used to dispatch actions which are then fed back to the update function.

The Transition Monad

type Transition action model = StateT model (Writer [Sub action]) Source #

A monad for succinctly expressing model transitions in the update function.

Transition is a state monad so it abstracts over manually passing the model around. It's also a writer monad where the accumulator is a list of scheduled IO actions. Multiple actions can be scheduled using Control.Monad.Writer.Class.tell from the mtl library and a single action can be scheduled using scheduleIO.

Tip: use the Transition monad in combination with the stateful lens operators (all operators ending in "="). The following example assumes the lenses field1, counter and field2 are in scope and that the LambdaCase language extension is enabled:

myApp = App
  { update = fromTransition . \case
      MyAction1 -> do
        field1 .= value1
        counter += 1
      MyAction2 -> do
        field2 %= f
        scheduleIO $ do
          putStrLn "Hello"
          putStrLn "World!"
  , ...
  }

mapAction :: (actionA -> actionB) -> Transition actionA model r -> Transition actionB model r Source #

Turn a transition that schedules subscriptions that consume actions of type a into a transition that schedules subscriptions that consume actions of type b using the supplied function of type a -> b.

fromTransition Source #

Arguments

:: Transition action model () 
-> model -> Effect action model

model update function.

Convert a Transition computation to a function that can be given to update.

toTransition Source #

Arguments

:: (model -> Effect action model)

model update function

-> Transition action model () 

Convert an update function to a Transition computation.

scheduleIO :: JSM action -> Transition action model () Source #

Schedule a single IO action for later execution.

Note that multiple IO action can be scheduled using Control.Monad.Writer.Class.tell from the mtl library.

scheduleIO_ :: JSM () -> Transition action model () Source #

Like scheduleIO but doesn't cause an action to be dispatched to the update function.

This is handy for scheduling IO computations where you don't care about their results or when they complete.

scheduleIOFor_ :: Foldable f => JSM (f action) -> Transition action model () Source #

Like scheduleIO_ but generalized to any instance of Foldable

This is handy for scheduling IO computations that return a Maybe value

scheduleSub :: Sub action -> Transition action model () Source #

Like scheduleIO but schedules a subscription which is an IO computation that has access to a Sink which can be used to asynchronously dispatch actions to the update function.

A use-case is scheduling an IO computation which creates a 3rd-party JS widget which has an associated callback. The callback can then call the sink to turn events into actions. To do this without accessing a sink requires going via a Subscription which introduces a leaky-abstraction.