Safe Haskell | None |
---|---|
Language | GHC2021 |
Hix.Data.Version
Synopsis
- data Major = Major {}
- newtype SourceHash = SourceHash Text
- range0 :: VersionRange
- newtype Versions = Versions (Map PackageName Version)
- packageIdVersions :: [PackageId] -> Versions
- prettyMajors :: NonEmpty Major -> Doc
- data Version
- data VersionRange
Documentation
Instances
Generic Major Source # | |||||
Defined in Hix.Data.Version Associated Types
| |||||
Show Major Source # | |||||
Eq Major Source # | |||||
type Rep Major Source # | |||||
Defined in Hix.Data.Version type Rep Major = D1 ('MetaData "Major" "Hix.Data.Version" "hix-0.7.2-7rwpoWJhaauIDtZl7KwtG7" 'False) (C1 ('MetaCons "Major" 'PrefixI 'True) (S1 ('MetaSel ('Just "prefix") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Version) :*: S1 ('MetaSel ('Just "versions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (NonEmpty Version)))) |
newtype SourceHash Source #
Constructors
SourceHash Text |
Instances
Constructors
Versions (Map PackageName Version) |
Instances
Pretty Versions Source # | |||||
Defined in Hix.Data.Version | |||||
FromJSON Versions Source # | |||||
Defined in Hix.Data.Version | |||||
Monoid Versions Source # | |||||
Semigroup Versions Source # | |||||
Generic Versions Source # | |||||
Defined in Hix.Data.Version Associated Types
| |||||
IsList Versions Source # | |||||
Show Versions Source # | |||||
Eq Versions Source # | |||||
EncodeNix Versions Source # | |||||
NMap Versions PackageName Version LookupMaybe Source # | |||||
Defined in Hix.Data.Version | |||||
type Rep Versions Source # | |||||
Defined in Hix.Data.Version | |||||
type Item Versions Source # | |||||
Defined in Hix.Data.Version |
packageIdVersions :: [PackageId] -> Versions Source #
A Version
represents the version of a software entity.
Instances of Eq
and Ord
are provided, which gives exact
equality and lexicographic ordering of the version number
components (i.e. 2.1 > 2.0, 1.2.3 > 1.2.2, etc.).
This type is opaque and distinct from the Version
type in
Data.Version since Cabal-2.0
. The difference extends to the
Binary
instance using a different (and more compact) encoding.
Since: Cabal-syntax-2.0.0.2
Instances
Parsec Version | |||||
Defined in Distribution.Types.Version Methods parsec :: CabalParsing m => m Version # | |||||
Pretty Version | |||||
Defined in Distribution.Types.Version | |||||
Structured Version | |||||
Defined in Distribution.Types.Version | |||||
Data Version | |||||
Defined in Distribution.Types.Version Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Version -> c Version # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Version # toConstr :: Version -> Constr # dataTypeOf :: Version -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Version) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Version) # gmapT :: (forall b. Data b => b -> b) -> Version -> Version # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Version -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Version -> r # gmapQ :: (forall d. Data d => d -> u) -> Version -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Version -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Version -> m Version # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Version -> m Version # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Version -> m Version # | |||||
Generic Version | |||||
Defined in Distribution.Types.Version Associated Types
| |||||
IsList Version Source # | |||||
Read Version | |||||
Show Version | |||||
Binary Version | |||||
NFData Version | |||||
Defined in Distribution.Types.Version | |||||
Eq Version | |||||
Ord Version | |||||
Defined in Distribution.Types.Version | |||||
EncodeNix Version Source # | |||||
NMap Versions PackageName Version LookupMaybe Source # | |||||
Defined in Hix.Data.Version | |||||
NMap SourcePackage Version SourcePackageId LookupMonoid Source # | |||||
Defined in Hix.Managed.Cabal.Data.SourcePackage Methods nGet :: SourcePackage -> Map Version SourcePackageId Source # | |||||
NMap SourcePackageVersions PackageName [Version] LookupMaybe Source # | |||||
Defined in Hix.Managed.Cabal.Data.SourcePackage Methods nGet :: SourcePackageVersions -> Map PackageName [Version] Source # | |||||
NMap MutableVersions MutableDep (Maybe Version) LookupMaybe Source # | |||||
Defined in Hix.Managed.Data.Mutable Methods nGet :: MutableVersions -> Map MutableDep (Maybe Version) Source # | |||||
type Rep Version | |||||
Defined in Distribution.Types.Version type Rep Version = D1 ('MetaData "Version" "Distribution.Types.Version" "Cabal-syntax-3.10.3.0-8Wh1L3dyXBBgfhJJEMBVi" 'False) (C1 ('MetaCons "PV0" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedUnpack) (Rec0 Word64)) :+: C1 ('MetaCons "PV1" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Int]))) | |||||
type Item Version Source # | |||||
Defined in Hix.Orphans.Version |
data VersionRange #
Instances
Parsec VersionRange |
Small history:
Set operations are introduced in 3.0
Operators are introduced in 1.8. Issues only a warning.
Wild-version ranges are introduced in 1.6. Issues only a warning.
| ||||
Defined in Distribution.Types.VersionRange.Internal Methods parsec :: CabalParsing m => m VersionRange # | |||||
Pretty VersionRange |
| ||||
Defined in Distribution.Types.VersionRange.Internal | |||||
Structured VersionRange | |||||
Defined in Distribution.Types.VersionRange.Internal | |||||
Data VersionRange | |||||
Defined in Distribution.Types.VersionRange.Internal Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VersionRange -> c VersionRange # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VersionRange # toConstr :: VersionRange -> Constr # dataTypeOf :: VersionRange -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c VersionRange) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VersionRange) # gmapT :: (forall b. Data b => b -> b) -> VersionRange -> VersionRange # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VersionRange -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VersionRange -> r # gmapQ :: (forall d. Data d => d -> u) -> VersionRange -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> VersionRange -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> VersionRange -> m VersionRange # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VersionRange -> m VersionRange # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VersionRange -> m VersionRange # | |||||
Generic VersionRange | |||||
Defined in Distribution.Types.VersionRange.Internal Associated Types
| |||||
IsList VersionRange Source # | |||||
Defined in Hix.Orphans.Version Associated Types
Methods fromList :: [Item VersionRange] -> VersionRange # fromListN :: Int -> [Item VersionRange] -> VersionRange # toList :: VersionRange -> [Item VersionRange] # | |||||
Read VersionRange | |||||
Defined in Distribution.Types.VersionRange.Internal Methods readsPrec :: Int -> ReadS VersionRange # readList :: ReadS [VersionRange] # | |||||
Show VersionRange | |||||
Defined in Distribution.Types.VersionRange.Internal Methods showsPrec :: Int -> VersionRange -> ShowS # show :: VersionRange -> String # showList :: [VersionRange] -> ShowS # | |||||
Binary VersionRange | |||||
Defined in Distribution.Types.VersionRange.Internal | |||||
NFData VersionRange | |||||
Defined in Distribution.Types.VersionRange.Internal Methods rnf :: VersionRange -> () # | |||||
Eq VersionRange | |||||
Defined in Distribution.Types.VersionRange.Internal | |||||
Ord VersionRange | |||||
Defined in Distribution.Types.VersionRange.Internal Methods compare :: VersionRange -> VersionRange -> Ordering # (<) :: VersionRange -> VersionRange -> Bool # (<=) :: VersionRange -> VersionRange -> Bool # (>) :: VersionRange -> VersionRange -> Bool # (>=) :: VersionRange -> VersionRange -> Bool # max :: VersionRange -> VersionRange -> VersionRange # min :: VersionRange -> VersionRange -> VersionRange # | |||||
EncodeNix VersionRange Source # | |||||
Defined in Hix.Class.EncodeNix Methods encodeNix :: VersionRange -> Expr Source # | |||||
NMap Ranges PackageName VersionRange LookupMaybe Source # | |||||
Defined in Hix.Data.Bounds Methods nGet :: Ranges -> Map PackageName VersionRange Source # | |||||
NMap LocalRanges LocalPackage VersionRange LookupMaybe Source # | |||||
Defined in Hix.Managed.Data.Mutable Methods nGet :: LocalRanges -> Map LocalPackage VersionRange Source # | |||||
NMap MutableRanges MutableDep VersionRange LookupMaybe Source # | |||||
Defined in Hix.Managed.Data.Mutable Methods nGet :: MutableRanges -> Map MutableDep VersionRange Source # | |||||
Newtype (CompilerFlavor, VersionRange) TestedWith | |||||
Defined in Distribution.FieldGrammar.Newtypes Methods pack :: (CompilerFlavor, VersionRange) -> TestedWith # unpack :: TestedWith -> (CompilerFlavor, VersionRange) # | |||||
type Rep VersionRange | |||||
Defined in Distribution.Types.VersionRange.Internal type Rep VersionRange = D1 ('MetaData "VersionRange" "Distribution.Types.VersionRange.Internal" "Cabal-syntax-3.10.3.0-8Wh1L3dyXBBgfhJJEMBVi" 'False) (((C1 ('MetaCons "ThisVersion" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Version)) :+: C1 ('MetaCons "LaterVersion" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Version))) :+: (C1 ('MetaCons "OrLaterVersion" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Version)) :+: C1 ('MetaCons "EarlierVersion" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Version)))) :+: ((C1 ('MetaCons "OrEarlierVersion" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Version)) :+: C1 ('MetaCons "MajorBoundVersion" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Version))) :+: (C1 ('MetaCons "UnionVersionRanges" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 VersionRange) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 VersionRange)) :+: C1 ('MetaCons "IntersectVersionRanges" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 VersionRange) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 VersionRange))))) | |||||
type Item VersionRange Source # | |||||
Defined in Hix.Orphans.Version |