{-# LANGUAGE NoImplicitPrelude #-}

module Stack.Types.DumpPackage
  ( DumpPackage (..)
  ) where

import qualified Distribution.License as C
import           Distribution.ModuleName ( ModuleName )
import           Stack.Prelude
import           Stack.Types.GhcPkgId ( GhcPkgId )

-- | Type representing dump information for a single package, as output by the

-- @ghc-pkg describe@ command.

data DumpPackage = DumpPackage
  { DumpPackage -> GhcPkgId
dpGhcPkgId :: !GhcPkgId
    -- ^ The @id@ field.

  , DumpPackage -> PackageIdentifier
dpPackageIdent :: !PackageIdentifier
    -- ^ The @name@ and @version@ fields. The @name@ field is the munged package

    -- name. If the package is not for a sub library, its munged name is its

    -- name.

  , DumpPackage -> Maybe PackageIdentifier
dpParentLibIdent :: !(Maybe PackageIdentifier)
    -- ^ The @package-name@ and @version@ fields, if @package-name@ is present.

    -- That field is present if the package is for a sub library.

  , DumpPackage -> Maybe License
dpLicense :: !(Maybe C.License)
  , DumpPackage -> [FilePath]
dpLibDirs :: ![FilePath]
    -- ^ The @library-dirs@ field.

  , DumpPackage -> [Text]
dpLibraries :: ![Text]
    -- ^ The @hs-libraries@ field.

  , DumpPackage -> Bool
dpHasExposedModules :: !Bool
  , DumpPackage -> Set ModuleName
dpExposedModules :: !(Set ModuleName)
  , DumpPackage -> [GhcPkgId]
dpDepends :: ![GhcPkgId]
    -- ^ The @depends@ field (packages on which this package depends).

  , DumpPackage -> [FilePath]
dpHaddockInterfaces :: ![FilePath]
  , DumpPackage -> Maybe FilePath
dpHaddockHtml :: !(Maybe FilePath)
  , DumpPackage -> Bool
dpIsExposed :: !Bool
  }
  deriving (DumpPackage -> DumpPackage -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DumpPackage -> DumpPackage -> Bool
$c/= :: DumpPackage -> DumpPackage -> Bool
== :: DumpPackage -> DumpPackage -> Bool
$c== :: DumpPackage -> DumpPackage -> Bool
Eq, ReadPrec [DumpPackage]
ReadPrec DumpPackage
Int -> ReadS DumpPackage
ReadS [DumpPackage]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DumpPackage]
$creadListPrec :: ReadPrec [DumpPackage]
readPrec :: ReadPrec DumpPackage
$creadPrec :: ReadPrec DumpPackage
readList :: ReadS [DumpPackage]
$creadList :: ReadS [DumpPackage]
readsPrec :: Int -> ReadS DumpPackage
$creadsPrec :: Int -> ReadS DumpPackage
Read, Int -> DumpPackage -> ShowS
[DumpPackage] -> ShowS
DumpPackage -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [DumpPackage] -> ShowS
$cshowList :: [DumpPackage] -> ShowS
show :: DumpPackage -> FilePath
$cshow :: DumpPackage -> FilePath
showsPrec :: Int -> DumpPackage -> ShowS
$cshowsPrec :: Int -> DumpPackage -> ShowS
Show)