{-# LANGUAGE DeriveAnyClass #-} {-# LANGUAGE DuplicateRecordFields #-} {-# LANGUAGE TemplateHaskell #-} module Horizon.Spec ( CabalFlag(MkCabalFlag) , Compiler(MkCompiler, fromCompiler) , Flag(Enable, Disable) , GitSource(MkGitSource, url, revision, subdir) , HackageSource(MkHackageSource, name, version) , HaskellPackage(MkHaskellPackage, source, modifiers, flags) , HaskellSource(FromGit, FromHackage, FromTarball, FromLocal) , HorizonExport(MakePackageSet, MakeOverlay) , LocalSource(MkLocalSource, fromLocalSource) , Modifiers(MkModifiers, doJailbreak, doBenchmark, doCheck, enableProfiling, includeBenchmarks, includeExecutables, includeTests) , Name(MkName, fromName) , OverlayExportSettings(MkOverlayExportSettings, packagesDir, overlayFile, overlay) , OverlayFile(MkOverlayFile, fromOverlayFile) , Overlay(MkOverlay, fromOverlay) , PackageList(MkPackageList, fromPackageList) , PackageSetExportSettings(MkPackageSetExportSettings, packagesDir, packageSetFile, packageSet) , PackageSetFile(MkPackageSetFile, fromPackageSetFile) , PackageSet(MkPackageSet, compiler, packages) , PackagesDir(MkPackagesDir, fromPackagesDir) , Repo(MkRepo, fromRepo) , Revision(MkRevision, fromRevision) , Subdir(MkSubdir, fromSubdir) , mkSubdir , TarballSource(MkTarballSource, fromTarballSource) , Url(MkUrl, fromUrl) , Version (MkVersion, fromVersion) ) where import Data.Kind (Type) import Data.Map (Map) import Data.String (IsString) import Data.Text (Text) import Dhall (FromDhall, Generic, ToDhall) import Language.Haskell.TH (Exp, Q) import Language.Haskell.TH.Lift (deriveLift, lift) import Path (Dir, File, Path, Rel, parseRelDir) import Path.Dhall () type Url :: Type newtype Url = MkUrl { fromUrl :: Text } deriving stock (Eq, Show) deriving newtype (FromDhall, ToDhall, IsString) type Repo :: Type newtype Repo = MkRepo { fromRepo :: Url } deriving stock (Eq, Show) deriving newtype (FromDhall, ToDhall, IsString) type Subdir :: Type newtype Subdir = MkSubdir { fromSubdir :: Path Rel Dir } deriving stock (Eq, Show) deriving newtype (FromDhall, ToDhall) $(deriveLift 'MkSubdir) mkSubdir :: FilePath -> Q Exp mkSubdir = either (error . show) (lift . MkSubdir) . parseRelDir type Name :: Type newtype Name = MkName { fromName :: Text } deriving stock (Eq, Ord, Show) deriving newtype (FromDhall, ToDhall, IsString) type Version :: Type newtype Version = MkVersion { fromVersion :: Text } deriving stock (Eq, Show) deriving newtype (FromDhall, ToDhall, IsString) 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 LocalSource :: Type newtype LocalSource where MkLocalSource :: { fromLocalSource :: Subdir } -> LocalSource deriving stock (Eq, Show, Generic) deriving newtype (FromDhall, ToDhall) type TarballSource :: Type newtype TarballSource where MkTarballSource :: { fromTarballSource :: Url } -> TarballSource deriving stock (Eq, Show, Generic) deriving newtype (FromDhall, ToDhall) type HaskellSource :: Type data HaskellSource where FromGit :: GitSource -> HaskellSource FromHackage :: HackageSource -> HaskellSource FromLocal :: LocalSource -> HaskellSource FromTarball :: TarballSource -> 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 :: { doBenchmark :: Bool , doCheck :: Bool , doJailbreak :: Bool , enableProfiling :: Bool , includeBenchmarks :: Bool , includeExecutables :: Bool , includeTests :: 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, IsString) 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 :: PackageSet } -> 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) type PackagesDir :: Type newtype PackagesDir where MkPackagesDir :: { fromPackagesDir :: Path Rel Dir } -> PackagesDir deriving stock (Show, Eq, Generic) deriving newtype (FromDhall, ToDhall) type PackageSetFile :: Type newtype PackageSetFile where MkPackageSetFile :: { fromPackageSetFile :: Path Rel File } -> PackageSetFile deriving stock (Show, Eq, Generic) deriving newtype (FromDhall, ToDhall) type OverlayFile :: Type newtype OverlayFile where MkOverlayFile :: { fromOverlayFile :: Path Rel File } -> OverlayFile deriving stock (Show, Eq, Generic) deriving newtype (FromDhall, ToDhall) type PackageSetExportSettings :: Type data PackageSetExportSettings where MkPackageSetExportSettings :: { packagesDir :: PackagesDir , packageSetFile :: PackageSetFile , packageSet :: PackageSet } -> PackageSetExportSettings deriving stock (Show, Eq, Generic) deriving anyclass (FromDhall, ToDhall) type OverlayExportSettings :: Type data OverlayExportSettings where MkOverlayExportSettings :: { packagesDir :: PackagesDir , overlayFile :: OverlayFile , overlay :: Overlay } -> OverlayExportSettings deriving stock (Show, Eq, Generic) deriving anyclass (FromDhall, ToDhall) type HorizonExport :: Type data HorizonExport where MakePackageSet :: PackageSetExportSettings -> HorizonExport MakeOverlay :: OverlayExportSettings -> HorizonExport deriving stock (Show, Eq, Generic) deriving anyclass (FromDhall, ToDhall)