summaryrefslogtreecommitdiff
path: root/ghc/compiler/absCSyn/CallConv.lhs
blob: 712a241c20a06eed29e1924c8eb4b9dd2655c968 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
%
% (c) The GRASP/AQUA Project, Glasgow University, 1992-1996
%
\section[Calling conventions]{External calling conventions}

\begin{code}
module CallConv
       (
	 CallConv
       , pprCallConv
       , callConvToInt

       , stdCallConv
       , cCallConv
       , defaultCallConv
       , callConvAttribute
       , decorateExtName
       ) where

#include "HsVersions.h"

import Outputable
import PrimRep     ( PrimRep, getPrimRepSizeInBytes )
\end{code}

\begin{code}
type CallConv = Int

pprCallConv :: CallConv -> SDoc
pprCallConv 0 = ptext SLIT("__stdcall")
pprCallConv _ = ptext SLIT("_ccall")

stdCallConv :: CallConv
stdCallConv = 0

cCallConv  :: CallConv
cCallConv = 1

defaultCallConv :: CallConv
defaultCallConv = cCallConv

callConvToInt :: CallConv -> Int
callConvToInt x = x
\end{code}

Generate the gcc attribute corresponding to the given
calling convention (used by PprAbsC):

ToDo: The stdcall calling convention is x86 (win32) specific,
so perhaps we should emit a warning if it's being used on other
platforms.

\begin{code}
callConvAttribute :: CallConv -> String
callConvAttribute cc
 | cc == stdCallConv   = "__attribute__((stdcall))"
 | cc == cCallConv     = ""
 | otherwise	       = panic ("callConvAttribute: cannot handle" ++ showSDoc (pprCallConv cc))

\end{code}

For stdcall and Win32, the linker expects to see names of the form 
 
   "f@n"

where n is the size (in 8-bit bytes) of the parameter area
that is pushed onto the stack before invocation. We take
care of mangling the function name here. 

This name mangler is only used by the x86 native code generator.

\begin{code}
decorateExtName :: CallConv -> FAST_STRING -> [PrimRep] -> FAST_STRING
decorateExtName cc fs ps
 | cc /= stdCallConv = fs
 | otherwise	     = fs _APPEND_ (_PK_ ('@':show (size::Int)))
 where
  size = sum (map (adjustParamSize.getPrimRepSizeInBytes) ps)

  adjustParamSize sz =  paramBoundary * ((sz + paramBoundary - 1) `div` paramBoundary)

  paramBoundary = 4

\end{code}