[GHC] #9719: Improve `mkInteger` interface

GHC ghc-devs at haskell.org
Fri Oct 24 08:48:28 UTC 2014


#9719: Improve `mkInteger` interface
-------------------------------------+-------------------------------------
              Reporter:  hvr         |            Owner:
                  Type:  task        |           Status:  new
              Priority:  low         |        Milestone:  7.12.1
             Component:  Compiler    |          Version:
            Resolution:              |         Keywords:  Integer
      Operating System:              |     Architecture:  Unknown/Multiple
  Unknown/Multiple                   |       Difficulty:  Unknown
       Type of failure:              |       Blocked By:
  None/Unknown                       |  Related Tickets:
             Test Case:              |
              Blocking:              |
Differential Revisions:              |
-------------------------------------+-------------------------------------
Description changed by hvr:

Old description:

> `mkInteger` is the current operation provided by the `Integer` libraries
> to construct (large) integer values. The current type-signature is
>
> {{{#!hs
> mkInteger :: Bool   -- sign-bit
>           -> [Int]  -- absolute value in 31 bit chunks, least significant
> first
>           -> Integer
> }}}
>
> A somewhat pathological example of why this representation is not so nice
> is the following simple CAF
>
> {{{#!hs
> c :: Integer
> c = 0xf000000000000000
> }}}
>
> that (this is for a 64bit arch!) gets compiled into the following STG:
>
> {{{
> ==================== STG syntax: ====================
> sat_sJQ :: GHC.Types.Int
> [LclId, Str=DmdType] =
>     NO_CCS GHC.Types.I#! [3];
> sat_sJR :: [GHC.Types.Int]
> [LclId, Str=DmdType] =
>     NO_CCS :! [sat_sJQ GHC.Types.[]];
> sat_sJP :: GHC.Types.Int
> [LclId, Str=DmdType] =
>     NO_CCS GHC.Types.I#! [1610612736];
> sat_sJS :: [GHC.Types.Int]
> [LclId, Str=DmdType] =
>     NO_CCS :! [sat_sJP sat_sJR];
> sat_sJO :: GHC.Types.Int
> [LclId, Str=DmdType] =
>     NO_CCS GHC.Types.I#! [0];
> sat_sJT :: [GHC.Types.Int]
> [LclId, Str=DmdType] =
>     NO_CCS :! [sat_sJO sat_sJS];
> Foo.c :: GHC.Integer.Type.Integer
> [GblId, Str=DmdType] =
>     \u srt:SRT:[0Y :-> GHC.Integer.Type.mkInteger, sJT :-> sat_sJT] []
>         GHC.Integer.Type.mkInteger GHC.Types.True sat_sJT;
> }}}
>

>
> Instead a more "natural" `mkInteger` would be desirable, possibly in the
> style of `unpackCString#`, in terms of a packed/unboxed vector of
> machine-word-sized chunks. A better `mkInteger` could then take a
> `ByteArray#` or a `Addr#` + length instead, e.g.
>
> {{{#!hs
> mkInteger :: Int#    -- signum(n) = sign of encoded Integer
>                      -- abs(n)    = number of machine-word sized chunks
>           -> Addr#   -- pointer to start of machine-word sized chunks,
>                      -- least-significant chunk first
>           -> Integer
> }}}

New description:

 `mkInteger` is the current operation provided by the `Integer` libraries
 to construct (large) integer values. The current type-signature is

 {{{#!hs
 mkInteger :: Bool   -- sign-bit
           -> [Int]  -- absolute value in 31 bit chunks, least significant
 first
           -> Integer
 }}}

 A somewhat pathological example of why this representation is not so nice
 is the following simple CAF

 {{{#!hs
 c :: Integer
 c = 0xf000000000000000
 }}}

 that (this is for a 64bit arch!) gets compiled into the following STG:

 {{{
 ==================== STG syntax: ====================
 sat_sJQ :: GHC.Types.Int
 [LclId, Str=DmdType] =
     NO_CCS GHC.Types.I#! [3];
 sat_sJR :: [GHC.Types.Int]
 [LclId, Str=DmdType] =
     NO_CCS :! [sat_sJQ GHC.Types.[]];
 sat_sJP :: GHC.Types.Int
 [LclId, Str=DmdType] =
     NO_CCS GHC.Types.I#! [1610612736];
 sat_sJS :: [GHC.Types.Int]
 [LclId, Str=DmdType] =
     NO_CCS :! [sat_sJP sat_sJR];
 sat_sJO :: GHC.Types.Int
 [LclId, Str=DmdType] =
     NO_CCS GHC.Types.I#! [0];
 sat_sJT :: [GHC.Types.Int]
 [LclId, Str=DmdType] =
     NO_CCS :! [sat_sJO sat_sJS];
 Foo.c :: GHC.Integer.Type.Integer
 [GblId, Str=DmdType] =
     \u srt:SRT:[0Y :-> GHC.Integer.Type.mkInteger, sJT :-> sat_sJT] []
         GHC.Integer.Type.mkInteger GHC.Types.True sat_sJT;
 }}}

 Moreover, determining how much space to allocate for the resulting
 `Integer` is a bit work as it for one, you need to traverse the list
 twice, and then you can't simply derive the exact allocation amount by the
 list-length alone due to the odd 31-bit chunks.

 Instead a more "natural" `mkInteger` would be desirable, possibly in the
 style of `unpackCString#`, in terms of a packed/unboxed vector of machine-
 word-sized chunks. A better `mkInteger` could then take a `ByteArray#` or
 a `Addr#` + length instead, e.g.

 {{{#!hs
 mkInteger :: Int#    -- signum(n) = sign of encoded Integer
                      -- abs(n)    = number of machine-word sized chunks
           -> Addr#   -- pointer to start of machine-word sized chunks,
                      -- least-significant chunk first
           -> Integer
 }}}

--

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


More information about the ghc-tickets mailing list