{-# LANGUAGE QuasiQuotes #-}
module Web.Scim.Schema.ResourceType where
import Data.Aeson
import Data.Text (Text)
import GHC.Generics (Generic)
import Network.URI.Static
import Web.Scim.Schema.Common
import Web.Scim.Schema.Schema (Schema (..))
import Prelude hiding (map)
data ResourceType
= UserResource
| GroupResource
deriving (Int -> ResourceType -> ShowS
[ResourceType] -> ShowS
ResourceType -> String
(Int -> ResourceType -> ShowS)
-> (ResourceType -> String)
-> ([ResourceType] -> ShowS)
-> Show ResourceType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ResourceType -> ShowS
showsPrec :: Int -> ResourceType -> ShowS
$cshow :: ResourceType -> String
show :: ResourceType -> String
$cshowList :: [ResourceType] -> ShowS
showList :: [ResourceType] -> ShowS
Show, ResourceType -> ResourceType -> Bool
(ResourceType -> ResourceType -> Bool)
-> (ResourceType -> ResourceType -> Bool) -> Eq ResourceType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ResourceType -> ResourceType -> Bool
== :: ResourceType -> ResourceType -> Bool
$c/= :: ResourceType -> ResourceType -> Bool
/= :: ResourceType -> ResourceType -> Bool
Eq, Int -> ResourceType
ResourceType -> Int
ResourceType -> [ResourceType]
ResourceType -> ResourceType
ResourceType -> ResourceType -> [ResourceType]
ResourceType -> ResourceType -> ResourceType -> [ResourceType]
(ResourceType -> ResourceType)
-> (ResourceType -> ResourceType)
-> (Int -> ResourceType)
-> (ResourceType -> Int)
-> (ResourceType -> [ResourceType])
-> (ResourceType -> ResourceType -> [ResourceType])
-> (ResourceType -> ResourceType -> [ResourceType])
-> (ResourceType -> ResourceType -> ResourceType -> [ResourceType])
-> Enum ResourceType
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: ResourceType -> ResourceType
succ :: ResourceType -> ResourceType
$cpred :: ResourceType -> ResourceType
pred :: ResourceType -> ResourceType
$ctoEnum :: Int -> ResourceType
toEnum :: Int -> ResourceType
$cfromEnum :: ResourceType -> Int
fromEnum :: ResourceType -> Int
$cenumFrom :: ResourceType -> [ResourceType]
enumFrom :: ResourceType -> [ResourceType]
$cenumFromThen :: ResourceType -> ResourceType -> [ResourceType]
enumFromThen :: ResourceType -> ResourceType -> [ResourceType]
$cenumFromTo :: ResourceType -> ResourceType -> [ResourceType]
enumFromTo :: ResourceType -> ResourceType -> [ResourceType]
$cenumFromThenTo :: ResourceType -> ResourceType -> ResourceType -> [ResourceType]
enumFromThenTo :: ResourceType -> ResourceType -> ResourceType -> [ResourceType]
Enum, ResourceType
ResourceType -> ResourceType -> Bounded ResourceType
forall a. a -> a -> Bounded a
$cminBound :: ResourceType
minBound :: ResourceType
$cmaxBound :: ResourceType
maxBound :: ResourceType
Bounded)
instance ToJSON ResourceType where
toJSON :: ResourceType -> Value
toJSON ResourceType
UserResource = Value
"User"
toJSON ResourceType
GroupResource = Value
"Group"
instance FromJSON ResourceType where
parseJSON :: Value -> Parser ResourceType
parseJSON = String
-> (Text -> Parser ResourceType) -> Value -> Parser ResourceType
forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
"ResourceType" ((Text -> Parser ResourceType) -> Value -> Parser ResourceType)
-> (Text -> Parser ResourceType) -> Value -> Parser ResourceType
forall a b. (a -> b) -> a -> b
$ \case
Text
"User" -> ResourceType -> Parser ResourceType
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ResourceType
UserResource
Text
"Group" -> ResourceType -> Parser ResourceType
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ResourceType
GroupResource
Text
other -> String -> Parser ResourceType
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String
"unknown ResourceType: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Text -> String
forall a. Show a => a -> String
show Text
other)
data Resource = Resource
{ Resource -> Text
name :: Text,
Resource -> URI
endpoint :: URI,
Resource -> Schema
schema :: Schema
}
deriving (Int -> Resource -> ShowS
[Resource] -> ShowS
Resource -> String
(Int -> Resource -> ShowS)
-> (Resource -> String) -> ([Resource] -> ShowS) -> Show Resource
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Resource -> ShowS
showsPrec :: Int -> Resource -> ShowS
$cshow :: Resource -> String
show :: Resource -> String
$cshowList :: [Resource] -> ShowS
showList :: [Resource] -> ShowS
Show, Resource -> Resource -> Bool
(Resource -> Resource -> Bool)
-> (Resource -> Resource -> Bool) -> Eq Resource
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Resource -> Resource -> Bool
== :: Resource -> Resource -> Bool
$c/= :: Resource -> Resource -> Bool
/= :: Resource -> Resource -> Bool
Eq, (forall x. Resource -> Rep Resource x)
-> (forall x. Rep Resource x -> Resource) -> Generic Resource
forall x. Rep Resource x -> Resource
forall x. Resource -> Rep Resource x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Resource -> Rep Resource x
from :: forall x. Resource -> Rep Resource x
$cto :: forall x. Rep Resource x -> Resource
to :: forall x. Rep Resource x -> Resource
Generic)
instance ToJSON Resource where
toJSON :: Resource -> Value
toJSON = Options -> Resource -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
serializeOptions
instance FromJSON Resource where
parseJSON :: Value -> Parser Resource
parseJSON = ([Text] -> Parser Resource)
-> (Value -> Parser Resource)
-> Either [Text] Value
-> Parser Resource
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (String -> Parser Resource
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser Resource)
-> ([Text] -> String) -> [Text] -> Parser Resource
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Text] -> String
forall a. Show a => a -> String
show) (Options -> Value -> Parser Resource
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
parseOptions) (Either [Text] Value -> Parser Resource)
-> (Value -> Either [Text] Value) -> Value -> Parser Resource
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> Either [Text] Value
forall (m :: * -> *). (m ~ Either [Text]) => Value -> m Value
jsonLower
usersResource :: Resource
usersResource :: Resource
usersResource =
Resource
{ name :: Text
name = Text
"User",
endpoint :: URI
endpoint = URI -> URI
URI [relativeReference|/Users|],
schema :: Schema
schema = Schema
User20
}
groupsResource :: Resource
groupsResource :: Resource
groupsResource =
Resource
{ name :: Text
name = Text
"Group",
endpoint :: URI
endpoint = URI -> URI
URI [relativeReference|/Groups|],
schema :: Schema
schema = Schema
Group20
}