module Hercules.API.ShowRead
( ShowRead (ShowRead),
)
where
import Data.Either (Either (Right))
import Data.Text qualified as T
import Web.HttpApiData (FromHttpApiData (parseQueryParam), ToHttpApiData)
import Web.Internal.HttpApiData (ToHttpApiData (toUrlPiece))
import Prelude (Either (Left), Read, Show (show), reads)
newtype ShowRead a = ShowRead a
instance (Show a) => ToHttpApiData (ShowRead a) where
toUrlPiece :: ShowRead a -> Text
toUrlPiece (ShowRead a
a) = Text -> Text
forall a. ToHttpApiData a => a -> Text
toUrlPiece (String -> Text
T.pack (a -> String
forall a. Show a => a -> String
show a
a))
instance (Read a) => FromHttpApiData (ShowRead a) where
parseQueryParam :: Text -> Either Text (ShowRead a)
parseQueryParam Text
t =
case ReadS a
forall a. Read a => ReadS a
reads (Text -> String
T.unpack Text
t) of
[(a
a, String
"")] -> ShowRead a -> Either Text (ShowRead a)
forall a b. b -> Either a b
Right (a -> ShowRead a
forall a. a -> ShowRead a
ShowRead a
a)
[(a, String)]
_ -> Text -> Either Text (ShowRead a)
forall a b. a -> Either a b
Left Text
"Could not parse"