[Git][haskell-team/DHG_packages][experimental] 5 commits: haskell-parsec-numbers: Fix capitalization error in X-Description

Ilias Tsitsimpis gitlab at salsa.debian.org
Fri Sep 28 13:12:47 BST 2018


Ilias Tsitsimpis pushed to branch experimental at Debian Haskell Group / DHG_packages


Commits:
607c5564 by Aggelos Avgerinos at 2018-09-13T10:29:32Z
haskell-parsec-numbers: Fix capitalization error in X-Description

- - - - -
b1aa16e5 by Aggelos Avgerinos at 2018-09-13T10:51:21Z
haskell-parsec-numbers: Add explanation for LICENSE in d/copyright

- - - - -
5195d758 by Ilias Tsitsimpis at 2018-09-26T09:09:39Z
Merge branch 'experimental'

- - - - -
0d47dfa9 by Ilias Tsitsimpis at 2018-09-26T09:10:51Z
ghc: Upload version 8.4.3+dfsg1-2 to unstable

- - - - -
585896a1 by Ilias Tsitsimpis at 2018-09-26T09:50:48Z
ghc: New upstream version (v8.6.1)

- - - - -


20 changed files:

- p/ghc/debian/changelog
- p/ghc/debian/clean
- p/ghc/debian/patches/ARM-VFPv3D16
- p/ghc/debian/patches/add_-latomic_to_ghc-prim
- p/ghc/debian/patches/bsymbolic-only-for-registerised.patch
- p/ghc/debian/patches/buildpath-abi-stability.patch
- p/ghc/debian/patches/e175aaf6918bb2b497b83618dc4c270a0d231a1c.patch
- − p/ghc/debian/patches/haddock-out-of-memory.patch
- − p/ghc/debian/patches/hurd.diff
- p/ghc/debian/patches/armel-revert-ghci-fixes.patch → p/ghc/debian/patches/llvm-arm-unknown-linux-gnueabi.patch
- − p/ghc/debian/patches/llvm-targets-Add-versioned-ARM-targets.patch
- p/ghc/debian/patches/no-missing-haddock-file-warning
- − p/ghc/debian/patches/risc-support.patch
- p/ghc/debian/patches/series
- p/ghc/debian/patches/use-debian-gen_contents_index
- − p/ghc/debian/patches/use-llvm-6.0.patch
- p/ghc/debian/patches/use-stage1-binaries-for-install.patch
- p/ghc/debian/patches/x32-use-native-x86_64-insn.patch
- p/haskell-parsec-numbers/debian/control
- p/haskell-parsec-numbers/debian/copyright


Changes:

=====================================
p/ghc/debian/changelog
=====================================
@@ -1,3 +1,16 @@
+ghc (8.6.1+dfsg1-1) experimental; urgency=medium
+
+  * New upstream version
+  * Update patches to apply cleanly
+
+ -- Ilias Tsitsimpis <iliastsi at debian.org>  Wed, 26 Sep 2018 12:44:06 +0300
+
+ghc (8.4.3+dfsg1-2) unstable; urgency=medium
+
+  * Upload to unstable
+
+ -- Ilias Tsitsimpis <iliastsi at debian.org>  Wed, 26 Sep 2018 12:10:37 +0300
+
 ghc (8.4.3+dfsg1-1) experimental; urgency=medium
 
   * Backport upstream commit 18cb44dfae3f.


=====================================
p/ghc/debian/clean
=====================================
@@ -1,4 +1,4 @@
-libraries/dph
-libraries/primitive
-libraries/vector
-libraries/random
+libraries/dph/
+libraries/primitive/
+libraries/vector/
+libraries/random/


=====================================
p/ghc/debian/patches/ARM-VFPv3D16
=====================================
@@ -10,7 +10,7 @@ Index: b/aclocal.m4
 ===================================================================
 --- a/aclocal.m4
 +++ b/aclocal.m4
-@@ -423,7 +423,7 @@ AC_DEFUN([GET_ARM_ISA],
+@@ -426,7 +426,7 @@ AC_DEFUN([GET_ARM_ISA],
                  )],
                  [changequote(, )dnl
                   ARM_ISA=ARMv7


=====================================
p/ghc/debian/patches/add_-latomic_to_ghc-prim
=====================================
@@ -1,128 +1,54 @@
-commit ec9aacf3eb2975fd302609163aaef429962ecd87
-Author: Moritz Angermann <moritz.angermann at gmail.com>
-Date:   Thu Feb 8 16:07:07 2018 +0800
+commit ce3897ffd6e7c8b8f36b8e920168bac8c7f836ae
+Author: Ilias Tsitsimpis <iliastsi at debian.org>
+Date:   Tue Sep 18 17:45:17 2018 +0200
 
-    adds -latomic to. ghc-prim
+    Fix check whether GCC supports __atomic_ builtins
     
-    Reviewers: bgamari, hvr
+    Summary:
+    C11 atomics are never used because:
+    
+    * The program used for checking whether GCC supports
+    __atomic_ builtins fails with the following error:
+    
+    ```
+      error: size mismatch in argument 2 of `__atomic_load`
+       int test(int *x) { int y; __atomic_load(&x, &y, __ATOMIC_SEQ_CST); return x; }
+    ```
+    
+    * There is a typo when checking if CONF_GCC_SUPPORTS__ATOMICS equals YES,
+    resulting in PRIM_CFLAGS and PRIM_EXTRA_LIBRARIES never being set.
+    
+    Reviewers: bgamari
     
     Reviewed By: bgamari
     
-    Subscribers: erikd, hvr, rwbarton, thomie, carter
+    Subscribers: rwbarton, erikd, carter
     
-    Differential Revision: https://phabricator.haskell.org/D4378
+    Differential Revision: https://phabricator.haskell.org/D5154
 
-    iliastsi: The original patch fails to correctly detect and use C11
-    atomics, so I modified it based on https://phabricator.haskell.org/D5154.
-
-Index: b/aclocal.m4
-===================================================================
---- a/aclocal.m4
-+++ b/aclocal.m4
-@@ -1284,24 +1284,6 @@ AC_SUBST(GccIsClang)
- rm -f conftest.txt
- ])
- 
--# FP_GCC_SUPPORTS__ATOMICS
--# ------------------------
--# Does gcc support the __atomic_* family of builtins?
--AC_DEFUN([FP_GCC_SUPPORTS__ATOMICS],
--[
--   AC_REQUIRE([AC_PROG_CC])
--   AC_MSG_CHECKING([whether GCC supports __atomic_ builtins])
--   echo 'int test(int *x) { int y; __atomic_load(&x, &y, __ATOMIC_SEQ_CST); return x; }' > conftest.c
--   if $CC -c conftest.c > /dev/null 2>&1; then
--       CONF_GCC_SUPPORTS__ATOMICS=YES
--       AC_MSG_RESULT([yes])
--   else
--       CONF_GCC_SUPPORTS__ATOMICS=NO
--       AC_MSG_RESULT([no])
--   fi
--   rm -f conftest.c conftest.o
--])
--
- # FP_GCC_SUPPORTS_NO_PIE
- # ----------------------
- # Does gcc support the -no-pie option? If so we should pass it to gcc when
-Index: b/configure.ac
-===================================================================
---- a/configure.ac
-+++ b/configure.ac
-@@ -714,11 +714,6 @@ FP_GCC_VERSION
- dnl ** See whether gcc supports -no-pie
- FP_GCC_SUPPORTS_NO_PIE
- 
--dnl ** Used to determine how to compile ghc-prim's atomics.c, used by
--dnl    unregisterised, Sparc, and PPC backends.
--FP_GCC_SUPPORTS__ATOMICS
--AC_DEFINE([HAVE_C11_ATOMICS], [$CONF_GCC_SUPPORTS__ATOMICS], [Does GCC support __atomic primitives?])
--
- FP_GCC_EXTRA_FLAGS
- 
- dnl ** look to see if we have a C compiler using an llvm back end.
-Index: b/libraries/ghc-prim/Setup.hs
-===================================================================
---- a/libraries/ghc-prim/Setup.hs
-+++ b/libraries/ghc-prim/Setup.hs
-@@ -18,7 +18,7 @@ import System.Exit
- import System.Directory
- 
- main :: IO ()
--main = do let hooks = simpleUserHooks {
-+main = do let hooks = autoconfUserHooks {
-                   regHook = addPrimModule
-                           $ regHook simpleUserHooks,
-                   buildHook = build_primitive_sources
 Index: b/libraries/ghc-prim/aclocal.m4
 ===================================================================
---- /dev/null
+--- a/libraries/ghc-prim/aclocal.m4
 +++ b/libraries/ghc-prim/aclocal.m4
-@@ -0,0 +1,17 @@
-+# FP_GCC_SUPPORTS__ATOMICS
-+# ------------------------
-+# Does gcc support the __atomic_* family of builtins?
-+AC_DEFUN([FP_GCC_SUPPORTS__ATOMICS],
-+[
-+   AC_REQUIRE([AC_PROG_CC])
-+   AC_MSG_CHECKING([whether GCC supports __atomic_ builtins])
+@@ -5,7 +5,7 @@ AC_DEFUN([FP_GCC_SUPPORTS__ATOMICS],
+ [
+    AC_REQUIRE([AC_PROG_CC])
+    AC_MSG_CHECKING([whether GCC supports __atomic_ builtins])
+-   echo 'int test(int *x) { int y; __atomic_load(&x, &y, __ATOMIC_SEQ_CST); return x; }' > conftest.c
 +   echo 'int test(int *x) { int y; __atomic_load(x, &y, __ATOMIC_SEQ_CST); return y; }' > conftest.c
-+   if $CC -c conftest.c > /dev/null 2>&1; then
-+       CONF_GCC_SUPPORTS__ATOMICS=YES
-+       AC_MSG_RESULT([yes])
-+   else
-+       CONF_GCC_SUPPORTS__ATOMICS=NO
-+       AC_MSG_RESULT([no])
-+   fi
-+   rm -f conftest.c conftest.o
-+])
+    if $CC -c conftest.c > /dev/null 2>&1; then
+        CONF_GCC_SUPPORTS__ATOMICS=YES
+        AC_MSG_RESULT([yes])
 Index: b/libraries/ghc-prim/configure.ac
 ===================================================================
---- /dev/null
+--- a/libraries/ghc-prim/configure.ac
 +++ b/libraries/ghc-prim/configure.ac
-@@ -0,0 +1,18 @@
-+AC_INIT([ghc-prim package], [2.1], [glasgow-haskell-bugs at haskell.org], [ghc-prim])
-+
-+AC_CONFIG_SRCDIR([ghc-prim.cabal])
-+
-+# -------------------------------------------------------------------------
-+dnl ** Used to determine how to compile ghc-prim's atomics.c, used by
-+dnl    unregisterised, Sparc, and PPC backends.
-+FP_GCC_SUPPORTS__ATOMICS
-+AC_DEFINE([HAVE_C11_ATOMICS], [$CONF_GCC_SUPPORTS__ATOMICS], [Does GCC support __atomic primitives?])
-+
+@@ -8,7 +8,7 @@ dnl    unregisterised, Sparc, and PPC ba
+ FP_GCC_SUPPORTS__ATOMICS
+ AC_DEFINE([HAVE_C11_ATOMICS], [$CONF_GCC_SUPPORTS__ATOMICS], [Does GCC support __atomic primitives?])
+ 
+-if test "x$CONF_GCC_SUPPORTS__ATOMICS" = YES
 +if test "$CONF_GCC_SUPPORTS__ATOMICS" = "YES"
-+then PRIM_CFLAGS=-DHAVE_C11_ATOMICS
-+     PRIM_EXTRA_LIBRARIES=atomic
-+fi
-+AC_SUBST([PRIM_CFLAGS])
-+AC_SUBST([PRIM_EXTRA_LIBRARIES])
-+AC_CONFIG_FILES([ghc-prim.buildinfo])
-+AC_OUTPUT
-Index: b/libraries/ghc-prim/ghc-prim.buildinfo.in
-===================================================================
---- /dev/null
-+++ b/libraries/ghc-prim/ghc-prim.buildinfo.in
-@@ -0,0 +1,2 @@
-+cc-options: @PRIM_CFLAGS@
-+extra-libraries: @PRIM_EXTRA_LIBRARIES@
-\ No newline at end of file
+ then PRIM_CFLAGS=-DHAVE_C11_ATOMICS
+      PRIM_EXTRA_LIBRARIES=atomic
+ fi


=====================================
p/ghc/debian/patches/bsymbolic-only-for-registerised.patch
=====================================
@@ -28,7 +28,7 @@ Index: b/compiler/main/SysTools.hs
 ===================================================================
 --- a/compiler/main/SysTools.hs
 +++ b/compiler/main/SysTools.hs
-@@ -534,9 +534,12 @@ linkDynLib dflags0 o_files dep_packages
+@@ -548,9 +548,12 @@ linkDynLib dflags0 o_files dep_packages
              -------------------------------------------------------------------
  
              let output_fn = case o_file of { Just s -> s; Nothing -> "a.out"; }
@@ -43,7 +43,7 @@ Index: b/compiler/main/SysTools.hs
  
              runLink dflags (
                      map Option verbFlags
-@@ -593,3 +596,27 @@ getFrameworkOpts dflags platform
+@@ -607,3 +610,27 @@ getFrameworkOpts dflags platform
      -- reverse because they're added in reverse order from the cmd line:
      framework_opts = concat [ ["-framework", fw]
                              | fw <- reverse frameworks ]


=====================================
p/ghc/debian/patches/buildpath-abi-stability.patch
=====================================
@@ -4,7 +4,7 @@ Index: b/compiler/iface/MkIface.hs
 ===================================================================
 --- a/compiler/iface/MkIface.hs
 +++ b/compiler/iface/MkIface.hs
-@@ -689,7 +689,7 @@ addFingerprints hsc_env mb_old_fingerpri
+@@ -702,7 +702,7 @@ addFingerprints hsc_env mb_old_fingerpri
     iface_hash <- computeFingerprint putNameLiterally
                        (mod_hash,
                         ann_fn (mkVarOcc "module"),  -- See mkIfaceAnnCache
@@ -13,7 +13,7 @@ Index: b/compiler/iface/MkIface.hs
                         sorted_deps,
                         mi_hpc iface0)
  
-@@ -724,6 +724,9 @@ addFingerprints hsc_env mb_old_fingerpri
+@@ -737,6 +737,9 @@ addFingerprints hsc_env mb_old_fingerpri
      (non_orph_fis,   orph_fis)   = mkOrphMap ifFamInstOrph (mi_fam_insts iface0)
      fix_fn = mi_fix_fn iface0
      ann_fn = mkIfaceAnnCache (mi_anns iface0)


=====================================
p/ghc/debian/patches/e175aaf6918bb2b497b83618dc4c270a0d231a1c.patch
=====================================
@@ -43,7 +43,7 @@ Index: b/rts/posix/OSMem.c
 ===================================================================
 --- a/rts/posix/OSMem.c
 +++ b/rts/posix/OSMem.c
-@@ -435,6 +435,8 @@ osTryReserveHeapMemory (W_ len, void *hi
+@@ -476,6 +476,8 @@ osTryReserveHeapMemory (W_ len, void *hi
      void *base, *top;
      void *start, *end;
  
@@ -52,7 +52,7 @@ Index: b/rts/posix/OSMem.c
      /* We try to allocate len + MBLOCK_SIZE,
         because we need memory which is MBLOCK_SIZE aligned,
         and then we discard what we don't need */
-@@ -502,6 +504,8 @@ void *osReserveHeapMemory(void *startAdd
+@@ -552,6 +554,8 @@ void *osReserveHeapMemory(void *startAdd
  
      attempt = 0;
      while (1) {


=====================================
p/ghc/debian/patches/haddock-out-of-memory.patch deleted
=====================================
@@ -1,248 +0,0 @@
-commit 18cb44dfae3f0847447da33c9d7a25d2709d838f
-Author: Alec Theriault <alec.theriault at gmail.com>
-Date:   Tue Aug 21 16:03:40 2018 -0400
-
-    Explicitly tell 'getNameToInstances' mods to load
-    
-    Calculating which modules to load based on the InteractiveContext means
-    maintaining a potentially very large GblRdrEnv.
-    
-    In Haddock's case, it is much cheaper (from a memory perspective) to
-    just keep track of which modules interfaces we want loaded then hand
-    these off explicitly to 'getNameToInstancesIndex'.
-    
-    Bumps haddock submodule (commit 40eb5aabed0ae)
-    
-    Reviewers: alexbiehl, bgamari
-    
-    Reviewed By: alexbiehl
-    
-    Subscribers: rwbarton, thomie, carter
-    
-    Differential Revision: https://phabricator.haskell.org/D5003
-    
-    (cherry picked from commit c971e1193fa44bb507d1806d5bb61768670dc912)
-
-Index: b/compiler/main/GHC.hs
-===================================================================
---- a/compiler/main/GHC.hs
-+++ b/compiler/main/GHC.hs
-@@ -117,6 +117,7 @@ module GHC (
-         showModule,
-         moduleIsBootOrNotObjectLinkable,
-         getNameToInstancesIndex,
-+        getNameToInstancesIndex2,
- 
-         -- ** Inspecting types and kinds
-         exprType, TcRnExprMode(..),
-@@ -297,7 +298,8 @@ import HscMain
- import GhcMake
- import DriverPipeline   ( compileOne' )
- import GhcMonad
--import TcRnMonad        ( finalSafeMode, fixSafeInstances )
-+import TcRnMonad        ( finalSafeMode, fixSafeInstances, initIfaceTcRn )
-+import LoadIface        ( loadSysInterface )
- import TcRnTypes
- import Packages
- import NameSet
-@@ -1247,10 +1249,27 @@ getNameToInstancesIndex :: GhcMonad m
-   => [Module]  -- ^ visible modules. An orphan instance will be returned if and
-                -- only it is visible from at least one module in the list.
-   -> m (Messages, Maybe (NameEnv ([ClsInst], [FamInst])))
--getNameToInstancesIndex visible_mods = do
-+getNameToInstancesIndex visible_mods =
-+  getNameToInstancesIndex2 visible_mods Nothing
-+
-+-- | Retrieve all type and family instances in the environment, indexed
-+-- by 'Name'. Each name's lists will contain every instance in which that name
-+-- is mentioned in the instance head.
-+getNameToInstancesIndex2 :: GhcMonad m
-+  => [Module]        -- ^ visible modules. An orphan instance will be returned
-+                     -- if it is visible from at least one module in the list.
-+  -> Maybe [Module]  -- ^ modules to load. If this is not specified, we load
-+                     -- modules for everything that is in scope unqualified.
-+  -> m (Messages, Maybe (NameEnv ([ClsInst], [FamInst])))
-+getNameToInstancesIndex2 visible_mods mods_to_load = do
-   hsc_env <- getSession
-   liftIO $ runTcInteractive hsc_env $
--    do { loadUnqualIfaces hsc_env (hsc_IC hsc_env)
-+    do { case mods_to_load of
-+           Nothing -> loadUnqualIfaces hsc_env (hsc_IC hsc_env)
-+           Just mods ->
-+             let doc = text "Need interface for reporting instances in scope"
-+             in initIfaceTcRn $ mapM_ (loadSysInterface doc) mods
-+
-        ; InstEnvs {ie_global, ie_local} <- tcGetInstEnvs
-        ; let visible_mods' = mkModuleSet visible_mods
-        ; (pkg_fie, home_fie) <- tcGetFamInstEnvs
-Index: b/utils/haddock/haddock-api/src/Haddock/Interface.hs
-===================================================================
---- a/utils/haddock/haddock-api/src/Haddock/Interface.hs
-+++ b/utils/haddock/haddock-api/src/Haddock/Interface.hs
-@@ -1,4 +1,4 @@
--{-# LANGUAGE CPP, OverloadedStrings #-}
-+{-# LANGUAGE CPP, OverloadedStrings, BangPatterns #-}
- -----------------------------------------------------------------------------
- -- |
- -- Module      :  Haddock.Interface
-@@ -51,6 +51,7 @@ import System.Directory
- import System.FilePath
- import Text.Printf
- 
-+import Module (mkModuleSet, emptyModuleSet, unionModuleSet, ModuleSet)
- import Digraph
- import DynFlags hiding (verbosity)
- import Exception
-@@ -59,7 +60,9 @@ import HscTypes
- import FastString (unpackFS)
- import MonadUtils (liftIO)
- import TcRnTypes (tcg_rdr_env)
--import RdrName (plusGlobalRdrEnv)
-+import Name (nameIsFromExternalPackage, nameOccName)
-+import OccName (isTcOcc)
-+import RdrName (unQualOK, gre_name, globalRdrEnvElts)
- import ErrUtils (withTiming)
- 
- #if defined(mingw32_HOST_OS)
-@@ -87,7 +90,7 @@ processModules verbosity modules flags e
-   out verbosity verbose "Creating interfaces..."
-   let instIfaceMap =  Map.fromList [ (instMod iface, iface) | ext <- extIfaces
-                                    , iface <- ifInstalledIfaces ext ]
--  interfaces <- createIfaces0 verbosity modules flags instIfaceMap
-+  (interfaces, ms) <- createIfaces0 verbosity modules flags instIfaceMap
- 
-   let exportedNames =
-         Set.unions $ map (Set.fromList . ifaceExports) $
-@@ -96,7 +99,7 @@ processModules verbosity modules flags e
-   out verbosity verbose "Attaching instances..."
-   interfaces' <- {-# SCC attachInstances #-}
-                  withTiming getDynFlags "attachInstances" (const ()) $ do
--                   attachInstances (exportedNames, mods) interfaces instIfaceMap
-+                   attachInstances (exportedNames, mods) interfaces instIfaceMap ms
- 
-   out verbosity verbose "Building cross-linking environment..."
-   -- Combine the link envs of the external packages into one
-@@ -120,7 +123,7 @@ processModules verbosity modules flags e
- --------------------------------------------------------------------------------
- 
- 
--createIfaces0 :: Verbosity -> [String] -> [Flag] -> InstIfaceMap -> Ghc [Interface]
-+createIfaces0 :: Verbosity -> [String] -> [Flag] -> InstIfaceMap -> Ghc ([Interface], ModuleSet)
- createIfaces0 verbosity modules flags instIfaceMap =
-   -- Output dir needs to be set before calling depanal since depanal uses it to
-   -- compute output file names that are stored in the DynFlags of the
-@@ -150,43 +153,52 @@ createIfaces0 verbosity modules flags in
-       depanal [] False
- 
- 
--createIfaces :: Verbosity -> [Flag] -> InstIfaceMap -> ModuleGraph -> Ghc [Interface]
-+createIfaces :: Verbosity -> [Flag] -> InstIfaceMap -> ModuleGraph -> Ghc ([Interface], ModuleSet)
- createIfaces verbosity flags instIfaceMap mods = do
-   let sortedMods = flattenSCCs $ topSortModuleGraph False mods Nothing
-   out verbosity normal "Haddock coverage:"
--  (ifaces, _) <- foldM f ([], Map.empty) sortedMods
--  return (reverse ifaces)
-+  (ifaces, _, !ms) <- foldM f ([], Map.empty, emptyModuleSet) sortedMods
-+  return (reverse ifaces, ms)
-   where
--    f (ifaces, ifaceMap) modSummary = do
-+    f (ifaces, ifaceMap, !ms) modSummary = do
-       x <- {-# SCC processModule #-}
-            withTiming getDynFlags "processModule" (const ()) $ do
-              processModule verbosity modSummary flags ifaceMap instIfaceMap
-       return $ case x of
--        Just iface -> (iface:ifaces, Map.insert (ifaceMod iface) iface ifaceMap)
--        Nothing    -> (ifaces, ifaceMap) -- Boot modules don't generate ifaces.
-+        Just (iface, ms') -> ( iface:ifaces
-+                             , Map.insert (ifaceMod iface) iface ifaceMap
-+                             , unionModuleSet ms ms' )
-+        Nothing           -> ( ifaces
-+                             , ifaceMap
-+                             , ms ) -- Boot modules don't generate ifaces.
- 
- 
--processModule :: Verbosity -> ModSummary -> [Flag] -> IfaceMap -> InstIfaceMap -> Ghc (Maybe Interface)
-+processModule :: Verbosity -> ModSummary -> [Flag] -> IfaceMap -> InstIfaceMap -> Ghc (Maybe (Interface, ModuleSet))
- processModule verbosity modsum flags modMap instIfaceMap = do
-   out verbosity verbose $ "Checking module " ++ moduleString (ms_mod modsum) ++ "..."
-   tm <- {-# SCC "parse/typecheck/load" #-} loadModule =<< typecheckModule =<< parseModule modsum
- 
--  -- We need to modify the interactive context's environment so that when
--  -- Haddock later looks for instances, it also looks in the modules it
--  -- encountered while typechecking.
--  --
--  -- See https://github.com/haskell/haddock/issues/469.
--  hsc_env at HscEnv{ hsc_IC = old_IC } <- getSession
--  let new_rdr_env = tcg_rdr_env . fst . GHC.tm_internals_ $ tm
--  setSession hsc_env{ hsc_IC = old_IC {
--    ic_rn_gbl_env = ic_rn_gbl_env old_IC `plusGlobalRdrEnv` new_rdr_env
--  } }
--
-   if not $ isBootSummary modsum then do
-     out verbosity verbose "Creating interface..."
-     (interface, msg) <- {-# SCC createIterface #-}
-                         withTiming getDynFlags "createInterface" (const ()) $ do
-                           runWriterGhc $ createInterface tm flags modMap instIfaceMap
-+
-+    -- We need to modify the interactive context's environment so that when
-+    -- Haddock later looks for instances, it also looks in the modules it
-+    -- encountered while typechecking.
-+    --
-+    -- See https://github.com/haskell/haddock/issues/469.
-+    hsc_env <- getSession
-+    let new_rdr_env = tcg_rdr_env . fst . GHC.tm_internals_ $ tm
-+        this_pkg = thisPackage (hsc_dflags hsc_env)
-+        !mods = mkModuleSet [ nameModule name
-+                            | gre <- globalRdrEnvElts new_rdr_env
-+                            , let name = gre_name gre
-+                            , nameIsFromExternalPackage this_pkg name
-+                            , isTcOcc (nameOccName name)   -- Types and classes only
-+                            , unQualOK gre ]               -- In scope unqualified
-+
-     liftIO $ mapM_ putStrLn msg
-     dflags <- getDynFlags
-     let (haddockable, haddocked) = ifaceHaddockCoverage interface
-@@ -220,7 +232,7 @@ processModule verbosity modsum flags mod
-         unless header $ out verbosity normal "    Module header"
-         mapM_ (out verbosity normal . ("    " ++)) undocumentedExports
-     interface' <- liftIO $ evaluate interface
--    return (Just interface')
-+    return (Just (interface', mods))
-   else
-     return Nothing
- 
-Index: b/utils/haddock/haddock-api/src/Haddock/Interface/AttachInstances.hs
-===================================================================
---- a/utils/haddock/haddock-api/src/Haddock/Interface/AttachInstances.hs
-+++ b/utils/haddock/haddock-api/src/Haddock/Interface/AttachInstances.hs
-@@ -1,4 +1,4 @@
--{-# LANGUAGE CPP, MagicHash #-}
-+{-# LANGUAGE CPP, MagicHash, BangPatterns #-}
- {-# LANGUAGE TypeFamilies #-}
- -----------------------------------------------------------------------------
- -- |
-@@ -34,6 +34,7 @@ import FamInstEnv
- import FastString
- import GHC
- import InstEnv
-+import Module ( ModuleSet, moduleSetElts )
- import MonadUtils (liftIO)
- import Name
- import NameEnv
-@@ -51,11 +52,13 @@ type Modules = Set.Set Module
- type ExportInfo = (ExportedNames, Modules)
- 
- -- Also attaches fixities
--attachInstances :: ExportInfo -> [Interface] -> InstIfaceMap -> Ghc [Interface]
--attachInstances expInfo ifaces instIfaceMap = do
--  (_msgs, mb_index) <- getNameToInstancesIndex (map ifaceMod ifaces)
-+attachInstances :: ExportInfo -> [Interface] -> InstIfaceMap -> ModuleSet -> Ghc [Interface]
-+attachInstances expInfo ifaces instIfaceMap mods = do
-+  (_msgs, mb_index) <- getNameToInstancesIndex2 (map ifaceMod ifaces) mods'
-   mapM (attach $ fromMaybe emptyNameEnv mb_index) ifaces
-   where
-+    mods' = Just (moduleSetElts mods)
-+
-     -- TODO: take an IfaceMap as input
-     ifaceMap = Map.fromList [ (ifaceMod i, i) | i <- ifaces ]
- 


=====================================
p/ghc/debian/patches/hurd.diff deleted
=====================================
@@ -1,43 +0,0 @@
-Provided by “Pino” via Samuel Thibault. Not yet pushed upstream.
-
-Index: b/aclocal.m4
-===================================================================
---- a/aclocal.m4
-+++ b/aclocal.m4
-@@ -272,12 +272,15 @@ AC_DEFUN([FPTOOLS_SET_HASKELL_PLATFORM_V
-         nto-qnx)
-             test -z "[$]2" || eval "[$]2=OSQNXNTO"
-             ;;
--        dragonfly|hpux|linuxaout|freebsd2|gnu|nextstep2|nextstep3|sunos4|ultrix)
-+        dragonfly|hpux|linuxaout|freebsd2|nextstep2|nextstep3|sunos4|ultrix)
-             test -z "[$]2" || eval "[$]2=OSUnknown"
-             ;;
-         aix)
-             test -z "[$]2" || eval "[$]2=OSAIX"
-             ;;
-+        gnu)
-+            test -z "[$]2" || eval "[$]2=OSHurd"
-+            ;;
-         *)
-             echo "Unknown OS '[$]1'"
-             exit 1
-Index: b/compiler/utils/Platform.hs
-===================================================================
---- a/compiler/utils/Platform.hs
-+++ b/compiler/utils/Platform.hs
-@@ -87,6 +87,7 @@ data OS
-         | OSHaiku
-         | OSQNXNTO
-         | OSAIX
-+        | OSHurd
-         deriving (Read, Show, Eq)
- 
- -- | ARM Instruction Set Architecture, Extensions and ABI
-@@ -136,6 +137,7 @@ osElfTarget OSKFreeBSD  = True
- osElfTarget OSHaiku     = True
- osElfTarget OSQNXNTO    = False
- osElfTarget OSAIX       = False
-+osElfTarget OSHurd      = True
- osElfTarget OSUnknown   = False
-  -- Defaulting to False is safe; it means don't rely on any
-  -- ELF-specific functionality.  It is important to have a default for


=====================================
p/ghc/debian/patches/armel-revert-ghci-fixes.patch → p/ghc/debian/patches/llvm-arm-unknown-linux-gnueabi.patch
=====================================
@@ -1,65 +1,6 @@
 Description: with new ghc 8.4.3, the armel situation seems to have improved,
  apply this patch unconditionally.
-#Description: Revert ghci ARM improvements (ticket #10375) on armel
-# This patch reverts a change which improved ghci on ARM (see
-# ghc ticket #10375). While the change fixed ghci on armhf, it
-# actually resulted in the ghc package FTBFS on armel since the
-# changes introduced made ghc incompatible with this architecture
-# (ticket #11058). As a temporary workaround, we revert this particular
-# change when ghc is built on armel. For this reason, this patch
-# is not applied using the series file but only selectively on
-# armel with the help of debian/rules.
-# .
-#
-#Index: ghc-8.4.1/aclocal.m4
-#===================================================================
-#--- ghc-8.4.1.orig/aclocal.m4
-#+++ ghc-8.4.1/aclocal.m4
-#@@ -651,15 +651,8 @@
-#         $3="$$3 -D_HPUX_SOURCE"
-#         $5="$$5 -D_HPUX_SOURCE"
-#         ;;
-#-    arm*linux*)
-#-        # On arm/linux and arm/android, tell gcc to generate Arm
-#-        # instructions (ie not Thumb).
-#-        $2="$$2 -marm"
-#-        $3="$$3 -Wl,-z,noexecstack"
-#-        $4="$$4 -z noexecstack"
-#-        ;;
-#-
-#-    aarch64*linux*)
-#+    arm*linux*		| \
-#+    aarch64*linux*	)
-#         $3="$$3 -Wl,-z,noexecstack"
-#         $4="$$4 -z noexecstack"
-#         ;;
-#Index: ghc-8.4.1/libraries/ghci/GHCi/InfoTable.hsc
-#===================================================================
-#--- ghc-8.4.1.orig/libraries/ghci/GHCi/InfoTable.hsc
-#+++ ghc-8.4.1/libraries/ghci/GHCi/InfoTable.hsc
-#@@ -245,17 +245,17 @@
-#                  , fromIntegral ((w64 `shiftR` 32) .&. 0x0000FFFF) ]
-# 
-#     ArchARM { } ->
-#-        -- Generates Arm sequence,
-#+        -- Generates Thumb sequence,
-#         --      ldr r1, [pc, #0]
-#         --      bx r1
-#         --
-#         -- which looks like:
-#         --     00000000 <.addr-0x8>:
-#-        --     0:       00109fe5    ldr    r1, [pc]      ; 8 <.addr>
-#-        --     4:       11ff2fe1    bx     r1
-#+        --     0:       4900        ldr    r1, [pc]      ; 8 <.addr>
-#+        --     4:       4708        bx     r1
-#         let w32 = fromIntegral (funPtrToInt a) :: Word32
-#-        in Left [ 0x00, 0x10, 0x9f, 0xe5
-#-                , 0x11, 0xff, 0x2f, 0xe1
-#+        in Left [ 0x49, 0x00
-#+                , 0x47, 0x08
-#                 , byte0 w32, byte1 w32, byte2 w32, byte3 w32]
-# 
-#     ArchARM64 { } ->
+
 Index: b/llvm-targets
 ===================================================================
 --- a/llvm-targets


=====================================
p/ghc/debian/patches/llvm-targets-Add-versioned-ARM-targets.patch deleted
=====================================
@@ -1,43 +0,0 @@
-From e4003b6dc6a84d870116de9f47057c15b1576f36 Mon Sep 17 00:00:00 2001
-From: Guillaume GARDET <guillaume.gardet at opensuse.org>
-Date: Fri, 18 May 2018 08:56:28 +0200
-Subject: [PATCH] llvm-targets: Add versioned ARM targets
-
-Namely armv6l-unknown-linux-gnueabihf and
-armv7l-unknown-linux-gnueabihf.
----
- llvm-targets                          | 4 +++-
- utils/llvm-targets/gen-data-layout.sh | 4 ++--
- 2 files changed, 5 insertions(+), 3 deletions(-)
-
-Index: b/llvm-targets
-===================================================================
---- a/llvm-targets
-+++ b/llvm-targets
-@@ -3,10 +3,12 @@
- ,("x86_64-unknown-windows", ("e-m:w-i64:64-f80:128-n8:16:32:64-S128", "x86-64", ""))
- ,("arm-unknown-linux-gnueabihf", ("e-m:e-p:32:32-i64:64-v128:64:128-a:0:32-n32-S64", "arm1176jzf-s", "+strict-align"))
- ,("armv6-unknown-linux-gnueabihf", ("e-m:e-p:32:32-i64:64-v128:64:128-a:0:32-n32-S64", "arm1136jf-s", "+strict-align"))
-+,("armv6l-unknown-linux-gnueabihf", ("e-m:e-p:32:32-i64:64-v128:64:128-a:0:32-n32-S64", "arm1176jzf-s", "+strict-align"))
- ,("armv7-unknown-linux-gnueabihf", ("e-m:e-p:32:32-i64:64-v128:64:128-a:0:32-n32-S64", "generic", ""))
-+,("armv7a-unknown-linux-gnueabi", ("e-m:e-p:32:32-i64:64-v128:64:128-a:0:32-n32-S64", "generic", ""))
-+,("armv7l-unknown-linux-gnueabihf", ("e-m:e-p:32:32-i64:64-v128:64:128-a:0:32-n32-S64", "generic", ""))
- ,("aarch64-unknown-linux-gnu", ("e-m:e-i8:8:32-i16:16:32-i64:64-i128:128-n32:64-S128", "generic", "+neon"))
- ,("aarch64-unknown-linux", ("e-m:e-i8:8:32-i16:16:32-i64:64-i128:128-n32:64-S128", "generic", "+neon"))
--,("armv7a-unknown-linux-gnueabi", ("e-m:e-p:32:32-i64:64-v128:64:128-a:0:32-n32-S64", "generic", ""))
- ,("i386-unknown-linux-gnu", ("e-m:e-p:32:32-f64:32:64-f80:32-n8:16:32-S128", "pentium4", ""))
- ,("i386-unknown-linux", ("e-m:e-p:32:32-f64:32:64-f80:32-n8:16:32-S128", "pentium4", ""))
- ,("x86_64-unknown-linux-gnu", ("e-m:e-i64:64-f80:128-n8:16:32:64-S128", "x86-64", ""))
-Index: b/utils/llvm-targets/gen-data-layout.sh
-===================================================================
---- a/utils/llvm-targets/gen-data-layout.sh
-+++ b/utils/llvm-targets/gen-data-layout.sh
-@@ -18,7 +18,7 @@
- 
- # Target sets
- WINDOWS_x86="i386-unknown-windows i686-unknown-windows x86_64-unknown-windows"
--LINUX_ARM="arm-unknown-linux-gnueabihf armv6-unknown-linux-gnueabihf armv7-unknown-linux-gnueabihf aarch64-unknown-linux-gnu aarch64-unknown-linux armv7a-unknown-linux-gnueabi"
-+LINUX_ARM="arm-unknown-linux-gnueabihf armv6-unknown-linux-gnueabihf armv7-unknown-linux-gnueabihf aarch64-unknown-linux-gnu aarch64-unknown-linux armv7a-unknown-linux-gnueabi armv7l-unknown-linux-gnueabihf"
- LINUX_x86="i386-unknown-linux-gnu i386-unknown-linux x86_64-unknown-linux-gnu x86_64-unknown-linux"
- ANDROID="armv7-unknown-linux-androideabi aarch64-unknown-linux-android"
- QNX="arm-unknown-nto-qnx-eabi"


=====================================
p/ghc/debian/patches/no-missing-haddock-file-warning
=====================================
@@ -7,7 +7,7 @@ Index: b/utils/ghc-pkg/Main.hs
 ===================================================================
 --- a/utils/ghc-pkg/Main.hs
 +++ b/utils/ghc-pkg/Main.hs
-@@ -1824,8 +1824,10 @@ checkPackageConfig pkg verbosity db_stac
+@@ -1888,8 +1888,10 @@ checkPackageConfig pkg verbosity db_stac
    mapM_ (checkDir True  "dynamic-library-dirs") (libraryDynDirs pkg)
    mapM_ (checkDir True  "include-dirs") (includeDirs pkg)
    mapM_ (checkDir True  "framework-dirs") (frameworkDirs pkg)


=====================================
p/ghc/debian/patches/risc-support.patch deleted
=====================================
@@ -1,31 +0,0 @@
-Description: cherry-pick of upstream commits
- beba89a0f16681c85d39fc8a894bde4162ff492a.patch:
- 5e63a25249f3cb07300258e115af9ff55079d2ea.patch:
-Last-Update: 2018-07-19
-
-Index: b/aclocal.m4
-===================================================================
---- a/aclocal.m4
-+++ b/aclocal.m4
-@@ -217,7 +217,7 @@ AC_DEFUN([FPTOOLS_SET_HASKELL_PLATFORM_V
-         mipsel)
-             test -z "[$]2" || eval "[$]2=ArchMipsel"
-             ;;
--        hppa|hppa1_1|ia64|m68k|rs6000|s390|s390x|sh4|vax)
-+        hppa|hppa1_1|ia64|m68k|riscv32|riscv64|rs6000|s390|s390x|sh4|vax)
-             test -z "[$]2" || eval "[$]2=ArchUnknown"
-             ;;
-         *)
-@@ -1884,6 +1884,12 @@ case "$1" in
-   powerpc*)
-     $2="powerpc"
-     ;;
-+  riscv64*)
-+    $2="riscv64"
-+    ;;
-+  riscv|riscv32*)
-+    $2="riscv32"
-+    ;;
-   rs6000)
-     $2="rs6000"
-     ;;


=====================================
p/ghc/debian/patches/series
=====================================
@@ -1,16 +1,11 @@
 use-debian-gen_contents_index
 ARM-VFPv3D16
 no-missing-haddock-file-warning
-hurd.diff
 buildpath-abi-stability.patch
 x32-use-native-x86_64-insn.patch
 use-stage1-binaries-for-install.patch
-llvm-targets-Add-versioned-ARM-targets.patch
+llvm-arm-unknown-linux-gnueabi.patch
 bsymbolic-only-for-registerised.patch
-use-llvm-6.0.patch
 e175aaf6918bb2b497b83618dc4c270a0d231a1c.patch
-risc-support.patch
-armel-revert-ghci-fixes.patch
 fix-build-using-unregisterized-v8.2
 add_-latomic_to_ghc-prim
-haddock-out-of-memory.patch


=====================================
p/ghc/debian/patches/use-debian-gen_contents_index
=====================================
@@ -2,7 +2,7 @@ Index: b/ghc.mk
 ===================================================================
 --- a/ghc.mk
 +++ b/ghc.mk
-@@ -820,7 +820,6 @@ endif
+@@ -809,7 +809,6 @@ endif
  # Build the Haddock contents and index
  ifeq "$(HADDOCK_DOCS)" "YES"
  libraries/dist-haddock/index.html: $(haddock_INPLACE) $(ALL_HADDOCK_FILES)
@@ -10,7 +10,7 @@ Index: b/ghc.mk
  ifeq "$(phase)" "final"
  $(eval $(call all-target,library_doc_index,libraries/dist-haddock/index.html))
  endif
-@@ -953,12 +952,8 @@ endif
+@@ -942,12 +941,8 @@ endif
  	$(INSTALL_DIR) "$(DESTDIR)$(docdir)/html"
  	$(INSTALL_DOC) $(INSTALL_OPTS) docs/index.html "$(DESTDIR)$(docdir)/html"
  ifneq "$(INSTALL_LIBRARY_DOCS)" ""
@@ -24,11 +24,11 @@ Index: b/ghc.mk
  endif
  ifneq "$(INSTALL_HTML_DOC_DIRS)" ""
  	for i in $(INSTALL_HTML_DOC_DIRS); do \
-@@ -1078,7 +1073,6 @@ $(eval $(call bindist-list,.,\
+@@ -1068,7 +1063,6 @@ $(eval $(call bindist-list,.,\
      mk/project.mk \
      mk/install.mk.in \
      bindist.mk \
 -    libraries/gen_contents_index \
      libraries/prologue.txt \
-     $(wildcard libraries/dph/LICENSE \
-                libraries/dph/ghc-packages \
+  ))
+ endif


=====================================
p/ghc/debian/patches/use-llvm-6.0.patch deleted
=====================================
@@ -1,17 +0,0 @@
-Description: Use llvm 6.0 on arm*
-Author: Gianfranco Costamagna <locutusofborg at debian.org>
-Last-Update: 2018-07-19
-
-Index: b/configure.ac
-===================================================================
---- a/configure.ac
-+++ b/configure.ac
-@@ -638,7 +638,7 @@ AC_SUBST([LibtoolCmd])
- # tools we are looking for. In the past, GHC supported a number of
- # versions of LLVM simultaneously, but that stopped working around
- # 3.5/3.6 release of LLVM.
--LlvmVersion=5.0
-+LlvmVersion=6.0
- AC_SUBST([LlvmVersion])
- sUPPORTED_LLVM_VERSION=$(echo \($LlvmVersion\) | sed 's/\./,/')
- AC_DEFINE_UNQUOTED([sUPPORTED_LLVM_VERSION], ${sUPPORTED_LLVM_VERSION}, [The supported LLVM version number])


=====================================
p/ghc/debian/patches/use-stage1-binaries-for-install.patch
=====================================
@@ -11,7 +11,7 @@ Index: b/ghc.mk
 ===================================================================
 --- a/ghc.mk
 +++ b/ghc.mk
-@@ -972,8 +972,12 @@ else # CrossCompiling
+@@ -961,8 +961,12 @@ else # CrossCompiling
  # Install packages in the right order, so that ghc-pkg doesn't complain.
  # Also, install ghc-pkg first.
  ifeq "$(Windows_Host)" "NO"


=====================================
p/ghc/debian/patches/x32-use-native-x86_64-insn.patch
=====================================
@@ -16,7 +16,7 @@ Index: b/rts/RtsSymbols.c
 ===================================================================
 --- a/rts/RtsSymbols.c
 +++ b/rts/RtsSymbols.c
-@@ -919,7 +919,7 @@
+@@ -934,7 +934,7 @@
  
  
  // 64-bit support functions in libgcc.a


=====================================
p/haskell-parsec-numbers/debian/control
=====================================
@@ -16,7 +16,7 @@ Standards-Version: 4.2.1
 Homepage: http://hackage.haskell.org/package/parsec-numbers
 Vcs-Browser: https://salsa.debian.org/haskell-team/DHG_packages/tree/master/p/cabal-debian/debian
 Vcs-Git: https://salsa.debian.org/haskell-team/DHG_packages.git [p/haskell-parsec-numbers]
-X-Description: Utilities for parsing numbers from strings
+X-Description: utilities for parsing numbers from strings
  parsec-numbers provides the number parsers without the need to
  use a large (and unportable) token parser
 


=====================================
p/haskell-parsec-numbers/debian/copyright
=====================================
@@ -6,6 +6,9 @@ Source: https://hackage.haskell.org/package/parsec-numbers
 Files: *
 Copyright: 2011-2018 Christian Maeder <chr.maeder at web.de>
 License: BSD-3-Clause
+Comment: The LICENSE file in the upstream source is blank.
+ Thus the code's license was obtained from the Hackage page and is consistent
+ with the source files' headers.
 
 Files: debian/*
 Copyright: held by the contributors mentioned in debian/changelog



View it on GitLab: https://salsa.debian.org/haskell-team/DHG_packages/compare/fcfb99beb8c98090d034643af06b91cf2205b769...585896a10b05c94c61a90764407f10be981687f4

-- 
View it on GitLab: https://salsa.debian.org/haskell-team/DHG_packages/compare/fcfb99beb8c98090d034643af06b91cf2205b769...585896a10b05c94c61a90764407f10be981687f4
You're receiving this email because of your account on salsa.debian.org.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://alioth-lists.debian.net/pipermail/pkg-haskell-commits/attachments/20180928/5ec4233d/attachment-0001.html>


More information about the Pkg-haskell-commits mailing list