module Web.Slack.Util (
formOpts,
jsonOpts,
toQueryParamIfJust,
) where
import Data.Aeson.TH
import Data.Aeson.Types
import Data.Char
import Data.Maybe (maybeToList)
import Data.Text (Text)
import Data.Text qualified as Text
import GHC.Exts (fromList)
import Web.FormUrlEncoded (Form, FormOptions (FormOptions))
import Web.HttpApiData (ToHttpApiData, toQueryParam)
import Prelude
formOpts ::
Text ->
FormOptions
formOpts :: Text -> FormOptions
formOpts Text
prefix =
(String -> String) -> FormOptions
FormOptions (Text -> String -> String
modifyLabel Text
prefix)
jsonOpts ::
Text ->
Options
jsonOpts :: Text -> Options
jsonOpts Text
prefix =
Options
defaultOptions
{ fieldLabelModifier = modifyLabel prefix
}
modifyLabel ::
Text ->
String ->
String
modifyLabel :: Text -> String -> String
modifyLabel Text
prefix =
(Char -> Char) -> String -> String
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Char -> Char
toLower
(String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
addUnderscores
(String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
drop (Text -> Int
Text.length Text
prefix)
addUnderscores ::
String ->
String
addUnderscores :: String -> String
addUnderscores =
Char -> String -> String
camelTo2 Char
'_'
toQueryParamIfJust :: (ToHttpApiData a) => Text -> Maybe a -> Form
toQueryParamIfJust :: forall a. ToHttpApiData a => Text -> Maybe a -> Form
toQueryParamIfJust Text
key =
[(Text, Text)] -> Form
[Item Form] -> Form
forall l. IsList l => [Item l] -> l
fromList ([(Text, Text)] -> Form)
-> (Maybe a -> [(Text, Text)]) -> Maybe a -> Form
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe (Text, Text) -> [(Text, Text)]
forall a. Maybe a -> [a]
maybeToList (Maybe (Text, Text) -> [(Text, Text)])
-> (Maybe a -> Maybe (Text, Text)) -> Maybe a -> [(Text, Text)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> (Text, Text)) -> Maybe a -> Maybe (Text, Text)
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\a
justVal -> (Text
key, a -> Text
forall a. ToHttpApiData a => a -> Text
toQueryParam a
justVal))