Hello community,

here is the log from the commit of package ghc-cabal-helper for 
openSUSE:Factory checked in at 2015-12-29 12:58:50
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
Comparing /work/SRC/openSUSE:Factory/ghc-cabal-helper (Old)
 and      /work/SRC/openSUSE:Factory/.ghc-cabal-helper.new (New)
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++

Package is "ghc-cabal-helper"

Changes:
--------
--- /work/SRC/openSUSE:Factory/ghc-cabal-helper/ghc-cabal-helper.changes        
2015-11-02 12:55:56.000000000 +0100
+++ /work/SRC/openSUSE:Factory/.ghc-cabal-helper.new/ghc-cabal-helper.changes   
2015-12-29 12:58:51.000000000 +0100
@@ -1,0 +2,5 @@
+Wed Dec 23 16:04:07 UTC 2015 - mimi...@gmail.com
+
+- update to 0.6.2.0
+
+-------------------------------------------------------------------

Old:
----
  cabal-helper-0.6.1.0.tar.gz

New:
----
  cabal-helper-0.6.2.0.tar.gz

++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++

Other differences:
------------------
++++++ ghc-cabal-helper.spec ++++++
--- /var/tmp/diff_new_pack.SQhKxu/_old  2015-12-29 12:58:52.000000000 +0100
+++ /var/tmp/diff_new_pack.SQhKxu/_new  2015-12-29 12:58:52.000000000 +0100
@@ -19,7 +19,7 @@
 %global pkg_name cabal-helper
 %bcond_with tests
 Name:           ghc-cabal-helper
-Version:        0.6.1.0
+Version:        0.6.2.0
 Release:        0
 Summary:        Simple interface to some of Cabal's configuration state used 
by ghc-mod
 License:        AGPL-3.0+

++++++ cabal-helper-0.6.1.0.tar.gz -> cabal-helper-0.6.2.0.tar.gz ++++++
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/cabal-helper-0.6.1.0/CabalHelper/Common.hs 
new/cabal-helper-0.6.2.0/CabalHelper/Common.hs
--- old/cabal-helper-0.6.1.0/CabalHelper/Common.hs      2015-10-05 
17:36:12.000000000 +0200
+++ new/cabal-helper-0.6.2.0/CabalHelper/Common.hs      2015-10-30 
17:25:27.000000000 +0100
@@ -95,3 +95,12 @@
     if takeFileName p == takeExtension p
       then "" -- just ".cabal" is not a valid cabal file
       else takeExtension p
+
+replace :: String -> String -> String -> String
+replace n r hs' = go "" hs'
+ where
+   go acc h
+       | take (length n) h == n =
+           reverse acc ++ r ++ drop (length n) h
+   go acc (h:hs) = go (h:acc) hs
+   go acc [] = reverse acc
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/cabal-helper-0.6.1.0/CabalHelper/Compile.hs 
new/cabal-helper-0.6.2.0/CabalHelper/Compile.hs
--- old/cabal-helper-0.6.1.0/CabalHelper/Compile.hs     2015-10-05 
17:36:12.000000000 +0200
+++ new/cabal-helper-0.6.2.0/CabalHelper/Compile.hs     2015-11-03 
14:27:21.000000000 +0100
@@ -34,6 +34,7 @@
 import System.Process
 import System.Exit
 import System.IO
+import System.IO.Temp
 import Prelude
 
 import Distribution.System (buildPlatform)
@@ -248,7 +249,17 @@
 \\n\
 \Installing Cabal %s ...\n" appdir sver sver sver
 
-  db <- createPkgDb opts ver
+  withSystemTempDirectory "cabal-helper" $ \tmpdir -> do
+    let
+        mpatch :: Maybe (FilePath -> IO ())
+        mpatch = snd <$> find ((ver`elem`) . fst) patchyCabalVersions
+    msrcdir <- sequenceA $ unpackPatchedCabal opts ver tmpdir <$> mpatch
+    db <- createPkgDb opts ver
+    cabalInstall opts db ver msrcdir
+    return db
+
+cabalInstall :: Options -> FilePath -> Version -> Maybe FilePath -> IO ()
+cabalInstall opts db ver msrcdir = do
   cabalInstallVer <- cabalInstallVersion opts
   cabal_opts <- return $ concat
       [
@@ -264,15 +275,77 @@
         , if ghcPkgProgram opts /= ghcPkgProgram defaultOptions
             then [ "--with-ghc-pkg=" ++ ghcPkgProgram opts ]
             else []
-        , [ "install", "Cabal", "--constraint"
-          , "Cabal == " ++ showVersion ver ]
+        ,
+          case msrcdir of
+            Nothing ->
+                [ "install", "Cabal"
+                , "--constraint", "Cabal == " ++ showVersion ver
+                ]
+            Just srcdir ->
+                [ "install", srcdir ]
       ]
 
-  vLog opts $ intercalate " " $ map (("\""++) . (++"\"")) $ cabalProgram 
opts:cabal_opts
+  vLog opts $ intercalate " "
+            $ map (("\""++) . (++"\""))
+            $ cabalProgram opts:cabal_opts
 
   callProcessStderr (Just "/") (cabalProgram opts) cabal_opts
   hPutStrLn stderr "done"
-  return db
+
+patchyCabalVersions :: [([Version], FilePath -> IO ())]
+patchyCabalVersions = [
+    ( [ Version [1,18,1] [] ]
+    , fixArrayConstraint
+    ),
+    ( [ Version [1,18,0] [] ]
+    , \dir -> do
+        fixArrayConstraint dir
+        fixOrphanInstance dir
+    )
+  ]
+ where
+   fixArrayConstraint dir = do
+     let cabalFile    = dir </> "Cabal.cabal"
+         cabalFileTmp = cabalFile ++ ".tmp"
+
+     cf <- readFile cabalFile
+     writeFile cabalFileTmp $ replace "&& < 0.5" "&& < 0.6" cf
+     renameFile cabalFileTmp cabalFile
+
+   fixOrphanInstance dir = do
+     let versionFile    = dir </> "Distribution/Version.hs"
+         versionFileTmp = versionFile ++ ".tmp"
+
+     let languagePragma =
+           "{-# LANGUAGE DeriveDataTypeable, StandaloneDeriving #-}"
+         languagePragmaCPP =
+           "{-# LANGUAGE CPP, DeriveDataTypeable, StandaloneDeriving #-}"
+
+         derivingDataVersion =
+           "deriving instance Data Version"
+         derivingDataVersionCPP = unlines [
+             "#if __GLASGOW_HASKELL__ < 707",
+             derivingDataVersion,
+             "#endif"
+           ]
+
+     vf <- readFile versionFile
+     writeFile versionFileTmp
+       $ replace derivingDataVersion derivingDataVersionCPP
+       $ replace languagePragma languagePragmaCPP vf
+
+     renameFile versionFileTmp versionFile
+
+unpackPatchedCabal ::
+    Options -> Version -> FilePath -> (FilePath -> IO ()) -> IO FilePath
+unpackPatchedCabal opts cabalVer tmpdir patch = do
+  let cabal = "Cabal-" ++ showVersion cabalVer
+      dir = tmpdir </> cabal
+
+  callProcessStderr (Just tmpdir) (cabalProgram opts) [ "get", cabal ]
+
+  patch dir
+  return dir
 
 errorInstallCabal :: Version -> FilePath -> a
 errorInstallCabal cabalVer _distdir = panic $ printf "\
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/cabal-helper-0.6.1.0/CabalHelper/Licenses.hs 
new/cabal-helper-0.6.2.0/CabalHelper/Licenses.hs
--- old/cabal-helper-0.6.1.0/CabalHelper/Licenses.hs    2015-10-05 
17:36:12.000000000 +0200
+++ new/cabal-helper-0.6.2.0/CabalHelper/Licenses.hs    2015-10-30 
20:09:31.000000000 +0100
@@ -4,80 +4,85 @@
 -- Copyright (c) 2014, Jasper Van der Jeugt <m...@jaspervdj.be>
 
 
--------------------------------------------------------------------------------
-import           Control.Arrow                      ((***), (&&&))
-import           Control.Monad                      (forM_, unless)
-import           Data.List                          (foldl', sort)
-import           Data.Maybe                         (catMaybes)
-import           Data.Version                       (Version)
-import           Data.Set                           (Set)
-import qualified Data.Set                           as Set
-import           Distribution.InstalledPackageInfo  (InstalledPackageInfo)
-import qualified Distribution.InstalledPackageInfo  as InstalledPackageInfo
-import qualified Distribution.License               as Cabal
-import qualified Distribution.Package               as Cabal
-import qualified Distribution.Simple.Configure      as Cabal
-import qualified Distribution.Simple.LocalBuildInfo as Cabal
-import qualified Distribution.Simple.PackageIndex   as Cabal
-import qualified Distribution.Text                  as Cabal
-import           System.Directory                   (getDirectoryContents)
-import           System.Exit                        (exitFailure)
-import           System.FilePath                    (takeExtension)
-import           System.IO                          (hPutStrLn, stderr)
-
+import Control.Arrow ((***), (&&&))
+import Control.Monad (forM_, unless)
+import Data.List (foldl', sort)
+import Data.Maybe (catMaybes)
+import Data.Version (Version)
+import Data.Set (Set)
+import qualified Data.Set as Set
+import System.Directory (getDirectoryContents)
+import System.Exit (exitFailure)
+import System.FilePath (takeExtension)
+import System.IO (hPutStrLn, stderr)
+
+import Distribution.InstalledPackageInfo
+import Distribution.License
+import Distribution.Package
+import Distribution.Simple.Configure
+import Distribution.Simple.LocalBuildInfo
+import Distribution.Simple.PackageIndex
+import Distribution.Text
 
--------------------------------------------------------------------------------
 
 #if CABAL_MAJOR == 1 && CABAL_MINOR >  22
-type PackageIndex a = Cabal.PackageIndex 
(InstalledPackageInfo.InstalledPackageInfo)
+type CPackageIndex a = PackageIndex (InstalledPackageInfo)
 #elif CABAL_MAJOR == 1 && CABAL_MINOR >= 22
-type PackageIndex a = Cabal.PackageIndex 
(InstalledPackageInfo.InstalledPackageInfo_ a)
+type CPackageIndex a = PackageIndex (InstalledPackageInfo_ a)
+#else
+type CPackageIndex a = PackageIndex
+#endif
+
+#if CABAL_MAJOR == 1 && CABAL_MINOR > 22
+type CInstalledPackageId = ComponentId
+lookupInstalledPackageId = lookupComponentId
 #else
-type PackageIndex a = Cabal.PackageIndex
+type CInstalledPackageId = InstalledPackageId
 #endif
 
 findTransitiveDependencies
-    :: PackageIndex a
-    -> Set Cabal.InstalledPackageId
-    -> Set Cabal.InstalledPackageId
+    :: CPackageIndex a
+    -> Set CInstalledPackageId
+    -> Set CInstalledPackageId
 findTransitiveDependencies pkgIdx set0 = go Set.empty (Set.toList set0)
   where
     go set []  = set
     go set (q : queue)
         | q `Set.member` set = go set queue
         | otherwise          =
-            case Cabal.lookupInstalledPackageId pkgIdx q of
+            case lookupInstalledPackageId pkgIdx q of
                 Nothing  ->
                     -- Not found can mean that the package still needs to be
                     -- installed (e.g. a component of the target cabal 
package).
                     -- We can ignore those.
                     go set queue
                 Just ipi ->
-                    go (Set.insert q set)
-                        (InstalledPackageInfo.depends ipi ++ queue)
+                    go (Set.insert q set) 
(Distribution.InstalledPackageInfo.depends ipi ++ queue)
 
 
 
--------------------------------------------------------------------------------
 getDependencyInstalledPackageIds
-    :: Cabal.LocalBuildInfo -> Set Cabal.InstalledPackageId
+    :: LocalBuildInfo -> Set InstalledPackageId
 getDependencyInstalledPackageIds lbi =
-    findTransitiveDependencies (Cabal.installedPkgs lbi) $
-      Set.fromList $ map fst $ Cabal.externalPackageDeps lbi
+    findTransitiveDependencies (installedPkgs lbi) $
+      Set.fromList $ map fst $ externalPackageDeps lbi
 
 
--------------------------------------------------------------------------------
 getDependencyInstalledPackageInfos
-    :: Cabal.LocalBuildInfo -> [InstalledPackageInfo]
+    :: LocalBuildInfo -> [InstalledPackageInfo]
 getDependencyInstalledPackageInfos lbi = catMaybes $
-    map (Cabal.lookupInstalledPackageId pkgIdx) $
+    map (lookupInstalledPackageId pkgIdx) $
     Set.toList (getDependencyInstalledPackageIds lbi)
   where
-    pkgIdx = Cabal.installedPkgs lbi
+    pkgIdx = installedPkgs lbi
 
 
 
--------------------------------------------------------------------------------
 groupByLicense
     :: [InstalledPackageInfo]
-    -> [(Cabal.License, [InstalledPackageInfo])]
+    -> [(License, [InstalledPackageInfo])]
 groupByLicense = foldl'
-    (\assoc ipi -> insert (InstalledPackageInfo.license ipi) ipi assoc) []
+    (\assoc ipi -> insert (license ipi) ipi assoc) []
   where
     -- 'Cabal.License' doesn't have an 'Ord' instance so we need to use an
     -- association list instead of 'Map'. The number of licenses probably won't
@@ -91,12 +96,12 @@
 
 
--------------------------------------------------------------------------------
 displayDependencyLicenseList
-    :: [(Cabal.License, [InstalledPackageInfo])]
+    :: [(License, [InstalledPackageInfo])]
     -> [(String, [(String, Version)])]
 displayDependencyLicenseList =
-    map (Cabal.display *** map (getName &&& getVersion))
+    map (display *** map (getName &&& getVersion))
   where
     getName =
-        Cabal.display . Cabal.pkgName . InstalledPackageInfo.sourcePackageId
+        display . pkgName . sourcePackageId
     getVersion =
-        Cabal.pkgVersion . InstalledPackageInfo.sourcePackageId
+        pkgVersion . sourcePackageId
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/cabal-helper-0.6.1.0/CabalHelper/Main.hs 
new/cabal-helper-0.6.2.0/CabalHelper/Main.hs
--- old/cabal-helper-0.6.1.0/CabalHelper/Main.hs        2015-10-05 
17:36:12.000000000 +0200
+++ new/cabal-helper-0.6.2.0/CabalHelper/Main.hs        2015-10-30 
19:38:32.000000000 +0100
@@ -47,8 +47,12 @@
                                            componentBuildInfo,
                                            externalPackageDeps,
                                            withComponentsLBI,
-                                           withLibLBI,
-                                           inplacePackageId)
+                                           withLibLBI)
+#if CABAL_MAJOR == 1 && CABAL_MINOR <= 22
+import Distribution.Simple.LocalBuildInfo (inplacePackageId)
+#else
+import Distribution.Simple.LocalBuildInfo (localComponentId)
+#endif
 
 import Distribution.Simple.GHC (componentGhcOptions)
 import Distribution.Simple.Program.GHC (GhcOptions(..), renderGhcOptions)
@@ -408,7 +412,10 @@
     libbi = libBuildInfo lib
     liboutdir = componentOutDir lbi (CLib lib)
     libopts = (componentGhcOptions normal lbi libbi libclbi liboutdir) {
-                                    ghcOptPackageDBs = []
+                                      ghcOptPackageDBs = []
+#if CABAL_MAJOR == 1 && CABAL_MINOR > 22
+                                    , ghcOptComponentId = NoFlag
+#endif
                                   }
 
     (ideps, deps) = partition isInplaceDep (componentPackageDeps clbi)
@@ -419,7 +426,12 @@
 
  where
    isInplaceDep :: (InstalledPackageId, PackageId) -> Bool
+#if CABAL_MAJOR == 1 && CABAL_MINOR <= 22
    isInplaceDep (ipid, pid) = inplacePackageId pid == ipid
+#else
+   isInplaceDep (ipid, pid) = localComponentId lbi == ipid
+#endif
+
 
 #if CABAL_MAJOR == 1 && CABAL_MINOR >= 22
 -- >= 1.22 uses NubListR
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/cabal-helper-0.6.1.0/cabal-helper.cabal 
new/cabal-helper-0.6.2.0/cabal-helper.cabal
--- old/cabal-helper-0.6.1.0/cabal-helper.cabal 2015-10-05 17:36:12.000000000 
+0200
+++ new/cabal-helper-0.6.2.0/cabal-helper.cabal 2015-11-19 13:22:02.000000000 
+0100
@@ -1,5 +1,5 @@
 name:                cabal-helper
-version:             0.6.1.0
+version:             0.6.2.0
 synopsis:            Simple interface to some of Cabal's configuration state 
used by ghc-mod
 description:
     @cabal-helper@ provides a library which wraps the internal use of
@@ -102,4 +102,4 @@
                      , bytestring
                      , utf8-string
                      , template-haskell
-                     , temporary
\ No newline at end of file
+                     , temporary
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/cabal-helper-0.6.1.0/tests/Spec.hs 
new/cabal-helper-0.6.2.0/tests/Spec.hs
--- old/cabal-helper-0.6.1.0/tests/Spec.hs      2015-10-05 17:36:12.000000000 
+0200
+++ new/cabal-helper-0.6.2.0/tests/Spec.hs      2015-11-03 14:27:21.000000000 
+0100
@@ -16,13 +16,13 @@
 main :: IO ()
 main = do
   flip (setEnv "HOME") True =<< fromMaybe "/tmp" <$> lookupEnv "TMPDIR"
-  writeAutogenFiles readProcess "." "./dist"
+  _ <- rawSystem "cabal" ["update"]
 
-  _ <- system "cabal update"
+  writeAutogenFiles readProcess "." "./dist"
 
   let vers :: [(Version, [Version])]
       vers = map (parseVer *** map parseVer) [
-               ("7.4", [ "1.14.0"
+               ("7.4", [ -- "1.14.0" -- not supported at runtime
                        ]),
 
                ("7.6", [ "1.16.0"
@@ -32,10 +32,10 @@
                        ]),
 
                ("7.8", [
---                         "1.18.0"
---                       , "1.18.1"
-                         "1.18.1.1"
---                       , "1.18.1.2"
+                         "1.18.0"
+                       , "1.18.1"
+                       , "1.18.1.1"
+                       , "1.18.1.2"
                        , "1.18.1.3"
                        , "1.18.1.4"
                        , "1.18.1.5"
@@ -57,14 +57,14 @@
                        ])
              ]
 
-  ghcVer <- ghcVersion defaultOptions
+  ghcVer <- majorVer <$> ghcVersion defaultOptions
 
   let cabalVers = concat $ map snd $ dropWhile ((<ghcVer) . fst)  vers
 
   rvs <- mapM compilePrivatePkgDb cabalVers
 
   if any isLeft' rvs
-     then exitFailure
+     then print rvs >> exitFailure
      else exitSuccess
  where
    isLeft' (Left _) = True
@@ -72,6 +72,7 @@
 
 compilePrivatePkgDb :: Version -> IO (Either ExitCode FilePath)
 compilePrivatePkgDb cabalVer = do
+    _ <- rawSystem "rm" [ "-r", "/tmp/.ghc-mod" ]
     db <- installCabal defaultOptions cabalVer `E.catch`
           \(SomeException _) -> errorInstallCabal cabalVer "dist"
     compileWithPkg "." (Just db) cabalVer


Reply via email to