{-# LANGUAGE OverloadedStrings #-}
module Text.Blaze.Htmx where
import Text.Blaze.Internal (attribute, Attribute, AttributeValue)
hxBoost_ :: AttributeValue -> Attribute
hxBoost_ :: AttributeValue -> Attribute
hxBoost_ = Tag -> Tag -> AttributeValue -> Attribute
attribute Tag
"hx-boost" Tag
" hx-boost=\""
{-# INLINE hxBoost_ #-}
hxBoost :: Attribute
hxBoost :: Attribute
hxBoost = AttributeValue -> Attribute
hxBoost_ AttributeValue
"true"
{-# INLINE hxBoost #-}
hxConfirm :: AttributeValue -> Attribute
hxConfirm :: AttributeValue -> Attribute
hxConfirm = Tag -> Tag -> AttributeValue -> Attribute
attribute Tag
"hx-confirm" Tag
" hx-confirm=\""
{-# INLINE hxConfirm #-}
hxDelete :: AttributeValue -> Attribute
hxDelete :: AttributeValue -> Attribute
hxDelete = Tag -> Tag -> AttributeValue -> Attribute
attribute Tag
"hx-delete" Tag
" hx-delete=\""
{-# INLINE hxDelete #-}
hxDisable_ :: AttributeValue -> Attribute
hxDisable_ :: AttributeValue -> Attribute
hxDisable_ = Tag -> Tag -> AttributeValue -> Attribute
attribute Tag
"hx-disable" Tag
" hx-disable=\""
{-# INLINE hxDisable_ #-}
hxDisable :: Attribute
hxDisable :: Attribute
hxDisable = AttributeValue -> Attribute
hxDisable_ AttributeValue
""
{-# INLINE hxDisable #-}
hxDisinherit :: AttributeValue -> Attribute
hxDisinherit :: AttributeValue -> Attribute
hxDisinherit = Tag -> Tag -> AttributeValue -> Attribute
attribute Tag
"hx-disinherit" Tag
" hx-disinherit=\""
{-# INLINE hxDisinherit #-}
hxEncoding_ :: AttributeValue -> Attribute
hxEncoding_ :: AttributeValue -> Attribute
hxEncoding_ = Tag -> Tag -> AttributeValue -> Attribute
attribute Tag
"hx-encoding" Tag
" hx-encoding=\""
{-# INLINE hxEncoding_ #-}
hxEncoding :: Attribute
hxEncoding :: Attribute
hxEncoding = AttributeValue -> Attribute
hxEncoding_ AttributeValue
"multipart/form-data"
{-# INLINE hxEncoding #-}
hxExt :: AttributeValue -> Attribute
hxExt :: AttributeValue -> Attribute
hxExt = Tag -> Tag -> AttributeValue -> Attribute
attribute Tag
"hx-ext" Tag
" hx-ext=\""
{-# INLINE hxExt #-}
hxGet :: AttributeValue -> Attribute
hxGet :: AttributeValue -> Attribute
hxGet = Tag -> Tag -> AttributeValue -> Attribute
attribute Tag
"hx-get" Tag
" hx-get=\""
{-# INLINE hxGet #-}
hxHeaders :: AttributeValue -> Attribute
 = Tag -> Tag -> AttributeValue -> Attribute
attribute Tag
"hx-headers" Tag
" hx-headers=\""
{-# INLINE hxHeaders #-}
hxHistoryElt_ :: AttributeValue -> Attribute
hxHistoryElt_ :: AttributeValue -> Attribute
hxHistoryElt_ = Tag -> Tag -> AttributeValue -> Attribute
attribute Tag
"hx-history-elt" Tag
" hx-history-elt=\""
{-# INLINE hxHistoryElt_ #-}
hxHistoryElt :: Attribute
hxHistoryElt :: Attribute
hxHistoryElt = AttributeValue -> Attribute
hxHistoryElt_ AttributeValue
""
{-# INLINE hxHistoryElt #-}
hxInclude :: AttributeValue -> Attribute
hxInclude :: AttributeValue -> Attribute
hxInclude = Tag -> Tag -> AttributeValue -> Attribute
attribute Tag
"hx-include" Tag
" hx-include=\""
{-# INLINE hxInclude #-}
hxParams :: AttributeValue -> Attribute
hxParams :: AttributeValue -> Attribute
hxParams = Tag -> Tag -> AttributeValue -> Attribute
attribute Tag
"hx-params" Tag
" hx-params=\""
{-# INLINE hxParams #-}
hxPatch :: AttributeValue -> Attribute
hxPatch :: AttributeValue -> Attribute
hxPatch = Tag -> Tag -> AttributeValue -> Attribute
attribute Tag
"hx-patch" Tag
" hx-patch=\""
{-# INLINE hxPatch #-}
hxPost :: AttributeValue -> Attribute
hxPost :: AttributeValue -> Attribute
hxPost = Tag -> Tag -> AttributeValue -> Attribute
attribute Tag
"hx-post" Tag
" hx-post=\""
{-# INLINE hxPost #-}
hxPreserve_ :: AttributeValue -> Attribute
hxPreserve_ :: AttributeValue -> Attribute
hxPreserve_ = Tag -> Tag -> AttributeValue -> Attribute
attribute Tag
"hx-preserve" Tag
" hx-preserve=\""
{-# INLINE hxPreserve_ #-}
hxPreserve :: Attribute
hxPreserve :: Attribute
hxPreserve = AttributeValue -> Attribute
hxPreserve_ AttributeValue
""
{-# INLINE hxPreserve #-}
hxPrompt :: AttributeValue -> Attribute
hxPrompt :: AttributeValue -> Attribute
hxPrompt = Tag -> Tag -> AttributeValue -> Attribute
attribute Tag
"hx-prompt" Tag
" hx-prompt=\""
{-# INLINE hxPrompt #-}
hxPushUrl :: AttributeValue -> Attribute
hxPushUrl :: AttributeValue -> Attribute
hxPushUrl = Tag -> Tag -> AttributeValue -> Attribute
attribute Tag
"hx-push-url" Tag
" hx-push-url=\""
{-# INLINE hxPushUrl #-}
hxPut :: AttributeValue -> Attribute
hxPut :: AttributeValue -> Attribute
hxPut = Tag -> Tag -> AttributeValue -> Attribute
attribute Tag
"hx-put" Tag
" hx-put=\""
{-# INLINE hxPut #-}
hxRequest :: AttributeValue -> Attribute
hxRequest :: AttributeValue -> Attribute
hxRequest = Tag -> Tag -> AttributeValue -> Attribute
attribute Tag
"hx-request" Tag
" hx-request=\""
{-# INLINE hxRequest #-}
hxSelect :: AttributeValue -> Attribute
hxSelect :: AttributeValue -> Attribute
hxSelect = Tag -> Tag -> AttributeValue -> Attribute
attribute Tag
"hx-select" Tag
" hx-select=\""
{-# INLINE hxSelect #-}
hxSse_ :: AttributeValue -> Attribute
hxSse_ :: AttributeValue -> Attribute
hxSse_ = Tag -> Tag -> AttributeValue -> Attribute
attribute Tag
"hx-sse" Tag
" hx-sse=\""
{-# INLINE hxSse_#-}
hxSwap :: AttributeValue -> Attribute
hxSwap :: AttributeValue -> Attribute
hxSwap = Tag -> Tag -> AttributeValue -> Attribute
attribute Tag
"hx-swap" Tag
" hx-swap=\""
{-# INLINE hxSwap #-}
hxSwapOob :: AttributeValue -> Attribute
hxSwapOob :: AttributeValue -> Attribute
hxSwapOob = Tag -> Tag -> AttributeValue -> Attribute
attribute Tag
"hx-swap-oob" Tag
" hx-swap-oob=\""
{-# INLINE hxSwapOob #-}
hxSync :: AttributeValue -> Attribute
hxSync :: AttributeValue -> Attribute
hxSync = Tag -> Tag -> AttributeValue -> Attribute
attribute Tag
"hx-sync" Tag
" hx-sync=\""
{-# INLINE hxSync #-}
hxTarget :: AttributeValue -> Attribute
hxTarget :: AttributeValue -> Attribute
hxTarget = Tag -> Tag -> AttributeValue -> Attribute
attribute Tag
"hx-target" Tag
" hx-target=\""
{-# INLINE hxTarget #-}
hxTrigger :: AttributeValue -> Attribute
hxTrigger :: AttributeValue -> Attribute
hxTrigger = Tag -> Tag -> AttributeValue -> Attribute
attribute Tag
"hx-trigger" Tag
" hx-trigger=\""
{-# INLINE hxTrigger #-}
hxVals :: AttributeValue -> Attribute
hxVals :: AttributeValue -> Attribute
hxVals = Tag -> Tag -> AttributeValue -> Attribute
attribute Tag
"hx-vals" Tag
" hx-vals=\""
{-# INLINE hxVals #-}
hxVars_ :: AttributeValue -> Attribute
hxVars_ :: AttributeValue -> Attribute
hxVars_ = Tag -> Tag -> AttributeValue -> Attribute
attribute Tag
"hx-vars" Tag
" hx-vars=\""
{-# INLINE hxVars_ #-}
hxWs_ :: AttributeValue -> Attribute
hxWs_ :: AttributeValue -> Attribute
hxWs_ = Tag -> Tag -> AttributeValue -> Attribute
attribute Tag
"hx-ws" Tag
" hx-ws=\""
{-# INLINE hxWs_ #-}