{-# LANGUAGE OverloadedStrings #-}
module Lucid.HTMX where
import Lucid.Base (Attribute, makeAttribute)
import Data.Text (Text)
hxBoost_ :: Text -> Attribute
hxBoost_ :: Text -> Attribute
hxBoost_ = Text -> Text -> Attribute
makeAttribute Text
"hx-boost"
hxConfirm_ :: Text -> Attribute
hxConfirm_ :: Text -> Attribute
hxConfirm_ = Text -> Text -> Attribute
makeAttribute Text
"hx-confirm"
hxDelete_ :: Text -> Attribute
hxDelete_ :: Text -> Attribute
hxDelete_ = Text -> Text -> Attribute
makeAttribute Text
"hx-delete"
hxDisable_ :: Attribute
hxDisable_ :: Attribute
hxDisable_ = Text -> Text -> Attribute
makeAttribute Text
"hx-disable" Text
forall a. Monoid a => a
mempty
hxEncoding_ :: Text -> Attribute
hxEncoding_ :: Text -> Attribute
hxEncoding_ = Text -> Text -> Attribute
makeAttribute Text
"hx-encoding"
hxExt_ :: Text -> Attribute
hxExt_ :: Text -> Attribute
hxExt_ = Text -> Text -> Attribute
makeAttribute Text
"hx-ext"
hxGet_ :: Text -> Attribute
hxGet_ :: Text -> Attribute
hxGet_ = Text -> Text -> Attribute
makeAttribute Text
"hx-get"
hxHeaders_ :: Text -> Attribute
= Text -> Text -> Attribute
makeAttribute Text
"hx-headers"
hxHistoryElt_ :: Attribute
hxHistoryElt_ :: Attribute
hxHistoryElt_ = Text -> Text -> Attribute
makeAttribute Text
"hx-history-elt" Text
forall a. Monoid a => a
mempty
hxInclude_ :: Text -> Attribute
hxInclude_ :: Text -> Attribute
hxInclude_ = Text -> Text -> Attribute
makeAttribute Text
"hx-include"
hxIndicator_ :: Text -> Attribute
hxIndicator_ :: Text -> Attribute
hxIndicator_ = Text -> Text -> Attribute
makeAttribute Text
"hx-indicator"
hxParams_ :: Text -> Attribute
hxParams_ :: Text -> Attribute
hxParams_ = Text -> Text -> Attribute
makeAttribute Text
"hx-params"
hxPatch_ :: Text -> Attribute
hxPatch_ :: Text -> Attribute
hxPatch_ = Text -> Text -> Attribute
makeAttribute Text
"hx-patch"
hxPost_ :: Text -> Attribute
hxPost_ :: Text -> Attribute
hxPost_ = Text -> Text -> Attribute
makeAttribute Text
"hx-post"
hxPreserve_ :: Text -> Attribute
hxPreserve_ :: Text -> Attribute
hxPreserve_ = Text -> Text -> Attribute
makeAttribute Text
"hx-preserve"
hxPrompt_ :: Text -> Attribute
hxPrompt_ :: Text -> Attribute
hxPrompt_ = Text -> Text -> Attribute
makeAttribute Text
"hx-prompt"
hxPushUrl_ :: Text -> Attribute
hxPushUrl_ :: Text -> Attribute
hxPushUrl_ = Text -> Text -> Attribute
makeAttribute Text
"hx-push-url"
hxPut_ :: Text -> Attribute
hxPut_ :: Text -> Attribute
hxPut_ = Text -> Text -> Attribute
makeAttribute Text
"hx-put"
hxRequest_ :: Text -> Attribute
hxRequest_ :: Text -> Attribute
hxRequest_ = Text -> Text -> Attribute
makeAttribute Text
"hx-request"
hxSelect_ :: Text -> Attribute
hxSelect_ :: Text -> Attribute
hxSelect_ = Text -> Text -> Attribute
makeAttribute Text
"hx-select"
hxSse_ :: Text -> Attribute
hxSse_ :: Text -> Attribute
hxSse_ = Text -> Text -> Attribute
makeAttribute Text
"hx-sse"
hxSwapOob_ :: Text -> Attribute
hxSwapOob_ :: Text -> Attribute
hxSwapOob_ = Text -> Text -> Attribute
makeAttribute Text
"hx-swap-oob"
hxSwap_ :: Text -> Attribute
hxSwap_ :: Text -> Attribute
hxSwap_ = Text -> Text -> Attribute
makeAttribute Text
"hx-swap"
hxTarget_ :: Text -> Attribute
hxTarget_ :: Text -> Attribute
hxTarget_ = Text -> Text -> Attribute
makeAttribute Text
"hx-target"
hxTrigger_ :: Text -> Attribute
hxTrigger_ :: Text -> Attribute
hxTrigger_ = Text -> Text -> Attribute
makeAttribute Text
"hx-trigger"
hxVals_ :: Text -> Attribute
hxVals_ :: Text -> Attribute
hxVals_ = Text -> Text -> Attribute
makeAttribute Text
"hx-vals"
hxWs_ :: Text -> Attribute
hxWs_ :: Text -> Attribute
hxWs_ = Text -> Text -> Attribute
makeAttribute Text
"hx-ws"