[GHC] #14664: "GHC.Integer can't throw exceptions" is wrong

GHC ghc-devs at haskell.org
Fri Jan 12 06:11:47 UTC 2018


#14664: "GHC.Integer can't throw exceptions" is wrong
-------------------------------------+-------------------------------------
           Reporter:  Zemyla         |             Owner:  (none)
               Type:  feature        |            Status:  new
  request                            |
           Priority:  low            |         Milestone:
          Component:  Compiler       |           Version:  8.2.2
           Keywords:                 |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  None/Unknown
  Unknown/Multiple                   |
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 The various integer packages, and anything else that might be loaded
 before the Prelude, goes through contortions to report errors, or else
 doesn't report them and crashes, because those packages are compiled
 before the `Exception` type is available.

 However, there is a way to throw exceptions from code that only has access
 to `ghc-prim`. It relies on the fact that the RTS itself throws an
 exception in a certain circumstance: when `atomically` is called from
 within `atomically`.

 This gives us the following:

 {{{#!hs
 {-# LANGUAGE MagicHash, UnboxedTuples, NoImplicitPrelude #-}
 import GHC.Prim
 import GHC.Magic

 atomicLoop :: State# RealWorld -> (# State# RealWorld, a #)
 atomicLoop s = atomically atomicLoop s

 exception :: a
 exception = runRW# (\s -> case atomicLoop s of
   (# _, a #) -> a)
 }}}

 I think that `integer-simple` and `integer-gmp`, and maybe the very
 earliest parts of `base`, are the only packages that would benefit from
 this circumlocution; however, having the error be a catchable exception
 rather than a straight-up crash has benefits.

 Priority is low because I don't think there have been any bugs regarding
 GHC.Integer crashing; I just think it might make the code a bit more
 elegant.

-- 
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14664>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list