{-# language NoMonomorphismRestriction #-}
{-# language CPP #-}
{-# language DataKinds #-}
module CodeGen.X86.CallConv where
import Foreign
import Data.Monoid
import CodeGen.X86.Asm
import CodeGen.X86.CodeGen
#if defined (mingw32_HOST_OS) || defined (mingw64_HOST_OS)
callFun :: Operand RW S64 -> FunPtr a -> Code
callFun r p = do
  sub rsp 32
  mov r (fromIntegral $ ptrToIntPtr $ castFunPtrToPtr p)
  call r
  add rsp 32
#elif defined (darwin_HOST_OS)
callFun :: Operand RW S64 -> FunPtr a -> Code
callFun r p = do
  push r15              
  mov r15 15            
  not_ r15              
  and_ r15 rsp          
  xchg r15 rsp          
  mov r (fromIntegral $ ptrToIntPtr $ castFunPtrToPtr p)
  call r
  mov rsp r15           
  pop r15               
#else
callFun :: Operand RW S64 -> FunPtr a -> Code
callFun :: Operand 'RW 'S64 -> FunPtr a -> Code
callFun Operand 'RW 'S64
r FunPtr a
p = do
  Operand 'RW 'S64 -> Operand 'R 'S64 -> Code
forall (s :: Size) (r :: Access).
IsSize s =>
Operand 'RW s -> Operand r s -> Code
mov Operand 'RW 'S64
r (Operand 'R 'S64 -> Code) -> Operand 'R 'S64 -> Code
forall a b. (a -> b) -> a -> b
$ IntPtr -> Operand 'R 'S64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (IntPtr -> Operand 'R 'S64) -> IntPtr -> Operand 'R 'S64
forall a b. (a -> b) -> a -> b
$ Ptr Any -> IntPtr
forall a. Ptr a -> IntPtr
ptrToIntPtr (Ptr Any -> IntPtr) -> Ptr Any -> IntPtr
forall a b. (a -> b) -> a -> b
$ FunPtr a -> Ptr Any
forall a b. FunPtr a -> Ptr b
castFunPtrToPtr FunPtr a
p
  Operand 'RW 'S64 -> Code
forall (r :: Access). Operand r 'S64 -> Code
call Operand 'RW 'S64
r
#endif
saveNonVolatile :: Code -> Code
saveNonVolatile :: Code -> Code
saveNonVolatile Code
code = Code
prologue Code -> Code -> Code
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Code
code Code -> Code -> Code
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Code
epilogue Code -> Code -> Code
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Code
ret
saveR12R15 :: Code -> Code
saveR12R15 :: Code -> Code
saveR12R15 Code
code = do
  Operand Any 'S64 -> Code
forall (r :: Access). Operand r 'S64 -> Code
push Operand Any 'S64
forall (c :: Size -> *). FromReg c => c 'S64
r12
  Operand Any 'S64 -> Code
forall (r :: Access). Operand r 'S64 -> Code
push Operand Any 'S64
forall (c :: Size -> *). FromReg c => c 'S64
r13
  Operand Any 'S64 -> Code
forall (r :: Access). Operand r 'S64 -> Code
push Operand Any 'S64
forall (c :: Size -> *). FromReg c => c 'S64
r14
  Operand Any 'S64 -> Code
forall (r :: Access). Operand r 'S64 -> Code
push Operand Any 'S64
forall (c :: Size -> *). FromReg c => c 'S64
r15
  Code
code
  Operand 'RW 'S64 -> Code
pop Operand 'RW 'S64
forall (c :: Size -> *). FromReg c => c 'S64
r15
  Operand 'RW 'S64 -> Code
pop Operand 'RW 'S64
forall (c :: Size -> *). FromReg c => c 'S64
r14
  Operand 'RW 'S64 -> Code
pop Operand 'RW 'S64
forall (c :: Size -> *). FromReg c => c 'S64
r13
  Operand 'RW 'S64 -> Code
pop Operand 'RW 'S64
forall (c :: Size -> *). FromReg c => c 'S64
r12
#if defined (mingw32_HOST_OS) || defined (mingw64_HOST_OS)
arg1 = rcx
arg2 = rdx
arg3 = r8
arg4 = r9
result = rax
prologue = do
  push rbp
  push rbx
  push rdi
  push rsi
epilogue = do
  pop rsi
  pop rdi
  pop rbx
  pop rbp
#else
arg1 :: c 'S64
arg1 = c 'S64
forall (c :: Size -> *). FromReg c => c 'S64
rdi
arg2 :: c 'S64
arg2 = c 'S64
forall (c :: Size -> *). FromReg c => c 'S64
rsi
arg3 :: c 'S64
arg3 = c 'S64
forall (c :: Size -> *). FromReg c => c 'S64
rdx
arg4 :: c 'S64
arg4 = c 'S64
forall (c :: Size -> *). FromReg c => c 'S64
rcx
arg5 :: c 'S64
arg5 = c 'S64
forall (c :: Size -> *). FromReg c => c 'S64
r8
arg6 :: c 'S64
arg6 = c 'S64
forall (c :: Size -> *). FromReg c => c 'S64
r9
result :: c 'S64
result = c 'S64
forall (c :: Size -> *). FromReg c => c 'S64
rax
prologue :: Code
prologue = do
  Operand Any 'S64 -> Code
forall (r :: Access). Operand r 'S64 -> Code
push Operand Any 'S64
forall (c :: Size -> *). FromReg c => c 'S64
rbp
  Operand Any 'S64 -> Code
forall (r :: Access). Operand r 'S64 -> Code
push Operand Any 'S64
forall (c :: Size -> *). FromReg c => c 'S64
rbx
epilogue :: Code
epilogue = do
  Operand 'RW 'S64 -> Code
pop Operand 'RW 'S64
forall (c :: Size -> *). FromReg c => c 'S64
rbx
  Operand 'RW 'S64 -> Code
pop Operand 'RW 'S64
forall (c :: Size -> *). FromReg c => c 'S64
rbp
#endif