Skip to content
Snippets Groups Projects
  1. Jul 12, 2017
  2. Jul 11, 2017
    • Ben Gamari's avatar
      Use correct section types syntax for architecture · 9b9f978f
      Ben Gamari authored and Ben Gamari's avatar Ben Gamari committed
      Previously GHC would always assume that section types began with `@` while
      producing assembly, which is not true. For instance, in ARM assembly syntax
      section types begin with `%`. This abstracts out section type pretty-printing
      and adjusts it to correctly account for the target architectures assembly
      flavor.
      
      Reviewers: austin, hvr, Phyx
      
      Reviewed By: Phyx
      
      Subscribers: Phyx, rwbarton, thomie, erikd
      
      GHC Trac Issues: #13937
      
      Differential Revision: https://phabricator.haskell.org/D3712
      9b9f978f
    • Ömer Sinan Ağacan's avatar
      Mention which -Werror promoted a warning to an error · 4befb415
      Ömer Sinan Ağacan authored
      Previously -Werror or -Werror=flag printed warnings as usual and then
      printed
      these two lines:
      
          <no location info>: error:
          Failing due to -Werror.
      
      This is not ideal: first, it's not clear which flag made one of the
      warnings an
      error. Second, warning messages are not modified in any way, so there's
      no way
      to know which warnings caused this error.
      
      With this patch we (1) promote warning messages to error messages if a
      relevant
      -Werror is enabled (2) mention which -Werror is used during this
      promotion.
      
      Previously:
      
          [1 of 1] Compiling Main             ( test.hs, test.o )
      
          test.hs:9:10: warning: [-Wincomplete-patterns]
              Pattern match(es) are non-exhaustive
              In a case alternative: Patterns not matched: (C2 _)
            |
          9 | sInt s = case s of
            |          ^^^^^^^^^...
      
          test.hs:12:14: warning: [-Wmissing-fields]
              • Fields of ‘Rec’ not initialised: f2
              • In the first argument of ‘print’, namely ‘Rec {f1 =
      1}’
                In the expression: print Rec {f1 = 1}
                In an equation for ‘main’: main = print Rec {f1 = 1}
             |
          12 | main = print Rec{ f1 = 1 }
             |              ^^^^^^^^^^^^^
      
          <no location info>: error:
          Failing due to -Werror.
      
      Now:
      
          [1 of 1] Compiling Main             ( test.hs, test.o )
      
          test.hs:9:10: error: [-Wincomplete-patterns,
      -Werror=incomplete-patterns]
              Pattern match(es) are non-exhaustive
              In a case alternative: Patterns not matched: (C2 _)
            |
          9 | sInt s = case s of
            |          ^^^^^^^^^...
      
          test.hs:12:14: error: [-Wmissing-fields, -Werror=missing-fields]
              • Fields of ‘Rec’ not initialised: f2
              • In the first argument of ‘print’, namely ‘Rec {f1 =
      1}’
                In the expression: print Rec {f1 = 1}
                In an equation for ‘main’: main = print Rec {f1 = 1}
             |
          12 | main = print Rec{ f1 = 1 }
             |              ^^^^^^^^^^^^^
      
      Test Plan: - Update old tests, add new tests if there aren't any
      relevant tests
      
      Reviewers: austin, bgamari
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie
      
      Differential Revision: https://phabricator.haskell.org/D3709
      4befb415
    • David Feuer's avatar
      Remove redundant import; fix note · 3a163aab
      David Feuer authored
      * Remove the redundant import of `Data.Maybe` from `GHC.Foreign`.
      
      * Fix the note in `GHC.Stack.Types` to give a correct explanation
      of the problematic cycle.
      
      Reviewers: austin, hvr, bgamari
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie
      
      Differential Revision: https://phabricator.haskell.org/D3722
      3a163aab
    • Ismail Suleman's avatar
      Fix minor typo · a0d91693
      Ismail Suleman authored
      a0d91693
    • Ben Gamari's avatar
      testsuite: Show stderr output on command failure · 20880b56
      Ben Gamari authored and Ben Gamari's avatar Ben Gamari committed
      Reviewers: austin
      
      Subscribers: rwbarton, thomie
      
      Differential Revision: https://phabricator.haskell.org/D3716
      20880b56
    • Ben Gamari's avatar
      StgLint: Don't loop on tycons with runtime rep arguments · be04c16b
      Ben Gamari authored and Ben Gamari's avatar Ben Gamari committed
      Test Plan: Validate
      
      Reviewers: austin
      
      Subscribers: rwbarton, thomie
      
      GHC Trac Issues: #13941
      
      Differential Revision: https://phabricator.haskell.org/D3714
      be04c16b
    • Ben Gamari's avatar
      configure: Ensure that we don't set LD to unusable linker · fcd2db14
      Ben Gamari authored and Ben Gamari's avatar Ben Gamari committed
      Previously if we found an unusable linker in PATH (e.g. ld.lld on OS X)
      we would notice the -fuse-ld=... was broken, but neglected to reset LD
      to a usable linker. This resulted in brokenness on OS X when lld is in
      PATH.
      
      Test Plan: Validate on OS X with lld in PATH
      
      Reviewers: austin, hvr, angerman
      
      Reviewed By: angerman
      
      Subscribers: rwbarton, thomie, erikd, angerman
      
      GHC Trac Issues: #13541
      
      Differential Revision: https://phabricator.haskell.org/D3713
      fcd2db14
    • Ben Gamari's avatar
      testsuite: Fix T13701 allocations yet again · d3bdd6c4
      Ben Gamari authored
      d3bdd6c4
    • Ryan Scott's avatar
      Remove unnecessarily returned res_ty from rejigConRes · a249e939
      Ryan Scott authored
      @goldfire noticed that we don't need to thread through `res_ty`
      through to the return type of `rejigConRes`, as it never changes.
      
      Reviewers: goldfire, austin, bgamari
      
      Reviewed By: goldfire
      
      Subscribers: rwbarton, thomie, goldfire
      
      Differential Revision: https://phabricator.haskell.org/D3725
      a249e939
    • Matthew Pickering's avatar
      Add Template Haskell support for overloaded labels · ec351b86
      Matthew Pickering authored and Ben Gamari's avatar Ben Gamari committed
      Reviewers: RyanGlScott, austin, goldfire, bgamari
      
      Reviewed By: RyanGlScott, goldfire, bgamari
      
      Subscribers: rwbarton, thomie
      
      Differential Revision: https://phabricator.haskell.org/D3715
      ec351b86
    • Eugene Akentyev's avatar
      Parenthesize infix type names in data declarations in TH printer · ef7fd0ae
      Eugene Akentyev authored and Ben Gamari's avatar Ben Gamari committed
      Previously datatype names were not paraenthesized (#13887).
      
      Reviewers: austin, bgamari, RyanGlScott
      
      Reviewed By: RyanGlScott
      
      Subscribers: RyanGlScott, rwbarton, thomie
      
      Differential Revision: https://phabricator.haskell.org/D3717
      ef7fd0ae
    • Ryan Scott's avatar
      Fix #13947 by checking for unbounded names more · 85ac65c5
      Ryan Scott authored
      Commit 2484d4da accidentally dropped a
      call to `isUnboundName` in an important location. This re-adds it.
      
      Fixes #13947.
      
      Test Plan: make test TEST=T13947
      
      Reviewers: adamgundry, austin, bgamari
      
      Reviewed By: adamgundry
      
      Subscribers: rwbarton, thomie
      
      GHC Trac Issues: #13947
      
      Differential Revision: https://phabricator.haskell.org/D3718
      85ac65c5
    • Ryan Scott's avatar
      Fix #13948 by being pickier about when to suggest DataKinds · ba46e63f
      Ryan Scott authored
      Commit 343cb32d (#13568) made GHC a bit
      too cavalier in suggesting when data constructors are in scope (and
      suggesting the use of `DataKinds`). This tones down the suggestions so
      that `DataKinds` is only suggested if a data constructor of that name is
      actually in scope (previously, it would always suggest, even if it was
      out of scope).
      
      Fixes #13948.
      
      Test Plan: ./validate
      
      Reviewers: mpickering, austin, bgamari
      
      Reviewed By: mpickering
      
      Subscribers: rwbarton, thomie
      
      GHC Trac Issues: #13948
      
      Differential Revision: https://phabricator.haskell.org/D3719
      ba46e63f
    • Douglas Wilson's avatar
      Fix logic error in GhcMake.enableCodeGenForTH · ea751248
      Douglas Wilson authored and Ben Gamari's avatar Ben Gamari committed
      transitive_deps_set was incorrect, it was not considering the
      dependencies of dependencies in some cases. I've corrected it and tidied
      it up a little.
      
      The test case from leftaroundabout, as linked to from the ticket, is
      added with small modifications to flatten directory structure.
      
      Test Plan: make test TEST=T13949
      
      Reviewers: austin, bgamari, alexbiehl
      
      Reviewed By: alexbiehl
      
      Subscribers: rwbarton, thomie, alexbiehl
      
      GHC Trac Issues: #13949
      
      Differential Revision: https://phabricator.haskell.org/D3720
      ea751248
    • Alex Biehl's avatar
      Optimize TimerManager · abda03be
      Alex Biehl authored
      After discussion with Kazu Yamamoto we decided to try two things:
        - replace current finger tree based priority queue through a radix
          tree based one (code is based on IntPSQ from the psqueues package)
        - after editing the timer queue: don't wake up the timer manager if
          the next scheduled time didn't change
      
      Benchmark results (number of TimerManager-Operations measured over 20
      seconds, 5 runs each, higher is better)
      
      ```
      -- baseline (timermanager action commented out)
      28817088
      28754681
      27230541
      27267441
      28828815
      
      -- ghc-8.3 with wake opt and new timer queue
      18085502
      17892831
      18005256
      18791301
      17912456
      
      -- ghc-8.3 with old timer queue
      6982155
      7003572
      6834625
      6979634
      6664339
      ```
      
      Here is the benchmark code:
      ```
      {-# LANGUAGE BangPatterns #-}
      module Main where
      
      import Control.Monad
      import Control.Monad.IO.Class
      import Control.Monad.Trans.State.Strict
      import Data.Foldable
      import GHC.Event
      import System.Random
      import Control.Concurrent
      import Control.Exception
      import Data.IORef
      
      main :: IO ()
      main = do
      
        let seed = 12345 :: Int
            nthreads = 1 :: Int
            benchTime = 20 :: Int -- in seconds
      
        timerManager <- getSystemTimerManager :: IO TimerManager
      
        let
          {- worker loop
             depending on the random generator it either
              * registers a new timeout
              * updates existing timeout
              * or cancels an existing timeout
      
            Additionally it keeps track of a counter tracking how
            often a timermanager was being modified.
          -}
          loop :: IORef Int -> [TimeoutKey] -> StdGen -> IO a
          loop !i !timeouts !rng = do
            let (rand0, rng')   = next rng
                (rand1, rng'')  = next rng'
            case rand0 `mod` 3 of
              0 -> do
                timeout <- registerTimeout timerManager (rand1) (return ())
                modifyIORef' i (+1)
                loop i (timeout:timeouts) rng''
              1 | (timeout:_) <- timeouts
                -> do
                  updateTimeout timerManager timeout (rand1)
                  modifyIORef' i (+1)
                  loop i timeouts rng''
                | otherwise
                -> loop i timeouts rng'
              2
                | (timeout:timeouts') <- timeouts
                -> do
                    unregisterTimeout timerManager timeout
                    modifyIORef' i (+1)
                    loop i timeouts' rng'
                | otherwise -> loop i timeouts rng'
      
              _ -> loop i timeouts rng'
      
        let
          -- run a computation which can produce new
          -- random generators on demand
          withRng m = evalStateT m (mkStdGen seed)
      
          -- split a new random generator
          newRng = do
            (rng1, rng2) <- split <$> get
            put rng1
            return rng2
      
        counters <- withRng $ do
          replicateM nthreads $ do
            rng <- newRng
            ref <- liftIO (newIORef 0)
            liftIO $ forkIO (loop ref [] rng)
            return ref
      
        threadDelay (1000000 * benchTime)
        for_ counters $ \ref -> do
          n <- readIORef ref
          putStrLn (show n)
      
      ```
      
      Reviewers: austin, hvr, bgamari
      
      Reviewed By: bgamari
      
      Subscribers: Phyx, rwbarton, thomie
      
      Differential Revision: https://phabricator.haskell.org/D3707
      abda03be
    • Matthew Pickering's avatar
      Add Template Haskell support for overloaded labels · 81de42cb
      Matthew Pickering authored
      Reviewers: RyanGlScott, austin, goldfire, bgamari
      
      Reviewed By: RyanGlScott, goldfire, bgamari
      
      Subscribers: rwbarton, thomie
      
      Differential Revision: https://phabricator.haskell.org/D3715
      81de42cb
    • Ben Gamari's avatar
      users-guide/rel-notes: Describe #13875 fix · ccb849f8
      Ben Gamari authored and Ben Gamari's avatar Ben Gamari committed
      Test Plan: Read it.
      
      Reviewers: simonmar, austin
      
      Reviewed By: simonmar
      
      Subscribers: rwbarton, thomie
      
      GHC Trac Issues: #13875
      
      Differential Revision: https://phabricator.haskell.org/D3710
      ccb849f8
    • Michal Terepeta's avatar
      ByteCodeGen: use depth instead of offsets in BCEnv · fe6618b1
      Michal Terepeta authored and Ben Gamari's avatar Ben Gamari committed
      
      This is based on unfinished work in D38 started by Simon Marlow and is
      the first step for fixing #13825. (next step use byte-indexing for
      stack)
      
      The change boils down to adjusting everything in BCEnv by +1, which
      simplifies the code a bit.
      
      I've also looked into a weird stack adjustement that we did in
      `getIdValFromApStack` and moved it to `ByteCodeGen` to just keep
      everything in one place. I've left a comment about this.
      
      Signed-off-by: default avatarMichal Terepeta <michal.terepeta@gmail.com>
      
      Test Plan: ./validate
      
      Reviewers: austin, hvr, bgamari, simonmar
      
      Reviewed By: bgamari, simonmar
      
      Subscribers: simonmar, rwbarton, thomie
      
      GHC Trac Issues: #13825
      
      Differential Revision: https://phabricator.haskell.org/D3708
      fe6618b1
    • Moritz Angermann's avatar
      Always allow -staticlib · b8f33bc6
      Moritz Angermann authored and Ben Gamari's avatar Ben Gamari committed
      the `-staticlib` flag is currently only supported on apple platforms,
      due to the avaiablity of libtool (the apple version, which is unlike the
      gnu version).  This however prevents the use of -staticlib in cases
      where it would be beneficial as well.  The functionality that
      `-staticlib` uses from `libtool` can be stubbed with a small script like
      the following:
      
      ```
      #!/bin/bash
      
      # This script pretends to be libtool.  And supports
      # only a limited set of flags.
      #
      # It is supposed to be a stand in for libtool -static, whic
      # creates a static archive.  This is done by locating all -l<lib>
      # libs in the provied -L<lib path> library paths, and building an
      # MRI script to create the final archive from all the libraries, and
      # other provided inputs.
      #
      
      name=${0##*/}
      target=${name%-*}
      
      set -e
      
      ldflags_L=()
      ldflags_l=()
      output=""
      inputs=()
      STATIC=0
      DYNAMIC=1
      mode=$DYNAMIC
      verbose=0
      
      # find_lib <name> path path path path
      function find_lib () {
              lib=$1; shift 1;
              for dir in $@; do
                      if [ -f "$dir/$lib" ]; then
                              echo "$dir/$lib"
                              break
                      fi
              done
      }
      
      while [ "$#" -gt 0 ]; do
              case "$1" in
                      -v|--verbose) verbose=1; shift 1;;
                      -o) output="$2"; shift 2;;
                      -L*) ldflags_L+=("${1:2:${#1}-2}"); shift 1;;
                      -l*) ldflags_l+=("lib${1:2:${#1}-2}.a"); shift 1;;
                      -static) mode=$STATIC; shift 1;;
                      -dynamic) mode=$DYNAMIC; shift 1;;
                      -Wl,*) ldflags+=("${1#*,}"); shift 1;;
                      -*) echo "unknown option: $1" >&2; exit 1;;
                      *) inputs+=("$1"); shift 1;;
              esac
      done
      
      if [ ! $mode == $STATIC ]; then
              echo "-dynamic not supported!" >&2; exit 1;
      fi
      
      MRI="create ${output}\n"
      for input in "${ldflags_l[@]}"; do
              lib=$(find_lib $input ${ldflags_L[@]})
              if [ -z $lib ]; then
                      echo "Failed to find lib $input" >&2
                      exit 1
              else
                      MRI+="addlib $lib\n"
                      continue
              fi
      done
      for input in "${inputs[@]}"; do
              MRI+="addmod $input\n"
      done
      MRI+="save\nend\n"
      echo -e "$MRI" | $target-ar -M
      $target-ranlib $output
      ```
      
      if `ar` supports MRI scripts.
      
      Reviewers: austin, bgamari
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie
      
      Differential Revision: https://phabricator.haskell.org/D3706
      b8f33bc6
    • Andreas Klebinger's avatar
      Sort list of failed tests for easier comparison between runs · cb8db9bc
      Andreas Klebinger authored
      Test Plan: Running the testsuite.
      
      Reviewers: austin, bgamari
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie
      
      GHC Trac Issues: #13922
      
      Differential Revision: https://phabricator.haskell.org/D3705
      cb8db9bc
    • Ryan Scott's avatar
      Suppress unused warnings for selectors for some derived classes · 15fcd9ad
      Ryan Scott authored
      Although derived `Read`, `Show`, and `Generic` instances technically
      don't //use// the record selectors of the data type for which an
      instance is being derived, the derived code is affected by the
      //presence// of record selectors. As a result, we should suppress
      `-Wunused-binds` for those record selectors when deriving these classes.
      This is accomplished by threading through more information from
      `hasStockDeriving`.
      
      Test Plan: make test TEST=T13919
      
      Reviewers: austin, bgamari
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie
      
      GHC Trac Issues: #13919
      
      Differential Revision: https://phabricator.haskell.org/D3704
      15fcd9ad
    • Douglas Wilson's avatar
      Add testcase for T13818 · 6cff2cad
      Douglas Wilson authored and Ben Gamari's avatar Ben Gamari committed
      Annotations currently fail to type check if they annotation cannot
      be loaded into ghci, such as when built with -fno-code.
      
      Test Plan: ./validate
      
      Reviewers: austin, bgamari
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie
      
      GHC Trac Issues: #13818
      
      Differential Revision: https://phabricator.haskell.org/D3701
      6cff2cad
    • Ben Gamari's avatar
      Improve Wmissing-home-modules warning under Cabal · b0c9f34a
      Ben Gamari authored and Ben Gamari's avatar Ben Gamari committed
      Reviewers: hvr, alanz, austin
      
      Reviewed By: alanz
      
      Subscribers: rwbarton, thomie
      
      GHC Trac Issues: #13899
      
      Differential Revision: https://phabricator.haskell.org/D3686
      b0c9f34a
    • Douglas Wilson's avatar
      Fix Work Balance computation in RTS stats · 7c9e356d
      Douglas Wilson authored and Ben Gamari's avatar Ben Gamari committed
      An additional stat is tracked per gc: par_balanced_copied This is the
      the number of bytes copied by each gc thread under the balanced lmit,
      which is simply (copied_bytes / num_gc_threads).  The stat is added to
      all the appropriate GC structures, so is visible in the eventlog and in
      GHC.Stats.
      
      A note is added explaining how work balance is computed.
      
      Remove some end of line whitespace
      
      Test Plan:
      ./validate
      experiment with the program attached to the ticket
      examine code changes carefully
      
      Reviewers: simonmar, austin, hvr, bgamari, erikd
      
      Reviewed By: simonmar
      
      Subscribers: Phyx, rwbarton, thomie
      
      GHC Trac Issues: #13830
      
      Differential Revision: https://phabricator.haskell.org/D3658
      7c9e356d
    • patrickdoc's avatar
      Make ':info Coercible' display an arbitrary string (fixes #12390) · 905dc8bc
      patrickdoc authored and Ben Gamari's avatar Ben Gamari committed
      This change enables the addition of an arbitrary string to the output of
      GHCi's ':info'. It was made for Coercible in particular but could be
      extended if desired.
      
      Updates haddock submodule.
      
      Test Plan: Modified test 'ghci059' to match new output.
      
      Reviewers: austin, bgamari
      
      Reviewed By: bgamari
      
      Subscribers: goldfire, rwbarton, thomie
      
      GHC Trac Issues: #12390
      
      Differential Revision: https://phabricator.haskell.org/D3634
      905dc8bc
    • Ben Gamari's avatar
      user-guide: Various fixes to FFI section · 31ceaba3
      Ben Gamari authored
      31ceaba3
    • Ben Gamari's avatar
      testsuite: Decrease T13701 allocations · 4f690133
      Ben Gamari authored
      4f690133
  3. Jul 10, 2017
  4. Jul 08, 2017
    • Tamar Christina's avatar
      Big-obj support for the Windows runtime linker · 81377e9e
      Tamar Christina authored
      Summary:
      The normal object file on Windows has a limit of `2^16`
      sections that can be in an object-file.
      
      The `big-obj` format raises this to `2^32` sections.
      
      The implementation is made difficult because we now need to support
      two header formats and two section formats that differ only by a single
      element size within each. The element that's different is in the middle
      of the structs and since the structs are used to map regions of memory
      directly, it means we need to know which struct it is when we do the
      mapping or pointer arithmetics.
      
      This is the final Object-Code format which Windows compilers can generate
      which we do not support yet in GHCI. All other major compilers on the platforms
      can produce it and all linkers consume it (bfd and lld).
      
      See http://tinyurl.com/bigobj
      
      This patch abstracts away retrieving the fields to functions which all take
      an struct which describes which object format is currently being parsed.
      These functions are always in-lined as they're small but would looks messy
      being copy-pasted everywhere.
      
      Test Plan:
      ./validate and new test `big-obj`
      
      ```
      Tamar@Rage MINGW64 /r
      $ gcc -c -Wa,-mbig-obj foo.c -o foo.o
      
      Tamar@Rage MINGW64 /r
      $ objdump -h foo.o
      
      foo.o:     file format pe-bigobj-x86-64
      
      Sections:
      Idx Name          Size      VMA               LMA               File off  Algn
        0 .text         00000010  0000000000000000  0000000000000000  00000128  2**4
                        CONTENTS, ALLOC, LOAD, READONLY, CODE
        1 .data         00000000  0000000000000000  0000000000000000  00000000  2**4
                        ALLOC, LOAD, DATA
        2 .bss          00000000  0000000000000000  0000000000000000  00000000  2**4
                        ALLOC
        3 .xdata        00000008  0000000000000000  0000000000000000  00000138  2**2
                        CONTENTS, ALLOC, LOAD, READONLY, DATA
        4 .pdata        0000000c  0000000000000000  0000000000000000  00000140  2**2
                        CONTENTS, ALLOC, LOAD, RELOC, READONLY, DATA
        5 .rdata$zzz    00000030  0000000000000000  0000000000000000  0000014c  2**4
                        CONTENTS, ALLOC, LOAD, READONLY, DATA
      
      Tamar@Rage MINGW64 /r
      $ echo main | ~/ghc/inplace/bin/ghc-stage2.exe --interactive bar.hs foo.o
      GHCi, version 8.3.20170430: http://www.haskell.org/ghc/  :? for help
      [1 of 1] Compiling Main             ( bar.hs, interpreted )
      Ok, modules loaded: Main.
      *Main> 17
      *Main> Leaving GHCi.
      ```
      
      Reviewers: austin, bgamari, erikd, simonmar
      
      Subscribers: awson, rwbarton, thomie, #ghc_windows_task_force
      
      GHC Trac Issues: #13815
      
      Differential Revision: https://phabricator.haskell.org/D3523
      81377e9e
    • Ömer Sinan Ağacan's avatar
      Fix typos in Bag.hs [ci skip] · e1146ed5
      Ömer Sinan Ağacan authored
      e1146ed5
    • Sergei Trofimovich's avatar
      aclocal.m4: allow arbitrary <vendor> string in toolchain triplets · c2303dff
      Sergei Trofimovich authored
      
      Canonical triplets have a form of
          <arch>-<vendor>-<os>[-<abi>]
      
      Checking for vendor is almost never correct as it's an
      arbitrary string.
      
      It's useful to have multiple "vendors" to denote
      otherwise the same (WRT <arch>, <os>, <abi>) target:
          --target=x86_64-pc-linux-gnu
          --target=x86_64-unknown-linux-gnu
          --target=x86_64-ghc80-linux-gnu
          --target=x86_64-ghchead-linux-gnu
      
      Do not fail unknown vendors. Only emit a warning.
      Ideally configure checks should never use "vendor".
      
      Signed-off-by: default avatarSergei Trofimovich <slyfox@gentoo.org>
      c2303dff
  5. Jul 07, 2017
    • Tamar Christina's avatar
      Implement split-sections support for windows. · bd4fdc6a
      Tamar Christina authored
      Summary:
      Initial implementation of split-section on Windows.
      
      This also corrects section namings and uses the platform
      convention of `$` instead of `.` to separate sections.
      
      Implementation is based on @awson's patches to binutils.
      
      Binutils requires some extra help when compiling the libraries
      for GHCi usage. We drop the `-T` and use implicit scripts to amend
      the linker scripts instead of replacing it.
      
      Because of these very large GHCi object files, we need big-obj support,
      which will be added by another patch.
      
      Test Plan: ./validate
      
      Reviewers: awson, austin, bgamari
      
      Subscribers: dfeuer, rwbarton, thomie, snowleopard, #ghc_windows_task_force
      
      GHC Trac Issues: #12913
      
      Differential Revision: https://phabricator.haskell.org/D3383
      bd4fdc6a
  6. Jul 06, 2017
Loading