-- | 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 empty value as a starting point and fill in
-- the components of the record that you need.
module Cartel.Empty where

import qualified Cartel.Ast as A

class Empty a where
  empty :: a

-- | A default 'A.Properties'.  'A.prCabalVersion' is @(1, 14)@ to
-- specify Cabal version 1.14; 'A.prBuildType' is 'A.Simple', and
-- 'A.prLicense' is 'A.BSD3'.  All other items are either the empty
-- 'String' or the empty list, including the 'A.prVersion', which is
-- left empty.
instance Empty A.Properties where
  empty = 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 = []
    }

-- | A default 'A.Cabal'.  'empty' is used for 'A.cProperties',
-- and 'A.cLibrary' is 'Nothing'; all other lists are empty.
instance Empty A.Cabal where
  empty = A.Cabal
    { A.cProperties = empty
    , A.cRepositories = []
    , A.cFlags = []
    , A.cLibrary = Nothing
    , A.cExecutables = []
    , A.cTestSuites = []
    , A.cBenchmarks = []
    }

-- | A default 'A.Repository'.  The VCS type is 'A.Git' and the
-- repository kind is 'A.Head'.  All other values are the empty
-- string.
instance Empty A.Repository where
  empty = A.Repository
    { A.repoVcs = A.Git
    , A.repoKind = A.Head
    , A.repoLocation = ""
    , A.repoBranch = ""
    , A.repoTag = ""
    , A.repoSubdir = ""
    }

-- | A default 'A.Flag'.  'A.flName' and 'A.flDescription' are
-- empty; 'A.flDefault' is 'True', and 'A.flManual' is 'False'.
instance Empty A.Flag where
  empty = A.Flag
    { A.flName = ""
    , A.flDescription = ""
    , A.flDefault = True
    , A.flManual = False
    }