{-# LANGUAGE RecordWildCards #-}
module Web.Scim.Schema.ListResponse
( ListResponse (..),
fromList,
)
where
import Data.Aeson
import GHC.Generics (Generic)
import Web.Scim.Schema.Common
import Web.Scim.Schema.Schema
data ListResponse a = ListResponse
{ forall a. ListResponse a -> [Schema]
schemas :: [Schema],
forall a. ListResponse a -> Int
totalResults :: Int,
forall a. ListResponse a -> Int
itemsPerPage :: Int,
forall a. ListResponse a -> Int
startIndex :: Int,
forall a. ListResponse a -> [a]
resources :: [a]
}
deriving (Int -> ListResponse a -> ShowS
[ListResponse a] -> ShowS
ListResponse a -> String
(Int -> ListResponse a -> ShowS)
-> (ListResponse a -> String)
-> ([ListResponse a] -> ShowS)
-> Show (ListResponse a)
forall a. Show a => Int -> ListResponse a -> ShowS
forall a. Show a => [ListResponse a] -> ShowS
forall a. Show a => ListResponse a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> ListResponse a -> ShowS
showsPrec :: Int -> ListResponse a -> ShowS
$cshow :: forall a. Show a => ListResponse a -> String
show :: ListResponse a -> String
$cshowList :: forall a. Show a => [ListResponse a] -> ShowS
showList :: [ListResponse a] -> ShowS
Show, ListResponse a -> ListResponse a -> Bool
(ListResponse a -> ListResponse a -> Bool)
-> (ListResponse a -> ListResponse a -> Bool)
-> Eq (ListResponse a)
forall a. Eq a => ListResponse a -> ListResponse a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall a. Eq a => ListResponse a -> ListResponse a -> Bool
== :: ListResponse a -> ListResponse a -> Bool
$c/= :: forall a. Eq a => ListResponse a -> ListResponse a -> Bool
/= :: ListResponse a -> ListResponse a -> Bool
Eq, (forall x. ListResponse a -> Rep (ListResponse a) x)
-> (forall x. Rep (ListResponse a) x -> ListResponse a)
-> Generic (ListResponse a)
forall x. Rep (ListResponse a) x -> ListResponse a
forall x. ListResponse a -> Rep (ListResponse a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (ListResponse a) x -> ListResponse a
forall a x. ListResponse a -> Rep (ListResponse a) x
$cfrom :: forall a x. ListResponse a -> Rep (ListResponse a) x
from :: forall x. ListResponse a -> Rep (ListResponse a) x
$cto :: forall a x. Rep (ListResponse a) x -> ListResponse a
to :: forall x. Rep (ListResponse a) x -> ListResponse a
Generic)
fromList :: [a] -> ListResponse a
fromList :: forall a. [a] -> ListResponse a
fromList [a]
list =
ListResponse
{ schemas :: [Schema]
schemas = [Schema
ListResponse20],
totalResults :: Int
totalResults = Int
len,
itemsPerPage :: Int
itemsPerPage = Int
len,
startIndex :: Int
startIndex = Int
1,
resources :: [a]
resources = [a]
list
}
where
len :: Int
len = [a] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [a]
list
instance (FromJSON a) => FromJSON (ListResponse a) where
parseJSON :: Value -> Parser (ListResponse a)
parseJSON = ([Text] -> Parser (ListResponse a))
-> (Value -> Parser (ListResponse a))
-> Either [Text] Value
-> Parser (ListResponse a)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (String -> Parser (ListResponse a)
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser (ListResponse a))
-> ([Text] -> String) -> [Text] -> Parser (ListResponse a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Text] -> String
forall a. Show a => a -> String
show) (Options -> Value -> Parser (ListResponse a)
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
parseOptions) (Either [Text] Value -> Parser (ListResponse a))
-> (Value -> Either [Text] Value)
-> Value
-> Parser (ListResponse a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> Either [Text] Value
forall (m :: * -> *). (m ~ Either [Text]) => Value -> m Value
jsonLower
instance (ToJSON a) => ToJSON (ListResponse a) where
toJSON :: ListResponse a -> Value
toJSON ListResponse {Int
[a]
[Schema]
startIndex :: forall a. ListResponse a -> Int
schemas :: forall a. ListResponse a -> [Schema]
totalResults :: forall a. ListResponse a -> Int
itemsPerPage :: forall a. ListResponse a -> Int
resources :: forall a. ListResponse a -> [a]
schemas :: [Schema]
totalResults :: Int
itemsPerPage :: Int
startIndex :: Int
resources :: [a]
..} =
[Pair] -> Value
object
[ Key
"Resources" Key -> [a] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= [a]
resources,
Key
"schemas" Key -> [Schema] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= [Schema]
schemas,
Key
"totalResults" Key -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= Int
totalResults,
Key
"itemsPerPage" Key -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= Int
itemsPerPage,
Key
"startIndex" Key -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= Int
startIndex
]