module Htmx.Lucid.Extra where
import Data.Foldable
import Data.List (intersperse)
import Data.Text (Text, pack)
import Htmx.Extension
import Htmx.Render
import Lucid (Html, HtmlT, script_, src_)
import Lucid.Base (Attribute, makeAttribute)
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
hxDisabledElt_ :: Text -> Attribute
hxDisabledElt_ :: Text -> Attribute
hxDisabledElt_ = Text -> Text -> Attribute
makeAttribute Text
"hx-disabled-elt"
hxDisinherit_ :: Text -> Attribute
hxDisinherit_ :: Text -> Attribute
hxDisinherit_ = Text -> Text -> Attribute
makeAttribute Text
"hx-disinherit"
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"
hxExtension_ :: HtmxExtension -> Attribute
hxExtension_ :: HtmxExtension -> Attribute
hxExtension_ = Text -> Text -> Attribute
makeAttribute Text
"hx-ext" (Text -> Attribute)
-> (HtmxExtension -> Text) -> HtmxExtension -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HtmxExtension -> Text
forall a. Render a => a -> Text
render
hxExtensions_ :: [HtmxExtension] -> Attribute
hxExtensions_ :: [HtmxExtension] -> Attribute
hxExtensions_ = Text -> Text -> Attribute
makeAttribute Text
"hx-ext" (Text -> Attribute)
-> ([HtmxExtension] -> Text) -> [HtmxExtension] -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Text] -> Text
forall m. Monoid m => [m] -> m
forall (t :: * -> *) m. (Foldable t, Monoid m) => t m -> m
fold ([Text] -> Text)
-> ([HtmxExtension] -> [Text]) -> [HtmxExtension] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
intersperse Text
"," ([Text] -> [Text])
-> ([HtmxExtension] -> [Text]) -> [HtmxExtension] -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (HtmxExtension -> Text) -> [HtmxExtension] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap HtmxExtension -> Text
forall a. Render a => a -> Text
render
hxHeaders_ :: Text -> Attribute
= Text -> Text -> Attribute
makeAttribute Text
"hx-headers"
hxHistory_ :: Text -> Attribute
hxHistory_ :: Text -> Attribute
hxHistory_ = Text -> Text -> Attribute
makeAttribute Text
"hx-history"
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"
data ParamsFilter
=
All
|
None
|
Exclude [Text]
|
Include [Text]
hxParams_ :: ParamsFilter -> Attribute
hxParams_ :: ParamsFilter -> Attribute
hxParams_ = \case
ParamsFilter
All -> Text -> Text -> Attribute
makeAttribute Text
"hx-params" Text
"*"
ParamsFilter
None -> Text -> Text -> Attribute
makeAttribute Text
"hx-params" Text
"none"
Exclude [Text]
ps -> Text -> Text -> Attribute
makeAttribute Text
"hx-params" (Text -> Attribute) -> Text -> Attribute
forall a b. (a -> b) -> a -> b
$ Text
"not " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> ([Text] -> Text
forall m. Monoid m => [m] -> m
forall (t :: * -> *) m. (Foldable t, Monoid m) => t m -> m
fold ([Text] -> Text) -> ([Text] -> [Text]) -> [Text] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
intersperse Text
"," ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ [Text]
ps)
Include [Text]
ps -> Text -> Text -> Attribute
makeAttribute Text
"hx-params" (Text -> Attribute) -> Text -> Attribute
forall a b. (a -> b) -> a -> b
$ [Text] -> Text
forall m. Monoid m => [m] -> m
forall (t :: * -> *) m. (Foldable t, Monoid m) => t m -> m
fold ([Text] -> Text) -> ([Text] -> [Text]) -> [Text] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
intersperse Text
"," ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ [Text]
ps
hxPatch_ :: Text -> Attribute
hxPatch_ :: Text -> Attribute
hxPatch_ = Text -> Text -> Attribute
makeAttribute Text
"hx-patch"
hxPreserve_ :: Attribute
hxPreserve_ :: Attribute
hxPreserve_ = Text -> Text -> Attribute
makeAttribute Text
"hx-preserve" Text
forall a. Monoid a => a
mempty
hxPrompt_ :: Text -> Attribute
hxPrompt_ :: Text -> Attribute
hxPrompt_ = Text -> Text -> Attribute
makeAttribute Text
"hx-prompt"
hxPut_ :: Text -> Attribute
hxPut_ :: Text -> Attribute
hxPut_ = Text -> Text -> Attribute
makeAttribute Text
"hx-put"
hxReplaceUrl_ :: Text -> Attribute
hxReplaceUrl_ :: Text -> Attribute
hxReplaceUrl_ = Text -> Text -> Attribute
makeAttribute Text
"hx-replace-url"
hxRequest_ :: Text -> Attribute
hxRequest_ :: Text -> Attribute
hxRequest_ = Text -> Text -> Attribute
makeAttribute Text
"hx-request"
{-# DEPRECATED
hxSse_
"Don't use hx-sse directly, please use the server sent events extension instead https://htmx.org/extensions/server-sent-events/"
#-}
hxSse_ :: Text -> Attribute
hxSse_ :: Text -> Attribute
hxSse_ = Text -> Text -> Attribute
makeAttribute Text
"hx-sse"
data SyncStrategy
=
SyncDrop
|
SyncAbort
|
SyncReplace
|
SyncQueueFirst
|
SyncQueueLast
|
SyncQueueAll
hxSync_ :: Text -> Attribute
hxSync_ :: Text -> Attribute
hxSync_ = Text -> Text -> Attribute
makeAttribute Text
"hx-sync"
hxSyncStrategy_ :: Text -> SyncStrategy -> Attribute
hxSyncStrategy_ :: Text -> SyncStrategy -> Attribute
hxSyncStrategy_ Text
selector = \case
SyncStrategy
SyncDrop -> Text -> Text -> Attribute
makeAttribute Text
"hx-sync" (Text -> Attribute) -> Text -> Attribute
forall a b. (a -> b) -> a -> b
$ Text
selector Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
":" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"drop"
SyncStrategy
SyncAbort -> Text -> Text -> Attribute
makeAttribute Text
"hx-sync" (Text -> Attribute) -> Text -> Attribute
forall a b. (a -> b) -> a -> b
$ Text
selector Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
":" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"abort"
SyncStrategy
SyncReplace -> Text -> Text -> Attribute
makeAttribute Text
"hx-sync" (Text -> Attribute) -> Text -> Attribute
forall a b. (a -> b) -> a -> b
$ Text
selector Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
":" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"replace"
SyncStrategy
SyncQueueFirst -> Text -> Text -> Attribute
makeAttribute Text
"hx-sync" (Text -> Attribute) -> Text -> Attribute
forall a b. (a -> b) -> a -> b
$ Text
selector Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
":" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"queue first"
SyncStrategy
SyncQueueLast -> Text -> Text -> Attribute
makeAttribute Text
"hx-sync" (Text -> Attribute) -> Text -> Attribute
forall a b. (a -> b) -> a -> b
$ Text
selector Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
":" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"queue last"
SyncStrategy
SyncQueueAll -> Text -> Text -> Attribute
makeAttribute Text
"hx-sync" (Text -> Attribute) -> Text -> Attribute
forall a b. (a -> b) -> a -> b
$ Text
selector Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
":" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"queue all"
hxValidate_ :: Text -> Attribute
hxValidate_ :: Text -> Attribute
hxValidate_ = Text -> Text -> Attribute
makeAttribute Text
"hx-validate"
hxVars_ :: Text -> Attribute
hxVars_ :: Text -> Attribute
hxVars_ = Text -> Text -> Attribute
makeAttribute Text
"hx-vars"
{-# DEPRECATED
hxWs_
"Don't use hx-ws directly, please use the web sockets extension instead https://htmx.org/extensions/server-sent-events/https://htmx.org/extensions/web-sockets/"
#-}
hxWs_ :: Text -> Attribute
hxWs_ :: Text -> Attribute
hxWs_ = Text -> Text -> Attribute
makeAttribute Text
"hx-ws"