{-# 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 "hx-boost" " hx-boost=\""
{-# INLINE hxBoost_ #-}

hxBoost :: Attribute
hxBoost :: Attribute
hxBoost = AttributeValue -> Attribute
hxBoost_ "true"
{-# INLINE hxBoost #-}

hxConfirm :: AttributeValue -> Attribute
hxConfirm :: AttributeValue -> Attribute
hxConfirm = Tag -> Tag -> AttributeValue -> Attribute
attribute "hx-confirm" " hx-confirm=\""
{-# INLINE hxConfirm #-}

hxDelete :: AttributeValue -> Attribute
hxDelete :: AttributeValue -> Attribute
hxDelete = Tag -> Tag -> AttributeValue -> Attribute
attribute "hx-delete" " hx-delete=\""
{-# INLINE hxDelete #-}

hxDisable_ :: AttributeValue -> Attribute
hxDisable_ :: AttributeValue -> Attribute
hxDisable_ = Tag -> Tag -> AttributeValue -> Attribute
attribute "hx-disable" " hx-disable=\""
{-# INLINE hxDisable_ #-}

hxDisable :: Attribute
hxDisable :: Attribute
hxDisable = AttributeValue -> Attribute
hxDisable_ ""
{-# INLINE hxDisable #-}

hxDisinherit :: AttributeValue -> Attribute
hxDisinherit :: AttributeValue -> Attribute
hxDisinherit = Tag -> Tag -> AttributeValue -> Attribute
attribute "hx-disinherit" " hx-disinherit=\""
{-# INLINE hxDisinherit #-}

hxEncoding_ :: AttributeValue -> Attribute
hxEncoding_ :: AttributeValue -> Attribute
hxEncoding_ = Tag -> Tag -> AttributeValue -> Attribute
attribute "hx-encoding" " hx-encoding=\""
{-# INLINE hxEncoding_ #-}

hxEncoding :: Attribute
hxEncoding :: Attribute
hxEncoding = AttributeValue -> Attribute
hxEncoding_ "multipart/form-data"
{-# INLINE hxEncoding #-}

hxExt :: AttributeValue -> Attribute
hxExt :: AttributeValue -> Attribute
hxExt = Tag -> Tag -> AttributeValue -> Attribute
attribute "hx-ext" " hx-ext=\""
{-# INLINE hxExt #-}

hxGet :: AttributeValue -> Attribute
hxGet :: AttributeValue -> Attribute
hxGet = Tag -> Tag -> AttributeValue -> Attribute
attribute "hx-get" " hx-get=\""
{-# INLINE hxGet #-}

hxHeaders :: AttributeValue -> Attribute
hxHeaders :: AttributeValue -> Attribute
hxHeaders = Tag -> Tag -> AttributeValue -> Attribute
attribute "hx-headers" " hx-headers=\""
{-# INLINE hxHeaders #-}

hxHistoryElt_ :: AttributeValue -> Attribute
hxHistoryElt_ :: AttributeValue -> Attribute
hxHistoryElt_ = Tag -> Tag -> AttributeValue -> Attribute
attribute "hx-history-elt" " hx-history-elt=\""
{-# INLINE hxHistoryElt_ #-}

hxHistoryElt :: Attribute
hxHistoryElt :: Attribute
hxHistoryElt = AttributeValue -> Attribute
hxHistoryElt_ ""
{-# INLINE hxHistoryElt #-}

hxInclude :: AttributeValue -> Attribute
hxInclude :: AttributeValue -> Attribute
hxInclude = Tag -> Tag -> AttributeValue -> Attribute
attribute "hx-include" " hx-include=\""
{-# INLINE hxInclude #-}

hxParams :: AttributeValue -> Attribute
hxParams :: AttributeValue -> Attribute
hxParams = Tag -> Tag -> AttributeValue -> Attribute
attribute "hx-params" " hx-params=\""
{-# INLINE hxParams #-}

hxPatch :: AttributeValue -> Attribute
hxPatch :: AttributeValue -> Attribute
hxPatch = Tag -> Tag -> AttributeValue -> Attribute
attribute "hx-patch" " hx-patch=\""
{-# INLINE hxPatch #-}

hxPost :: AttributeValue -> Attribute
hxPost :: AttributeValue -> Attribute
hxPost = Tag -> Tag -> AttributeValue -> Attribute
attribute "hx-post" " hx-post=\""
{-# INLINE hxPost #-}

hxPreserve_ :: AttributeValue -> Attribute
hxPreserve_ :: AttributeValue -> Attribute
hxPreserve_ = Tag -> Tag -> AttributeValue -> Attribute
attribute "hx-preserve" " hx-preserve=\""
{-# INLINE hxPreserve_ #-}

hxPreserve :: Attribute
hxPreserve :: Attribute
hxPreserve = AttributeValue -> Attribute
hxPreserve_ ""
{-# INLINE hxPreserve #-}

hxPrompt :: AttributeValue -> Attribute
hxPrompt :: AttributeValue -> Attribute
hxPrompt = Tag -> Tag -> AttributeValue -> Attribute
attribute "hx-prompt" " hx-prompt=\""
{-# INLINE hxPrompt #-}

hxPushUrl :: AttributeValue -> Attribute
hxPushUrl :: AttributeValue -> Attribute
hxPushUrl = Tag -> Tag -> AttributeValue -> Attribute
attribute "hx-push-url" " hx-push-url=\""
{-# INLINE hxPushUrl #-}

hxPut :: AttributeValue -> Attribute
hxPut :: AttributeValue -> Attribute
hxPut = Tag -> Tag -> AttributeValue -> Attribute
attribute "hx-put" " hx-put=\""
{-# INLINE hxPut #-}

hxRequest :: AttributeValue -> Attribute
hxRequest :: AttributeValue -> Attribute
hxRequest = Tag -> Tag -> AttributeValue -> Attribute
attribute "hx-request" " hx-request=\""
{-# INLINE hxRequest #-}

hxSelect :: AttributeValue -> Attribute
hxSelect :: AttributeValue -> Attribute
hxSelect = Tag -> Tag -> AttributeValue -> Attribute
attribute "hx-select" " hx-select=\""
{-# INLINE hxSelect #-}

-- | Deprecated. Use "Text.Blaze.Htmx.ServerSentEvents" instead.
hxSse_ :: AttributeValue -> Attribute
hxSse_ :: AttributeValue -> Attribute
hxSse_ = Tag -> Tag -> AttributeValue -> Attribute
attribute "hx-sse" " hx-sse=\""
{-# INLINE hxSse_#-}

hxSwap :: AttributeValue -> Attribute
hxSwap :: AttributeValue -> Attribute
hxSwap = Tag -> Tag -> AttributeValue -> Attribute
attribute "hx-swap" " hx-swap=\""
{-# INLINE hxSwap #-}

hxSwapOob :: AttributeValue -> Attribute
hxSwapOob :: AttributeValue -> Attribute
hxSwapOob = Tag -> Tag -> AttributeValue -> Attribute
attribute "hx-swap-oob" " hx-swap-oob=\""
{-# INLINE hxSwapOob #-}

hxSync :: AttributeValue -> Attribute
hxSync :: AttributeValue -> Attribute
hxSync = Tag -> Tag -> AttributeValue -> Attribute
attribute "hx-sync" " hx-sync=\""
{-# INLINE hxSync #-}

hxTarget :: AttributeValue -> Attribute
hxTarget :: AttributeValue -> Attribute
hxTarget = Tag -> Tag -> AttributeValue -> Attribute
attribute "hx-target" " hx-target=\""
{-# INLINE hxTarget #-}

hxTrigger :: AttributeValue -> Attribute
hxTrigger :: AttributeValue -> Attribute
hxTrigger = Tag -> Tag -> AttributeValue -> Attribute
attribute "hx-trigger" " hx-trigger=\""
{-# INLINE hxTrigger #-}

hxVals :: AttributeValue -> Attribute
hxVals :: AttributeValue -> Attribute
hxVals = Tag -> Tag -> AttributeValue -> Attribute
attribute "hx-vals" " hx-vals=\""
{-# INLINE hxVals #-}

-- | Deprecated. Use 'hxVals'.
hxVars_ :: AttributeValue -> Attribute
hxVars_ :: AttributeValue -> Attribute
hxVars_ = Tag -> Tag -> AttributeValue -> Attribute
attribute "hx-vars" " hx-vars=\""
{-# INLINE hxVars_ #-}

-- | Deprecated. Use "Text.Blaze.Htmx.WebSockets" instead.
hxWs_ :: AttributeValue -> Attribute
hxWs_ :: AttributeValue -> Attribute
hxWs_ = Tag -> Tag -> AttributeValue -> Attribute
attribute "hx-ws" " hx-ws=\""
{-# INLINE hxWs_ #-}