Skip to content
Snippets Groups Projects
  1. Mar 11, 2016
  2. Mar 10, 2016
    • Sergei Trofimovich's avatar
      fix Float/Double unreg cross-compilation · c42cdb7f
      Sergei Trofimovich authored
      
      Looking at more failures on m68k (Trac #11395)
      I've noticed the arith001 and arith012 test failures.
      (--host=x86_64-linux --target=m68k-linux).
      
      The following example was enough to reproduce a problem:
      
          v :: Float
          v = 43
          main = print v
      
      m68k binaries printed '0.0' instead of '43.0'.
      
      The bug here is how we encode Floats and Double
      as Words with the same binary representation.
      
      Floats:
        Before the patch we just coerced Float to Int.
        That breaks when we cross-compile from
        64-bit LE to 32-bit BE.
      
        The patch fixes conversion by accounting for padding.
        when we extend 32-bit value to 64-bit value (LE and BE
        do it slightly differently).
      
      Doubles:
        Before the patch Doubles were coerced to a pair of Ints
        (not correct as x86_64 can hold Double in one Int) and
        then trucated this pair of Ints to pair of Word32.
      
        The patch fixes conversion by always decomposing in
        Word32 and accounting for host endianness (newly
        introduced hostBE)  and target endianness (wORDS_BIGENDIAN).
      
      I've tested this patch on Double and Float conversion on
          --host=x86_64-linux --target=m68k-linux
      crosscompiler. It fixes 10 tests related to printing Floats
      and Doubles.
      
      Thanks to Bertram Felgenhauer who poined out this probem.
      
      Signed-off-by: default avatarSergei Trofimovich <siarheit@google.com>
      
      Test Plan: checked some examples manually, fixed 10 tests in test suite
      
      Reviewers: int-e, austin, bgamari
      
      Subscribers: thomie
      
      Differential Revision: https://phabricator.haskell.org/D1990
      
      GHC Trac Issues: #11395
      c42cdb7f
  3. Mar 09, 2016
  4. Mar 08, 2016
    • Herbert Valerio Riedel's avatar
      template-haskell: define `MonadFail Q` instance · 1c76e168
      Herbert Valerio Riedel authored
      When `MonadFail`is available, this patch makes `MonadFail` a superclass
      of `Quasi`, and `Q` an instance of `MonadFail`.
      
      NB: Since f16ddcee, we need to be able
          to compile `template-haskell` with stage0 compilers that don't provide
          a `MonadFail` class yet. Once we reach GHC 8.3 development we can drop
          the CPP conditionals again.
      
      Addresses #11661
      
      Reviewed By: bgamari, goldfire
      
      Differential Revision: https://phabricator.haskell.org/D1982
      1c76e168
    • Herbert Valerio Riedel's avatar
      template-haskell: remove redundant CPP use · 941b8f5f
      Herbert Valerio Riedel authored
      GHC 8.1's template-haskell package requires base>=4.8 anyway, so
      we can assume Numeric.Natural to be available unconditionally.
      941b8f5f
    • Herbert Valerio Riedel's avatar
      template-haskell: Drop use of Rank2Types/PolymorphicComponents · 1a9734a6
      Herbert Valerio Riedel authored
      As per #6032, `Rank2Types` and `PolymorphicComponents` have been
      deprecated in favour of `RankNTypes`.
      
      also update `other-extensions` in template-haskell.cabal flag to
      reflect reality.
      1a9734a6
    • Sergei Trofimovich's avatar
      Split external symbol prototypes (EF_) (Trac #11395) · 90e1e160
      Sergei Trofimovich authored
      
      Before the patch both Cmm and C symbols were declared
      with 'EF_' macro:
      
          #define EF_(f)    extern StgFunPtr f()
      
      but for Cmm symbols we know exact prototypes.
      
      The patch splits there prototypes in to:
      
          #define EFF_(f)   void f() /* See Note [External function prototypes] */
          #define EF_(f)    StgFunPtr f(void)
      
      Cmm functions are 'EF_' (External Functions),
      C functions are 'EFF_' (External Foreign Functions).
      
      While at it changed external C function prototype
      to return 'void' to workaround ghc bug on m68k.
      Described in detail in Trac #11395.
      
      This makes simple tests work on m68k-linux target!
      
      Thanks to Michael Karcher for awesome analysis
      happening in Trac #11395.
      
      Signed-off-by: default avatarSergei Trofimovich <siarheit@google.com>
      
      Test Plan: ran "hello world" on m68k successfully
      
      Reviewers: simonmar, austin, bgamari
      
      Reviewed By: bgamari
      
      Subscribers: thomie
      
      Differential Revision: https://phabricator.haskell.org/D1975
      
      GHC Trac Issues: #11395
      90e1e160
  5. Mar 07, 2016
  6. Mar 06, 2016
    • Sergei Trofimovich's avatar
      Fix minimum alignment for StgClosure (Trac #11395) · ade1a461
      Sergei Trofimovich authored
      
      The bug is observed on m68k-linux target as crash
      in RTS:
      
          -- a.hs:
          main = print 43
      
          $ inplace/bin/ghc-stage1 --make -debug a.hs
      
          $ ./a
          Program terminated with signal SIGSEGV, Segmentation fault.
          #0  0x80463b0a in LOOKS_LIKE_INFO_PTR_NOT_NULL (p=32858)
              at includes/rts/storage/ClosureMacros.h:248
          (gdb) bt
          #0  0x80463b0a in LOOKS_LIKE_INFO_PTR_NOT_NULL (p=32858)
              at includes/rts/storage/ClosureMacros.h:248
          #1  0x80463b46 in LOOKS_LIKE_INFO_PTR (p=32858)
              at includes/rts/storage/ClosureMacros.h:253
          #2  0x80463b6c in LOOKS_LIKE_CLOSURE_PTR (
                  p=0x805aac6e <stg_dummy_ret_closure>)
              at includes/rts/storage/ClosureMacros.h:258
          #3  0x80463e4c in initStorage ()
              at rts/sm/Storage.c:121
          #4  0x8043ffb4 in hs_init_ghc (...)
              at rts/RtsStartup.c:181
          #5  0x80455982 in hs_main (...)
              at rts/RtsMain.c:51
          #6  0x80003c1c in main ()
      
      GHC assumes last 2 pointer bits are tags on 32-bit targets.
      But here 'stg_dummy_ret_closure' address violates the assumption:
      
          LOOKS_LIKE_CLOSURE_PTR (p=0x805aac6e <stg_dummy_ret_closure>)
      
      I've added compiler hint for static StgClosure objects to
      align closures at least by their natural alignment (what GHC assumes).
      See Note [StgWord alignment].
      
      Signed-off-by: default avatarSergei Trofimovich <siarheit@google.com>
      
      Test Plan: ran basic test on m68k qemu, it got past ASSERTs
      
      Reviewers: simonmar, austin, bgamari
      
      Reviewed By: bgamari
      
      Subscribers: thomie
      
      Differential Revision: https://phabricator.haskell.org/D1974
      
      GHC Trac Issues: #11395
      ade1a461
  7. Mar 05, 2016
  8. Mar 04, 2016
  9. Mar 02, 2016
    • Simon Peyton Jones's avatar
      Use tyConArity rather than (length tvs) · aea1e5db
      Simon Peyton Jones authored
      A bit more efficient
      aea1e5db
    • Simon Peyton Jones's avatar
      Fix an outright bug in expandTypeSynonyms · 286dc021
      Simon Peyton Jones authored
      The bug was in this code:
      
          go subst (TyConApp tc tys)
            | Just (tenv, rhs, tys') <- expandSynTyCon_maybe tc tys
            = let subst' = unionTCvSubst subst (mkTvSubstPrs tenv) in
              go subst' (mkAppTys rhs tys')
      
      This is wrong in two ways.
       * It is wrong to apply the expanded substitution to tys',
       * The unionTCvSubst is utterly wrong; after all, rhs is
         completely separate, and the union makes a non-idempotent
         substitution.
      
      It was the non-idempotency that gave the Lint failure in Trac #11665,
      when there was a type synonym whose RHS mentioned another type synonym,
      something like
      
        type T a b = a -> b
        type S x y = T y x
      
      It only affects SpecConstr because that's about the only place where
      expandTypeSyonym is called.  I tried to trigger the failure with a
      simple test case, but failed, so I have not added a regression test.
      
      Fortunately the solution is very simple and solid.
      
      FWIW, the culprit was 674654, "Add kind equalities to GHC".
      286dc021
  10. Mar 01, 2016
  11. Feb 29, 2016
Loading