package-version-0.1.0.0: A package for retrieving a package's version number.
Copyright2021 Thomas Bidne
LicenseBSD-3-Clause
Stabilityexperimental
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Version.Package

Description

This module provides functionality for reading a package's version at compile-time, along with a type representing PVP version numbers. If only the former is of interest then see packageVersionStringTH, as this is likely the most useful function.

Since: 0.1.0.0

Synopsis

Type

data PackageVersion where Source #

PackageVersion represents PVP version numbers. It is similar to Data.Version's Version (i.e. wraps a [Int]) except:

  1. PackageVersion has no versionTags.
  2. We enforce PVP's "tags must be at least A.B" invariant via the smart-constructor pattern.
  3. Trailing zeroes are ignored in Eq, Ord, Semigroup, and Monoid.

That is, we declare an equivalence class up to trailing zeroes. In particular, the Monoid identity is

[0] = { [0,0], [0,0,0], ... }

and its Semigroup instance takes the greatest version (based on Ord).

Note: Because we export the underlying list in various ways, (e.g. show), Eq's extensionality law,

x == y ==> f x == f y

can be broken. Take care that you do not rely on this law if you are using its underlying [Int] (or String) representation.

Examples

Expand
>>> UnsafePackageVersion [0,0,0,0] == UnsafePackageVersion [0,0,0]
True
>>> UnsafePackageVersion [4,0,0] > UnsafePackageVersion [1,2,0,0]
True
>>> UnsafePackageVersion [5,6,0] <> UnsafePackageVersion [9,0,0]
UnsafePackageVersion {unPackageVersion = [9,0,0]}
>>> UnsafePackageVersion [0,9] <> UnsafePackageVersion [0,9,0,0]
UnsafePackageVersion {unPackageVersion = [0,9]}
>>> TR.readEither @PackageVersion "UnsafePackageVersion {unPackageVersion = [3,2,1]}"
Right (UnsafePackageVersion {unPackageVersion = [3,2,1]})
>>> TR.readEither @PackageVersion "UnsafePackageVersion {unPackageVersion = [3]}"
Left "Prelude.read: no parse"

Since: 0.1.0.0

Bundled Patterns

pattern MkPackageVersion :: [Int] -> PackageVersion

Since: 0.1.0.0

Instances

Instances details
Eq PackageVersion Source #

Since: 0.1.0.0

Instance details

Defined in Data.Version.Package.Internal

Ord PackageVersion Source #

Since: 0.1.0.0

Instance details

Defined in Data.Version.Package.Internal

Read PackageVersion Source #

Derived by GHC 8.10.7 with validation via mkPackageVersion.

Since: 0.1.0.0

Instance details

Defined in Data.Version.Package.Internal

Show PackageVersion Source #

Since: 0.1.0.0

Instance details

Defined in Data.Version.Package.Internal

Semigroup PackageVersion Source #

Since: 0.1.0.0

Instance details

Defined in Data.Version.Package.Internal

Monoid PackageVersion Source #

Since: 0.1.0.0

Instance details

Defined in Data.Version.Package.Internal

NFData PackageVersion Source #

Since: 0.1.0.0

Instance details

Defined in Data.Version.Package.Internal

Methods

rnf :: PackageVersion -> () #

Pretty PackageVersion Source #

Since: 0.1.0.0

Instance details

Defined in Data.Version.Package.Internal

Methods

pretty :: PackageVersion -> Doc ann #

prettyList :: [PackageVersion] -> Doc ann #

Lift PackageVersion Source #

Since: 0.1.0.0

Instance details

Defined in Data.Version.Package.Internal

Creation

mkPackageVersion :: [Int] -> Either ValidationError PackageVersion Source #

Smart constructor for PackageVersion. The length of the list must be > 1 to match PVP's minimal A.B. Furthermore, all digits must be non-negative.

Examples

Expand
>>> mkPackageVersion [1,2]
Right (UnsafePackageVersion {unPackageVersion = [1,2]})
>>> mkPackageVersion [2,87,7,1]
Right (UnsafePackageVersion {unPackageVersion = [2,87,7,1]})
>>> mkPackageVersion [1,2,-3,-4,5]
Left (VNegativeErr (-3))
>>> mkPackageVersion [3]
Left (VTooShortErr [3])
>>> mkPackageVersion []
Left (VTooShortErr [])

Since: 0.1.0.0

mkPackageVersionTH :: [Int] -> Q (TExp PackageVersion) Source #

Safely constructs a PackageVersion at compile-time.

Examples

Expand
>>> $$(mkPackageVersionTH [2,4,0])
UnsafePackageVersion {unPackageVersion = [2,4,0]}

Since: 0.1.0.0

unsafePackageVersion :: [Int] -> PackageVersion Source #

Unsafe version of mkPackageVersion, intended to be used with known constants. Maybe you should use mkPackageVersionTH?

WARNING: This function is not total. Exercise restraint!

Examples

Expand
>>> unsafePackageVersion [1,2,3]
UnsafePackageVersion {unPackageVersion = [1,2,3]}

Since: 0.1.0.0

fromVersion :: Version -> Either ValidationError PackageVersion Source #

Creates a PackageVersion from Version.

Note: Because PackageVersion does not have a versionTags, fromVersion is not injective even on "well-formed" Versions (i.e. non-negative and length > 1). That is, toVersion . fromVersion is not an isomorphism.

Examples

Expand
>>> fromVersion (Version [2,13,0] ["alpha"])
Right (UnsafePackageVersion {unPackageVersion = [2,13,0]})
>>> fromVersion (Version [] [])
Left (VTooShortErr [])

Since: 0.1.0.0

fromString :: String -> Either ReadStringError PackageVersion Source #

Attempts to read a String into a PackageVersion. Leading and/or trailing dots will result in an error, as will the empty string.

Examples

Expand
>>> fromString "1.4.27.3"
Right (UnsafePackageVersion {unPackageVersion = [1,4,27,3]})
>>> fromString ""
Left (RsReadStrErr "Prelude.read: no parse")
>>> fromString "1.a.2"
Left (RsReadStrErr "Prelude.read: no parse")
>>> fromString ".1.2"
Left (RsReadStrErr "Prelude.read: no parse")
>>> fromString "1.2."
Left (RsReadStrErr "Prelude.read: no parse")
>>> fromString "1"
Left (RsValidateErr (VTooShortErr [1]))
>>> fromString "-3.1.2"
Left (RsValidateErr (VNegativeErr (-3)))

Since: 0.1.0.0

fromText :: Text -> Either ReadStringError PackageVersion Source #

Attempts to read a Text into a PackageVersion. Leading and/or trailing dots will result in an error, as will the empty string.

Examples

Expand
>>> fromText "1.4.27.3"
Right (UnsafePackageVersion {unPackageVersion = [1,4,27,3]})
>>> fromText ""
Left (RsReadStrErr "Prelude.read: no parse")
>>> fromText "1.a.2"
Left (RsReadStrErr "Prelude.read: no parse")
>>> fromText ".1.2"
Left (RsReadStrErr "Prelude.read: no parse")
>>> fromText "1.2."
Left (RsReadStrErr "Prelude.read: no parse")
>>> fromText "1"
Left (RsValidateErr (VTooShortErr [1]))
>>> fromText "-3.1.2"
Left (RsValidateErr (VNegativeErr (-3)))

Since: 0.1.0.0

Elimination

toVersion :: PackageVersion -> Version Source #

Creates a Version with empty versionTags from PackageVersion.

Examples

Expand
>>> toVersion (UnsafePackageVersion [3,2,0])
Version {versionBranch = [3,2,0], versionTags = []}

Since: 0.1.0.0

toString :: PackageVersion -> String Source #

Displays PackageVersion in String format.

Examples

Expand
>>> toString (UnsafePackageVersion [2,7,10,0])
"2.7.10.0"

Since: 0.1.0.0

toText :: PackageVersion -> Text Source #

Displays PackageVersion in Text format.

Examples

Expand
>>> toText (UnsafePackageVersion [2,7,10,0])
"2.7.10.0"

Since: 0.1.0.0

Reading Cabal Files

TemplateHaskell

These functions allow for reading a cabal's version at compile-time. If the intention is to simply read the value so it can be printed during runtime (e.g. for an executable's --version flag), then packageVersionStringTH (or packageVersionTextTH) is the best choice, as any errors encountered will not prevent compilation.

packageVersionTH :: FilePath -> Q (TExp PackageVersion) Source #

TemplateHaskell for reading the cabal file's version at compile-time. Errors encountered will be returned as compilation errors.

Examples

Expand
>>> $$(packageVersionTH "package-version.cabal")
UnsafePackageVersion {unPackageVersion = [0,1,0,0]}

Since: 0.1.0.0

packageVersionStringTH :: FilePath -> Q (TExp String) Source #

Version of packageVersionTH that returns a String representation of PackageVersion at compile-time. Returns "UNKNOWN" if any errors are encountered.

Examples

Expand
>>> $$(packageVersionStringTH "package-version.cabal")
"0.1.0.0"
>>> $$(packageVersionStringTH "not-found.cabal")
"UNKNOWN"

Since: 0.1.0.0

packageVersionTextTH :: FilePath -> Q (TExp Text) Source #

Version of packageVersionTH that returns a Text representation of PackageVersion at compile-time. Returns "UNKNOWN" if any errors are encountered.

Examples

Expand
>>> $$(packageVersionTextTH "package-version.cabal")
"0.1.0.0"
>>> $$(packageVersionTextTH "not-found.cabal")
"UNKNOWN"

Since: 0.1.0.0

IO

packageVersionThrowIO :: FilePath -> IO PackageVersion Source #

Version of packageVersionEitherIO that throws an Exception if any errors are encountered.

Examples

Expand
>>> packageVersionThrowIO "package-version.cabal"
UnsafePackageVersion {unPackageVersion = [0,1,0,0]}

Since: 0.1.0.0

packageVersionStringIO :: FilePath -> IO String Source #

Version of packageVersionEitherIO that returns a String representation of PackageVersion at runtime. Returns "UNKNOWN" if any errors are encountered.

Examples

Expand
>>> packageVersionStringIO "package-version.cabal"
"0.1.0.0"
>>> packageVersionStringIO "not-found.cabal"
"UNKNOWN"

Since: 0.1.0.0

packageVersionTextIO :: FilePath -> IO Text Source #

Version of packageVersionEitherIO that returns a Text representation of PackageVersion at runtime. Returns "UNKNOWN" if any errors are encountered.

Examples

Expand
>>> packageVersionTextIO "package-version.cabal"
"0.1.0.0"
>>> packageVersionTextIO "not-found.cabal"
"UNKNOWN"

Since: 0.1.0.0

packageVersionEitherIO :: FilePath -> IO (Either ReadFileError PackageVersion) Source #

Reads the cabal-file's version.

Examples

Expand
>>> packageVersionEitherIO "package-version.cabal"
Right (UnsafePackageVersion {unPackageVersion = [0,1,0,0]})

Since: 0.1.0.0

Errors

data ValidationError Source #

Errors that can occur when validating PVP version numbers.

Since: 0.1.0.0

Constructors

VTooShortErr [Int]

PVP version numbers must be at least A.B

Since: 0.1.0.0

VNegativeErr Int

PVP version numbers cannot be negative.

Since: 0.1.0.0

Instances

Instances details
Eq ValidationError Source #

Since: 0.1.0.0

Instance details

Defined in Data.Version.Package.Internal

Show ValidationError Source #

Since: 0.1.0.0

Instance details

Defined in Data.Version.Package.Internal

Generic ValidationError Source #

Since: 0.1.0.0

Instance details

Defined in Data.Version.Package.Internal

Associated Types

type Rep ValidationError :: Type -> Type #

Exception ValidationError Source #

Since: 0.1.0.0

Instance details

Defined in Data.Version.Package.Internal

Pretty ValidationError Source #

Since: 0.1.0.0

Instance details

Defined in Data.Version.Package.Internal

type Rep ValidationError Source # 
Instance details

Defined in Data.Version.Package.Internal

type Rep ValidationError = D1 ('MetaData "ValidationError" "Data.Version.Package.Internal" "package-version-0.1.0.0-inplace" 'False) (C1 ('MetaCons "VTooShortErr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Int])) :+: C1 ('MetaCons "VNegativeErr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

data ReadStringError Source #

Errors that can occur when reading PVP version numbers.

Since: 0.1.0.0

Constructors

RsReadStrErr String

Error when reading a string.

Since: 0.1.0.0

RsValidateErr ValidationError

Validation error.

Since: 0.1.0.0

Instances

Instances details
Eq ReadStringError Source #

Since: 0.1.0.0

Instance details

Defined in Data.Version.Package.Internal

Show ReadStringError Source #

Since: 0.1.0.0

Instance details

Defined in Data.Version.Package.Internal

Generic ReadStringError Source #

Since: 0.1.0.0

Instance details

Defined in Data.Version.Package.Internal

Associated Types

type Rep ReadStringError :: Type -> Type #

Exception ReadStringError Source #

Since: 0.1.0.0

Instance details

Defined in Data.Version.Package.Internal

Pretty ReadStringError Source #

Since: 0.1.0.0

Instance details

Defined in Data.Version.Package.Internal

type Rep ReadStringError Source # 
Instance details

Defined in Data.Version.Package.Internal

type Rep ReadStringError = D1 ('MetaData "ReadStringError" "Data.Version.Package.Internal" "package-version-0.1.0.0-inplace" 'False) (C1 ('MetaCons "RsReadStrErr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "RsValidateErr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ValidationError)))

data ReadFileError Source #

Errors that can occur when reading PVP version numbers from a file.

Since: 0.1.0.0

Constructors

RfFileNotFoundErr String

Error for missing file.

Since: 0.1.0.0

RfVersionNotFoundErr FilePath

Error for missing version.

Since: 0.1.0.0

RfReadValidateErr ReadStringError

Read/Validation error.

Since: 0.1.0.0

Instances

Instances details
Eq ReadFileError Source #

Since: 0.1.0.0

Instance details

Defined in Data.Version.Package.Internal

Show ReadFileError Source #

Since: 0.1.0.0

Instance details

Defined in Data.Version.Package.Internal

Generic ReadFileError Source #

Since: 0.1.0.0

Instance details

Defined in Data.Version.Package.Internal

Associated Types

type Rep ReadFileError :: Type -> Type #

Exception ReadFileError Source #

Since: 0.1.0.0

Instance details

Defined in Data.Version.Package.Internal

Pretty ReadFileError Source #

Since: 0.1.0.0

Instance details

Defined in Data.Version.Package.Internal

Methods

pretty :: ReadFileError -> Doc ann #

prettyList :: [ReadFileError] -> Doc ann #

type Rep ReadFileError Source # 
Instance details

Defined in Data.Version.Package.Internal

type Rep ReadFileError = D1 ('MetaData "ReadFileError" "Data.Version.Package.Internal" "package-version-0.1.0.0-inplace" 'False) (C1 ('MetaCons "RfFileNotFoundErr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: (C1 ('MetaCons "RfVersionNotFoundErr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath)) :+: C1 ('MetaCons "RfReadValidateErr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ReadStringError))))