{-# LANGUAGE DeriveAnyClass #-} module Horizon.Spec.Types.GitSource (GitSource(MkGitSource), url, revision, subdir) where import Data.Kind (Type) import Dhall (FromDhall, Generic, ToDhall) import Horizon.Spec.Types.Repo (Repo) import Horizon.Spec.Types.Revision (Revision) import Horizon.Spec.Types.Subdir (Subdir) type GitSource :: Type data GitSource where MkGitSource :: { GitSource -> Repo url :: Repo, GitSource -> Revision revision :: Revision, GitSource -> Maybe Subdir subdir :: Maybe Subdir } -> GitSource deriving stock (GitSource -> GitSource -> Bool forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: GitSource -> GitSource -> Bool $c/= :: GitSource -> GitSource -> Bool == :: GitSource -> GitSource -> Bool $c== :: GitSource -> GitSource -> Bool Eq, Int -> GitSource -> ShowS [GitSource] -> ShowS GitSource -> String forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [GitSource] -> ShowS $cshowList :: [GitSource] -> ShowS show :: GitSource -> String $cshow :: GitSource -> String showsPrec :: Int -> GitSource -> ShowS $cshowsPrec :: Int -> GitSource -> ShowS Show, forall x. Rep GitSource x -> GitSource forall x. GitSource -> Rep GitSource x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep GitSource x -> GitSource $cfrom :: forall x. GitSource -> Rep GitSource x Generic) deriving anyclass (InputNormalizer -> Decoder GitSource forall a. (InputNormalizer -> Decoder a) -> FromDhall a autoWith :: InputNormalizer -> Decoder GitSource $cautoWith :: InputNormalizer -> Decoder GitSource FromDhall, InputNormalizer -> Encoder GitSource forall a. (InputNormalizer -> Encoder a) -> ToDhall a injectWith :: InputNormalizer -> Encoder GitSource $cinjectWith :: InputNormalizer -> Encoder GitSource ToDhall)