{-# LANGUAGE OverloadedStrings #-}
module Lucid.Htmx
( hxBoost_,
hxConfirm_,
hxEncoding_,
hxExt_,
hxDelete_,
hxDisable_,
hxGet_,
hxHeaders_,
hxHistoryElt_,
hxInclude_,
hxIndicator_,
hxParams_,
hxPatch_,
hxPost_,
hxPreserve_,
hxPrompt_,
hxPushUrl_,
hxPut_,
hxRequest_,
hxSelect_,
hxSse_,
hxSwapOob_,
hxSwap_,
hxTarget_,
hxTrigger_,
hxVals_,
hxWs_,
useHtmx,
useHtmxExtension,
useHtmxVersion,
useHtmxVersionExtension,
)
where
import Data.Text (Text, pack)
import Lucid (Html, HtmlT, script_, src_)
import Lucid.Base (Attribute, makeAttribute)
hxBoost_ :: Text -> Attribute
hxBoost_ :: Text -> Attribute
hxBoost_ = Text -> Text -> Attribute
makeAttribute Text
"data-hx-boost"
hxConfirm_ :: Text -> Attribute
hxConfirm_ :: Text -> Attribute
hxConfirm_ = Text -> Text -> Attribute
makeAttribute Text
"data-hx-confirm"
hxDelete_ :: Text -> Attribute
hxDelete_ :: Text -> Attribute
hxDelete_ = Text -> Text -> Attribute
makeAttribute Text
"data-hx-delete"
hxDisable_ :: Attribute
hxDisable_ :: Attribute
hxDisable_ = Text -> Text -> Attribute
makeAttribute Text
"data-hx-disable" Text
forall a. Monoid a => a
mempty
hxEncoding_ :: Text -> Attribute
hxEncoding_ :: Text -> Attribute
hxEncoding_ = Text -> Text -> Attribute
makeAttribute Text
"data-hx-encoding"
hxExt_ :: Text -> Attribute
hxExt_ :: Text -> Attribute
hxExt_ = Text -> Text -> Attribute
makeAttribute Text
"data-hx-ext"
hxGet_ :: Text -> Attribute
hxGet_ :: Text -> Attribute
hxGet_ = Text -> Text -> Attribute
makeAttribute Text
"data-hx-get"
hxHeaders_ :: Text -> Attribute
= Text -> Text -> Attribute
makeAttribute Text
"data-hx-headers"
hxHistoryElt_ :: Attribute
hxHistoryElt_ :: Attribute
hxHistoryElt_ = Text -> Text -> Attribute
makeAttribute Text
"data-hx-history-elt" Text
forall a. Monoid a => a
mempty
hxInclude_ :: Text -> Attribute
hxInclude_ :: Text -> Attribute
hxInclude_ = Text -> Text -> Attribute
makeAttribute Text
"data-hx-include"
hxIndicator_ :: Text -> Attribute
hxIndicator_ :: Text -> Attribute
hxIndicator_ = Text -> Text -> Attribute
makeAttribute Text
"data-hx-indicator"
hxParams_ :: Text -> Attribute
hxParams_ :: Text -> Attribute
hxParams_ = Text -> Text -> Attribute
makeAttribute Text
"data-hx-params"
hxPatch_ :: Text -> Attribute
hxPatch_ :: Text -> Attribute
hxPatch_ = Text -> Text -> Attribute
makeAttribute Text
"data-hx-patch"
hxPost_ :: Text -> Attribute
hxPost_ :: Text -> Attribute
hxPost_ = Text -> Text -> Attribute
makeAttribute Text
"data-hx-post"
hxPreserve_ :: Text -> Attribute
hxPreserve_ :: Text -> Attribute
hxPreserve_ = Text -> Text -> Attribute
makeAttribute Text
"data-hx-preserve"
hxPrompt_ :: Text -> Attribute
hxPrompt_ :: Text -> Attribute
hxPrompt_ = Text -> Text -> Attribute
makeAttribute Text
"data-hx-prompt"
hxPushUrl_ :: Text -> Attribute
hxPushUrl_ :: Text -> Attribute
hxPushUrl_ = Text -> Text -> Attribute
makeAttribute Text
"data-hx-push-url"
hxPut_ :: Text -> Attribute
hxPut_ :: Text -> Attribute
hxPut_ = Text -> Text -> Attribute
makeAttribute Text
"data-hx-put"
hxRequest_ :: Text -> Attribute
hxRequest_ :: Text -> Attribute
hxRequest_ = Text -> Text -> Attribute
makeAttribute Text
"data-hx-request"
hxSelect_ :: Text -> Attribute
hxSelect_ :: Text -> Attribute
hxSelect_ = Text -> Text -> Attribute
makeAttribute Text
"data-hx-select"
hxSse_ :: Text -> Attribute
hxSse_ :: Text -> Attribute
hxSse_ = Text -> Text -> Attribute
makeAttribute Text
"data-hx-sse"
hxSwapOob_ :: Text -> Attribute
hxSwapOob_ :: Text -> Attribute
hxSwapOob_ = Text -> Text -> Attribute
makeAttribute Text
"data-hx-swap-oob"
hxSwap_ :: Text -> Attribute
hxSwap_ :: Text -> Attribute
hxSwap_ = Text -> Text -> Attribute
makeAttribute Text
"data-hx-swap"
hxTarget_ :: Text -> Attribute
hxTarget_ :: Text -> Attribute
hxTarget_ = Text -> Text -> Attribute
makeAttribute Text
"data-hx-target"
hxTrigger_ :: Text -> Attribute
hxTrigger_ :: Text -> Attribute
hxTrigger_ = Text -> Text -> Attribute
makeAttribute Text
"data-hx-trigger"
hxVals_ :: Text -> Attribute
hxVals_ :: Text -> Attribute
hxVals_ = Text -> Text -> Attribute
makeAttribute Text
"data-hx-vals"
hxWs_ :: Text -> Attribute
hxWs_ :: Text -> Attribute
hxWs_ = Text -> Text -> Attribute
makeAttribute Text
"data-hx-ws"
useHtmx :: Monad m => HtmlT m ()
useHtmx :: HtmlT m ()
useHtmx = [Attribute] -> Html () -> HtmlT m ()
forall arg result. TermRaw arg result => arg -> result
script_ [Text -> Attribute
src_ Text
htmxSrc] (Html ()
"" :: Html ())
useHtmxExtension :: Monad m => Text -> HtmlT m ()
useHtmxExtension :: Text -> HtmlT m ()
useHtmxExtension Text
ext = [Attribute] -> Html () -> HtmlT m ()
forall arg result. TermRaw arg result => arg -> result
script_ [Text -> Attribute
src_ (Text -> Attribute) -> Text -> Attribute
forall a b. (a -> b) -> a -> b
$ Text
htmxSrc Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Text
extensionPath Text
ext] (Html ()
"" :: Html ())
useHtmxVersion :: Monad m => (Int, Int, Int) -> HtmlT m ()
useHtmxVersion :: (Int, Int, Int) -> HtmlT m ()
useHtmxVersion (Int, Int, Int)
semVer = [Attribute] -> Html () -> HtmlT m ()
forall arg result. TermRaw arg result => arg -> result
script_ [Text -> Attribute
src_ (Text -> Attribute) -> Text -> Attribute
forall a b. (a -> b) -> a -> b
$ (Int, Int, Int) -> Text
htmxSrcWithSemVer (Int, Int, Int)
semVer] (Html ()
"" :: Html ())
useHtmxVersionExtension :: Monad m => (Int, Int, Int) -> Text -> HtmlT m ()
useHtmxVersionExtension :: (Int, Int, Int) -> Text -> HtmlT m ()
useHtmxVersionExtension (Int, Int, Int)
semVer Text
ext = [Attribute] -> Html () -> HtmlT m ()
forall arg result. TermRaw arg result => arg -> result
script_ [Text -> Attribute
src_ (Text -> Attribute) -> Text -> Attribute
forall a b. (a -> b) -> a -> b
$ (Int, Int, Int) -> Text
htmxSrcWithSemVer (Int, Int, Int)
semVer Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Text
extensionPath Text
ext] (Html ()
"" :: Html ())
htmxSrc :: Text
htmxSrc :: Text
htmxSrc = Text
"https://unpkg.com/htmx.org"
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
htmxSrcWithSemVer :: (Int, Int, Int) -> Text
htmxSrcWithSemVer :: (Int, Int, Int) -> Text
htmxSrcWithSemVer (Int
major, Int
minor, Int
patch) =
Text
htmxSrc
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
extensionPath :: Text -> Text
extensionPath :: Text -> Text
extensionPath Text
ext = Text
"/dist/ext/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
ext Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
".js"