module Distribution.Types.PackageId
( PackageIdentifier(..)
, PackageId
) where
import Distribution.Compat.Prelude
import Prelude ()
import Distribution.Parsec (Parsec (..), simpleParsec)
import Distribution.Pretty
import Distribution.Types.PackageName
import Distribution.Version (Version, nullVersion)
import qualified Distribution.Compat.CharParsing as P
import qualified Text.PrettyPrint as Disp
type PackageId = PackageIdentifier
data PackageIdentifier
= PackageIdentifier {
pkgName :: PackageName,
pkgVersion :: Version
}
deriving (Generic, Read, Show, Eq, Ord, Typeable, Data)
instance Binary PackageIdentifier
instance Pretty PackageIdentifier where
pretty (PackageIdentifier n v)
| v == nullVersion = pretty n
| otherwise = pretty n <<>> Disp.char '-' <<>> pretty v
instance Parsec PackageIdentifier where
parsec = do
xs' <- P.sepBy1 component (P.char '-')
(v, xs) <- case simpleParsec (last xs') of
Nothing -> return (nullVersion, xs')
Just v -> return (v, init xs')
if not (null xs) && all (\c -> all (/= '.') c && not (all isDigit c)) xs
then return $ PackageIdentifier (mkPackageName (intercalate "-" xs)) v
else fail "all digits or a dot in a portion of package name"
where
component = P.munch1 (\c -> isAlphaNum c || c == '.')
instance NFData PackageIdentifier where
rnf (PackageIdentifier name version) = rnf name `seq` rnf version