{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE CPP #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DeriveFunctor #-} {-# LANGUAGE RecordWildCards #-} {-# OPTIONS_GHC -fno-warn-orphans #-} ----------------------------------------------------------------------------- -- | -- Module : Miso.Html.Internal -- Copyright : (C) 2016-2017 David M. Johnson -- License : BSD3-style (see the file LICENSE) -- Maintainer : David M. Johnson -- Stability : experimental -- Portability : non-portable ---------------------------------------------------------------------------- module Miso.Html.Internal ( -- * Core types and interface VTree (..) , View (..) , ToView (..) , Attribute (..) -- * Smart `View` constructors , node , text -- * Key patch internals , Key (..) , ToKey (..) -- * Namespace , NS (..) -- * Setting properties on virtual DOM nodes , prop -- * Setting css , style_ -- * Handling events , on , onWithOptions -- * Events , defaultEvents -- * Subscription type , Sub ) where import Control.Monad import Data.Aeson.Types (parseEither) import Data.JSString import Data.JSString.Text import qualified Data.Map as M import Data.Monoid import Data.Proxy import Data.String (IsString(..)) import qualified Data.Text as T import GHCJS.Foreign.Callback import GHCJS.Marshal import GHCJS.Types import JavaScript.Array.Internal (fromList) import JavaScript.Object import JavaScript.Object.Internal (Object (Object)) import Servant.API import Miso.Event.Decoder import Miso.Event.Types import Miso.String import Miso.FFI -- | Type synonym for constructing event subscriptions. -- -- The first argument passed to a subscription provides a way to -- access the current value of the model (without blocking). The -- callback is used to dispatch actions which are then fed back to the -- @update@ function. type Sub action model = IO model -> (action -> IO ()) -> IO () -- | Virtual DOM implemented as a JavaScript `Object`. -- Used for diffing, patching and event delegation. -- Not meant to be constructed directly, see `View` instead. newtype VTree = VTree { getTree :: Object } -- | Core type for constructing a `VTree`, use this instead of `VTree` directly. newtype View action = View { runView :: (action -> IO ()) -> IO VTree } deriving Functor -- | For constructing type-safe links instance HasLink (View a) where type MkLink (View a) = MkLink (Get '[] ()) toLink _ = toLink (Proxy :: Proxy (Get '[] ())) -- | Convenience class for using View class ToView v where toView :: v -> View m set :: ToJSVal v => JSString -> v -> Object -> IO () set k v obj = toJSVal v >>= \x -> setProp k x obj -- | Create a new @VNode@. -- -- @node ns tag key attrs children@ creates a new node with tag @tag@ -- and 'Key' @key@ in the namespace @ns@. All @attrs@ are called when -- the node is created and its children are initialized to @children@. node :: NS -> MisoString -> Maybe Key -> [Attribute m] -> [View m] -> View m node ns tag key attrs kids = View $ \sink -> do vnode <- create cssObj <- jsval <$> create propsObj <- jsval <$> create eventObj <- jsval <$> create set "css" cssObj vnode set "props" propsObj vnode set "events" eventObj vnode set "type" ("vnode" :: JSString) vnode set "ns" ns vnode set "tag" tag vnode set "key" key vnode setAttrs vnode sink flip (set "children") vnode =<< setKids sink pure $ VTree vnode where setAttrs vnode sink = forM_ attrs $ \(Attribute attr) -> attr sink vnode setKids sink = jsval . fromList <$> fmap (jsval . getTree) <$> traverse (flip runView sink) kids instance ToJSVal Options instance ToJSVal Key where toJSVal (Key x) = toJSVal x instance ToJSVal NS where toJSVal SVG = toJSVal ("svg" :: JSString) toJSVal HTML = toJSVal ("html" :: JSString) -- | Namespace of DOM elements. data NS = HTML -- ^ HTML Namespace | SVG -- ^ SVG Namespace deriving (Show, Eq) -- | Create a new @VText@ with the given content. text :: MisoString -> View m text t = View . const $ do vtree <- create set "type" ("vtext" :: JSString) vtree set "text" t vtree pure $ VTree vtree -- | `IsString` instance instance IsString (View a) where fromString = text . fromString -- | A unique key for a dom node. -- -- This key is only used to speed up diffing the children of a DOM -- node, the actual content is not important. The keys of the children -- of a given DOM node must be unique. Failure to satisfy this -- invariant gives undefined behavior at runtime. newtype Key = Key MisoString -- | Convert custom key types to `Key`. -- -- Instances of this class do not have to guarantee uniqueness of the -- generated keys, it is up to the user to do so. `toKey` must be an -- injective function. class ToKey key where toKey :: key -> Key -- | Identity instance instance ToKey Key where toKey = id -- | Convert `MisoString` to `Key` instance ToKey MisoString where toKey = Key -- | Convert `Text` to `Key` instance ToKey T.Text where toKey = Key . textToJSString -- | Convert `String` to `Key` instance ToKey String where toKey = Key . pack -- | Convert `Int` to `Key` instance ToKey Int where toKey = Key . pack . show -- | Convert `Double` to `Key` instance ToKey Double where toKey = Key . pack . show -- | Convert `Float` to `Key` instance ToKey Float where toKey = Key . pack . show -- | Convert `Word` to `Key` instance ToKey Word where toKey = Key . pack . show -- | Attribute of a vnode in a `View`. -- -- The callback can be used to dispatch actions which are fed back to -- the @update@ function. This is especially useful for event handlers -- like the @onclick@ attribute. The second argument represents the -- vnode the attribute is attached to. newtype Attribute action = Attribute ((action -> IO ()) -> Object -> IO ()) -- | @prop k v@ is an attribute that will set the attribute @k@ of the DOM node associated with the vnode -- to @v@. prop :: ToJSVal a => MisoString -> a -> Attribute action prop k v = Attribute . const $ \n -> do val <- toJSVal v o <- getProp ("props" :: MisoString) n set k val (Object o) -- | Convenience wrapper for @onWithOptions defaultOptions@. -- -- > let clickHandler = on "click" emptyDecoder $ \() -> Action -- > in button_ [ clickHandler, class_ "add" ] [ text_ "+" ] -- on :: MisoString -> Decoder r -> (r -> action) -> Attribute action on = onWithOptions defaultOptions foreign import javascript unsafe "$r = objectToJSON($1,$2);" objectToJSON :: JSVal -- ^ decodeAt :: [JSString] -> JSVal -- ^ object with impure references to the DOM -> IO JSVal -- | @onWithOptions opts eventName decoder toAction@ is an attribute -- that will set the event handler of the associated DOM node to a function that -- decodes its argument using @decoder@, converts it to an action -- using @toAction@ and then feeds that action back to the @update@ function. -- -- @opts@ can be used to disable further event propagation. -- -- > let clickHandler = onWithOptions defaultOptions "click" emptyDecoder $ \() -> Action -- > in button_ [ clickHandler, class_ "add" ] [ text_ "+" ] -- onWithOptions :: Options -> MisoString -> Decoder r -> (r -> action) -> Attribute action onWithOptions options eventName Decoder{..} toAction = Attribute $ \sink n -> do eventObj <- getProp "events" n eventHandlerObject@(Object eo) <- create jsOptions <- toJSVal options decodeAtVal <- toJSVal decodeAt cb <- jsval <$> (asyncCallback1 $ \e -> do Just v <- jsvalToValue =<< objectToJSON decodeAtVal e case parseEither decoder v of Left s -> error $ "Parse error on " <> unpack eventName <> ": " <> s Right r -> sink (toAction r)) setProp "runEvent" cb eventHandlerObject setProp "options" jsOptions eventHandlerObject setProp eventName eo (Object eventObj) -- | @style_ attrs@ is an attribute that will set the @style@ -- attribute of the associated DOM node to @attrs@. -- -- @style@ attributes not contained in @attrs@ will be deleted. -- -- > import qualified Data.Map as M -- > div_ [ style_ $ M.singleton "background" "red" ] [ ] -- -- -- style_ :: M.Map MisoString MisoString -> Attribute action style_ m = Attribute . const $ \n -> do cssObj <- getProp "css" n forM_ (M.toList m) $ \(k,v) -> setProp k (jsval v) (Object cssObj)