{- |
Module      : Htmx.Servant.Lucid
Description : Typesafe versions of HTMX request tags

This module exports Lucid combinators that leverage the Servant 'Link'
type to guarantee that they are live URLs, therefore making the requests
"safe".
-}
module Htmx.Servant.Lucid (
    hxDeleteSafe_,
    hxGetSafe_,
    hxPatchSafe_,
    hxPostSafe_,
    hxPushUrlSafe_,
    hxPutSafe_,
)
where

import Data.Text (Text)
import Htmx.Lucid.Core (
    hxGet_,
    hxPost_,
    hxPushUrl_,
 )
import Htmx.Lucid.Extra (
    hxDelete_,
    hxPatch_,
    hxPut_,
 )
import Lucid.Base (Attributes)
import Servant.API (ToHttpApiData (..), toUrlPiece)
import Servant.Links (Link)

-- | Type-safe version of 'hxDelete_'
hxDeleteSafe_ :: Link -> Attributes
hxDeleteSafe_ :: Link -> Attributes
hxDeleteSafe_ = Text -> Attributes
hxDelete_ (Text -> Attributes) -> (Link -> Text) -> Link -> Attributes
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Link -> Text
forall a. ToHttpApiData a => a -> Text
toUrl

-- | Type-safe version of 'hxGet_'
hxGetSafe_ :: Link -> Attributes
hxGetSafe_ :: Link -> Attributes
hxGetSafe_ = Text -> Attributes
hxGet_ (Text -> Attributes) -> (Link -> Text) -> Link -> Attributes
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Link -> Text
forall a. ToHttpApiData a => a -> Text
toUrl

-- | Type-safe version of 'hxPatch_'
hxPatchSafe_ :: Link -> Attributes
hxPatchSafe_ :: Link -> Attributes
hxPatchSafe_ = Text -> Attributes
hxPatch_ (Text -> Attributes) -> (Link -> Text) -> Link -> Attributes
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Link -> Text
forall a. ToHttpApiData a => a -> Text
toUrl

-- | Type-safe version of 'hxPatch_'
hxPostSafe_ :: Link -> Attributes
hxPostSafe_ :: Link -> Attributes
hxPostSafe_ = Text -> Attributes
hxPost_ (Text -> Attributes) -> (Link -> Text) -> Link -> Attributes
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Link -> Text
forall a. ToHttpApiData a => a -> Text
toUrl

-- | Type-safe version of 'hxPushUrl_'
hxPushUrlSafe_ :: Either Bool Link -> Attributes
hxPushUrlSafe_ :: Either Bool Link -> Attributes
hxPushUrlSafe_ Either Bool Link
boolOrUrl = Text -> Attributes
hxPushUrl_ (Text -> Attributes) -> Text -> Attributes
forall a b. (a -> b) -> a -> b
$ case Either Bool Link
boolOrUrl of
    Left Bool
bool -> if Bool
bool then Text
"true" else Text
"false"
    Right Link
url -> Link -> Text
forall a. ToHttpApiData a => a -> Text
toUrl Link
url

-- | Type-safe version of 'hxPut_'
hxPutSafe_ :: Link -> Attributes
hxPutSafe_ :: Link -> Attributes
hxPutSafe_ = Text -> Attributes
hxPut_ (Text -> Attributes) -> (Link -> Text) -> Link -> Attributes
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Link -> Text
forall a. ToHttpApiData a => a -> Text
toUrl

toUrl :: (ToHttpApiData a) => a -> Text
toUrl :: forall a. ToHttpApiData a => a -> Text
toUrl = (Text
"/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>) (Text -> Text) -> (a -> Text) -> a -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Text
forall a. ToHttpApiData a => a -> Text
toUrlPiece