diff --git a/Cabal/ChangeLog.md b/Cabal/ChangeLog.md index bd80ef3c89b319617c7c79289f12fd95204b1aae..bf91e60f78544b3882b501a87940ec9d5e7f1330 100644 --- a/Cabal/ChangeLog.md +++ b/Cabal/ChangeLog.md @@ -1,10 +1,40 @@ -# 3.1.0.0 (current development version) +# 3.2.0.0 [Someone](mailto:somewhere@example.com) February 2020 * `cabal check` verifies `cpp-options` more pedantically, allowing only options starting with `-D` and `-U`. * Don’t rebuild world when new ghc flags that affect how error messages are presented is specified. - - ---- + * Fix multilib build-depends parsing (#5846) + * Change free text `String` fields to use `ShortText` in package description + and installed packge info. + * Split `Distribution.Types.Flag` and `Distribution.Types.ConfVar` + `Distribution.Types.GenericPackageDescription` + * Add GHC-8.10 support, including new extensions to + `Language.Haskell.Extension` + * Use more `NonEmpty` instead of ordinary lists + * Add `Distribution.Utils.Structured` for fingeprinting `Binary` blobs + * Add `null`, `length` and `unsafeFromUTF8BS` to `Distribution.Utils.ShortText` + * Refactor `Distribution.Utils.IOData` module + * Rename `Distribution.Compat.MD5` to `Distribution.Utils.MD5` + * Add `safeHead`, `safeTail`, `safeLast` to `Distribution.Utils.Generic` + * Add `unsnoc` and `unsnocNE` to `Distribution.Utils.Generic` + * Add `Set'` modifier to `Distribution.Parsec.Newtypes` + * Add `Distribution.Compat.Async` + +# 3.0.1.0 TBW + * Add GHC-8.8 flags to normaliseGhcFlags + ([#6379](https://github.com/haskell/cabal/pull/6379)) + * Typo fixes + ([#6372](https://github.com/haskell/cabal/pull/6372)) + * Limit version number parts to contain at most 9 digits + ([#6386](https://github.com/haskell/cabal/pull/6386) + * Fix boundless sublibrary depedency parse failure + ([#5846](https://github.com/haskell/cabal/issues/5846)) + * `cabal check` verifies `cpp-options` more pedantically, allowing only + options starting with `-D` and `-U`. + * Don’t rebuild world when new ghc flags that affect how error + messages are presented is specified. + * Fix dropExeExtension behaviour on Windows + ([#6287](https://github.com/haskell/cabal/pull/6287) # 3.0.0.0 [Mikhail Glushenkov](mailto:mikhail.glushenkov@gmail.com) August 2019 * The 3.0 migration guide gives advice on adapting Custom setup diff --git a/Cabal/Distribution/Compat/Async.hs b/Cabal/Distribution/Compat/Async.hs index a0b36ca1179541652fe3f8d84f448991a0394584..a2644974b091e5ebfb15d29b3cd5ffb32d5906ab 100644 --- a/Cabal/Distribution/Compat/Async.hs +++ b/Cabal/Distribution/Compat/Async.hs @@ -6,6 +6,8 @@ -- Copyright (c) 2012, Simon Marlow -- Licensed under BSD-3-Clause -- +-- @since 3.2.0.0 +-- module Distribution.Compat.Async ( AsyncM, withAsync, waitCatch, diff --git a/Cabal/Distribution/Parsec/Newtypes.hs b/Cabal/Distribution/Parsec/Newtypes.hs index 42c5b3e66ec44ee4f946834c481d6e1dd9a666ef..817d74476558dbfb43c419330461b6eb4830c7c3 100644 --- a/Cabal/Distribution/Parsec/Newtypes.hs +++ b/Cabal/Distribution/Parsec/Newtypes.hs @@ -122,6 +122,8 @@ instance (Newtype a b, Sep sep, Pretty b) => Pretty (List sep b a) where pretty = prettySep (Proxy :: Proxy sep) . map (pretty . (pack :: a -> b)) . unpack -- | Like 'List', but for 'Set'. +-- +-- @since 3.2.0.0 newtype Set' sep b a = Set' { _getSet :: Set a } -- | 'alaSet' and 'alaSet'' are simply 'Set'' constructor, with additional phantom @@ -136,10 +138,13 @@ newtype Set' sep b a = Set' { _getSet :: Set a } -- >>> unpack' (alaSet' FSep Token) <$> eitherParsec "foo bar foo" -- Right (fromList ["bar","foo"]) -- +-- @since 3.2.0.0 alaSet :: sep -> Set a -> Set' sep (Identity a) a alaSet _ = Set' -- | More general version of 'alaSet'. +-- +-- @since 3.2.0.0 alaSet' :: sep -> (a -> b) -> Set a -> Set' sep b a alaSet' _ _ = Set' diff --git a/Cabal/Distribution/Utils/Generic.hs b/Cabal/Distribution/Utils/Generic.hs index 993dfa9b69af5fc88eb35d1b3d78b9d5a5a2e4c0..e0e72cec51fb3cf78c981e487a4fa0b211edb8ce 100644 --- a/Cabal/Distribution/Utils/Generic.hs +++ b/Cabal/Distribution/Utils/Generic.hs @@ -493,6 +493,8 @@ unfoldrM f = go where -- >>> unsnoc [] -- Nothing -- +-- @since 3.2.0.0 +-- unsnoc :: [a] -> Maybe ([a], a) unsnoc [] = Nothing unsnoc (x:xs) = Just (unsnocNE (x :| xs)) @@ -507,6 +509,8 @@ unsnoc (x:xs) = Just (unsnocNE (x :| xs)) -- >>> unsnocNE (1 :| []) -- ([],1) -- +-- @since 3.2.0.0 +-- unsnocNE :: NonEmpty a -> ([a], a) unsnocNE (x:|xs) = go x xs where go y [] = ([], y) diff --git a/Cabal/Distribution/Utils/MD5.hs b/Cabal/Distribution/Utils/MD5.hs index 98cc8837960dbe41e77bfec78561637b70046f86..da34959317e67a56ae6604e9199b4830580ed057 100644 --- a/Cabal/Distribution/Utils/MD5.hs +++ b/Cabal/Distribution/Utils/MD5.hs @@ -28,21 +28,25 @@ type MD5 = Fingerprint -- >>> showMD5 $ md5 $ BS.pack [0..127] -- "37eff01866ba3f538421b30b7cbefcac" -- +-- @since 3.2.0.0 showMD5 :: MD5 -> String showMD5 (Fingerprint a b) = pad a' ++ pad b' where a' = showHex a "" b' = showHex b "" pad s = replicate (16 - length s) '0' ++ s +-- | @since 3.2.0.0 md5 :: BS.ByteString -> MD5 md5 bs = unsafeDupablePerformIO $ BS.unsafeUseAsCStringLen bs $ \(ptr, len) -> fingerprintData (castPtr ptr) len +-- | @since 3.2.0.0 binaryPutMD5 :: MD5 -> Put binaryPutMD5 (Fingerprint a b) = do putWord64le a putWord64le b +-- | @since 3.2.0.0 binaryGetMD5 :: Get MD5 binaryGetMD5 = do a <- getWord64le diff --git a/Cabal/Distribution/Utils/ShortText.hs b/Cabal/Distribution/Utils/ShortText.hs index d626879ed6dbc1c4801a6474639075d2910feab0..ed73b7b6ad5742a3691ee676ea692a191644ceeb 100644 --- a/Cabal/Distribution/Utils/ShortText.hs +++ b/Cabal/Distribution/Utils/ShortText.hs @@ -71,9 +71,13 @@ toShortText :: String -> ShortText fromShortText :: ShortText -> String -- | Convert from UTF-8 encoded strict 'ByteString'. +-- +-- @since 3.2.0.0 unsafeFromUTF8BS :: BS.ByteString -> ShortText -- | Text whether 'ShortText' is empty. +-- +-- @since 3.2.0.0 null :: ShortText -> Bool -- | Compact representation of short 'Strings' @@ -148,6 +152,8 @@ instance IsString ShortText where fromString = toShortText -- | /O(n)/. Length in characters. /Slow/ as converts to string. +-- +-- @since 3.2.0.0 length :: ShortText -> Int length = List.length . fromShortText -- Note: avoid using it, we use it @cabal check@ implementation, where it's ok. diff --git a/Cabal/Distribution/Utils/Structured.hs b/Cabal/Distribution/Utils/Structured.hs index 23f8d4c002f45e75191265652abae0913517ca91..37f7d2ef82b3b169d15835ed966c208268d9f69f 100644 --- a/Cabal/Distribution/Utils/Structured.hs +++ b/Cabal/Distribution/Utils/Structured.hs @@ -236,6 +236,8 @@ structureBuilder s0 = State.evalState (go s0) Map.empty where -- instance 'Structured' Record -- @ -- +-- @since 3.2.0.0 +-- class Typeable a => Structured a where structure :: Proxy a -> Structure default structure :: (Generic a, GStructured (Rep a)) => Proxy a -> Structure diff --git a/cabal-install/changelog b/cabal-install/changelog index 93fdd2d6a9298791386683939cd681ea74ad8f8f..bc87f1035ba9b351172f28782839753dbbb8bc9d 100644 --- a/cabal-install/changelog +++ b/cabal-install/changelog @@ -1,18 +1,45 @@ -*-change-log-*- -3.1.0.0 (current development version) +3.2.0.0 Someone <mailto:somewhere@example.com> February 2020 * `v2-build` (and other `v2-`prefixed commands) now accept the `--benchmark-option(s)` flags, which pass options to benchmark executables (analogous to how `--test-option(s)` works). (#6209) * Add solver optimization to skip a version of a package if it does not resolve any conflicts encountered in the last version, controlled by flag '--fine-grained-conflicts'. (#5918) + * `cabal v2-exec` doesn't fail in clean package (#6479) + * Show full ABI hash for installed packages in solver log (#5892) + * Create incoming directory even for empty packages (#4130) + * Start GHCi with `main-is` module in scope (#6311) + * Implement `--benchmark-options` for `v2-bench` (#6224) + * Fix store-dir in ghc env files generated by `cabal install --lib + --package-env` (#6298) + * `cabal v2-run` works with `.lhs` files (#6134) + * `subdir` in source-repository-package accepts multiple entries (#5472) + +3.0.1.0 TBW December 2019 + * Create store incoming directory + ([#4130](https://github.com/haskell/cabal/issues/4130)) + * `fetchRepoTarball` output is not marked + ([#6385](https://github.com/haskell/cabal/pull/6385)) + * Update `setupMinCabalVersionConstraint` for GHC-8.8 + ([#6217](https://github.com/haskell/cabal/pull/6217)) + * Implement `cabal install --ignore-project` + ([#5919](https://github.com/haskell/cabal/issues/5919)) + * `cabal install executable` solver isn't affected by default + environment contents + ([#6410](https://github.com/haskell/cabal/issues/6410)) + * Use `lukko` for file locking + ([#6345](https://github.com/haskell/cabal/pull/6345)) + * Use `hackage-security-0.6` + ([#6388](https://github.com/haskell/cabal/pull/6388)) + * Other dependency upgrades 3.0.0.0 Mikhail Glushenkov <mikhail.glushenkov@gmail.com> August 2019 - * Parse comma-separated lists for extra-prog-path, extra-lib-dirs, extra-framework-dirs, - and extra-include-dirs as actual lists. (#5420) * `v2-haddock` fails on `haddock` failures (#5977) * `v2-run` works when given `File.lhs` literate file. (#6134) + * Parse comma-separated lists for extra-prog-path, extra-lib-dirs, extra-framework-dirs, + and extra-include-dirs as actual lists. (#5420) * `v2-repl` no longer changes directory to a randomized temporary folder when used outside of a project. (#5544) * `install-method` and `overwrite-policy` in `.cabal/config` now actually work. (#5942)