{-# LANGUAGE DeriveAnyClass #-} module Horizon.Spec where import Data.Kind (Type) import Data.Map (Map) import Data.Text (Text) import Dhall (FromDhall, Generic, ToDhall) import Path (Dir, Path, Rel) import Path.Dhall () type Url :: Type newtype Url = MkUrl { fromUrl :: Text } deriving stock (Eq, Show) deriving newtype (FromDhall, ToDhall) type Repo :: Type newtype Repo = MkRepo { fromRepo :: Url } deriving stock (Eq, Show) deriving newtype (FromDhall, ToDhall) type Subdir :: Type newtype Subdir = MkSubdir { fromSubdir :: Path Rel Dir } deriving stock (Eq, Show) deriving newtype (FromDhall, ToDhall) type Name :: Type newtype Name = MkName { fromName :: Text } deriving stock (Eq, Ord, Show) deriving newtype (FromDhall, ToDhall) type Version :: Type newtype Version = MkVersion { fromVersion :: Text } deriving stock (Eq, Show) deriving newtype (FromDhall, ToDhall) type GitSource :: Type data GitSource where MkGitSource :: { url :: Repo, revision :: Revision, subdir :: Maybe Subdir } -> GitSource deriving stock (Eq, Show, Generic) deriving anyclass (FromDhall, ToDhall) type HackageSource :: Type data HackageSource where MkHackageSource :: { name :: Name, version :: Version } -> HackageSource deriving stock (Eq, Show, Generic) deriving anyclass (FromDhall, ToDhall) type HaskellSource :: Type data HaskellSource where FromGit :: GitSource -> HaskellSource FromHackage :: HackageSource -> HaskellSource deriving stock (Show, Eq, Generic) deriving anyclass (FromDhall, ToDhall) type Flag :: Type -> Type data Flag a where Enable :: a -> Flag a Disable :: a -> Flag a deriving stock (Show, Eq, Generic) deriving anyclass (FromDhall, ToDhall) type CabalFlag :: Type data CabalFlag where MkCabalFlag :: Flag Text -> CabalFlag deriving stock (Show, Eq, Generic) deriving anyclass (FromDhall, ToDhall) type Modifiers :: Type data Modifiers where MkModifiers :: { doJailbreak :: Bool , doCheck :: Bool , enableProfiling :: Bool } -> Modifiers deriving stock (Show, Eq, Generic) deriving anyclass (FromDhall, ToDhall) type HaskellPackage :: Type data HaskellPackage where MkHaskellPackage :: { source :: HaskellSource , modifiers :: Modifiers , flags :: [CabalFlag] } -> HaskellPackage deriving stock (Show, Eq, Generic) deriving anyclass (FromDhall, ToDhall) type Revision :: Type newtype Revision where MkRevision :: { fromRevision :: Text } -> Revision deriving stock (Show, Eq, Generic) deriving newtype (FromDhall, ToDhall) type Compiler :: Type newtype Compiler where MkCompiler :: { fromCompiler :: Text } -> Compiler deriving stock (Show, Eq, Generic) deriving newtype (FromDhall, ToDhall) type PackageList :: Type newtype PackageList where MkPackageList :: { fromPackageList :: Map Name HaskellPackage } -> PackageList deriving stock (Show, Eq, Generic) deriving newtype (FromDhall, ToDhall) type Overlay :: Type newtype Overlay where MkOverlay :: { fromOverlay :: PackageList } -> Overlay deriving stock (Show, Eq, Generic) deriving newtype (FromDhall, ToDhall) type PackageSet :: Type data PackageSet where MkPackageSet :: { compiler :: Compiler , packages :: PackageList } -> PackageSet deriving stock (Show, Eq, Generic) deriving anyclass (FromDhall, ToDhall)