module Web.Minion.Request.Query.Internal where import Data.Bifunctor (Bifunctor (..)) import Data.ByteString import Data.Text (Text) import Data.ByteString.Lazy qualified as Bytes.Lazy import Data.String.Conversions (ConvertibleStrings (..)) import Data.Text.Encoding qualified as Text.Encoding import Network.HTTP.Types qualified as Http import Web.HttpApiData (FromHttpApiData (parseQueryParam)) import Web.Minion.Error (ServerError (..)) import Web.Minion.Router.Internal (MakeError) queryParamKeyNotFoundError :: Text -> Bytes.Lazy.ByteString queryParamKeyNotFoundError :: Text -> ByteString queryParamKeyNotFoundError Text qn = Text -> ByteString forall a b. ConvertibleStrings a b => a -> b convertString (Text -> ByteString) -> Text -> ByteString forall a b. (a -> b) -> a -> b $ Text "Query param not found: " Text -> Text -> Text forall a. Semigroup a => a -> a -> a <> Text qn queryParamValueNotFoundError :: Text -> Bytes.Lazy.ByteString queryParamValueNotFoundError :: Text -> ByteString queryParamValueNotFoundError Text qn = Text -> ByteString forall a b. ConvertibleStrings a b => a -> b convertString (Text -> ByteString) -> Text -> ByteString forall a b. (a -> b) -> a -> b $ Text "Query param value not found: " Text -> Text -> Text forall a. Semigroup a => a -> a -> a <> Text qn decodeQueryParam :: (FromHttpApiData a) => ByteString -> Either Text a decodeQueryParam :: forall a. FromHttpApiData a => ByteString -> Either Text a decodeQueryParam = Text -> Either Text a forall a. FromHttpApiData a => Text -> Either Text a parseQueryParam (Text -> Either Text a) -> (ByteString -> Text) -> ByteString -> Either Text a forall b c a. (b -> c) -> (a -> b) -> a -> c . ByteString -> Text Text.Encoding.decodeUtf8 decodeQueryParamOrServerError :: (FromHttpApiData a) => MakeError -> ByteString -> Either ServerError a decodeQueryParamOrServerError :: forall a. FromHttpApiData a => MakeError -> ByteString -> Either ServerError a decodeQueryParamOrServerError MakeError makeError = (Text -> ServerError) -> Either Text a -> Either ServerError a forall a b c. (a -> b) -> Either a c -> Either b c forall (p :: * -> * -> *) a b c. Bifunctor p => (a -> b) -> p a c -> p b c first (MakeError makeError Status Http.status400 (ByteString -> ServerError) -> (Text -> ByteString) -> Text -> ServerError forall b c a. (b -> c) -> (a -> b) -> a -> c . Text -> ByteString forall a b. ConvertibleStrings a b => a -> b convertString) (Either Text a -> Either ServerError a) -> (ByteString -> Either Text a) -> ByteString -> Either ServerError a forall b c a. (b -> c) -> (a -> b) -> a -> c . ByteString -> Either Text a forall a. FromHttpApiData a => ByteString -> Either Text a decodeQueryParam