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
1500f089
Commit
1500f089
authored
Feb 17, 2020
by
Sylvain Henry
Committed by
Marge Bot
Feb 18, 2020
Browse files
Options
Browse Files
Download
Email Patches
Plain Diff
Modules: Llvm (#13009)
parent
192caf58
Changes
16
Show whitespace changes
Inline
Side-by-side
Showing
16 changed files
with
73 additions
and
68 deletions
+73
-68
compiler/GHC/CmmToLlvm.hs
compiler/GHC/CmmToLlvm.hs
+14
-8
compiler/GHC/CmmToLlvm/Base.hs
compiler/GHC/CmmToLlvm/Base.hs
+3
-3
compiler/GHC/CmmToLlvm/CodeGen.hs
compiler/GHC/CmmToLlvm/CodeGen.hs
+8
-8
compiler/GHC/CmmToLlvm/Data.hs
compiler/GHC/CmmToLlvm/Data.hs
+3
-3
compiler/GHC/CmmToLlvm/Mangler.hs
compiler/GHC/CmmToLlvm/Mangler.hs
+1
-1
compiler/GHC/CmmToLlvm/Ppr.hs
compiler/GHC/CmmToLlvm/Ppr.hs
+4
-4
compiler/GHC/CmmToLlvm/Regs.hs
compiler/GHC/CmmToLlvm/Regs.hs
+9
-9
compiler/GHC/Llvm.hs
compiler/GHC/Llvm.hs
+5
-5
compiler/GHC/Llvm/MetaData.hs
compiler/GHC/Llvm/MetaData.hs
+2
-2
compiler/GHC/Llvm/Ppr.hs
compiler/GHC/Llvm/Ppr.hs
+4
-4
compiler/GHC/Llvm/Syntax.hs
compiler/GHC/Llvm/Syntax.hs
+3
-3
compiler/GHC/Llvm/Types.hs
compiler/GHC/Llvm/Types.hs
+2
-2
compiler/ghc.cabal.in
compiler/ghc.cabal.in
+12
-13
compiler/main/CodeOutput.hs
compiler/main/CodeOutput.hs
+1
-1
compiler/main/DriverPipeline.hs
compiler/main/DriverPipeline.hs
+1
-1
compiler/main/SysTools/Tasks.hs
compiler/main/SysTools/Tasks.hs
+1
-1
No files found.
compiler/
llvmGen/LlvmCodeGen
.hs
→
compiler/
GHC/CmmToLlvm
.hs
View file @
1500f089
...
...
@@ -3,19 +3,25 @@
-- -----------------------------------------------------------------------------
-- | This is the top-level module in the LLVM code generator.
--
module
LlvmCodeGen
(
LlvmVersion
,
llvmVersionList
,
llvmCodeGen
,
llvmFixupAsm
)
where
module
GHC.CmmToLlvm
(
LlvmVersion
,
llvmVersionList
,
llvmCodeGen
,
llvmFixupAsm
)
where
#
include
"HsVersions.h"
import
GhcPrelude
import
Llvm
import
LlvmCodeGen
.Base
import
LlvmCodeGen
.CodeGen
import
LlvmCodeGen
.Data
import
LlvmCodeGen
.Ppr
import
LlvmCodeGen
.Regs
import
Llvm
Mangler
import
GHC.
Llvm
import
GHC.CmmToLlvm
.Base
import
GHC.CmmToLlvm
.CodeGen
import
GHC.CmmToLlvm
.Data
import
GHC.CmmToLlvm
.Ppr
import
GHC.CmmToLlvm
.Regs
import
GHC.CmmToLlvm.
Mangler
import
GHC.StgToCmm.CgUtils
(
fixStgRegisters
)
import
GHC.Cmm
...
...
compiler/
llvmGen/LlvmCodeGen
/Base.hs
→
compiler/
GHC/CmmToLlvm
/Base.hs
View file @
1500f089
...
...
@@ -9,7 +9,7 @@
-- Contains functions useful through out the code generator.
--
module
LlvmCodeGen
.Base
(
module
GHC.CmmToLlvm
.Base
(
LlvmCmmDecl
,
LlvmBasicBlock
,
LiveGlobalRegs
,
...
...
@@ -43,8 +43,8 @@ module LlvmCodeGen.Base (
import
GhcPrelude
import
Llvm
import
LlvmCodeGen
.Regs
import
GHC.
Llvm
import
GHC.CmmToLlvm
.Regs
import
GHC.Cmm.CLabel
import
GHC.Platform.Regs
(
activeStgRegs
)
...
...
compiler/
llvmGen/LlvmCodeGen
/CodeGen.hs
→
compiler/
GHC/CmmToLlvm
/CodeGen.hs
View file @
1500f089
...
...
@@ -4,15 +4,15 @@
-- ----------------------------------------------------------------------------
-- | Handle conversion of CmmProc to LLVM code.
--
module
LlvmCodeGen
.CodeGen
(
genLlvmProc
)
where
module
GHC.CmmToLlvm
.CodeGen
(
genLlvmProc
)
where
#
include
"HsVersions.h"
import
GhcPrelude
import
Llvm
import
LlvmCodeGen
.Base
import
LlvmCodeGen
.Regs
import
GHC.
Llvm
import
GHC.CmmToLlvm
.Base
import
GHC.CmmToLlvm
.Regs
import
GHC.Cmm.BlockId
import
GHC.Platform.Regs
(
activeStgRegs
)
...
...
@@ -422,8 +422,8 @@ genCall target res args = runStmtsDecls $ do
_
->
CC_Ccc
CCallConv
->
CC_Ccc
CApiConv
->
CC_Ccc
PrimCallConv
->
panic
"LlvmCodeGen
.CodeGen.genCall: PrimCallConv"
JavaScriptCallConv
->
panic
"
LlvmCodeGen
.CodeGen.genCall: JavaScriptCallConv"
PrimCallConv
->
panic
"GHC.CmmToLlvm
.CodeGen.genCall: PrimCallConv"
JavaScriptCallConv
->
panic
"
GHC.CmmToLlvm
.CodeGen.genCall: JavaScriptCallConv"
PrimTarget
_
->
CC_Ccc
...
...
@@ -1927,10 +1927,10 @@ toIWord dflags = mkIntLit (llvmWord dflags)
-- | Error functions
panic
::
String
->
a
panic
s
=
Outputable
.
panic
$
"
LlvmCodeGen
.CodeGen."
++
s
panic
s
=
Outputable
.
panic
$
"
GHC.CmmToLlvm
.CodeGen."
++
s
pprPanic
::
String
->
SDoc
->
a
pprPanic
s
d
=
Outputable
.
pprPanic
(
"
LlvmCodeGen
.CodeGen."
++
s
)
d
pprPanic
s
d
=
Outputable
.
pprPanic
(
"
GHC.CmmToLlvm
.CodeGen."
++
s
)
d
-- | Returns TBAA meta data by unique
...
...
compiler/
llvmGen/LlvmCodeGen
/Data.hs
→
compiler/
GHC/CmmToLlvm
/Data.hs
View file @
1500f089
...
...
@@ -3,7 +3,7 @@
-- | Handle conversion of CmmData to LLVM code.
--
module
LlvmCodeGen
.Data
(
module
GHC.CmmToLlvm
.Data
(
genLlvmData
,
genData
)
where
...
...
@@ -11,8 +11,8 @@ module LlvmCodeGen.Data (
import
GhcPrelude
import
Llvm
import
LlvmCodeGen
.Base
import
GHC.
Llvm
import
GHC.CmmToLlvm
.Base
import
GHC.Cmm.BlockId
import
GHC.Cmm.CLabel
...
...
compiler/
llvmGen/Llvm
Mangler.hs
→
compiler/
GHC/CmmToLlvm/
Mangler.hs
View file @
1500f089
...
...
@@ -9,7 +9,7 @@
-- instructions require 32-byte alignment.
--
module
Llvm
Mangler
(
llvmFixupAsm
)
where
module
GHC.CmmToLlvm.
Mangler
(
llvmFixupAsm
)
where
import
GhcPrelude
...
...
compiler/
llvmGen/LlvmCodeGen
/Ppr.hs
→
compiler/
GHC/CmmToLlvm
/Ppr.hs
View file @
1500f089
...
...
@@ -3,7 +3,7 @@
-- ----------------------------------------------------------------------------
-- | Pretty print helpers for the LLVM Code generator.
--
module
LlvmCodeGen
.Ppr
(
module
GHC.CmmToLlvm
.Ppr
(
pprLlvmCmmDecl
,
pprLlvmData
,
infoSection
)
where
...
...
@@ -11,9 +11,9 @@ module LlvmCodeGen.Ppr (
import
GhcPrelude
import
Llvm
import
LlvmCodeGen
.Base
import
LlvmCodeGen
.Data
import
GHC.
Llvm
import
GHC.CmmToLlvm
.Base
import
GHC.CmmToLlvm
.Data
import
GHC.Cmm.CLabel
import
GHC.Cmm
...
...
compiler/
llvmGen/LlvmCodeGen
/Regs.hs
→
compiler/
GHC/CmmToLlvm
/Regs.hs
View file @
1500f089
...
...
@@ -4,7 +4,7 @@
-- | Deal with Cmm registers
--
module
LlvmCodeGen
.Regs
(
module
GHC.CmmToLlvm
.Regs
(
lmGlobalRegArg
,
lmGlobalRegVar
,
alwaysLive
,
stgTBAA
,
baseN
,
stackN
,
heapN
,
rxN
,
topN
,
tbaa
,
getTBAA
)
where
...
...
@@ -13,7 +13,7 @@ module LlvmCodeGen.Regs (
import
GhcPrelude
import
Llvm
import
GHC.
Llvm
import
GHC.Cmm.Expr
import
DynFlags
...
...
@@ -79,7 +79,7 @@ lmGlobalReg dflags suf reg
ZmmReg
5
->
zmmGlobal
$
"ZMM5"
++
suf
ZmmReg
6
->
zmmGlobal
$
"ZMM6"
++
suf
MachSp
->
wordGlobal
$
"MachSp"
++
suf
_other
->
panic
$
"
LlvmCodeGen
.Reg: GlobalReg ("
++
(
show
reg
)
_other
->
panic
$
"
GHC.CmmToLlvm
.Reg: GlobalReg ("
++
(
show
reg
)
++
") not supported!"
-- LongReg, HpLim, CCSS, CurrentTSO, CurrentNusery, HpAlloc
-- EagerBlackholeInfo, GCEnter1, GCFun, BaseReg, PicBaseReg
...
...
@@ -116,12 +116,12 @@ stgTBAA
-- hierarchy and as of LLVM 4.0 should *only* be referenced by other nodes. It
-- should never occur in any LLVM instruction statement.
rootN
,
topN
,
stackN
,
heapN
,
rxN
,
baseN
::
Unique
rootN
=
getUnique
(
fsLit
"
LlvmCodeGen
.Regs.rootN"
)
topN
=
getUnique
(
fsLit
"
LlvmCodeGen
.Regs.topN"
)
stackN
=
getUnique
(
fsLit
"
LlvmCodeGen
.Regs.stackN"
)
heapN
=
getUnique
(
fsLit
"
LlvmCodeGen
.Regs.heapN"
)
rxN
=
getUnique
(
fsLit
"
LlvmCodeGen
.Regs.rxN"
)
baseN
=
getUnique
(
fsLit
"
LlvmCodeGen
.Regs.baseN"
)
rootN
=
getUnique
(
fsLit
"
GHC.CmmToLlvm
.Regs.rootN"
)
topN
=
getUnique
(
fsLit
"
GHC.CmmToLlvm
.Regs.topN"
)
stackN
=
getUnique
(
fsLit
"
GHC.CmmToLlvm
.Regs.stackN"
)
heapN
=
getUnique
(
fsLit
"
GHC.CmmToLlvm
.Regs.heapN"
)
rxN
=
getUnique
(
fsLit
"
GHC.CmmToLlvm
.Regs.rxN"
)
baseN
=
getUnique
(
fsLit
"
GHC.CmmToLlvm
.Regs.baseN"
)
-- | The TBAA metadata identifier
tbaa
::
LMString
...
...
compiler/
llvmGen
/Llvm.hs
→
compiler/
GHC
/Llvm.hs
View file @
1500f089
...
...
@@ -9,7 +9,7 @@
-- (EHC) project (<http://www.cs.uu.nl/wiki/Ehc/WebHome>).
--
module
Llvm
(
module
GHC.
Llvm
(
-- * Modules, Functions and Blocks
LlvmModule
(
..
),
...
...
@@ -57,8 +57,8 @@ module Llvm (
)
where
import
Llvm.AbsSyn
import
Llvm.MetaData
import
Llvm.PpLlvm
import
Llvm.Types
import
GHC.Llvm.Syntax
import
GHC.
Llvm.MetaData
import
GHC.Llvm.Ppr
import
GHC.
Llvm.Types
compiler/
llvmGen
/Llvm/MetaData.hs
→
compiler/
GHC
/Llvm/MetaData.hs
View file @
1500f089
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module
Llvm.MetaData
where
module
GHC.
Llvm.MetaData
where
import
GhcPrelude
import
Llvm.Types
import
GHC.
Llvm.Types
import
Outputable
-- The LLVM Metadata System.
...
...
compiler/
llvmGen/Llvm/PpLlvm
.hs
→
compiler/
GHC/Llvm/Ppr
.hs
View file @
1500f089
...
...
@@ -4,7 +4,7 @@
-- | Pretty print LLVM IR Code.
--
module
Llvm.PpLlvm
(
module
GHC.Llvm.Ppr
(
-- * Top level LLVM objects.
ppLlvmModule
,
...
...
@@ -27,9 +27,9 @@ module Llvm.PpLlvm (
import
GhcPrelude
import
Llvm.AbsSyn
import
Llvm.MetaData
import
Llvm.Types
import
GHC.Llvm.Syntax
import
GHC.
Llvm.MetaData
import
GHC.
Llvm.Types
import
Data.List
(
intersperse
)
import
Outputable
...
...
compiler/
llvmGen/Llvm/AbsSyn
.hs
→
compiler/
GHC/Llvm/Syntax
.hs
View file @
1500f089
...
...
@@ -2,12 +2,12 @@
-- | The LLVM abstract syntax.
--
module
Llvm.AbsSyn
where
module
GHC.Llvm.Syntax
where
import
GhcPrelude
import
Llvm.MetaData
import
Llvm.Types
import
GHC.
Llvm.MetaData
import
GHC.
Llvm.Types
import
Unique
...
...
compiler/
llvmGen
/Llvm/Types.hs
→
compiler/
GHC
/Llvm/Types.hs
View file @
1500f089
...
...
@@ -4,7 +4,7 @@
-- | The LLVM Type System.
--
module
Llvm.Types
where
module
GHC.
Llvm.Types
where
#
include
"HsVersions.h"
...
...
@@ -372,7 +372,7 @@ llvmWidthInBits _ (LMStructU _) =
-- It's not trivial to calculate the bit width of the unpacked structs,
-- since they will be aligned depending on the specified datalayout (
-- http://llvm.org/docs/LangRef.html#data-layout ). One way we could support
-- this could be to make the
LlvmCodeGen
.Ppr.moduleLayout be a data type
-- this could be to make the
GHC.CmmToLlvm
.Ppr.moduleLayout be a data type
-- that exposes the alignment information. However, currently the only place
-- we use unpacked structs is LLVM intrinsics that return them (e.g.,
-- llvm.sadd.with.overflow.*), so we don't actually need to compute their
...
...
compiler/ghc.cabal.in
View file @
1500f089
...
...
@@ -165,7 +165,6 @@ Library
cmm
coreSyn
iface
llvmGen
main
nativeGen
parser
...
...
@@ -212,18 +211,18 @@ Library
Predicate
Lexeme
Literal
Llvm
Llvm.AbsSyn
Llvm.MetaData
Llvm.PpLlvm
Llvm.Types
LlvmCodeGen
LlvmCodeGen
.Base
LlvmCodeGen
.CodeGen
LlvmCodeGen
.Data
LlvmCodeGen
.Ppr
LlvmCodeGen
.Regs
Llvm
Mangler
GHC.
Llvm
GHC.Llvm.Syntax
GHC.
Llvm.MetaData
GHC.Llvm.Ppr
GHC.
Llvm.Types
GHC.CmmToLlvm
GHC.CmmToLlvm
.Base
GHC.CmmToLlvm
.CodeGen
GHC.CmmToLlvm
.Data
GHC.CmmToLlvm
.Ppr
GHC.CmmToLlvm
.Regs
GHC.CmmToLlvm.
Mangler
MkId
Module
Name
...
...
compiler/main/CodeOutput.hs
View file @
1500f089
...
...
@@ -13,7 +13,7 @@ module CodeOutput( codeOutput, outputForeignStubs ) where
import
GhcPrelude
import
AsmCodeGen
(
nativeCodeGen
)
import
LlvmCodeGen
(
llvmCodeGen
)
import
GHC.CmmToLlvm
(
llvmCodeGen
)
import
UniqSupply
(
mkSplitUniqSupply
)
...
...
compiler/main/DriverPipeline.hs
View file @
1500f089
...
...
@@ -57,7 +57,7 @@ import StringBuffer ( hGetStringBuffer, hPutStringBuffer )
import
BasicTypes
(
SuccessFlag
(
..
)
)
import
Maybes
(
expectJust
)
import
SrcLoc
import
LlvmCodeGen
(
llvmFixupAsm
,
llvmVersionList
)
import
GHC.CmmToLlvm
(
llvmFixupAsm
,
llvmVersionList
)
import
MonadUtils
import
GHC.Platform
import
TcRnTypes
...
...
compiler/main/SysTools/Tasks.hs
View file @
1500f089
...
...
@@ -22,7 +22,7 @@ import System.IO
import
System.Process
import
GhcPrelude
import
LlvmCodeGen
.Base
(
LlvmVersion
,
llvmVersionStr
,
supportedLlvmVersion
,
parseLlvmVersion
)
import
GHC.CmmToLlvm
.Base
(
LlvmVersion
,
llvmVersionStr
,
supportedLlvmVersion
,
parseLlvmVersion
)
import
SysTools.Process
import
SysTools.Info
...
...
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