{-# LANGUAGE GADTs #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Reflex.Bulmex.Tag.Odd
( image
, imageClass
, ahref
, ahref'
, ahrefDyn
, textSpace
, elDynAttrPrevDef
, elDynAttrModConf
) where
import Control.Lens ((%~), (.~))
import Data.Map (Map)
import qualified Data.Map.Strict as Map
import Data.Proxy (Proxy (..))
import Data.Text (Text)
import qualified Data.Text as Text
import Reflex
import Reflex.Bulmex.Attr
import Reflex.Bulmex.Space
import qualified Reflex.Dom.Builder.Class as Dom
import Reflex.Dom.Core
import qualified Reflex.Dom.Widget as Dom
import qualified Reflex.Tags as T
image :: Dom.DomBuilder t m => Text.Text -> m ()
image url = T.imgAttr (Map.singleton "src" url) Dom.blank
imageClass :: Dom.DomBuilder t m => Text.Text -> Text.Text -> m ()
imageClass clazz url =
T.imgAttr (Map.fromList [("src", url), ("class", clazz)]) Dom.blank
textSpace :: Dom.DomBuilder t m => m ()
textSpace = Dom.text space
ahref :: (Dom.DomBuilder t m, PostBuild t m) => Text.Text -> m a -> m a
ahref = ahref' mempty
ahref' ::
(Dom.DomBuilder t m, PostBuild t m) => AttrMap -> Text.Text -> m a -> m a
ahref' uno = ahrefDyn (constDyn uno) . constDyn
ahrefDyn ::
(Dom.DomBuilder t m, PostBuild t m)
=> Dynamic t AttrMap
-> Dynamic t Text.Text
-> m a
-> m a
ahrefDyn uno txt =
T.aDynAttr $ (attrUnion <$> uno) <*> (Map.singleton "href" <$> txt)
elDynAttrPrevDef ::
forall a en m t. (DomBuilder t m, PostBuild t m)
=> EventName en
-> Text
-> Dynamic t (Map Text Text)
-> m a
-> m (Element EventResult (DomBuilderSpace m) t, a)
elDynAttrPrevDef ev =
elDynAttrModConf
(\elCfg ->
elCfg &
elementConfig_eventSpec %~
addEventSpecFlags
(Proxy :: Proxy (DomBuilderSpace m))
ev
(const preventDefault))
elDynAttrModConf ::
(DomBuilder t m, PostBuild t m)
=> (ElementConfig EventResult t (DomBuilderSpace m) -> ElementConfig EventResult t (DomBuilderSpace m))
-> Text
-> Dynamic t (Map Text Text)
-> m a
-> m (Element EventResult (DomBuilderSpace m) t, a)
elDynAttrModConf f elementTag attrs child = do
modifyAttrs <- dynamicAttributesToModifyAttributes attrs
let cfg =
def & modifyAttributes .~ fmapCheap mapKeysToAttributeName modifyAttrs
result <- element elementTag (f cfg) child
postBuild <- getPostBuild
notReadyUntil postBuild
pure result