[GHC] #8955: Syscall intrinsic
GHC
ghc-devs at haskell.org
Thu Aug 18 10:18:47 UTC 2016
#8955: Syscall intrinsic
-------------------------------------+-------------------------------------
Reporter: schyler | Owner:
Type: feature request | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.6.3
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Runtime | Unknown/Multiple
performance bug | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Changes (by slyfox):
* cc: slyfox (added)
Comment:
What is your vision on how it's supposed to be used in haskell?
A new 'foreign import' type per OS/arch target type?
A new syntax to be able to call assembly instructions directly from
haskell?
> Also, marginally increased speed for calling syscalls since it doesn't
need to go through libffi into C-land.
On at least i386 and amd64 GHC does not use libffi to call simple libc
functions.
For 'foreign import ccall unsafe' symbols GHC emits '''call <symbol>'''
instruction directly.
Native/via-libc difference might be in order of a few instructions.
Note the amount of existing indirections:
{{{#!hs
module M where
import Foreign.C
foreign import ccall unsafe "foo" c_foo :: CInt -> IO CInt
}}}
gets translated to
{{{
.section .data
.align 8
.align 1
.globl __stginit_M
.type __stginit_M, @object
__stginit_M:
.section .rodata
.align 8
.align 1
c2oj_str:
.byte 109
.byte 97
.byte 105
.byte 110
.byte 0
.section .data
.align 8
.align 1
.globl M_zdtrModule2_closure
.type M_zdtrModule2_closure, @object
M_zdtrModule2_closure:
.quad ghczmprim_GHCziTypes_TrNameS_static_info
.quad c2oj_str
.section .rodata
.align 8
.align 1
c2om_str:
.byte 77
.byte 0
.section .data
.align 8
.align 1
.globl M_zdtrModule1_closure
.type M_zdtrModule1_closure, @object
M_zdtrModule1_closure:
.quad ghczmprim_GHCziTypes_TrNameS_static_info
.quad c2om_str
.section .data
.align 8
.align 1
.globl M_zdtrModule_closure
.type M_zdtrModule_closure, @object
M_zdtrModule_closure:
.quad ghczmprim_GHCziTypes_Module_static_info
.quad M_zdtrModule2_closure+1
.quad M_zdtrModule1_closure+1
.quad 3
.section .data
.align 8
.align 1
r2eE_closure:
.quad r2eE_info
.section .text
.align 8
.align 8
.quad 8589934597
.quad 0
.quad 15
r2eE_info:
.Lc2ow:
leaq -8(%rbp),%rax
cmpq %r15,%rax
jb .Lc2oF
.Lc2oG:
movq $c2ot_info,-8(%rbp)
movq %r14,%rbx
addq $-8,%rbp
testb $7,%bl
jne .Lc2ot
.Lc2ou:
jmp *(%rbx)
.Lc2oJ:
movq $16,904(%r13)
jmp stg_gc_unpt_r1
.align 8
.quad 0
.quad 31
c2ot_info:
.Lc2ot:
addq $16,%r12
cmpq 856(%r13),%r12
ja .Lc2oJ
.Lc2oI:
movq 7(%rbx),%rdi
subq $8,%rsp
xorl %eax,%eax
call foo
addq $8,%rsp
movq $base_GHCziInt_I32zh_con_info,-8(%r12)
movslq %eax,%rax
movq %rax,(%r12)
leaq -7(%r12),%rbx
addq $8,%rbp
jmp *(%rbp)
.Lc2oF:
movl $r2eE_closure,%ebx
jmp *-8(%r13)
.size r2eE_info, .-r2eE_info
.section .data
.align 8
.align 1
.globl M_czufoo_closure
.type M_czufoo_closure, @object
M_czufoo_closure:
.quad M_czufoo_info
.section .text
.align 8
.align 8
.quad 8589934597
.quad 0
.quad 15
.globl M_czufoo_info
.type M_czufoo_info, @object
M_czufoo_info:
.Lc2oT:
jmp r2eE_info
.size M_czufoo_info, .-M_czufoo_info
.section .data.rel.ro
.align 8
.align 1
S2p0_srt:
.section .note.GNU-stack,"", at progbits
.ident "GHC 8.1.20160817"
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/8955#comment:3>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list