Hello community, here is the log from the commit of package hpack for openSUSE:Factory checked in at 2018-08-20 16:21:05 ++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++ Comparing /work/SRC/openSUSE:Factory/hpack (Old) and /work/SRC/openSUSE:Factory/.hpack.new (New) ++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
Package is "hpack" Mon Aug 20 16:21:05 2018 rev:12 rq:630377 version:0.29.7 Changes: -------- --- /work/SRC/openSUSE:Factory/hpack/hpack.changes 2018-07-24 17:23:37.879395521 +0200 +++ /work/SRC/openSUSE:Factory/.hpack.new/hpack.changes 2018-08-20 16:21:05.800964524 +0200 @@ -1,0 +2,10 @@ +Fri Aug 17 09:43:24 UTC 2018 - [email protected] + +- Update hpack to version 0.29.7. + ## Changes in 0.29.7 + - Expose more stuff from `Hpack.Yaml` so that it can be used by third parties + + ## Changes in 0.29.6 + - Add `spec-version` (see #300) + +------------------------------------------------------------------- Old: ---- hpack-0.29.5.tar.gz New: ---- hpack-0.29.7.tar.gz ++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++ Other differences: ------------------ ++++++ hpack.spec ++++++ --- /var/tmp/diff_new_pack.vmDUwz/_old 2018-08-20 16:21:06.172965050 +0200 +++ /var/tmp/diff_new_pack.vmDUwz/_new 2018-08-20 16:21:06.172965050 +0200 @@ -19,9 +19,9 @@ %global pkg_name hpack %bcond_with tests Name: %{pkg_name} -Version: 0.29.5 +Version: 0.29.7 Release: 0 -Summary: An alternative format for Haskell packages +Summary: A modern format for Haskell packages License: MIT Group: Development/Libraries/Haskell URL: https://hackage.haskell.org/package/%{name} @@ -60,7 +60,7 @@ %endif %description -An alternative format for Haskell packages. +A modern format for Haskell packages. %package -n ghc-%{name} Summary: Haskell %{name} library ++++++ hpack-0.29.5.tar.gz -> hpack-0.29.7.tar.gz ++++++ diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/hpack-0.29.5/CHANGELOG.md new/hpack-0.29.7/CHANGELOG.md --- old/hpack-0.29.5/CHANGELOG.md 2018-07-16 22:27:18.000000000 +0200 +++ new/hpack-0.29.7/CHANGELOG.md 2018-08-14 05:36:12.000000000 +0200 @@ -1,3 +1,9 @@ +## Changes in 0.29.7 + - Expose more stuff from `Hpack.Yaml` so that it can be used by third parties + +## Changes in 0.29.6 + - Add `spec-version` (see #300) + ## Changes in 0.29.5 - Fix a regression related to indentation sniffing (close #310) diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/hpack-0.29.5/hpack.cabal new/hpack-0.29.7/hpack.cabal --- old/hpack-0.29.5/hpack.cabal 2018-07-16 22:27:18.000000000 +0200 +++ new/hpack-0.29.7/hpack.cabal 2018-08-14 05:36:12.000000000 +0200 @@ -1,14 +1,14 @@ cabal-version: >= 1.10 --- This file has been generated from package.yaml by hpack version 0.29.4. +-- This file has been generated from package.yaml by hpack version 0.29.6. -- -- see: https://github.com/sol/hpack -- --- hash: c9c40490b86bd987b33ab63f10fd311c44b89e37d5a75d5af8cd25db72992e99 +-- hash: 8d1eb0679326dc7c31be647812822700dc8277a27737239f5a704e45f367abdf name: hpack -version: 0.29.5 -synopsis: An alternative format for Haskell packages +version: 0.29.7 +synopsis: A modern format for Haskell packages description: See README at <https://github.com/sol/hpack#readme> category: Development homepage: https://github.com/sol/hpack#readme @@ -70,6 +70,7 @@ Hpack.Render.Hints Hpack.Syntax.Defaults Hpack.Syntax.Dependency + Hpack.Syntax.DependencyVersion Hpack.Syntax.Git Hpack.Utf8 Hpack.Util @@ -184,6 +185,7 @@ Hpack.Render.Hints Hpack.Syntax.Defaults Hpack.Syntax.Dependency + Hpack.Syntax.DependencyVersion Hpack.Syntax.Git Hpack.Utf8 Hpack.Util diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/hpack-0.29.5/src/Data/Aeson/Config/FromValue.hs new/hpack-0.29.7/src/Data/Aeson/Config/FromValue.hs --- old/hpack-0.29.5/src/Data/Aeson/Config/FromValue.hs 2018-07-16 22:27:18.000000000 +0200 +++ new/hpack-0.29.7/src/Data/Aeson/Config/FromValue.hs 2018-08-14 05:36:12.000000000 +0200 @@ -28,6 +28,8 @@ , withNumber , withBool +, parseArray + , (.:) , (.:?) @@ -90,10 +92,13 @@ fromValue value = liftParser (parseJSON value) >>= traverse fromValue instance FromValue a => FromValue [a] where - fromValue = withArray $ zipWithM (parseIndexed fromValue) [0..] . V.toList - where - parseIndexed :: (Value -> Parser a) -> Int -> Value -> Parser a - parseIndexed p n value = p value <?> Index n + fromValue = withArray (parseArray fromValue) + +parseArray :: (Value -> Parser a) -> Array -> Parser [a] +parseArray f = zipWithM (parseIndexed f) [0..] . V.toList + where + parseIndexed :: (Value -> Parser a) -> Int -> Value -> Parser a + parseIndexed p n value = p value <?> Index n instance FromValue a => FromValue (Map String a) where fromValue = withObject $ \ o -> do diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/hpack-0.29.5/src/Hpack/Config.hs new/hpack-0.29.7/src/Hpack/Config.hs --- old/hpack-0.29.5/src/Hpack/Config.hs 2018-07-16 22:27:18.000000000 +0200 +++ new/hpack-0.29.7/src/Hpack/Config.hs 2018-08-14 05:36:12.000000000 +0200 @@ -26,6 +26,7 @@ -- tool that supports Hpack (e.g. @stack@ or @cabal2nix@). DecodeOptions(..) +, ProgramName(..) , defaultDecodeOptions , packageConfig , DecodeResult(..) @@ -83,6 +84,7 @@ import Data.Maybe import Data.Semigroup (Semigroup(..)) import Data.Ord +import Data.String import Data.Text (Text) import qualified Data.Text as T import Data.Scientific (Scientific) @@ -92,7 +94,7 @@ import Control.Monad.Trans.Writer import Control.Monad.Trans.Except import Control.Monad.IO.Class -import Data.Version +import Data.Version (Version, makeVersion, showVersion) import Distribution.Pretty (prettyShow) import qualified Distribution.SPDX.License as SPDX @@ -106,8 +108,12 @@ import qualified Hpack.Util as Util import Hpack.Defaults import qualified Hpack.Yaml as Yaml +import Hpack.Syntax.DependencyVersion import Hpack.Syntax.Dependency import Hpack.License +import Hpack.CabalFile (parseVersion) + +import qualified Paths_hpack as Hpack (version) package :: String -> String -> Package package name version = Package { @@ -554,17 +560,24 @@ type Warnings m = WriterT [String] m type Errors = ExceptT String -decodeYaml :: FromValue a => FilePath -> Warnings (Errors IO) a -decodeYaml file = lift (ExceptT $ Yaml.decodeYaml file) >>= decodeValue file +decodeYaml :: FromValue a => ProgramName -> FilePath -> Warnings (Errors IO) a +decodeYaml programName file = lift (ExceptT $ Yaml.decodeYaml file) >>= decodeValue programName file data DecodeOptions = DecodeOptions { - decodeOptionsTarget :: FilePath + decodeOptionsProgramName :: ProgramName +, decodeOptionsTarget :: FilePath , decodeOptionsUserDataDir :: Maybe FilePath , decodeOptionsDecode :: FilePath -> IO (Either String Value) } +newtype ProgramName = ProgramName String + deriving (Eq, Show) + +instance IsString ProgramName where + fromString = ProgramName + defaultDecodeOptions :: DecodeOptions -defaultDecodeOptions = DecodeOptions packageConfig Nothing Yaml.decodeYaml +defaultDecodeOptions = DecodeOptions "hpack" packageConfig Nothing Yaml.decodeYaml data DecodeResult = DecodeResult { decodeResultPackage :: Package @@ -574,12 +587,12 @@ } deriving (Eq, Show) readPackageConfig :: DecodeOptions -> IO (Either String DecodeResult) -readPackageConfig (DecodeOptions file mUserDataDir readValue) = runExceptT $ fmap addCabalFile . runWriterT $ do +readPackageConfig (DecodeOptions programName file mUserDataDir readValue) = runExceptT $ fmap addCabalFile . runWriterT $ do value <- lift . ExceptT $ readValue file - config <- decodeValue file value + config <- decodeValue programName file value dir <- liftIO $ takeDirectory <$> canonicalizePath file userDataDir <- liftIO $ maybe (getAppUserDataDirectory "hpack") return mUserDataDir - toPackage userDataDir dir config + toPackage programName userDataDir dir config where addCabalFile :: ((Package, String), [String]) -> DecodeResult addCabalFile ((pkg, cabalVersion), warnings) = DecodeResult pkg cabalVersion (takeDirectory_ file </> (packageName pkg ++ ".cabal")) warnings @@ -665,7 +678,7 @@ makeVersion [1,22] <$ guard hasReexportedModules , makeVersion [2,0] <$ guard hasSignatures , makeVersion [2,0] <$ guard hasGeneratedModules - , makeVersion [2,2] <$ guard (hasCxxParams sect) + , sectionCabalVersion sect ] where hasReexportedModules = any (not . null . libraryReexportedModules) sect @@ -685,32 +698,56 @@ executableCabalVersion :: Section Executable -> Maybe Version executableCabalVersion sect = maximum [ makeVersion [2,0] <$ guard (executableHasGeneratedModules sect) - , makeVersion [2,2] <$ guard (hasCxxParams sect) + , sectionCabalVersion sect ] executableHasGeneratedModules :: Section Executable -> Bool executableHasGeneratedModules = any (not . null . executableGeneratedModules) - hasCxxParams :: Section a -> Bool - hasCxxParams sect = or [ - check sect - , any (any check) (sectionConditionals sect) + sectionCabalVersion :: Section a -> Maybe Version + sectionCabalVersion sect = maximum [ + makeVersion [2,2] <$ guard (sectionSatisfies (not . null . sectionCxxSources) sect) + , makeVersion [2,2] <$ guard (sectionSatisfies (not . null . sectionCxxOptions) sect) ] - where - check s = or [ - (not . null . sectionCxxOptions) s - , (not . null . sectionCxxSources) s - ] - -decodeValue :: FromValue a => FilePath -> Value -> Warnings (Errors IO) a -decodeValue file value = do - (a, unknown) <- lift . ExceptT . return $ first (prefix ++) (Config.decodeValue value) - tell (map formatUnknownField unknown) - return a + + sectionSatisfies :: (Section a -> Bool) -> Section a -> Bool + sectionSatisfies p sect = or [ + p sect + , any (any (sectionSatisfies p)) (sectionConditionals sect) + ] + +decodeValue :: FromValue a => ProgramName -> FilePath -> Value -> Warnings (Errors IO) a +decodeValue (ProgramName programName) file value = do + (r, unknown) <- lift . ExceptT . return $ first (prefix ++) (Config.decodeValue value) + case r of + UnsupportedSpecVersion v -> do + lift $ throwE ("The file " ++ file ++ " requires version " ++ showVersion v ++ " of the Hpack package specification, however this version of " ++ programName ++ " only supports versions up to " ++ showVersion Hpack.version ++ ". Upgrading to the latest version of " ++ programName ++ " may resolve this issue.") + SupportedSpecVersion a -> do + tell (map formatUnknownField unknown) + return a where prefix = file ++ ": " formatUnknownField name = prefix ++ "Ignoring unrecognized field " ++ name +data CheckSpecVersion a = SupportedSpecVersion a | UnsupportedSpecVersion Version + +instance FromValue a => FromValue (CheckSpecVersion a) where + fromValue = withObject $ \ o -> o .:? "spec-version" >>= \ case + Just (ParseSpecVersion v) | Hpack.version < v -> return $ UnsupportedSpecVersion v + _ -> SupportedSpecVersion <$> fromValue (Object o) + +newtype ParseSpecVersion = ParseSpecVersion Version + +instance FromValue ParseSpecVersion where + fromValue value = do + s <- case value of + Number n -> return (scientificToVersion n) + String s -> return (T.unpack s) + _ -> typeMismatch "Number or String" value + case parseVersion s of + Just v -> return (ParseSpecVersion v) + Nothing -> fail ("invalid value " ++ show s) + data Package = Package { packageName :: String , packageVersion :: String @@ -830,39 +867,42 @@ type CommonOptionsWithDefaults a = Product DefaultsConfig (CommonOptions ParseCSources ParseCxxSources ParseJsSources a) type WithCommonOptionsWithDefaults a = Product DefaultsConfig (WithCommonOptions ParseCSources ParseCxxSources ParseJsSources a) -toPackage :: FilePath -> FilePath -> ConfigWithDefaults -> Warnings (Errors IO) (Package, String) -toPackage userDataDir dir = - expandDefaultsInConfig userDataDir dir +toPackage :: ProgramName -> FilePath -> FilePath -> ConfigWithDefaults -> Warnings (Errors IO) (Package, String) +toPackage programName userDataDir dir = + expandDefaultsInConfig programName userDataDir dir >=> traverseConfig (expandForeignSources dir) >=> toPackage_ dir expandDefaultsInConfig - :: FilePath + :: ProgramName + -> FilePath -> FilePath -> ConfigWithDefaults -> Warnings (Errors IO) (Config ParseCSources ParseCxxSources ParseJsSources) -expandDefaultsInConfig userDataDir dir = bitraverse (expandGlobalDefaults userDataDir dir) (expandSectionDefaults userDataDir dir) +expandDefaultsInConfig programName userDataDir dir = bitraverse (expandGlobalDefaults programName userDataDir dir) (expandSectionDefaults programName userDataDir dir) expandGlobalDefaults - :: FilePath + :: ProgramName + -> FilePath -> FilePath -> CommonOptionsWithDefaults Empty -> Warnings (Errors IO) (CommonOptions ParseCSources ParseCxxSources ParseJsSources Empty) -expandGlobalDefaults userDataDir dir = do - fmap (`Product` Empty) >>> expandDefaults userDataDir dir >=> \ (Product c Empty) -> return c +expandGlobalDefaults programName userDataDir dir = do + fmap (`Product` Empty) >>> expandDefaults programName userDataDir dir >=> \ (Product c Empty) -> return c expandSectionDefaults - :: FilePath + :: ProgramName + -> FilePath -> FilePath -> PackageConfigWithDefaults ParseCSources ParseCxxSources ParseJsSources -> Warnings (Errors IO) (PackageConfig ParseCSources ParseCxxSources ParseJsSources) -expandSectionDefaults userDataDir dir p@PackageConfig{..} = do - library <- traverse (expandDefaults userDataDir dir) packageConfigLibrary - internalLibraries <- traverse (traverse (expandDefaults userDataDir dir)) packageConfigInternalLibraries - executable <- traverse (expandDefaults userDataDir dir) packageConfigExecutable - executables <- traverse (traverse (expandDefaults userDataDir dir)) packageConfigExecutables - tests <- traverse (traverse (expandDefaults userDataDir dir)) packageConfigTests - benchmarks <- traverse (traverse (expandDefaults userDataDir dir)) packageConfigBenchmarks +expandSectionDefaults programName userDataDir dir p@PackageConfig{..} = do + library <- traverse (expandDefaults programName userDataDir dir) packageConfigLibrary + internalLibraries <- traverse (traverse (expandDefaults programName userDataDir dir)) packageConfigInternalLibraries + executable <- traverse (expandDefaults programName userDataDir dir) packageConfigExecutable + executables <- traverse (traverse (expandDefaults programName userDataDir dir)) packageConfigExecutables + tests <- traverse (traverse (expandDefaults programName userDataDir dir)) packageConfigTests + benchmarks <- traverse (traverse (expandDefaults programName userDataDir dir)) packageConfigBenchmarks return p{ packageConfigLibrary = library , packageConfigInternalLibraries = internalLibraries @@ -874,11 +914,12 @@ expandDefaults :: (FromValue a, Semigroup a, Monoid a) - => FilePath + => ProgramName + -> FilePath -> FilePath -> WithCommonOptionsWithDefaults a -> Warnings (Errors IO) (WithCommonOptions ParseCSources ParseCxxSources ParseJsSources a) -expandDefaults userDataDir = expand [] +expandDefaults programName userDataDir = expand [] where expand :: (FromValue a, Semigroup a, Monoid a) => [FilePath] @@ -898,7 +939,7 @@ file <- lift $ ExceptT (ensure userDataDir dir defaults) seen_ <- lift (checkCycle seen file) let dir_ = takeDirectory file - decodeYaml file >>= expand seen_ dir_ + decodeYaml programName file >>= expand seen_ dir_ checkCycle :: [FilePath] -> FilePath -> Errors IO [FilePath] checkCycle seen file = do @@ -925,15 +966,18 @@ globalVerbatim = commonOptionsVerbatim g globalOptions = g {commonOptionsVerbatim = Nothing} - mLibrary <- liftIO $ traverse (toLibrary dir packageName_ globalOptions) packageConfigLibrary + toSect :: Monoid a => WithCommonOptions CSources CxxSources JsSources a -> Section a + toSect = toSection . first ((mempty <$ globalOptions) <>) - internalLibraries <- liftIO $ toInternalLibraries dir packageName_ globalOptions packageConfigInternalLibraries + toLib = toLibrary dir packageName_ . toSect + toExecutables = liftIO . maybe mempty (traverse $ toExecutable dir packageName_ . toSect) - executables <- toExecutableMap packageName_ packageConfigExecutables packageConfigExecutable - >>= liftIO . toExecutables dir packageName_ globalOptions + mLibrary <- liftIO $ traverse toLib packageConfigLibrary + internalLibraries <- liftIO $ maybe mempty (traverse toLib) packageConfigInternalLibraries - tests <- liftIO $ toExecutables dir packageName_ globalOptions packageConfigTests - benchmarks <- liftIO $ toExecutables dir packageName_ globalOptions packageConfigBenchmarks + executables <- toExecutableMap packageName_ packageConfigExecutables packageConfigExecutable >>= toExecutables + tests <- toExecutables packageConfigTests + benchmarks <- toExecutables packageConfigBenchmarks licenseFileExists <- liftIO $ doesFileExist (dir </> "LICENSE") @@ -1117,10 +1161,9 @@ r = fromConfig pathsModule inferableModules conf return (outerModules ++ getInferredModules r, r) -toLibrary :: FilePath -> String -> GlobalOptions -> WithCommonOptions CSources CxxSources JsSources LibrarySection -> IO (Section Library) -toLibrary dir name globalOptions = +toLibrary :: FilePath -> String -> Section LibrarySection -> IO (Section Library) +toLibrary dir name = inferModules dir name getMentionedLibraryModules getLibraryModules fromLibrarySectionTopLevel fromLibrarySectionInConditional - . toSection (mempty <$ globalOptions) where getLibraryModules :: Library -> [String] getLibraryModules Library{..} = libraryExposedModules ++ libraryOtherModules @@ -1159,21 +1202,14 @@ , librarySignatures = fromMaybeList librarySectionSignatures } -toInternalLibraries :: FilePath -> String -> GlobalOptions -> Maybe (Map String (WithCommonOptions CSources CxxSources JsSources LibrarySection)) -> IO (Map String (Section Library)) -toInternalLibraries dir packageName_ globalOptions = traverse (toLibrary dir packageName_ globalOptions) . fromMaybe mempty - -toExecutables :: FilePath -> String -> GlobalOptions -> Maybe (Map String (WithCommonOptions CSources CxxSources JsSources ExecutableSection)) -> IO (Map String (Section Executable)) -toExecutables dir packageName_ globalOptions = traverse (toExecutable dir packageName_ globalOptions) . fromMaybe mempty - getMentionedExecutableModules :: ExecutableSection -> [String] getMentionedExecutableModules (ExecutableSection main otherModules generatedModules)= maybe id (:) (main >>= toModule . splitDirectories) $ fromMaybeList (otherModules <> generatedModules) -toExecutable :: FilePath -> String -> GlobalOptions -> WithCommonOptions CSources CxxSources JsSources ExecutableSection -> IO (Section Executable) -toExecutable dir packageName_ globalOptions = +toExecutable :: FilePath -> String -> Section ExecutableSection -> IO (Section Executable) +toExecutable dir packageName_ = inferModules dir packageName_ getMentionedExecutableModules executableOtherModules fromExecutableSection (fromExecutableSection []) . expandMain - . toSection (mempty <$ globalOptions) where fromExecutableSection :: [String] -> [String] -> ExecutableSection -> Executable fromExecutableSection pathsModule inferableModules ExecutableSection{..} = @@ -1201,11 +1237,10 @@ , sectionConditionals = map (fmap flatten) sectionConditionals } -toSection :: CommonOptions CSources CxxSources JsSources a -> WithCommonOptions CSources CxxSources JsSources a -> Section a -toSection globalOptions (Product options a) = toSection_ (Product (globalOptions <> options) a) - -toSection_ :: WithCommonOptions CSources CxxSources JsSources a -> Section a -toSection_ (Product CommonOptions{..} a) = Section { +toSection :: WithCommonOptions CSources CxxSources JsSources a -> Section a +toSection = go + where + go (Product CommonOptions{..} a) = Section { sectionData = a , sectionSourceDirs = fromMaybeList commonOptionsSourceDirs , sectionDefaultExtensions = fromMaybeList commonOptionsDefaultExtensions @@ -1229,17 +1264,15 @@ , sectionBuildable = commonOptionsBuildable , sectionDependencies = fromMaybe mempty commonOptionsDependencies , sectionPkgConfigDependencies = fromMaybeList commonOptionsPkgConfigDependencies - , sectionConditionals = conditionals + , sectionConditionals = map toConditional (fromMaybeList commonOptionsWhen) , sectionBuildTools = fromMaybe mempty commonOptionsBuildTools , sectionVerbatim = fromMaybeList commonOptionsVerbatim } - where - conditionals = map toConditional (fromMaybeList commonOptionsWhen) toConditional :: ConditionalSection CSources CxxSources JsSources a -> Conditional (Section a) toConditional x = case x of - ThenElseConditional (Product (ThenElse then_ else_) c) -> conditional c (toSection_ then_) (Just $ toSection_ else_) - FlatConditional (Product sect c) -> conditional c (toSection_ sect) Nothing + ThenElseConditional (Product (ThenElse then_ else_) c) -> conditional c (go then_) (Just $ go else_) + FlatConditional (Product sect c) -> conditional c (go sect) Nothing where conditional (Condition (Cond c)) = Conditional c diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/hpack-0.29.5/src/Hpack/Syntax/Dependency.hs new/hpack-0.29.7/src/Hpack/Syntax/Dependency.hs --- old/hpack-0.29.5/src/Hpack/Syntax/Dependency.hs 2018-07-16 22:27:18.000000000 +0200 +++ new/hpack-0.29.7/src/Hpack/Syntax/Dependency.hs 2018-08-14 05:36:12.000000000 +0200 @@ -1,37 +1,22 @@ -{-# LANGUAGE CPP #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE TypeFamilies #-} -{-# LANGUAGE LambdaCase #-} module Hpack.Syntax.Dependency ( Dependencies(..) -, DependencyVersion(..) -, SourceDependency(..) -, GitRef -, GitUrl -, githubBaseUrl -, scientificToVersion ) where +import Data.Text (Text) import qualified Data.Text as T import Data.Semigroup (Semigroup(..)) -import Text.PrettyPrint (renderStyle, Style(..), Mode(..)) import Control.Monad -import Distribution.Version (VersionRangeF(..)) -import qualified Distribution.Compat.ReadP as D import qualified Distribution.Package as D -import qualified Distribution.Text as D -import qualified Distribution.Version as D import Data.Map.Lazy (Map) import qualified Data.Map.Lazy as Map -import Data.Scientific -import Control.Applicative import GHC.Exts import Data.Aeson.Config.FromValue -githubBaseUrl :: String -githubBaseUrl = "https://github.com/" +import Hpack.Syntax.DependencyVersion newtype Dependencies = Dependencies { unDependencies :: Map String DependencyVersion @@ -42,18 +27,6 @@ fromList = Dependencies . Map.fromList toList = Map.toList . unDependencies -data DependencyVersion = - AnyVersion - | VersionRange String - | SourceDependency SourceDependency - deriving (Eq, Show) - -data SourceDependency = GitRef GitUrl GitRef (Maybe FilePath) | Local FilePath - deriving (Eq, Show) - -type GitUrl = String -type GitRef = String - instance FromValue Dependencies where fromValue v = case v of String _ -> dependenciesFromList . return <$> fromValue v @@ -67,54 +40,6 @@ dependenciesFromList :: [Dependency] -> Dependencies dependenciesFromList = Dependencies . Map.fromList . map fromDependency - -instance FromValue DependencyVersion where - fromValue v = case v of - Null -> return AnyVersion - Object _ -> SourceDependency <$> fromValue v - Number n -> return (scientificToDependencyVersion n) - String s -> parseVersionRange ("== " ++ input) <|> parseVersionRange input - where - input = T.unpack s - - _ -> typeMismatch "Null, Object, Number, or String" v - -scientificToDependencyVersion :: Scientific -> DependencyVersion -scientificToDependencyVersion n = VersionRange ("==" ++ version) - where - version = scientificToVersion n - -scientificToVersion :: Scientific -> String -scientificToVersion n = version - where - version = formatScientific Fixed (Just decimalPlaces) n - decimalPlaces - | e < 0 = abs e - | otherwise = 0 - e = base10Exponent n - -instance FromValue SourceDependency where - fromValue = withObject (\o -> let - local :: Parser SourceDependency - local = Local <$> o .: "path" - - git :: Parser SourceDependency - git = GitRef <$> url <*> ref <*> subdir - - url :: Parser String - url = - ((githubBaseUrl ++) <$> o .: "github") - <|> (o .: "git") - <|> fail "neither key \"git\" nor key \"github\" present" - - ref :: Parser String - ref = o .: "ref" - - subdir :: Parser (Maybe FilePath) - subdir = o .:? "subdir" - - in local <|> git) - data Dependency = Dependency { _dependencyName :: String , _dependencyVersion :: DependencyVersion @@ -122,73 +47,20 @@ instance FromValue Dependency where fromValue v = case v of - String s -> uncurry Dependency <$> parseDependency (T.unpack s) - Object o -> addSourceDependency o + String s -> uncurry Dependency <$> parseDependency "dependency" s + Object o -> sourceDependency o _ -> typeMismatch "Object or String" v where - addSourceDependency o = Dependency <$> name <*> (SourceDependency <$> fromValue v) + sourceDependency o = Dependency <$> name <*> (SourceDependency <$> fromValue v) where name :: Parser String name = o .: "name" -depPkgName :: D.Dependency -> String -#if MIN_VERSION_Cabal(2,0,0) -depPkgName = D.unPackageName . D.depPkgName -#else -depPkgName (D.Dependency (D.PackageName name) _) = name -#endif - -depVerRange :: D.Dependency -> D.VersionRange -#if MIN_VERSION_Cabal(2,0,0) -depVerRange = D.depVerRange -#else -depVerRange (D.Dependency _ versionRange) = versionRange -#endif - -parseDependency :: Monad m => String -> m (String, DependencyVersion) -parseDependency = liftM fromCabal . parseCabalDependency +parseDependency :: Monad m => String -> Text -> m (String, DependencyVersion) +parseDependency subject = liftM fromCabal . parseCabalDependency subject . T.unpack where fromCabal :: D.Dependency -> (String, DependencyVersion) - fromCabal d = (depPkgName d, dependencyVersionFromCabal $ depVerRange d) - -dependencyVersionFromCabal :: D.VersionRange -> DependencyVersion -dependencyVersionFromCabal versionRange - | D.isAnyVersion versionRange = AnyVersion - | otherwise = VersionRange . renderStyle style . D.disp $ toPreCabal2VersionRange versionRange - where - style = Style OneLineMode 0 0 - -parseCabalDependency :: Monad m => String -> m D.Dependency -parseCabalDependency = cabalParse "dependency" - -parseVersionRange :: Monad m => String -> m DependencyVersion -parseVersionRange = liftM dependencyVersionFromCabal . parseCabalVersionRange - -parseCabalVersionRange :: Monad m => String -> m D.VersionRange -parseCabalVersionRange = cabalParse "constraint" - -cabalParse :: (Monad m, D.Text a) => String -> String -> m a -cabalParse subject s = case [d | (d, "") <- D.readP_to_S D.parse s] of - [d] -> return d - _ -> fail $ unwords ["invalid", subject, show s] - -toPreCabal2VersionRange :: D.VersionRange -> D.VersionRange -toPreCabal2VersionRange = D.embedVersionRange . D.cataVersionRange f - where - f :: VersionRangeF (VersionRangeF D.VersionRange) -> VersionRangeF D.VersionRange - f = \ case - MajorBoundVersionF v -> IntersectVersionRangesF (D.embedVersionRange lower) (D.embedVersionRange upper) - where - lower = OrLaterVersionF v - upper = EarlierVersionF (D.majorUpperBound v) + fromCabal d = (D.unPackageName $ D.depPkgName d, dependencyVersionFromCabal $ D.depVerRange d) - AnyVersionF -> AnyVersionF - ThisVersionF v -> ThisVersionF v - LaterVersionF v -> LaterVersionF v - OrLaterVersionF v -> OrLaterVersionF v - EarlierVersionF v -> EarlierVersionF v - OrEarlierVersionF v -> OrEarlierVersionF v - WildcardVersionF v -> WildcardVersionF v - UnionVersionRangesF a b -> UnionVersionRangesF (D.embedVersionRange a) (D.embedVersionRange b) - IntersectVersionRangesF a b -> IntersectVersionRangesF (D.embedVersionRange a) (D.embedVersionRange b) - VersionRangeParensF a -> VersionRangeParensF (D.embedVersionRange a) +parseCabalDependency :: Monad m => String -> String -> m D.Dependency +parseCabalDependency = cabalParse diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/hpack-0.29.5/src/Hpack/Syntax/DependencyVersion.hs new/hpack-0.29.7/src/Hpack/Syntax/DependencyVersion.hs --- old/hpack-0.29.5/src/Hpack/Syntax/DependencyVersion.hs 1970-01-01 01:00:00.000000000 +0100 +++ new/hpack-0.29.7/src/Hpack/Syntax/DependencyVersion.hs 2018-08-14 05:36:12.000000000 +0200 @@ -0,0 +1,126 @@ +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE LambdaCase #-} +module Hpack.Syntax.DependencyVersion ( + githubBaseUrl +, GitRef +, GitUrl +, DependencyVersion(..) +, SourceDependency(..) +, dependencyVersionFromCabal + +, scientificToVersion +, cabalParse +) where + +import Control.Applicative +import Data.Scientific +import qualified Data.Text as T +import Text.PrettyPrint (renderStyle, Style(..), Mode(..)) + +import Distribution.Version (VersionRangeF(..)) +import qualified Distribution.Text as D +import qualified Distribution.Version as D +import qualified Distribution.Parsec.Class as D + +import Data.Aeson.Config.FromValue + +githubBaseUrl :: String +githubBaseUrl = "https://github.com/" + +type GitUrl = String +type GitRef = String + +data DependencyVersion = + AnyVersion + | VersionRange String + | SourceDependency SourceDependency + deriving (Eq, Show) + +instance FromValue DependencyVersion where + fromValue v = case v of + Null -> return AnyVersion + Object _ -> SourceDependency <$> fromValue v + Number n -> return (scientificToDependencyVersion n) + String s -> parseVersionRange ("== " ++ input) <|> parseVersionRange input + where + input = T.unpack s + + _ -> typeMismatch "Null, Object, Number, or String" v + +data SourceDependency = GitRef GitUrl GitRef (Maybe FilePath) | Local FilePath + deriving (Eq, Show) + +instance FromValue SourceDependency where + fromValue = withObject (\o -> let + local :: Parser SourceDependency + local = Local <$> o .: "path" + + git :: Parser SourceDependency + git = GitRef <$> url <*> ref <*> subdir + + url :: Parser String + url = + ((githubBaseUrl ++) <$> o .: "github") + <|> (o .: "git") + <|> fail "neither key \"git\" nor key \"github\" present" + + ref :: Parser String + ref = o .: "ref" + + subdir :: Parser (Maybe FilePath) + subdir = o .:? "subdir" + + in local <|> git) + +scientificToDependencyVersion :: Scientific -> DependencyVersion +scientificToDependencyVersion n = VersionRange ("==" ++ version) + where + version = scientificToVersion n + +scientificToVersion :: Scientific -> String +scientificToVersion n = version + where + version = formatScientific Fixed (Just decimalPlaces) n + decimalPlaces + | e < 0 = abs e + | otherwise = 0 + e = base10Exponent n + +parseVersionRange :: Monad m => String -> m DependencyVersion +parseVersionRange = fmap dependencyVersionFromCabal . parseCabalVersionRange + +parseCabalVersionRange :: Monad m => String -> m D.VersionRange +parseCabalVersionRange = cabalParse "constraint" + +cabalParse :: (Monad m, D.Parsec a) => String -> String -> m a +cabalParse subject s = case D.eitherParsec s of + Right d -> return d + Left _ ->fail $ unwords ["invalid", subject, show s] + +dependencyVersionFromCabal :: D.VersionRange -> DependencyVersion +dependencyVersionFromCabal versionRange + | D.isAnyVersion versionRange = AnyVersion + | otherwise = VersionRange . renderStyle style . D.disp $ toPreCabal2VersionRange versionRange + where + style = Style OneLineMode 0 0 + + toPreCabal2VersionRange :: D.VersionRange -> D.VersionRange + toPreCabal2VersionRange = D.embedVersionRange . D.cataVersionRange f + where + f :: VersionRangeF (VersionRangeF D.VersionRange) -> VersionRangeF D.VersionRange + f = \ case + MajorBoundVersionF v -> IntersectVersionRangesF (D.embedVersionRange lower) (D.embedVersionRange upper) + where + lower = OrLaterVersionF v + upper = EarlierVersionF (D.majorUpperBound v) + + AnyVersionF -> AnyVersionF + ThisVersionF v -> ThisVersionF v + LaterVersionF v -> LaterVersionF v + OrLaterVersionF v -> OrLaterVersionF v + EarlierVersionF v -> EarlierVersionF v + OrEarlierVersionF v -> OrEarlierVersionF v + WildcardVersionF v -> WildcardVersionF v + UnionVersionRangesF a b -> UnionVersionRangesF (D.embedVersionRange a) (D.embedVersionRange b) + IntersectVersionRangesF a b -> IntersectVersionRangesF (D.embedVersionRange a) (D.embedVersionRange b) + VersionRangeParensF a -> VersionRangeParensF (D.embedVersionRange a) diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/hpack-0.29.5/src/Hpack/Yaml.hs new/hpack-0.29.7/src/Hpack/Yaml.hs --- old/hpack-0.29.5/src/Hpack/Yaml.hs 2018-07-16 22:27:18.000000000 +0200 +++ new/hpack-0.29.7/src/Hpack/Yaml.hs 2018-08-14 05:36:12.000000000 +0200 @@ -13,10 +13,12 @@ -- tool that supports Hpack (e.g. @stack@ or @cabal2nix@). decodeYaml +, module Data.Aeson.Config.FromValue ) where import Data.Yaml hiding (decodeFile, decodeFileEither) import Data.Yaml.Include +import Data.Aeson.Config.FromValue decodeYaml :: FilePath -> IO (Either String Value) decodeYaml file = do diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/hpack-0.29.5/src/Hpack.hs new/hpack-0.29.7/src/Hpack.hs --- old/hpack-0.29.5/src/Hpack.hs 2018-07-16 22:27:18.000000000 +0200 +++ new/hpack-0.29.7/src/Hpack.hs 2018-08-14 05:36:12.000000000 +0200 @@ -25,6 +25,7 @@ -- * Options , defaultOptions +, setProgramName , setTarget , setDecode , getOptions @@ -113,6 +114,10 @@ setTarget target options@Options{..} = options {optionsDecodeOptions = optionsDecodeOptions {decodeOptionsTarget = target}} +setProgramName :: ProgramName -> Options -> Options +setProgramName name options@Options{..} = + options {optionsDecodeOptions = optionsDecodeOptions {decodeOptionsProgramName = name}} + setDecode :: (FilePath -> IO (Either String Value)) -> Options -> Options setDecode decode options@Options{..} = options {optionsDecodeOptions = optionsDecodeOptions {decodeOptionsDecode = decode}} diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/hpack-0.29.5/test/EndToEndSpec.hs new/hpack-0.29.7/test/EndToEndSpec.hs --- old/hpack-0.29.5/test/EndToEndSpec.hs 2018-07-16 22:27:18.000000000 +0200 +++ new/hpack-0.29.7/test/EndToEndSpec.hs 2018-08-14 05:36:12.000000000 +0200 @@ -16,11 +16,14 @@ import Data.List import Data.String.Interpolate import Data.String.Interpolate.Util +import Data.Version (showVersion) import qualified Hpack.Render as Hpack import Hpack.Config (packageConfig, readPackageConfig, DecodeOptions(..), DecodeResult(..), defaultDecodeOptions) import Hpack.Render.Hints (FormattingHints(..), sniffFormattingHints) +import qualified Paths_hpack as Hpack (version) + writeFile :: FilePath -> String -> IO () writeFile file c = touch file >> Prelude.writeFile file c @@ -36,6 +39,37 @@ other-modules: Paths_foo |] + describe "spec-version" $ do + it "accepts spec-version" $ do + [i| + spec-version: 0.29.5 + |] `shouldRenderTo` package [i| + |] + + it "fails on malformed spec-version" $ do + [i| + spec-version: foo + |] `shouldFailWith` "package.yaml: Error while parsing $.spec-version - invalid value \"foo\"" + + it "fails on unsupported spec-version" $ do + [i| + spec-version: 25.0 + dependencies: foo == bar + |] `shouldFailWith` ("The file package.yaml requires version 25.0 of the Hpack package specification, however this version of hpack only supports versions up to " ++ showVersion Hpack.version ++ ". Upgrading to the latest version of hpack may resolve this issue.") + + it "fails on unsupported spec-version from defaults" $ do + let file = joinPath ["defaults", "sol", "hpack-template", "2017", "defaults.yaml"] + writeFile file [i| + spec-version: 25.0 + |] + + [i| + defaults: + github: sol/hpack-template + path: defaults.yaml + ref: "2017" + library: {} + |] `shouldFailWith` ("The file " ++ file ++ " requires version 25.0 of the Hpack package specification, however this version of hpack only supports versions up to " ++ showVersion Hpack.version ++ ". Upgrading to the latest version of hpack may resolve this issue.") describe "data-files" $ do it "accepts data-files" $ do @@ -554,6 +588,24 @@ cxx-options: -Wall |]) {packageCabalVersion = "2.2"} + context "when used inside a nested conditional" $ do + it "infers correct cabal-version" $ do + [i| + executable: + when: + condition: True + when: + condition: True + when: + condition: True + cxx-options: -Wall + |] `shouldRenderTo` (executable_ "foo" [i| + if true + if true + if true + cxx-options: -Wall + |]) {packageCabalVersion = "2.2"} + describe "cxx-sources" $ before_ (touch "foo.cc" >> touch "cxxbits/bar.cc") $ do it "accepts cxx-sources" $ do [i| @@ -1398,7 +1450,7 @@ content = [i| executable #{name} other-modules: - Paths_#{name} + Paths_foo #{indentBy 2 $ unindent e} default-language: Haskell2010 |] diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/hpack-0.29.5/test/Hpack/Syntax/DependencySpec.hs new/hpack-0.29.7/test/Hpack/Syntax/DependencySpec.hs --- old/hpack-0.29.5/test/Hpack/Syntax/DependencySpec.hs 2018-07-16 22:27:18.000000000 +0200 +++ new/hpack-0.29.7/test/Hpack/Syntax/DependencySpec.hs 2018-08-14 05:36:12.000000000 +0200 @@ -1,7 +1,5 @@ {-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE OverloadedLists #-} -{-# LANGUAGE FlexibleContexts #-} -{-# LANGUAGE ConstraintKinds #-} module Hpack.Syntax.DependencySpec (spec) where import Helper @@ -9,6 +7,7 @@ import Data.Aeson.Config.FromValueSpec (shouldDecodeTo, shouldDecodeTo_) import Data.Aeson.Config.FromValue +import Hpack.Syntax.DependencyVersion import Hpack.Syntax.Dependency left :: String -> Result Dependencies
