-- | Default values for the data types in "Cartel.Ast".  These
-- defaults are genrally filled in with blank values.  Use these
-- default values where you can; by doing so you help future-proof
-- your code.  Use the default as a starting point and fill in the
-- values that you need.
module Cartel.Defaults where

import qualified Cartel.Ast as A

properties :: A.Properties
properties = A.Properties
  { A.prName = ""
  , A.prVersion = A.Version []
  , A.prCabalVersion = (1, 14)
  , A.prBuildType = A.Simple
  , A.prLicense = A.BSD3
  , A.prLicenseFile = ""
  , A.prLicenseFiles = []
  , A.prCopyright = ""
  , A.prAuthor = ""
  , A.prMaintainer = ""
  , A.prStability = ""
  , A.prHomepage = ""
  , A.prBugReports = ""
  , A.prPackageUrl = ""
  , A.prSynopsis = ""
  , A.prDescription = []
  , A.prCategory = ""
  , A.prTestedWith = []
  , A.prDataFiles = []
  , A.prDataDir = ""
  , A.prExtraSourceFiles = []
  , A.prExtraDocFiles = []
  , A.prExtraTmpFiles = []
  }

cabal :: A.Cabal
cabal = A.Cabal
  { A.cProperties = properties
  , A.cRepositories = []
  , A.cFlags = []
  , A.cLibrary = Nothing
  , A.cExecutables = []
  , A.cTestSuites = []
  , A.cBenchmarks = []
  }

repository
  :: A.Vcs
  -- ^ Type of VCS in use
  -> Maybe String
  -- ^ To use the @this@ repo kind, use Just String, where the
  -- String is the tag corresponding to the current branch.  To use
  -- the @head@ repository kind, use Nothing.
  -> String
  -- ^ Repo location
  -> A.Repository
repository v ms l = A.Repository
  { A.repoVcs = v
  , A.repoKind = maybe A.Head (const A.This) ms
  , A.repoLocation = l
  , A.repoBranch = ""
  , A.repoTag = maybe "" id ms
  , A.repoSubdir = ""
  }