{-# LANGUAGE OverloadedStrings #-}
module Lucid.Alpine where
import Data.Text (Text, intercalate, pack)
import Lucid (Html, HtmlT, defer_, script_, src_)
import Lucid.Base (Attribute, makeAttribute)
xData_ :: Text -> Attribute
xData_ :: Text -> Attribute
xData_ = Text -> Text -> Attribute
makeAttribute Text
"x-data"
xBind_ ::
Text ->
Text ->
Attribute
xBind_ :: Text -> Text -> Attribute
xBind_ Text
attr = Text -> Text -> Attribute
makeAttribute (Text
"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
"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
"x-text"
xHtml_ :: Text -> Attribute
xHtml_ :: Text -> Attribute
xHtml_ = Text -> Text -> Attribute
makeAttribute Text
"x-html"
xModel_ ::
[Text] ->
Text ->
Attribute
xModel_ :: [Text] -> Text -> Attribute
xModel_ [Text]
mods = case [Text]
mods of
[] -> Text -> Text -> Attribute
makeAttribute Text
"x-model"
[Text]
_ -> Text -> Text -> Attribute
makeAttribute (Text
"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
"x-show"
xTransition_ ::
Maybe Text ->
[Text] ->
Text ->
Attribute
xTransition_ :: Maybe Text -> [Text] -> Text -> Attribute
xTransition_ Maybe Text
Nothing [] Text
_ = Text -> Text -> Attribute
makeAttribute Text
"x-transition" Text
forall a. Monoid a => a
mempty
xTransition_ (Just Text
dir) [] Text
attrVal = Text -> Text -> Attribute
makeAttribute (Text
"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
"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
"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
"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
"x-if"
xInit_ :: Text -> Attribute
xInit_ :: Text -> Attribute
xInit_ = Text -> Text -> Attribute
makeAttribute Text
"x-init"
xEffect_ :: Text -> Attribute
xEffect_ :: Text -> Attribute
xEffect_ = Text -> Text -> Attribute
makeAttribute Text
"x-effect"
xRef_ :: Text -> Attribute
xRef_ :: Text -> Attribute
xRef_ = Text -> Text -> Attribute
makeAttribute Text
"x-ref"
xCloak_ :: Attribute
xCloak_ :: Attribute
xCloak_ = Text -> Text -> Attribute
makeAttribute Text
"x-cloak" Text
forall a. Monoid a => a
mempty
xIgnore_ :: Attribute
xIgnore_ :: Attribute
xIgnore_ = Text -> Text -> Attribute
makeAttribute Text
"x-ignore" Text
forall a. Monoid a => a
mempty
useAlpine :: Monad m => HtmlT m ()
useAlpine :: HtmlT m ()
useAlpine = [Attribute] -> Html () -> HtmlT m ()
forall arg result. TermRaw arg result => arg -> result
script_ [Text -> Attribute
defer_ Text
"", Text -> Attribute
src_ Text
alpineSrc] (Html ()
"" :: Html ())
useAlpineVersion :: Monad m => (Int, Int, Int) -> HtmlT m ()
useAlpineVersion :: (Int, Int, Int) -> HtmlT m ()
useAlpineVersion (Int, Int, Int)
semVer = [Attribute] -> Html () -> HtmlT m ()
forall arg result. TermRaw arg result => arg -> result
script_ [Text -> Attribute
defer_ Text
"", Text -> Attribute
src_ (Text -> Attribute) -> Text -> Attribute
forall a b. (a -> b) -> a -> b
$ (Int, Int, Int) -> Text
alpineSrcWithSemVer (Int, Int, Int)
semVer] (Html ()
"" :: Html ())
alpineSrc :: Text
alpineSrc :: Text
alpineSrc = Text
"https://unpkg.com/alpinejs"
alpineSrcWithSemVer :: (Int, Int, Int) -> Text
alpineSrcWithSemVer :: (Int, Int, Int) -> Text
alpineSrcWithSemVer (Int
major, Int
minor, Int
patch) =
Text
alpineSrc
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"@"
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Int -> Text
forall a. Show a => a -> Text
showT Int
major
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"."
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Int -> Text
forall a. Show a => a -> Text
showT Int
minor
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"."
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Int -> Text
forall a. Show a => a -> Text
showT Int
patch
showT :: Show a => a -> Text
showT :: a -> Text
showT = String -> Text
pack (String -> Text) -> (a -> String) -> a -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> String
forall a. Show a => a -> String
show