module Network.API.Builder.Query where

import Data.Monoid
import Data.Text (Text)
import qualified Data.Text as Text

class ToQuery a where
  toQuery :: Text -> a -> [(Text, Text)]

instance ToQuery Integer where
  toQuery k v = [(k, Text.pack $ show v)]

instance ToQuery Bool where
  toQuery k True = [(k, "true")]
  toQuery k False = [(k, "false")]

instance ToQuery Int where
  toQuery k v = [(k, Text.pack $ show v)]

instance ToQuery Text where
  toQuery k v = [(k, v)]

instance ToQuery a => ToQuery (Maybe a) where
  toQuery k (Just a) = toQuery k a
  toQuery _ Nothing = []

instance ToQuery a => ToQuery [a] where
  toQuery _ [] = []
  toQuery k xs = [(k, Text.intercalate "," $ map snd $ concatMap (toQuery k) xs)]

newtype IndexedList a = IndexedList [a]
  deriving (Show, Read, Eq)

instance ToQuery a => ToQuery (IndexedList a) where
  toQuery _ (IndexedList []) = []
  toQuery k (IndexedList l) =
    zipWith (\n (x, y) -> (x <> "[" <> tshow n <> "]", y)) ([0..] :: [Integer]) $ concatMap (toQuery k) l
    where tshow = Text.pack . show