Skip to content
GitLab
Projects
Groups
Snippets
Help
Loading...
Help
Help
Support
Community forum
Keyboard shortcuts
?
Submit feedback
Sign in / Register
Toggle navigation
Glasgow Haskell Compiler
Project overview
Project overview
Details
Activity
Releases
Repository
Repository
Files
Commits
Branches
Tags
Contributors
Graph
Compare
Locked Files
Issues
0
Issues
0
List
Boards
Labels
Service Desk
Milestones
Iterations
Merge Requests
0
Merge Requests
0
Requirements
Requirements
List
CI / CD
CI / CD
Pipelines
Jobs
Schedules
Security & Compliance
Security & Compliance
Dependency List
License Compliance
Operations
Operations
Incidents
Environments
Packages & Registries
Packages & Registries
Package Registry
Container Registry
Analytics
Analytics
CI / CD
Code Review
Insights
Issue
Repository
Value Stream
Wiki
Wiki
Snippets
Snippets
Members
Members
Collapse sidebar
Close sidebar
Activity
Graph
Create a new issue
Jobs
Commits
Issue Boards
Open sidebar
Shayne Fletcher
Glasgow Haskell Compiler
Commits
da15d0c5
Commit
da15d0c5
authored
Jun 13, 2011
by
Edward Z. Yang
Browse files
Options
Browse Files
Download
Email Patches
Plain Diff
Remove type synonyms for CmmFormals, CmmActuals (and hinted versions).
Signed-off-by:
Edward Z. Yang
<
ezyang@mit.edu
>
parent
f3a1b28e
Changes
19
Hide whitespace changes
Inline
Side-by-side
Showing
19 changed files
with
65 additions
and
71 deletions
+65
-71
compiler/cmm/CmmCvt.hs
compiler/cmm/CmmCvt.hs
+1
-1
compiler/cmm/CmmDecl.hs
compiler/cmm/CmmDecl.hs
+1
-3
compiler/cmm/CmmNode.hs
compiler/cmm/CmmNode.hs
+4
-4
compiler/cmm/CmmProcPoint.hs
compiler/cmm/CmmProcPoint.hs
+1
-1
compiler/cmm/MkGraph.hs
compiler/cmm/MkGraph.hs
+17
-17
compiler/cmm/OldCmm.hs
compiler/cmm/OldCmm.hs
+6
-8
compiler/cmm/OldCmmUtils.hs
compiler/cmm/OldCmmUtils.hs
+2
-2
compiler/cmm/PprC.hs
compiler/cmm/PprC.hs
+2
-2
compiler/cmm/cmm-notes
compiler/cmm/cmm-notes
+0
-2
compiler/codeGen/CgForeignCall.hs
compiler/codeGen/CgForeignCall.hs
+3
-3
compiler/codeGen/CgInfoTbls.hs
compiler/codeGen/CgInfoTbls.hs
+2
-2
compiler/codeGen/CgMonad.lhs
compiler/codeGen/CgMonad.lhs
+1
-1
compiler/codeGen/CgPrimOp.hs
compiler/codeGen/CgPrimOp.hs
+2
-2
compiler/codeGen/StgCmmForeign.hs
compiler/codeGen/StgCmmForeign.hs
+8
-8
compiler/codeGen/StgCmmMonad.hs
compiler/codeGen/StgCmmMonad.hs
+2
-2
compiler/llvmGen/LlvmCodeGen/CodeGen.hs
compiler/llvmGen/LlvmCodeGen/CodeGen.hs
+2
-2
compiler/nativeGen/PPC/CodeGen.hs
compiler/nativeGen/PPC/CodeGen.hs
+4
-4
compiler/nativeGen/SPARC/CodeGen/CCall.hs
compiler/nativeGen/SPARC/CodeGen/CCall.hs
+3
-3
compiler/nativeGen/X86/CodeGen.hs
compiler/nativeGen/X86/CodeGen.hs
+4
-4
No files found.
compiler/cmm/CmmCvt.hs
View file @
da15d0c5
...
...
@@ -83,7 +83,7 @@ toZgraph fun_name g@(Old.ListGraph (Old.BasicBlock id ss : other_blocks)) =
strip_hints
::
[
Old
.
CmmHinted
a
]
->
[
a
]
strip_hints
=
map
Old
.
hintlessCmm
convert_target
::
Old
.
CmmCallTarget
->
Old
.
HintedCmmFormals
->
Old
.
HintedCmmActuals
->
ForeignTarget
convert_target
::
Old
.
CmmCallTarget
->
[
Old
.
HintedCmmFormal
]
->
[
Old
.
HintedCmmActual
]
->
ForeignTarget
convert_target
(
Old
.
CmmCallee
e
cc
)
ress
args
=
ForeignTarget
e
(
ForeignConvention
cc
(
map
Old
.
cmmHint
args
)
(
map
Old
.
cmmHint
ress
))
convert_target
(
Old
.
CmmPrim
op
)
_ress
_args
=
PrimTarget
op
...
...
compiler/cmm/CmmDecl.hs
View file @
da15d0c5
...
...
@@ -10,7 +10,7 @@ module CmmDecl (
GenCmm
(
..
),
GenCmmTop
(
..
),
CmmInfoTable
(
..
),
HasStaticClosure
,
ClosureTypeInfo
(
..
),
ConstrDescription
,
ProfilingInfo
(
..
),
ClosureTypeTag
,
CmmActual
,
Cmm
Actuals
,
CmmFormal
,
CmmFormals
,
ForeignHint
(
..
),
CmmActual
,
Cmm
Formal
,
ForeignHint
(
..
),
CmmStatic
(
..
),
Section
(
..
),
)
where
...
...
@@ -114,8 +114,6 @@ type SelectorOffset = StgWord
type
CmmActual
=
CmmExpr
type
CmmFormal
=
LocalReg
type
CmmActuals
=
[
CmmActual
]
type
CmmFormals
=
[
CmmFormal
]
data
ForeignHint
=
NoHint
|
AddrHint
|
SignedHint
...
...
compiler/cmm/CmmNode.hs
View file @
da15d0c5
...
...
@@ -42,8 +42,8 @@ data CmmNode e x where
-- Like a "fat machine instruction"; can occur
-- in the middle of a block
ForeignTarget
->
-- call target
CmmFormals
->
-- zero or more results
CmmActuals
->
-- zero or more arguments
[
CmmFormal
]
->
-- zero or more results
[
CmmActual
]
->
-- zero or more arguments
CmmNode
O
O
-- Semantics: kills only result regs; all other regs (both GlobalReg
-- and LocalReg) are preserved. But there is a current
...
...
@@ -105,8 +105,8 @@ data CmmNode e x where
CmmForeignCall
::
{
-- A safe foreign call; see Note [Foreign calls]
-- Always the last node of a block
tgt
::
ForeignTarget
,
-- call target and convention
res
::
CmmFormals
,
-- zero or more results
args
::
CmmActuals
,
-- zero or more arguments; see Note [Register parameter passing]
res
::
[
CmmFormal
],
-- zero or more results
args
::
[
CmmActual
],
-- zero or more arguments; see Note [Register parameter passing]
succ
::
Label
,
-- Label of continuation
updfr
::
UpdFrameOffset
,
-- where the update frame is (for building infotable)
intrbl
::
Bool
-- whether or not the call is interruptible
...
...
compiler/cmm/CmmProcPoint.hs
View file @
da15d0c5
...
...
@@ -234,7 +234,7 @@ algorithm would be just as good, so that's what we do.
-}
data
Protocol
=
Protocol
Convention
CmmFormals
Area
data
Protocol
=
Protocol
Convention
[
CmmFormal
]
Area
deriving
Eq
instance
Outputable
Protocol
where
ppr
(
Protocol
c
fs
a
)
=
text
"Protocol"
<+>
ppr
c
<+>
ppr
fs
<+>
ppr
a
...
...
compiler/cmm/MkGraph.hs
View file @
da15d0c5
...
...
@@ -119,25 +119,25 @@ mkAssign :: CmmReg -> CmmExpr -> CmmAGraph
mkStore
::
CmmExpr
->
CmmExpr
->
CmmAGraph
---------- Calls
mkCall
::
CmmExpr
->
(
Convention
,
Convention
)
->
CmmFormals
->
CmmActuals
->
mkCall
::
CmmExpr
->
(
Convention
,
Convention
)
->
[
CmmFormal
]
->
[
CmmActual
]
->
UpdFrameOffset
->
CmmAGraph
mkCmmCall
::
CmmExpr
->
CmmFormals
->
CmmActuals
->
mkCmmCall
::
CmmExpr
->
[
CmmFormal
]
->
[
CmmActual
]
->
UpdFrameOffset
->
CmmAGraph
-- Native C-- calling convention
mkSafeCall
::
ForeignTarget
->
CmmFormals
->
CmmActuals
->
UpdFrameOffset
->
Bool
->
CmmAGraph
mkUnsafeCall
::
ForeignTarget
->
CmmFormals
->
CmmActuals
->
CmmAGraph
mkFinalCall
::
CmmExpr
->
CCallConv
->
CmmActuals
->
UpdFrameOffset
->
CmmAGraph
mkSafeCall
::
ForeignTarget
->
[
CmmFormal
]
->
[
CmmActual
]
->
UpdFrameOffset
->
Bool
->
CmmAGraph
mkUnsafeCall
::
ForeignTarget
->
[
CmmFormal
]
->
[
CmmActual
]
->
CmmAGraph
mkFinalCall
::
CmmExpr
->
CCallConv
->
[
CmmActual
]
->
UpdFrameOffset
->
CmmAGraph
-- Never returns; like exit() or barf()
---------- Control transfer
mkJump
::
CmmExpr
->
CmmActuals
->
UpdFrameOffset
->
CmmAGraph
mkDirectJump
::
CmmExpr
->
CmmActuals
->
UpdFrameOffset
->
CmmAGraph
mkJumpGC
::
CmmExpr
->
CmmActuals
->
UpdFrameOffset
->
CmmAGraph
mkForeignJump
::
Convention
->
CmmExpr
->
CmmActuals
->
UpdFrameOffset
->
CmmAGraph
mkJump
::
CmmExpr
->
[
CmmActual
]
->
UpdFrameOffset
->
CmmAGraph
mkDirectJump
::
CmmExpr
->
[
CmmActual
]
->
UpdFrameOffset
->
CmmAGraph
mkJumpGC
::
CmmExpr
->
[
CmmActual
]
->
UpdFrameOffset
->
CmmAGraph
mkForeignJump
::
Convention
->
CmmExpr
->
[
CmmActual
]
->
UpdFrameOffset
->
CmmAGraph
mkCbranch
::
CmmExpr
->
BlockId
->
BlockId
->
CmmAGraph
mkSwitch
::
CmmExpr
->
[
Maybe
BlockId
]
->
CmmAGraph
mkReturn
::
CmmExpr
->
CmmActuals
->
UpdFrameOffset
->
CmmAGraph
mkReturnSimple
::
CmmActuals
->
UpdFrameOffset
->
CmmAGraph
mkReturn
::
CmmExpr
->
[
CmmActual
]
->
UpdFrameOffset
->
CmmAGraph
mkReturnSimple
::
[
CmmActual
]
->
UpdFrameOffset
->
CmmAGraph
mkBranch
::
BlockId
->
CmmAGraph
mkCmmIfThenElse
::
CmmExpr
->
CmmAGraph
->
CmmAGraph
->
CmmAGraph
...
...
@@ -288,8 +288,8 @@ stackStubExpr w = CmmLit (CmmInt 0 w)
-- the variables in their spill slots.
-- Therefore, for copying arguments and results, we provide different
-- functions to pass the arguments in an overflow area and to pass them in spill slots.
copyInOflow
::
Convention
->
Area
->
CmmFormals
->
(
Int
,
CmmAGraph
)
copyInSlot
::
Convention
->
CmmFormals
->
[
CmmNode
O
O
]
copyInOflow
::
Convention
->
Area
->
[
CmmFormal
]
->
(
Int
,
CmmAGraph
)
copyInSlot
::
Convention
->
[
CmmFormal
]
->
[
CmmNode
O
O
]
copyOutSlot
::
Convention
->
[
LocalReg
]
->
[
CmmNode
O
O
]
copyInOflow
conv
area
formals
=
(
offset
,
catAGraphs
$
map
mkMiddle
nodes
)
...
...
@@ -298,7 +298,7 @@ copyInSlot c f = snd $ copyIn oneCopySlotI c (panic "no area for copying to slot
type
SlotCopier
=
Area
->
(
LocalReg
,
ByteOff
)
->
(
ByteOff
,
[
CmmNode
O
O
])
->
(
ByteOff
,
[
CmmNode
O
O
])
type
CopyIn
=
SlotCopier
->
Convention
->
Area
->
CmmFormals
->
(
ByteOff
,
[
CmmNode
O
O
])
type
CopyIn
=
SlotCopier
->
Convention
->
Area
->
[
CmmFormal
]
->
(
ByteOff
,
[
CmmNode
O
O
])
-- Return the number of bytes used for copying arguments, as well as the
-- instructions to copy the arguments.
...
...
@@ -331,7 +331,7 @@ oneCopySlotI _ (reg, _) (n, ms) =
-- Factoring out the common parts of the copyout functions yielded something
-- more complicated:
copyOutOflow
::
Convention
->
Transfer
->
Area
->
CmmActuals
->
UpdFrameOffset
->
copyOutOflow
::
Convention
->
Transfer
->
Area
->
[
CmmActual
]
->
UpdFrameOffset
->
(
Int
,
CmmAGraph
)
-- Generate code to move the actual parameters into the locations
-- required by the calling convention. This includes a store for the return address.
...
...
@@ -372,10 +372,10 @@ copyOutSlot conv actuals = foldr co [] args
toExp
r
=
CmmReg
(
CmmLocal
r
)
args
=
assignArgumentsPos
conv
localRegType
actuals
mkCallEntry
::
Convention
->
CmmFormals
->
(
Int
,
CmmAGraph
)
mkCallEntry
::
Convention
->
[
CmmFormal
]
->
(
Int
,
CmmAGraph
)
mkCallEntry
conv
formals
=
copyInOflow
conv
(
CallArea
Old
)
formals
lastWithArgs
::
Transfer
->
Area
->
Convention
->
CmmActuals
->
UpdFrameOffset
->
lastWithArgs
::
Transfer
->
Area
->
Convention
->
[
CmmActual
]
->
UpdFrameOffset
->
(
ByteOff
->
CmmAGraph
)
->
CmmAGraph
lastWithArgs
transfer
area
conv
actuals
updfr_off
last
=
let
(
outArgs
,
copies
)
=
copyOutOflow
conv
transfer
area
actuals
updfr_off
in
...
...
compiler/cmm/OldCmm.hs
View file @
da15d0c5
...
...
@@ -14,7 +14,7 @@ module OldCmm (
cmmMapGraphM
,
cmmTopMapGraphM
,
GenBasicBlock
(
..
),
CmmBasicBlock
,
blockId
,
blockStmts
,
mapBlockStmts
,
CmmStmt
(
..
),
CmmReturnInfo
(
..
),
CmmHinted
(
..
),
HintedCmmFormal
,
HintedCmm
Formals
,
HintedCmmActual
,
HintedCmmActuals
,
HintedCmmFormal
,
HintedCmm
Actual
,
CmmSafety
(
..
),
CmmCallTarget
(
..
),
module
CmmDecl
,
module
CmmExpr
,
...
...
@@ -146,8 +146,8 @@ data CmmStmt -- Old-style
|
CmmCall
-- A call (foreign, native or primitive), with
CmmCallTarget
HintedCmmFormals
-- zero or more results
HintedCmmActuals
-- zero or more arguments
[
HintedCmmFormal
]
-- zero or more results
[
HintedCmmActual
]
-- zero or more arguments
CmmSafety
-- whether to build a continuation
CmmReturnInfo
-- Some care is necessary when handling the arguments of these, see
...
...
@@ -164,22 +164,20 @@ data CmmStmt -- Old-style
-- Undefined outside range, and when there's a Nothing
|
CmmJump
CmmExpr
-- Jump to another C-- function,
HintedCmmActuals
-- with these parameters. (parameters never used)
[
HintedCmmActual
]
-- with these parameters. (parameters never used)
|
CmmReturn
-- Return from a native C-- function,
HintedCmmActuals
-- with these return values. (parameters never used)
[
HintedCmmActual
]
-- with these return values. (parameters never used)
data
CmmHinted
a
=
CmmHinted
{
hintlessCmm
::
a
,
cmmHint
::
ForeignHint
}
deriving
(
Eq
)
type
HintedCmmActuals
=
[
HintedCmmActual
]
type
HintedCmmFormals
=
[
HintedCmmFormal
]
type
HintedCmmFormal
=
CmmHinted
CmmFormal
type
HintedCmmActual
=
CmmHinted
CmmActual
data
CmmSafety
=
CmmUnsafe
|
CmmSafe
C_SRT
|
CmmInterruptible
-- | enable us to fold used registers over '
CmmActuals' and 'CmmFormals
'
-- | enable us to fold used registers over '
[CmmActual]' and '[CmmFormal]
'
instance
UserOfLocalRegs
CmmStmt
where
foldRegsUsed
f
(
set
::
b
)
s
=
stmt
s
set
where
...
...
compiler/cmm/OldCmmUtils.hs
View file @
da15d0c5
...
...
@@ -78,8 +78,8 @@ cheapEqReg _ _ = False
---------------------------------------------------
loadArgsIntoTemps
::
[
Unique
]
->
HintedCmmActuals
->
([
Unique
],
[
CmmStmt
],
HintedCmmActuals
)
->
[
HintedCmmActual
]
->
([
Unique
],
[
CmmStmt
],
[
HintedCmmActual
]
)
loadArgsIntoTemps
uniques
[]
=
(
uniques
,
[]
,
[]
)
loadArgsIntoTemps
uniques
((
CmmHinted
e
hint
)
:
args
)
=
(
uniques''
,
...
...
compiler/cmm/PprC.hs
View file @
da15d0c5
...
...
@@ -266,7 +266,7 @@ pprStmt stmt = case stmt of
CmmJump
lbl
_params
->
mkJMP_
(
pprExpr
lbl
)
<>
semi
CmmSwitch
arg
ids
->
pprSwitch
arg
ids
pprCFunType
::
SDoc
->
CCallConv
->
HintedCmmFormals
->
HintedCmmActuals
->
SDoc
pprCFunType
::
SDoc
->
CCallConv
->
[
HintedCmmFormal
]
->
[
HintedCmmActual
]
->
SDoc
pprCFunType
ppr_fn
cconv
ress
args
=
res_type
ress
<+>
parens
(
text
(
ccallConvAttribute
cconv
)
<>
ppr_fn
)
<>
...
...
@@ -807,7 +807,7 @@ pprLocalReg (LocalReg uniq _) = char '_' <> ppr uniq
-- -----------------------------------------------------------------------------
-- Foreign Calls
pprCall
::
SDoc
->
CCallConv
->
HintedCmmFormals
->
HintedCmmActuals
->
CmmSafety
pprCall
::
SDoc
->
CCallConv
->
[
HintedCmmFormal
]
->
[
HintedCmmActual
]
->
CmmSafety
->
SDoc
pprCall
ppr_fn
cconv
results
args
_
...
...
compiler/cmm/cmm-notes
View file @
da15d0c5
More notes (June 11)
~~~~~~~~~~~~~~~~~~~~
* CmmActuals -> [CmmActual] similary CmmFormals
* Possible refactoring: Nuke AGraph in favour of
mkIfThenElse :: Expr -> Graph -> Graph -> FCode Graph
or even
...
...
compiler/codeGen/CgForeignCall.hs
View file @
da15d0c5
...
...
@@ -43,7 +43,7 @@ import Control.Monad
-- Code generation for Foreign Calls
cgForeignCall
::
HintedCmmFormals
-- where to put the results
::
[
HintedCmmFormal
]
-- where to put the results
->
ForeignCall
-- the op
->
[
StgArg
]
-- arguments
->
StgLiveVars
-- live vars, in case we need to save them
...
...
@@ -64,7 +64,7 @@ cgForeignCall results fcall stg_args live
emitForeignCall
::
HintedCmmFormals
-- where to put the results
::
[
HintedCmmFormal
]
-- where to put the results
->
ForeignCall
-- the op
->
[
CmmHinted
CmmExpr
]
-- arguments
->
StgLiveVars
-- live vars, in case we need to save them
...
...
@@ -114,7 +114,7 @@ emitForeignCall results (CCall (CCallSpec target cconv safety)) args live
-- is not presently exported.)
emitForeignCall'
::
Safety
->
HintedCmmFormals
-- where to put the results
->
[
HintedCmmFormal
]
-- where to put the results
->
CmmCallTarget
-- the op
->
[
CmmHinted
CmmExpr
]
-- arguments
->
Maybe
[
GlobalReg
]
-- live vars, in case we need to save them
...
...
compiler/codeGen/CgInfoTbls.hs
View file @
da15d0c5
...
...
@@ -53,7 +53,7 @@ import Outputable
-- representation as a list of 'CmmAddr' is handled later
-- in the pipeline by 'cmmToRawCmm'.
emitClosureCodeAndInfoTable
::
ClosureInfo
->
CmmFormals
->
CgStmts
->
Code
emitClosureCodeAndInfoTable
::
ClosureInfo
->
[
CmmFormal
]
->
CgStmts
->
Code
emitClosureCodeAndInfoTable
cl_info
args
body
=
do
{
blks
<-
cgStmtsToBlocks
body
;
info
<-
mkCmmInfo
cl_info
...
...
@@ -412,7 +412,7 @@ funInfoTable info_ptr
emitInfoTableAndCode
::
CLabel
-- Label of entry or ret
->
CmmInfo
-- ...the info table
->
CmmFormals
-- ...args
->
[
CmmFormal
]
-- ...args
->
[
CmmBasicBlock
]
-- ...and body
->
Code
...
...
compiler/codeGen/CgMonad.lhs
View file @
da15d0c5
...
...
@@ -743,7 +743,7 @@ emitData sect lits
where
data_block = CmmData sect lits
emitProc :: CmmInfo -> CLabel ->
CmmFormals
-> [CmmBasicBlock] -> Code
emitProc :: CmmInfo -> CLabel ->
[CmmFormal]
-> [CmmBasicBlock] -> Code
emitProc info lbl [] blocks
= do { let proc_block = CmmProc info lbl (ListGraph blocks)
; state <- getState
...
...
compiler/codeGen/CgPrimOp.hs
View file @
da15d0c5
...
...
@@ -35,7 +35,7 @@ import FastString
-- ---------------------------------------------------------------------------
-- Code generation for PrimOps
cgPrimOp
::
CmmFormals
-- where to put the results
cgPrimOp
::
[
CmmFormal
]
-- where to put the results
->
PrimOp
-- the op
->
[
StgArg
]
-- arguments
->
StgLiveVars
-- live vars, in case we need to save them
...
...
@@ -47,7 +47,7 @@ cgPrimOp results op args live
emitPrimOp
results
op
non_void_args
live
emitPrimOp
::
CmmFormals
-- where to put the results
emitPrimOp
::
[
CmmFormal
]
-- where to put the results
->
PrimOp
-- the op
->
[
CmmExpr
]
-- arguments
->
StgLiveVars
-- live vars, in case we need to save them
...
...
compiler/codeGen/StgCmmForeign.hs
View file @
da15d0c5
...
...
@@ -104,20 +104,20 @@ emitCCall hinted_results fn hinted_args
fc
=
ForeignConvention
CCallConv
arg_hints
result_hints
emitPrimCall
::
CmmFormals
->
CallishMachOp
->
CmmActuals
->
FCode
()
emitPrimCall
::
[
CmmFormal
]
->
CallishMachOp
->
[
CmmActual
]
->
FCode
()
emitPrimCall
res
op
args
=
emitForeignCall
PlayRisky
res
(
PrimTarget
op
)
args
NoC_SRT
CmmMayReturn
-- alternative entry point, used by CmmParse
emitForeignCall
::
Safety
->
CmmFormals
-- where to put the results
->
ForeignTarget
-- the op
->
CmmActuals
-- arguments
::
Safety
->
[
CmmFormal
]
-- where to put the results
->
ForeignTarget
-- the op
->
[
CmmActual
]
-- arguments
->
C_SRT
-- the SRT of the calls continuation
->
CmmReturnInfo
-- This can say "never returns"
-- only RTS procedures do this
->
FCode
()
->
CmmReturnInfo
-- This can say "never returns"
-- only RTS procedures do this
->
FCode
()
emitForeignCall
safety
results
target
args
_srt
_ret
|
not
(
playSafe
safety
)
=
do
let
(
caller_save
,
caller_load
)
=
callerSaveVolatileRegs
...
...
compiler/codeGen/StgCmmMonad.hs
View file @
da15d0c5
...
...
@@ -600,7 +600,7 @@ emitData sect lits
where
data_block
=
CmmData
sect
lits
emitProcWithConvention
::
Convention
->
CmmInfoTable
->
CLabel
->
CmmFormals
->
emitProcWithConvention
::
Convention
->
CmmInfoTable
->
CLabel
->
[
CmmFormal
]
->
CmmAGraph
->
FCode
()
emitProcWithConvention
conv
info
lbl
args
blocks
=
do
{
us
<-
newUniqSupply
...
...
@@ -611,7 +611,7 @@ emitProcWithConvention conv info lbl args blocks
;
state
<-
getState
;
setState
$
state
{
cgs_tops
=
cgs_tops
state
`
snocOL
`
proc_block
}
}
emitProc
::
CmmInfoTable
->
CLabel
->
CmmFormals
->
CmmAGraph
->
FCode
()
emitProc
::
CmmInfoTable
->
CLabel
->
[
CmmFormal
]
->
CmmAGraph
->
FCode
()
emitProc
=
emitProcWithConvention
NativeNodeCall
emitSimpleProc
::
CLabel
->
CmmAGraph
->
FCode
()
...
...
compiler/llvmGen/LlvmCodeGen/CodeGen.hs
View file @
da15d0c5
...
...
@@ -147,7 +147,7 @@ stmtToInstrs env stmt = case stmt of
-- | Foreign Calls
genCall
::
LlvmEnv
->
CmmCallTarget
->
HintedCmmFormals
->
HintedCmmActuals
genCall
::
LlvmEnv
->
CmmCallTarget
->
[
HintedCmmFormal
]
->
[
HintedCmmActual
]
->
CmmReturnInfo
->
UniqSM
StmtData
-- Write barrier needs to be handled specially as it is implemented as an LLVM
...
...
@@ -347,7 +347,7 @@ getFunPtr env funTy targ = case targ of
-- | Conversion of call arguments.
arg_vars
::
LlvmEnv
->
HintedCmmActuals
->
[
HintedCmmActual
]
->
([
LlvmVar
],
LlvmStatements
,
[
LlvmCmmTop
])
->
UniqSM
(
LlvmEnv
,
[
LlvmVar
],
LlvmStatements
,
[
LlvmCmmTop
])
...
...
compiler/nativeGen/PPC/CodeGen.hs
View file @
da15d0c5
...
...
@@ -838,8 +838,8 @@ genCondJump id bool = do
-- register allocator.
genCCall
::
CmmCallTarget
-- function to call
->
HintedCmmFormals
-- where to put the result
->
HintedCmmActuals
-- arguments (of mixed type)
->
[
HintedCmmFormal
]
-- where to put the result
->
[
HintedCmmActual
]
-- arguments (of mixed type)
->
NatM
InstrBlock
genCCall
target
dest_regs
argsAndHints
=
do
dflags
<-
getDynFlagsNat
...
...
@@ -857,8 +857,8 @@ data GenCCallPlatform = GCPLinux | GCPDarwin
genCCall'
::
GenCCallPlatform
->
CmmCallTarget
-- function to call
->
HintedCmmFormals
-- where to put the result
->
HintedCmmActuals
-- arguments (of mixed type)
->
[
HintedCmmFormal
]
-- where to put the result
->
[
HintedCmmActual
]
-- arguments (of mixed type)
->
NatM
InstrBlock
{-
...
...
compiler/nativeGen/SPARC/CodeGen/CCall.hs
View file @
da15d0c5
...
...
@@ -62,9 +62,9 @@ import Outputable
-}
genCCall
::
CmmCallTarget
-- function to call
->
HintedCmmFormals
-- where to put the result
->
HintedCmmActuals
-- arguments (of mixed type)
::
CmmCallTarget
-- function to call
->
[
HintedCmmFormal
]
-- where to put the result
->
[
HintedCmmActual
]
-- arguments (of mixed type)
->
NatM
InstrBlock
...
...
compiler/nativeGen/X86/CodeGen.hs
View file @
da15d0c5
...
...
@@ -1497,9 +1497,9 @@ genCondJump id bool = do
-- register allocator.
genCCall
::
CmmCallTarget
-- function to call
->
HintedCmmFormals
-- where to put the result
->
HintedCmmActuals
-- arguments (of mixed type)
::
CmmCallTarget
-- function to call
->
[
HintedCmmFormal
]
-- where to put the result
->
[
HintedCmmActual
]
-- arguments (of mixed type)
->
NatM
InstrBlock
-- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
...
...
@@ -1875,7 +1875,7 @@ genCCall = panic "X86.genCCAll: not defined"
#
endif
/*
x86_64_TARGET_ARCH
*/
outOfLineCmmOp
::
CallishMachOp
->
Maybe
HintedCmmFormal
->
HintedCmmActuals
->
NatM
InstrBlock
outOfLineCmmOp
::
CallishMachOp
->
Maybe
HintedCmmFormal
->
[
HintedCmmActual
]
->
NatM
InstrBlock
outOfLineCmmOp
mop
res
args
=
do
dflags
<-
getDynFlagsNat
...
...
Write
Preview
Markdown
is supported
0%
Try again
or
attach a new file
.
Attach a file
Cancel
You are about to add
0
people
to the discussion. Proceed with caution.
Finish editing this message first!
Cancel
Please
register
or
sign in
to comment