Skip to content
Snippets Groups Projects
Commit 977737b8 authored by andreas.abel's avatar andreas.abel Committed by Mergify
Browse files

Re #7916: undeprecate Distribution.Types.VersionInterval.Legacy

Third party tools like `hackage-cli` rely on this API.
While `Distribution.Types.VersionInterval` does not export the Boolean
algebra operations union, intersection and complement on
`VersionIntervals`, the Legacy variant is still needed.
parent 54ebd1b8
No related branches found
No related tags found
No related merge requests found
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE DeriveDataTypeable #-}
-- | In @Cabal-3.6@ this module have been rewritten.
-- | This module implements a view of a 'VersionRange' as a finite
-- list of separated version intervals.
--
-- In conversion from and to 'VersionRange' it makes some effort to
-- preserve the caret operator @^>=x.y@. This constraint a priori
-- specifies the same interval as @==x.y.*@, but indicates that newer
-- versions could be acceptable (@allow-newer: ^@).
--
module Distribution.Types.VersionInterval (
-- * Version intervals
......
{-# LANGUAGE DeriveDataTypeable #-}
-- | This is old version of "Distribution.Types.VersionInterval" module.
-- | This module implements a view of a 'VersionRange' as a finite
-- list of separated version intervals and provides the Boolean
-- algebra operations union, intersection, and complement.
--
-- It will be removed in @Cabal-3.8@.
-- It interprets the caret operator @^>=x.y@ as simply @==x.y.*@.
-- Until @Cabal < 3.6@, this module was called "Distribution.Types.VersionInterval".
-- The current module "Distribution.Types.VersionInterval" (refurbished since
-- @Cabal >= 3.6@) makes some effort to preserve the caret operator,
-- but so far does not expose the Boolean algebra structure.
--
module Distribution.Types.VersionInterval.Legacy {-# DEPRECATED "Use Distribution.Types.VersionInterval instead" #-} (
module Distribution.Types.VersionInterval.Legacy (
-- * Version intervals
VersionIntervals,
toVersionIntervals,
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment