{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE LambdaCase #-}
module Lucid.Alpine where
import Data.Text
import Lucid.Base (Attribute, makeAttribute)
xData_ :: Maybe Text -> Attribute
xData_ :: Maybe Text -> Attribute
xData_ = \case
Maybe Text
Nothing -> Text -> Text -> Attribute
makeAttribute Text
"data-x-data" Text
forall a. Monoid a => a
mempty
Just Text
object -> Text -> Text -> Attribute
makeAttribute Text
"data-x-data" Text
object
xBind_
:: Text
-> Text
-> Attribute
xBind_ :: Text -> Text -> Attribute
xBind_ Text
attr = Text -> Text -> Attribute
makeAttribute (Text
"data-x-bind:" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
attr)
xOn_
:: Text
-> Text
-> Attribute
xOn_ :: Text -> Text -> Attribute
xOn_ Text
event = Text -> Text -> Attribute
makeAttribute (Text
"data-x-on:" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
event)
xText_ :: Text -> Attribute
xText_ :: Text -> Attribute
xText_ = Text -> Text -> Attribute
makeAttribute Text
"data-x-text"
xHtml_ :: Text -> Attribute
xHtml_ :: Text -> Attribute
xHtml_ = Text -> Text -> Attribute
makeAttribute Text
"data-x-html"
xModel_
:: [Text]
-> Text
-> Attribute
xModel_ :: [Text] -> Text -> Attribute
xModel_ [Text]
mods = case [Text]
mods of
[] -> Text -> Text -> Attribute
makeAttribute Text
"data-x-model"
[Text]
_ -> Text -> Text -> Attribute
makeAttribute (Text
"data-x-model." Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> [Text] -> Text
intercalate Text
"." [Text]
mods)
xShow_ :: Text -> Attribute
xShow_ :: Text -> Attribute
xShow_ = Text -> Text -> Attribute
makeAttribute Text
"data-x-show"
xTransition_
:: Maybe Text
-> [Text]
-> Text
-> Attribute
xTransition_ :: Maybe Text -> [Text] -> Text -> Attribute
xTransition_ Maybe Text
Nothing [] Text
_ = Text -> Text -> Attribute
makeAttribute Text
"data-x-transition" Text
forall a. Monoid a => a
mempty
xTransition_ (Just Text
dir) [] Text
attrVal = Text -> Text -> Attribute
makeAttribute (Text
"data-x-transition:" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
dir) Text
attrVal
xTransition_ Maybe Text
Nothing [Text]
mods Text
_ = Text -> Text -> Attribute
makeAttribute (Text
"data-x-transition." Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> [Text] -> Text
intercalate Text
"." [Text]
mods) Text
forall a. Monoid a => a
mempty
xTransition_ (Just Text
dir) [Text]
mods Text
_ = Text -> Text -> Attribute
makeAttribute (Text
"data-x-transition:" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
dir Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"." Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> [Text] -> Text
intercalate Text
"." [Text]
mods) Text
forall a. Monoid a => a
mempty
xFor_ :: Text -> Attribute
xFor_ :: Text -> Attribute
xFor_ = Text -> Text -> Attribute
makeAttribute Text
"data-x-for"
xForKey_ :: Text -> Attribute
xForKey_ :: Text -> Attribute
xForKey_ = Text -> Text -> Attribute
makeAttribute Text
":key"
xIf_ :: Text -> Attribute
xIf_ :: Text -> Attribute
xIf_ = Text -> Text -> Attribute
makeAttribute Text
"data-x-if"
xInit_ :: Text -> Attribute
xInit_ :: Text -> Attribute
xInit_ = Text -> Text -> Attribute
makeAttribute Text
"data-x-init"
xEffect_ :: Text -> Attribute
xEffect_ :: Text -> Attribute
xEffect_ = Text -> Text -> Attribute
makeAttribute Text
"data-x-effect"
xRef_ :: Text -> Attribute
xRef_ :: Text -> Attribute
xRef_ = Text -> Text -> Attribute
makeAttribute Text
"data-x-ref"
xCloak_ :: Attribute
xCloak_ :: Attribute
xCloak_ = Text -> Text -> Attribute
makeAttribute Text
"data-x-cloak" Text
forall a. Monoid a => a
mempty
xIgnore_ :: Attribute
xIgnore_ :: Attribute
xIgnore_ = Text -> Text -> Attribute
makeAttribute Text
"data-x-ignore" Text
forall a. Monoid a => a
mempty