question about coercions between primitive types in STG level
Reid Barton
rwbarton at gmail.com
Mon Dec 7 16:58:40 UTC 2015
Note that int2Float# converts an Int# to the Float# with the same numeric
value (e.g. 72 -> 72.0), not the one with the same bit representation
(which doesn't really make sense anyways since Int# and Float# may be
different sizes). So I think it's not what you want.
At least on x86_64, it's rather expensive to move a bit representation
between a general-purpose register and a floating-point (xmm) register. As
far as I know, the only way is to go through memory. This may have design
implications for your work. For example, if you have an unboxed sum of two
Double#s, it would certainly be better to store the data part in a
floating-point register than a general-purpose register. If you have a sum
that contains both integral and floating-point variants, it may be better
depending on the situation to store its data in integer registers,
floating-point registers, or a combination (using extra space). I doubt you
want to give the programmer that much control though... One option would
be, at least for a first version, treat Int# and Double# and Float# as
three incompatible kinds of memory/registers that cannot alias each other.
As for your assembly code, can you provide the Cmm code that compiles to
it? But in any case "movq 16(%xmm1),%rax" is certainly wrong, it should be
offseting 16 bytes from a register like Sp or R1.
Regards,
Reid Barton
On Mon, Dec 7, 2015 at 11:21 AM, Ömer Sinan Ağacan <omeragacan at gmail.com>
wrote:
> Thanks Simon, primops worked fine, but not I'm getting assembler
> errors(even
> though -dcore-lint, -dstg-lint and -dcmm-lint are all passing).
>
> The error is caused by this STG expression:
>
> case (#,#) [ds_gX8 ds_gX9] of _ {
> (#,#) tag_gWR ubx_gWS ->
> case tag_gWR of tag_gWR {
> __DEFAULT -> GHC.Err.undefined;
> 1# ->
> let {
> sat_sWD :: [GHC.Types.Char] =
> \u srt:SRT:[roK :-> GHC.Show.$fShowInt] []
> let { sat_sWC :: GHC.Types.Int = NO_CCS
> GHC.Types.I#! [ubx_gWS];
> } in GHC.Show.show GHC.Show.$fShowInt sat_sWC;
> } in
> let {
> sat_sWB :: [GHC.Types.Char] =
> \u srt:SRT:[0k :-> GHC.CString.unpackCString#] []
> GHC.CString.unpackCString# "Left "#;
> } in GHC.Base.++ sat_sWB sat_sWD;
> 2# ->
> let {
> co_gWT :: GHC.Prim.Float# =
> sat-only \s [] int2Float# [ubx_gWS]; } in
> let {
> sat_sWH :: [GHC.Types.Char] =
> \u srt:SRT:[rd2 :-> GHC.Float.$fShowFloat] []
> let { sat_sWG :: GHC.Types.Float = NO_CCS
> GHC.Types.F#! [co_gWT];
> } in GHC.Show.show GHC.Float.$fShowFloat
> sat_sWG; } in
> let {
> sat_sWF :: [GHC.Types.Char] =
> \u srt:SRT:[0k :-> GHC.CString.unpackCString#] []
> GHC.CString.unpackCString# "Right "#;
> } in GHC.Base.++ sat_sWF sat_sWH;
> };
> };
>
> In the first case(when the tag is 1#) I'm not doing any coercions, second
> argument of the tuple is directly used. In the second case(when the tag is
> 2#),
> I'm generating this let-binding:
>
> let {
> co_gWT :: GHC.Prim.Float# =
> sat-only \s [] int2Float# [ubx_gWS]; }
>
> And then in the RHS of case alternative I'm using co_gWT instead of
> ubx_gWS,
> but for some reason GHC is generating invalid assembly for this expression:
>
> /tmp/ghc2889_0/ghc_2.s: Assembler messages:
>
> /tmp/ghc2889_0/ghc_2.s:125:0: error:
> Error: `16(%xmm1)' is not a valid base/index expression
> `gcc' failed in phase `Assembler'. (Exit code: 1)
>
> The assembly seems to be:
>
> ==================== Asm code ====================
> .section .text
> .align 8
> .quad 4294967296
> .quad 18
> co_gWT_info:
> _cY7:
> _cY9:
> movq 16(%xmm1),%rax
> cvtsi2ssq %rax,%xmm0
> movss %xmm0,%xmm1
> jmp *(%rbp)
> .size co_gWT_info, .-co_gWT_info
>
> Do you have any ideas why this may be happening?
>
> 2015-12-07 7:23 GMT-05:00 Simon Peyton Jones <simonpj at microsoft.com>:
> > If memory serves, there are primops for converting between unboxed
> values of different widths.
> >
> > Certainly converting between a float and a non-float will require an
> instruction on some architectures, since they use different register sets.
> >
> > Re (2) I have no idea. You'll need to get more information... pprTrace
> or something.
> >
> > Simon
> >
> > | -----Original Message-----
> > | From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of
> Ömer
> > | Sinan Agacan
> > | Sent: 06 December 2015 18:25
> > | To: ghc-devs <ghc-devs at haskell.org>
> > | Subject: question about coercions between primitive types in STG level
> > |
> > | Hi all,
> > |
> > | In my compiler pass(D1559, see ElimUbxSums.hs) I'm doing some unsafe
> > | coercions at the STG level. It works fine for lifted types, but for
> > | unlifted ones I'm having some problems. What I'm trying to do is given
> > | a number of primitive types I'm finding the one with biggest size, and
> > | then generating a constructor that takes this biggest primitive type
> > | as argument.
> > |
> > | The problem is that this is not working very well - GHC is generating
> > | illegal instructions that try to load a F32 value to a register
> > | allocated for I64, using movss instruction.
> > |
> > | CoreLint is catching this error and printing this:
> > |
> > | Cmm lint error:
> > | in basic block c1hF
> > | in assignment:
> > | _g16W::I64 = 4.5 :: W32; // CmmAssign
> > | Reg ty: I64
> > | Rhs ty: F32
> > |
> > | So I have two questions about this:
> > |
> > | 1. Is there a way to safely do this? What are my options here? What
> > | I'm trying
> > | to do is to use a single data constructor field for different
> > | primitive
> > | types. The field is guaranteed to be as big as necessary.
> > |
> > | 2. In the Cmm code shown above, the type annotation is showing `W32`
> > | but in the
> > | error message it says `F32`. I'm confused about this, is this error
> > | message
> > | given because the sizes don't match? (64bits vs 32bits) Why the
> > | type
> > | annotation says W32 while the value has type F32?
> > |
> > | Thanks..
> > | _______________________________________________
> > | ghc-devs mailing list
> > | ghc-devs at haskell.org
> > |
> https://na01.safelinks.protection.outlook.com/?url=http%3a%2f%2fmail.h
> > | askell.org%2fcgi-bin%2fmailman%2flistinfo%2fghc-
> > | devs&data=01%7c01%7csimonpj%40064d.mgd.microsoft.com
> %7ced6a1fbfa6254e5
> > | 2a7d808d2fe6a9a63%7c72f988bf86f141af91ab2d7cd011db47%7c1&sdata=7j3fQs4
> > | ox67SZbA4jv4uPVVdvp5X5yUUuMaqp4sh%2fpg%3d
> _______________________________________________
> ghc-devs mailing list
> ghc-devs at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-devs/attachments/20151207/d1ce064b/attachment.html>
More information about the ghc-devs
mailing list