{-# LANGUAGE DeriveDataTypeable, FlexibleInstances, TemplateHaskell, TypeSynonymInstances #-} module Debian.Debianize.SourceDebDescription ( SourceDebDescription , newSourceDebDescription , newSourceDebDescription' , source , maintainer , changedBy , uploaders , dmUploadAllowed , priority , section , buildDepends , buildConflicts , buildDependsIndep , buildConflictsIndep , standardsVersion , homepage , vcsFields , xFields , xDescription , binaryPackages , VersionControlSpec(..) , XField(..) , XFieldDest(..) ) where import Control.Lens.TH (makeLenses) import Data.Generics (Data, Typeable) import Data.Set as Set (empty, Set) import Data.Text (Text) import Debian.Debianize.BinaryDebDescription (BinaryDebDescription, Canonical(canonical)) import Debian.Orphans () import Debian.Policy (PackagePriority, Section, StandardsVersion) import Debian.Relation (Relations, SrcPkgName) import Prelude hiding (init, init, log, log, unlines) import Text.ParserCombinators.Parsec.Rfc2822 (NameAddr) -- | This type represents the debian/control file, which is the core -- of the source package debianization. It includes the information -- that goes in the first, or source, section, and then a list of the -- succeeding binary package sections. data SourceDebDescription = SourceDebDescription { _source :: Maybe SrcPkgName -- ^ , _maintainer :: Either String NameAddr -- ^ , _changedBy :: Maybe NameAddr -- ^ , _uploaders :: [NameAddr] -- ^ , _dmUploadAllowed :: Bool -- ^ , _priority :: Maybe PackagePriority -- ^ , _section :: Maybe Section -- ^ , _standardsVersion :: Maybe StandardsVersion -- ^ , _homepage :: Maybe Text -- ^ , _vcsFields :: Set VersionControlSpec -- ^ , _xFields :: Set XField -- ^ , _buildDepends :: Relations , _buildConflicts :: Relations , _buildDependsIndep :: Relations , _buildConflictsIndep :: Relations , _xDescription :: Maybe Text , _binaryPackages :: [BinaryDebDescription] -- ^ The binary debs. This should be a map, but we may need to preserve the order } deriving (Eq, Ord, Show, Data, Typeable) instance Canonical SourceDebDescription where canonical x = x { _binaryPackages = canonical (_binaryPackages x) , _buildDepends = canonical (_buildDepends x) , _buildConflicts = canonical (_buildConflicts x) , _buildDependsIndep = canonical (_buildDependsIndep x) , _buildConflictsIndep = canonical (_buildConflictsIndep x) } newSourceDebDescription :: SourceDebDescription newSourceDebDescription = SourceDebDescription { _source = Nothing , _maintainer = Left "Maintainer not set" , _changedBy = Nothing , _uploaders = [] , _dmUploadAllowed = False , _priority = Nothing , _section = Nothing , _buildDepends = [] , _buildConflicts = [] , _buildDependsIndep = [] , _buildConflictsIndep = [] , _standardsVersion = Nothing , _homepage = Nothing , _vcsFields = Set.empty , _xFields = Set.empty , _xDescription = Nothing -- Quick hack, I should maybe put this into _xFields , _binaryPackages = [] } newSourceDebDescription' :: SrcPkgName -> NameAddr -> SourceDebDescription newSourceDebDescription' src who = newSourceDebDescription { _source = Just src , _maintainer = Right who } data VersionControlSpec = VCSBrowser Text | VCSArch Text | VCSBzr Text | VCSCvs Text | VCSDarcs Text | VCSGit Text | VCSHg Text | VCSMtn Text | VCSSvn Text deriving (Eq, Ord, Show, Data, Typeable) -- | User defined fields. Parse the line "XBS-Comment: I stand -- between the candle and the star." to get XField (fromList "BS") -- "Comment" " I stand between the candle and the star." data XField = XField (Set XFieldDest) Text Text deriving (Eq, Ord, Show, Data, Typeable) data XFieldDest = B -- ^ Field will be copied to the binary packgae control files | S -- ^ Field will be copied to the source packgae control files | C -- ^ Field will be copied to the upload control (.changes) file deriving (Eq, Ord, Read, Show, Data, Typeable) $(makeLenses ''SourceDebDescription)