{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE OverloadedStrings #-} module Zuul.Project (Project (..), ProjectType (..)) where import Data.Aeson (FromJSON (..), ToJSON (..), Value (String)) import Data.Aeson.Types (prependFailure, typeMismatch) import Data.Text (Text) import GHC.Generics (Generic) import Zuul.Aeson (zuulParseJSON, zuulToJSON) data ProjectType = ProjectConfig | ProjectUntrusted deriving (Int -> ProjectType -> ShowS [ProjectType] -> ShowS ProjectType -> String (Int -> ProjectType -> ShowS) -> (ProjectType -> String) -> ([ProjectType] -> ShowS) -> Show ProjectType forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [ProjectType] -> ShowS $cshowList :: [ProjectType] -> ShowS show :: ProjectType -> String $cshow :: ProjectType -> String showsPrec :: Int -> ProjectType -> ShowS $cshowsPrec :: Int -> ProjectType -> ShowS Show, ProjectType -> ProjectType -> Bool (ProjectType -> ProjectType -> Bool) -> (ProjectType -> ProjectType -> Bool) -> Eq ProjectType forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: ProjectType -> ProjectType -> Bool $c/= :: ProjectType -> ProjectType -> Bool == :: ProjectType -> ProjectType -> Bool $c== :: ProjectType -> ProjectType -> Bool Eq, Eq ProjectType Eq ProjectType -> (ProjectType -> ProjectType -> Ordering) -> (ProjectType -> ProjectType -> Bool) -> (ProjectType -> ProjectType -> Bool) -> (ProjectType -> ProjectType -> Bool) -> (ProjectType -> ProjectType -> Bool) -> (ProjectType -> ProjectType -> ProjectType) -> (ProjectType -> ProjectType -> ProjectType) -> Ord ProjectType ProjectType -> ProjectType -> Bool ProjectType -> ProjectType -> Ordering ProjectType -> ProjectType -> ProjectType forall a. Eq a -> (a -> a -> Ordering) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> a) -> (a -> a -> a) -> Ord a min :: ProjectType -> ProjectType -> ProjectType $cmin :: ProjectType -> ProjectType -> ProjectType max :: ProjectType -> ProjectType -> ProjectType $cmax :: ProjectType -> ProjectType -> ProjectType >= :: ProjectType -> ProjectType -> Bool $c>= :: ProjectType -> ProjectType -> Bool > :: ProjectType -> ProjectType -> Bool $c> :: ProjectType -> ProjectType -> Bool <= :: ProjectType -> ProjectType -> Bool $c<= :: ProjectType -> ProjectType -> Bool < :: ProjectType -> ProjectType -> Bool $c< :: ProjectType -> ProjectType -> Bool compare :: ProjectType -> ProjectType -> Ordering $ccompare :: ProjectType -> ProjectType -> Ordering $cp1Ord :: Eq ProjectType Ord, (forall x. ProjectType -> Rep ProjectType x) -> (forall x. Rep ProjectType x -> ProjectType) -> Generic ProjectType forall x. Rep ProjectType x -> ProjectType forall x. ProjectType -> Rep ProjectType x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep ProjectType x -> ProjectType $cfrom :: forall x. ProjectType -> Rep ProjectType x Generic) data Project = Project { Project -> Text projectName :: Text, Project -> ProjectType projectType :: ProjectType, Project -> Text projectCanonicalName :: Text, Project -> Text projectConnectionName :: Text } deriving (Int -> Project -> ShowS [Project] -> ShowS Project -> String (Int -> Project -> ShowS) -> (Project -> String) -> ([Project] -> ShowS) -> Show Project forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [Project] -> ShowS $cshowList :: [Project] -> ShowS show :: Project -> String $cshow :: Project -> String showsPrec :: Int -> Project -> ShowS $cshowsPrec :: Int -> Project -> ShowS Show, Project -> Project -> Bool (Project -> Project -> Bool) -> (Project -> Project -> Bool) -> Eq Project forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: Project -> Project -> Bool $c/= :: Project -> Project -> Bool == :: Project -> Project -> Bool $c== :: Project -> Project -> Bool Eq, Eq Project Eq Project -> (Project -> Project -> Ordering) -> (Project -> Project -> Bool) -> (Project -> Project -> Bool) -> (Project -> Project -> Bool) -> (Project -> Project -> Bool) -> (Project -> Project -> Project) -> (Project -> Project -> Project) -> Ord Project Project -> Project -> Bool Project -> Project -> Ordering Project -> Project -> Project forall a. Eq a -> (a -> a -> Ordering) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> a) -> (a -> a -> a) -> Ord a min :: Project -> Project -> Project $cmin :: Project -> Project -> Project max :: Project -> Project -> Project $cmax :: Project -> Project -> Project >= :: Project -> Project -> Bool $c>= :: Project -> Project -> Bool > :: Project -> Project -> Bool $c> :: Project -> Project -> Bool <= :: Project -> Project -> Bool $c<= :: Project -> Project -> Bool < :: Project -> Project -> Bool $c< :: Project -> Project -> Bool compare :: Project -> Project -> Ordering $ccompare :: Project -> Project -> Ordering $cp1Ord :: Eq Project Ord, (forall x. Project -> Rep Project x) -> (forall x. Rep Project x -> Project) -> Generic Project forall x. Rep Project x -> Project forall x. Project -> Rep Project x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep Project x -> Project $cfrom :: forall x. Project -> Rep Project x Generic) instance ToJSON ProjectType where toJSON :: ProjectType -> Value toJSON ProjectType v = case ProjectType v of ProjectType ProjectConfig -> Value "config" ProjectType ProjectUntrusted -> Value "untrusted" instance FromJSON ProjectType where parseJSON :: Value -> Parser ProjectType parseJSON (String Text s) = ProjectType -> Parser ProjectType forall (f :: * -> *) a. Applicative f => a -> f a pure (ProjectType -> Parser ProjectType) -> ProjectType -> Parser ProjectType forall a b. (a -> b) -> a -> b $ case Text s of Text "config" -> ProjectType ProjectConfig Text "untrusted" -> ProjectType ProjectUntrusted Text _ -> String -> ProjectType forall a. HasCallStack => String -> a error String "Received unrecognized ProjectType" parseJSON Value invalid = String -> Parser ProjectType -> Parser ProjectType forall a. String -> Parser a -> Parser a prependFailure String "parsing ProjectType failed, " (String -> Value -> Parser ProjectType forall a. String -> Value -> Parser a typeMismatch String "String" Value invalid) instance ToJSON Project where toJSON :: Project -> Value toJSON = Text -> Project -> Value forall a. (Generic a, GToJSON' Value Zero (Rep a)) => Text -> a -> Value zuulToJSON Text "project" instance FromJSON Project where parseJSON :: Value -> Parser Project parseJSON = Text -> Value -> Parser Project forall a. (Generic a, GFromJSON Zero (Rep a)) => Text -> Value -> Parser a zuulParseJSON Text "project"