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..

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@haskell.org] On Behalf Of Ömer
| Sinan Agacan
| Sent: 06 December 2015 18:25
| To: ghc-devs

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
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@haskell.org] On Behalf Of Ömer | Sinan Agacan | Sent: 06 December 2015 18:25 | To: ghc-devs
| 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@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

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
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
: 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@haskell.org] On Behalf Of Ömer | Sinan Agacan | Sent: 06 December 2015 18:25 | To: ghc-devs
| 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@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@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs

Simon's right, you need an explicit conversion, and unfortunately those conversions don't currently exist. You would have to add them to the MachOp type, and implement them in each of the native code generators. The good news is that if you did this, we could implement cheap conversions between the IEEE floating point types and their representations as unboxed integers, which is currently done by poking the values to memory and then peeking them back at the desired type. There's a ticket for this around somewhere.... Cheers Simon On 07/12/2015 12:23, Simon Peyton Jones wrote:
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@haskell.org] On Behalf Of Ömer | Sinan Agacan | Sent: 06 December 2015 18:25 | To: ghc-devs
| 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@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@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs

Thanks for all the answers,
Simon, do you remember anything about the ticket about converting between
floating point types and integers? I spend quite a bit of time in Trac
searching for this but couldn't find it.
Before implementing a new primop, MachOp, and code generation functions for
that I tried this: Since type signature of this new primop will be same as
float2Int# I thought maybe I should first make current implementation working,
and then I can just change the primop to coerceFloat2Int# and it would work.
However I'm still this same problem(illegal assembly). What I changed is I
looked at the GHC-generated, working STG code that uses float2Int#, and tried
to generate a very similar code myself. The change I had to make for this was
to use a case expression instead of let expression to bind result of this
primop.
Here's an example. This STG is working fine:
sat_s1Ic :: GHC.Types.Float -> GHC.Types.IO () =
\r srt:SRT:[0B :-> System.IO.print,
rUB :-> GHC.Show.$fShowInt] [ds_s1I7]
case
ds_s1I7 :: GHC.Types.Float :: Alg GHC.Types.Float
of
(wild_s1I8 :: GHC.Types.Float)
{ GHC.Types.F# (f_s1I9 :: GHC.Prim.Float#) ->
case
float2Int# [(f_s1I9 :: GHC.Prim.Float#)] :: Prim
GHC.Prim.Int#
of
(sat_s1Ia :: GHC.Prim.Int#)
{ __DEFAULT ->
let {
sat_s1Ib :: GHC.Types.Int =
NO_CCS GHC.Types.I#! [(sat_s1Ia ::
GHC.Prim.Int#)];
} in
System.IO.print
:: forall a_aUq. GHC.Show.Show a_aUq =>
a_aUq -> GHC.Types.IO ()
(GHC.Show.$fShowInt :: GHC.Show.Show
GHC.Types.Int)
(sat_s1Ib :: GHC.Types.Int);
};
};
(Sorry for extra noisy output, I changed Outputable instances to print some
extra info)
This code is generated by GHC for a program that uses the primop directly and
it's working. This is the code generated by my pass:
Main.main2 :: [GHC.Types.Char] =
\u srt:SRT:[r4 :-> Main.showEither2] []
case
case
float2Int# [1.2#] :: Prim GHC.Prim.Int#
of
(co_g21m :: GHC.Prim.Int#)
{ __DEFAULT -> (#,#) [2## (co_g21m :: GHC.Prim.Int#)];
} :: UbxTup 2
of
(sat_s21b :: (# GHC.Prim.Int#, GHC.Prim.Int# #))
{ (#,#) (sat_g21R :: GHC.Prim.Int#) (sat_g21S :: GHC.Prim.Int#) ->
Main.showEither2
:: (# GHC.Prim.Int#, GHC.Prim.Int# #) -> [GHC.Types.Char]
(sat_g21R :: GHC.Prim.Int#) (sat_g21S :: GHC.Prim.Int#);
};
Types look correct, and I'm using a case expression to bind the result of the
primop. But generated assembly for this is still invalid! I'm wondering if
there are some invariants that I'm invalidating here, even although -dstg-lint
is passing. Does anyone know what I might be doing wrong here?
One thing that I'm not being very careful is the information about live
variables, but I don't see how it might be related with this illegal
instruction error.
Thanks again..
2015-12-07 13:57 GMT-05:00 Simon Marlow
Simon's right, you need an explicit conversion, and unfortunately those conversions don't currently exist. You would have to add them to the MachOp type, and implement them in each of the native code generators.
The good news is that if you did this, we could implement cheap conversions between the IEEE floating point types and their representations as unboxed integers, which is currently done by poking the values to memory and then peeking them back at the desired type. There's a ticket for this around somewhere....
Cheers Simon
On 07/12/2015 12:23, Simon Peyton Jones wrote:
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@haskell.org] On Behalf Of Ömer | Sinan Agacan | Sent: 06 December 2015 18:25 | To: ghc-devs
| 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@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@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs

Omer
Honestly I'm out of my depth here, and so time-poor that I don't think I can realistically help much. I hope others can be more useful!
Simon
| -----Original Message-----
| From: Ömer Sinan Ağacan [mailto:omeragacan@gmail.com]
| Sent: 10 December 2015 02:46
| To: Simon Marlow

On 10/12/2015 02:45, Ömer Sinan Ağacan wrote:
Thanks for all the answers,
Simon, do you remember anything about the ticket about converting between floating point types and integers? I spend quite a bit of time in Trac searching for this but couldn't find it.
Sorry, I searched too but I couldn't find it. I did find an implementation of the conversion in GHC (ByteCodeAsm.mkLitD).
Before implementing a new primop, MachOp, and code generation functions for that I tried this: Since type signature of this new primop will be same as float2Int# I thought maybe I should first make current implementation working, and then I can just change the primop to coerceFloat2Int# and it would work.
However I'm still this same problem(illegal assembly). What I changed is I looked at the GHC-generated, working STG code that uses float2Int#, and tried to generate a very similar code myself. The change I had to make for this was to use a case expression instead of let expression to bind result of this primop.
Here's an example. This STG is working fine:
sat_s1Ic :: GHC.Types.Float -> GHC.Types.IO () = \r srt:SRT:[0B :-> System.IO.print, rUB :-> GHC.Show.$fShowInt] [ds_s1I7] case ds_s1I7 :: GHC.Types.Float :: Alg GHC.Types.Float of (wild_s1I8 :: GHC.Types.Float) { GHC.Types.F# (f_s1I9 :: GHC.Prim.Float#) -> case float2Int# [(f_s1I9 :: GHC.Prim.Float#)] :: Prim GHC.Prim.Int# of (sat_s1Ia :: GHC.Prim.Int#) { __DEFAULT -> let { sat_s1Ib :: GHC.Types.Int = NO_CCS GHC.Types.I#! [(sat_s1Ia :: GHC.Prim.Int#)]; } in System.IO.print :: forall a_aUq. GHC.Show.Show a_aUq => a_aUq -> GHC.Types.IO () (GHC.Show.$fShowInt :: GHC.Show.Show GHC.Types.Int) (sat_s1Ib :: GHC.Types.Int); }; };
(Sorry for extra noisy output, I changed Outputable instances to print some extra info)
This code is generated by GHC for a program that uses the primop directly and it's working. This is the code generated by my pass:
Main.main2 :: [GHC.Types.Char] = \u srt:SRT:[r4 :-> Main.showEither2] [] case case float2Int# [1.2#] :: Prim GHC.Prim.Int# of (co_g21m :: GHC.Prim.Int#) { __DEFAULT -> (#,#) [2## (co_g21m :: GHC.Prim.Int#)]; } :: UbxTup 2 of (sat_s21b :: (# GHC.Prim.Int#, GHC.Prim.Int# #)) { (#,#) (sat_g21R :: GHC.Prim.Int#) (sat_g21S :: GHC.Prim.Int#) -> Main.showEither2 :: (# GHC.Prim.Int#, GHC.Prim.Int# #) -> [GHC.Types.Char] (sat_g21R :: GHC.Prim.Int#) (sat_g21S :: GHC.Prim.Int#); };
Types look correct, and I'm using a case expression to bind the result of the primop. But generated assembly for this is still invalid! I'm wondering if there are some invariants that I'm invalidating here, even although -dstg-lint is passing. Does anyone know what I might be doing wrong here?
One thing that I'm not being very careful is the information about live variables, but I don't see how it might be related with this illegal instruction error.
I'm not sure what you did to get to this point, but let me elaborate on what I think is needed: - Add primops for the conversions - Add appropriate MachOps for the conversions (F32 -> I32, F64 -> I64) - Make sure the primops get compiled into the appropriate MachOps (see StgCmmPrim) - Implement those MachOps in the native code generator (X86/CodeGen.hs). For this part you'll need to figure out what the appropriate x86/x86_64 instructions to generate are; it may be that you need to go via memory, which would be unfortunate. Cheers, Simon
Thanks again..
2015-12-07 13:57 GMT-05:00 Simon Marlow
: Simon's right, you need an explicit conversion, and unfortunately those conversions don't currently exist. You would have to add them to the MachOp type, and implement them in each of the native code generators.
The good news is that if you did this, we could implement cheap conversions between the IEEE floating point types and their representations as unboxed integers, which is currently done by poking the values to memory and then peeking them back at the desired type. There's a ticket for this around somewhere....
Cheers Simon
On 07/12/2015 12:23, Simon Peyton Jones wrote:
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@haskell.org] On Behalf Of Ömer | Sinan Agacan | Sent: 06 December 2015 18:25 | To: ghc-devs
| 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@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@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs

Simon Marlow
I'm not sure what you did to get to this point, but let me elaborate on what I think is needed:
- Add primops for the conversions - Add appropriate MachOps for the conversions (F32 -> I32, F64 -> I64) - Make sure the primops get compiled into the appropriate MachOps (see StgCmmPrim) - Implement those MachOps in the native code generator (X86/CodeGen.hs).
For this part you'll need to figure out what the appropriate x86/x86_64 instructions to generate are; it may be that you need to go via memory, which would be unfortunate.
Ömer, LLVM can be a useful tool for working out proper instruction generation. You may find this LLVM snippet helpful (along with some simplified output), $ cat hi.ll define i32 @float_to_int(float %x) { %x1 = fadd float 1.0, %x; %y = bitcast float %x1 to i32; ret i32 %y; } define i64 @double_to_int(double %x) { %x1 = fadd double 0.1, %x; %y = bitcast double %x1 to i64; ret i64 %y; } $ llc hi.ll --march=x86 && cat hi.s float_to_int: # @float_to_int fld1 fadds 8(%esp) fstps (%esp) movl (%esp), %eax popl %edx retl double_to_int: # @double_to_int fldl 16(%esp) faddl .LCPI1_0 fstpl (%esp) movl (%esp), %eax movl 4(%esp), %edx addl $12, %esp retl $ llc hi.ll --march=x86_64 && cat hi.s float_to_int: # @float_to_int addss .LCPI0_0(%rip), %xmm0 movd %xmm0, %eax double_to_int: # @double_to_int addsd .LCPI1_0(%rip), %xmm0 movd %xmm0, %rax retq
participants (5)
-
Ben Gamari
-
Reid Barton
-
Simon Marlow
-
Simon Peyton Jones
-
Ömer Sinan Ağacan