module Proteome.Data.ProjectSpec where import Ribosome (MsgpackDecode, MsgpackEncode) import Proteome.Data.ProjectLang (ProjectLang) import Proteome.Data.ProjectName (ProjectName) import Proteome.Data.ProjectRoot (ProjectRoot) import Proteome.Data.ProjectType (ProjectType) data ProjectSpec = ProjectSpec { ProjectSpec -> ProjectName name :: ProjectName, ProjectSpec -> ProjectRoot root :: ProjectRoot, ProjectSpec -> Maybe ProjectType tpe :: Maybe ProjectType, ProjectSpec -> [ProjectType] types :: [ProjectType], ProjectSpec -> Maybe ProjectLang lang :: Maybe ProjectLang, ProjectSpec -> [ProjectLang] langs :: [ProjectLang] } deriving stock (ProjectSpec -> ProjectSpec -> Bool (ProjectSpec -> ProjectSpec -> Bool) -> (ProjectSpec -> ProjectSpec -> Bool) -> Eq ProjectSpec forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: ProjectSpec -> ProjectSpec -> Bool $c/= :: ProjectSpec -> ProjectSpec -> Bool == :: ProjectSpec -> ProjectSpec -> Bool $c== :: ProjectSpec -> ProjectSpec -> Bool Eq, Int -> ProjectSpec -> ShowS [ProjectSpec] -> ShowS ProjectSpec -> String (Int -> ProjectSpec -> ShowS) -> (ProjectSpec -> String) -> ([ProjectSpec] -> ShowS) -> Show ProjectSpec forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [ProjectSpec] -> ShowS $cshowList :: [ProjectSpec] -> ShowS show :: ProjectSpec -> String $cshow :: ProjectSpec -> String showsPrec :: Int -> ProjectSpec -> ShowS $cshowsPrec :: Int -> ProjectSpec -> ShowS Show, (forall x. ProjectSpec -> Rep ProjectSpec x) -> (forall x. Rep ProjectSpec x -> ProjectSpec) -> Generic ProjectSpec forall x. Rep ProjectSpec x -> ProjectSpec forall x. ProjectSpec -> Rep ProjectSpec x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep ProjectSpec x -> ProjectSpec $cfrom :: forall x. ProjectSpec -> Rep ProjectSpec x Generic) deriving anyclass (Object -> Either DecodeError ProjectSpec (Object -> Either DecodeError ProjectSpec) -> MsgpackDecode ProjectSpec forall a. (Object -> Either DecodeError a) -> MsgpackDecode a fromMsgpack :: Object -> Either DecodeError ProjectSpec $cfromMsgpack :: Object -> Either DecodeError ProjectSpec MsgpackDecode, ProjectSpec -> Object (ProjectSpec -> Object) -> MsgpackEncode ProjectSpec forall a. (a -> Object) -> MsgpackEncode a toMsgpack :: ProjectSpec -> Object $ctoMsgpack :: ProjectSpec -> Object MsgpackEncode)