module Distribution.Nixpkgs.Meta
( Meta, nullMeta
, homepage, description, license, platforms, hydraPlatforms, maintainers, broken
, allKnownPlatforms
) where
import Control.DeepSeq
import Control.Lens
import Data.Set ( Set )
import qualified Data.Set as Set
import Distribution.Nixpkgs.License
import Distribution.System
import GHC.Generics ( Generic )
import Internal.OrphanInstances ( )
import Language.Nix.Identifier
import Language.Nix.PrettyPrinting
data Meta = Meta
{ _homepage :: String
, _description :: String
, _license :: License
, _platforms :: Set Platform
, _hydraPlatforms :: Set Platform
, _maintainers :: Set Identifier
, _broken :: Bool
}
deriving (Show, Eq, Ord, Generic)
makeLenses ''Meta
instance NFData Meta
instance Pretty Meta where
pPrint Meta {..} = vcat
[ onlyIf (not (null _homepage)) $ attr "homepage" $ string _homepage
, onlyIf (not (null _description)) $ attr "description" $ string _description
, attr "license" $ pPrint _license
, onlyIf (_platforms /= allKnownPlatforms) $ renderPlatforms "platforms" _platforms
, onlyIf (_hydraPlatforms /= _platforms) $ renderPlatforms "hydraPlatforms" _hydraPlatforms
, setattr "maintainers" (text "with stdenv.lib.maintainers;") (Set.map (view ident) _maintainers)
, boolattr "broken" _broken _broken
]
renderPlatforms :: String -> Set Platform -> Doc
renderPlatforms field ps
| Set.null ps = sep [ text field <+> equals <+> text "stdenv.lib.platforms.none" <> semi ]
| otherwise = sep [ text field <+> equals <+> lbrack
, nest 2 $ fsep $ map text (toAscList (Set.map fromCabalPlatform ps))
, rbrack <> semi
]
nullMeta :: Meta
nullMeta = Meta
{ _homepage = error "undefined Meta.homepage"
, _description = error "undefined Meta.description"
, _license = error "undefined Meta.license"
, _platforms = error "undefined Meta.platforms"
, _hydraPlatforms = error "undefined Meta.hydraPlatforms"
, _maintainers = error "undefined Meta.maintainers"
, _broken = error "undefined Meta.broken"
}
allKnownPlatforms :: Set Platform
allKnownPlatforms = Set.fromList [ Platform I386 Linux, Platform X86_64 Linux
, Platform X86_64 OSX
]
fromCabalPlatform :: Platform -> String
fromCabalPlatform (Platform I386 Linux) = "\"i686-linux\""
fromCabalPlatform (Platform X86_64 Linux) = "\"x86_64-linux\""
fromCabalPlatform (Platform X86_64 OSX) = "\"x86_64-darwin\""
fromCabalPlatform p = error ("fromCabalPlatform: invalid Nix platform" ++ show p)