Reputation: 983
I'm building an API client for one service and the main reason to use that over raw API is to present all the nice types for the user.
One type I made is for optional query parameters which will be different for each endpoint (instead of forcing the user to provide a list of tuples of strings):
data ListDatasetsParams = ListDatasetsParams {
offset :: Maybe Int,
limit :: Maybe Int,
desc :: Maybe Bool,
unnamed :: Maybe Bool
}
Now I would like to convert this type into a Query which has the signature
type Query = [QueryItem]
type QueryItem = (ByteString, Maybe ByteString)
I didn't really find a way to do it at least a bit generic. The only way I got it working is pure hardcode where I check every param and manually add a correct string.
Can I do better? Or is there any other more idiomatic way to do this in Haskell?
Upvotes: 1
Views: 196
Reputation: 48592
You can do this with generics:
{-# LANGUAGE DefaultSignatures, DeriveGeneric, FlexibleContexts, FlexibleInstances, TypeOperators #-}
import GHC.Generics
import Data.ByteString (ByteString)
import Data.String
type Query = [QueryItem]
type QueryItem = (ByteString, Maybe ByteString)
class ToByteString a where
toByteString :: a -> ByteString
default toByteString :: Show a => a -> ByteString
toByteString = fromString . show
instance ToByteString Int
instance ToByteString Bool
instance ToByteString [Char] where
toByteString = fromString
class GToQuery f where
gToQuery :: f a -> Query
instance (GToQuery a, GToQuery b) => GToQuery (a :*: b) where
gToQuery (a :*: b) = gToQuery a ++ gToQuery b
instance GToQuery a => GToQuery (M1 D c a) where
gToQuery (M1 x) = gToQuery x
instance GToQuery a => GToQuery (M1 C c a) where
gToQuery (M1 x) = gToQuery x
instance (Selector c, ToByteString a) => GToQuery (M1 S c (K1 i (Maybe a))) where
gToQuery s@(M1 (K1 x)) = [(toByteString (selName s), fmap toByteString x)]
class ToQuery a where
toQuery :: a -> Query
default toQuery :: (Generic a, GToQuery (Rep a)) => a -> Query
toQuery = gToQuery . from
data ListDatasetsParams = ListDatasetsParams {
offset :: Maybe Int,
limit :: Maybe Int,
desc :: Maybe Bool,
unnamed :: Maybe Bool
} deriving(Generic)
instance ToQuery ListDatasetsParams
It works like this:
*Main> toQuery (ListDatasetsParams (Just 1) Nothing (Just True) Nothing )
[("offset",Just "1"),("limit",Nothing),("desc",Just "True"),("unnamed",Nothing)]
*Main>
Upvotes: 3