module Twilio.Types.List
( List(..)
, PagingInformation(..)
, Wrapper
, wrap
) where
import Control.Applicative
import Control.Monad
import Data.Aeson
import Data.Aeson.Types
import Data.Data
import Data.Text (Text)
import Debug.Trace (trace)
import GHC.Generics
import Network.URI
(<&>) :: Functor f => f a -> (a -> b) -> f b
(<&>) = flip fmap
class FromJSON b => List a b | a -> b where
getListWrapper :: Wrapper (Maybe PagingInformation -> [b] -> a)
getList :: a -> [b]
getPlural :: Const Text (a, b)
parseJSONToList :: Value -> Parser a
parseJSONToList o@(Object v)
= unwrap (getListWrapper :: Wrapper (Maybe PagingInformation -> [b] -> a))
<$> maybePagingInformation
<*> (v .: getConst (getPlural :: Const Text (a, b)) :: Parser [b])
where
maybePagingInformation = case fromJSON o of
Success pagingInformation -> return $ Just pagingInformation
_ -> return Nothing
parseJSONToList v = trace (show v) mzero
data PagingInformation = PagingInformation
{
pageNumber :: !Integer
, numberOfPages :: !(Maybe Integer)
, pageSize :: !Integer
, total :: !(Maybe Integer)
, start :: !Integer
, end :: !Integer
, pageURI :: !(Maybe URI)
, firstPageURI :: !(Maybe URI)
, nextPageURI :: !(Maybe URI)
, previousPageURI :: !(Maybe URI)
, lastPageURI :: !(Maybe URI)
} deriving (Data, Eq, Generic, Ord, Show, Typeable)
instance FromJSON PagingInformation where
parseJSON (Object v)
= PagingInformation
<$> v .: "page"
<*> v .:? "num_pages"
<*> v .: "page_size"
<*> v .:? "total"
<*> v .: "start"
<*> v .: "end"
<*> (v .: "uri" <&> fmap parseRelativeReference
>>= maybeReturn')
<*> (v .: "first_page_uri" <&> fmap parseRelativeReference
>>= maybeReturn')
<*> (v .: "next_page_uri" <&> fmap parseRelativeReference
>>= maybeReturn')
<*> (v .: "previous_page_uri" <&> fmap parseRelativeReference
>>= maybeReturn')
<*> (v .:? "last_page_uri" <&> fmap parseRelativeReference
>>= maybeReturn')
parseJSON _ = mzero
maybeReturn' :: Maybe (Maybe a) -> Parser (Maybe a)
maybeReturn' Nothing = return Nothing
maybeReturn' (Just Nothing) = mzero
maybeReturn' (Just ma) = return ma
newtype Wrapper a = Wrapper { unwrap :: a }
wrap :: a -> Wrapper a
wrap = Wrapper