Skip to content
GitLab
Projects
Groups
Snippets
Help
Loading...
Help
Help
Support
Community forum
Keyboard shortcuts
?
Submit feedback
Sign in / Register
Toggle navigation
GHC
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
Alex D
GHC
Commits
64efee62
Commit
64efee62
authored
Nov 12, 2012
by
Michal Terepeta
Committed by
ian@well-typed.com
Nov 23, 2012
Browse files
Options
Browse Files
Download
Email Patches
Plain Diff
Add fixity information to primops (ticket #6026)
parent
951e28c0
Changes
9
Hide whitespace changes
Inline
Side-by-side
Showing
9 changed files
with
102 additions
and
7 deletions
+102
-7
compiler/ghc.mk
compiler/ghc.mk
+3
-0
compiler/iface/LoadIface.lhs
compiler/iface/LoadIface.lhs
+4
-2
compiler/prelude/PrimOp.lhs
compiler/prelude/PrimOp.lhs
+13
-2
compiler/prelude/primops.txt.pp
compiler/prelude/primops.txt.pp
+24
-0
utils/genprimopcode/Lexer.x
utils/genprimopcode/Lexer.x
+5
-0
utils/genprimopcode/Main.hs
utils/genprimopcode/Main.hs
+26
-3
utils/genprimopcode/Parser.y
utils/genprimopcode/Parser.y
+13
-0
utils/genprimopcode/ParserM.hs
utils/genprimopcode/ParserM.hs
+5
-0
utils/genprimopcode/Syntax.hs
utils/genprimopcode/Syntax.hs
+9
-0
No files found.
compiler/ghc.mk
View file @
64efee62
...
...
@@ -240,6 +240,7 @@ PRIMOP_BITS_NAMES = primop-data-decl.hs-incl \
primop-code-size.hs-incl
\
primop-can-fail.hs-incl
\
primop-strictness.hs-incl
\
primop-fixity.hs-incl
\
primop-primop-info.hs-incl
PRIMOP_BITS_STAGE1
=
$(
addprefix
compiler/stage1/build/,
$(PRIMOP_BITS_NAMES)
)
...
...
@@ -276,6 +277,8 @@ compiler/stage$1/build/primop-can-fail.hs-incl: compiler/stage$1/build/primops.t
"
$
$(GENPRIMOP_INPLACE)
"
--can-fail
<
$$
<
>
$$
@
compiler/stage$1/build/primop-strictness.hs-incl
:
compiler/stage$1/build/primops.txt $$(GENPRIMOP_INPLACE)
"
$
$(GENPRIMOP_INPLACE)
"
--strictness
<
$$
<
>
$$
@
compiler/stage$1/build/primop-fixity.hs-incl
:
compiler/stage$1/build/primops.txt $$(GENPRIMOP_INPLACE)
"
$
$(GENPRIMOP_INPLACE)
"
--fixity
<
$$
<
>
$$
@
compiler/stage$1/build/primop-primop-info.hs-incl
:
compiler/stage$1/build/primops.txt $$(GENPRIMOP_INPLACE)
"
$
$(GENPRIMOP_INPLACE)
"
--primop-primop-info
<
$$
<
>
$$
@
...
...
compiler/iface/LoadIface.lhs
View file @
64efee62
...
...
@@ -38,6 +38,7 @@ import TcRnMonad
import Constants
import PrelNames
import PrelInfo
import PrimOp ( allThePrimOps, primOpFixity, primOpOcc )
import MkId ( seqId )
import Rules
import Annotations
...
...
@@ -604,8 +605,9 @@ ghcPrimIface
mi_fix_fn = mkIfaceFixCache fixities
}
where
fixities = [(getOccName seqId, Fixity 0 InfixR)]
-- seq is infixr 0
fixities = (getOccName seqId, Fixity 0 InfixR) -- seq is infixr 0
: mapMaybe mkFixity allThePrimOps
mkFixity op = (,) (primOpOcc op) <$> primOpFixity op
\end{code}
%*********************************************************
...
...
compiler/prelude/PrimOp.lhs
View file @
64efee62
...
...
@@ -13,7 +13,7 @@ module PrimOp (
primOpOutOfLine, primOpCodeSize,
primOpOkForSpeculation, primOpOkForSideEffects,
primOpIsCheap,
primOpIsCheap,
primOpFixity,
getPrimOpResultInfo, PrimOpResultInfo(..),
...
...
@@ -31,7 +31,7 @@ import OccName ( OccName, pprOccName, mkVarOccFS )
import TyCon ( TyCon, isPrimTyCon, tyConPrimRep, PrimRep(..) )
import Type ( Type, mkForAllTys, mkFunTy, mkFunTys, tyConAppTyCon,
typePrimRep )
import BasicTypes ( Arity, TupleSort(..) )
import BasicTypes ( Arity,
Fixity(..), FixityDirection(..),
TupleSort(..) )
import ForeignCall ( CLabelString )
import Unique ( Unique, mkPrimOpIdUnique )
import Outputable
...
...
@@ -151,6 +151,17 @@ primOpStrictness :: PrimOp -> Arity -> StrictSig
#include "primop-strictness.hs-incl"
\end{code}
%************************************************************************
%* *
\subsubsection{Fixity}
%* *
%************************************************************************
\begin{code}
primOpFixity :: PrimOp -> Maybe Fixity
#include "primop-fixity.hs-incl"
\end{code}
%************************************************************************
%* *
\subsubsection[PrimOp-comparison]{PrimOpInfo basic comparison ops}
...
...
compiler/prelude/primops.txt.pp
View file @
64efee62
...
...
@@ -46,6 +46,7 @@ defaults
commutable = False
code_size = { primOpCodeSizeDefault }
strictness = { \ arity -> mkStrictSig (mkTopDmdType (replicate arity lazyDmd) TopRes) }
fixity = Nothing
-- Currently, documentation is produced using latex, so contents of
...
...
@@ -166,13 +167,16 @@ primtype Int#
primop IntAddOp "+#" Dyadic
Int# -> Int# -> Int#
with commutable = True
fixity = infixl 6
primop IntSubOp "-#" Dyadic Int# -> Int# -> Int#
with fixity = infixl 6
primop IntMulOp "*#"
Dyadic Int# -> Int# -> Int#
{Low word of signed integer multiply.}
with commutable = True
fixity = infixl 7
primop IntMulMayOfloOp "mulIntMayOflo#"
Dyadic Int# -> Int# -> Int#
...
...
@@ -225,18 +229,26 @@ primop IntSubCOp "subIntC#" GenPrimOp Int# -> Int# -> (# Int#, Int# #)
with code_size = 2
primop IntGtOp ">#" Compare Int# -> Int# -> Bool
with fixity = infix 4
primop IntGeOp ">=#" Compare Int# -> Int# -> Bool
with fixity = infix 4
primop IntEqOp "==#" Compare
Int# -> Int# -> Bool
with commutable = True
fixity = infix 4
primop IntNeOp "/=#" Compare
Int# -> Int# -> Bool
with commutable = True
fixity = infix 4
primop IntLtOp "<#" Compare Int# -> Int# -> Bool
with fixity = infix 4
primop IntLeOp "<=#" Compare Int# -> Int# -> Bool
with fixity = infix 4
primop ChrOp "chr#" GenPrimOp Int# -> Char#
with code_size = 0
...
...
@@ -401,32 +413,44 @@ section "Double#"
primtype Double#
primop DoubleGtOp ">##" Compare Double# -> Double# -> Bool
with fixity = infix 4
primop DoubleGeOp ">=##" Compare Double# -> Double# -> Bool
with fixity = infix 4
primop DoubleEqOp "==##" Compare
Double# -> Double# -> Bool
with commutable = True
fixity = infix 4
primop DoubleNeOp "/=##" Compare
Double# -> Double# -> Bool
with commutable = True
fixity = infix 4
primop DoubleLtOp "<##" Compare Double# -> Double# -> Bool
with fixity = infix 4
primop DoubleLeOp "<=##" Compare Double# -> Double# -> Bool
with fixity = infix 4
primop DoubleAddOp "+##" Dyadic
Double# -> Double# -> Double#
with commutable = True
fixity = infixl 6
primop DoubleSubOp "-##" Dyadic Double# -> Double# -> Double#
with fixity = infixl 6
primop DoubleMulOp "*##" Dyadic
Double# -> Double# -> Double#
with commutable = True
fixity = infixl 7
primop DoubleDivOp "/##" Dyadic
Double# -> Double# -> Double#
with can_fail = True
fixity = infixl 7
primop DoubleNegOp "negateDouble#" Monadic Double# -> Double#
...
...
utils/genprimopcode/Lexer.x
View file @
64efee62
...
...
@@ -51,6 +51,11 @@ words :-
<0> "Monadic" { mkT TMonadic }
<0> "Compare" { mkT TCompare }
<0> "GenPrimOp" { mkT TGenPrimOp }
<0> "fixity" { mkT TFixity }
<0> "infix" { mkT TInfixN }
<0> "infixl" { mkT TInfixL }
<0> "infixr" { mkT TInfixR }
<0> "Nothing" { mkT TNothing }
<0> "thats_all_folks" { mkT TThatsAllFolks }
<0> [a-z][a-zA-Z0-9\#_]* { mkTv TLowerName }
<0> [A-Z][a-zA-Z0-9\#_]* { mkTv TUpperName }
...
...
utils/genprimopcode/Main.hs
View file @
64efee62
...
...
@@ -61,6 +61,11 @@ main = getArgs >>= \args ->
"strictness"
"primOpStrictness"
p_o_specs
)
"--fixity"
->
putStr
(
gen_switch_from_attribs
"fixity"
"primOpFixity"
p_o_specs
)
"--primop-primop-info"
->
putStr
(
gen_primop_info
p_o_specs
)
...
...
@@ -94,6 +99,7 @@ known_args
"--code-size"
,
"--can-fail"
,
"--strictness"
,
"--fixity"
,
"--primop-primop-info"
,
"--primop-tag"
,
"--primop-list"
,
...
...
@@ -142,6 +148,7 @@ gen_hs_source (Info defaults entries) =
opt
(
OptionTrue
n
)
=
n
++
" = True"
opt
(
OptionString
n
v
)
=
n
++
" = { "
++
v
++
"}"
opt
(
OptionInteger
n
v
)
=
n
++
" = "
++
show
v
opt
(
OptionFixity
mf
)
=
"fixity"
++
" = "
++
show
mf
hdr
s
@
(
Section
{})
=
sec
s
hdr
(
PrimOpSpec
{
name
=
n
})
=
wrapOp
n
++
","
...
...
@@ -159,7 +166,9 @@ gen_hs_source (Info defaults entries) =
spec
o
=
comm
:
decls
where
decls
=
case
o
of
PrimOpSpec
{
name
=
n
,
ty
=
t
}
->
PrimOpSpec
{
name
=
n
,
ty
=
t
,
opts
=
options
}
->
[
pprFixity
fixity
n
|
OptionFixity
(
Just
fixity
)
<-
options
]
++
[
wrapOp
n
++
" :: "
++
pprTy
t
,
wrapOp
n
++
" = let x = x in x"
]
PseudoOpSpec
{
name
=
n
,
ty
=
t
}
->
...
...
@@ -191,6 +200,8 @@ gen_hs_source (Info defaults entries) =
escape
=
concatMap
(
\
c
->
if
c
`
elem
`
special
then
'
\\
'
:
c
:
[]
else
c
:
[]
)
where
special
=
"/'`
\"
@<"
pprFixity
(
Fixity
i
d
)
n
=
pprFixityDir
d
++
" "
++
show
i
++
" "
++
n
pprTy
::
Ty
->
String
pprTy
=
pty
where
...
...
@@ -396,6 +407,7 @@ gen_latex_doc (Info defaults entries)
++
mk_commutable
o
++
"}{"
++
mk_needs_wrapper
o
++
"}{"
++
mk_can_fail
o
++
"}{"
++
mk_fixity
o
++
"}{"
++
latex_encode
(
mk_strictness
o
)
++
"}{"
++
"}"
...
...
@@ -411,14 +423,20 @@ gen_latex_doc (Info defaults entries)
Just
(
OptionFalse
_
)
->
if_false
Just
(
OptionString
_
_
)
->
error
"String value for boolean option"
Just
(
OptionInteger
_
_
)
->
error
"Integer value for boolean option"
Just
(
OptionFixity
_
)
->
error
"Fixity value for boolean option"
Nothing
->
""
mk_strictness
o
=
case
lookup_attrib
"strictness"
o
of
Just
(
OptionString
_
s
)
->
s
-- for now
Just
_
->
error
"
Boolean
value for strictness"
Just
_
->
error
"
Wrong
value for strictness"
Nothing
->
""
mk_fixity
o
=
case
lookup_attrib
"fixity"
o
of
Just
(
OptionFixity
(
Just
(
Fixity
i
d
)))
->
pprFixityDir
d
++
" "
++
show
i
_
->
""
zencode
xs
=
case
maybe_tuple
xs
of
Just
n
->
n
-- Tuples go to Z2T etc
...
...
@@ -554,6 +572,7 @@ gen_switch_from_attribs attrib_name fn_name (Info defaults entries)
getAltRhs
(
OptionTrue
_
)
=
"True"
getAltRhs
(
OptionInteger
_
i
)
=
show
i
getAltRhs
(
OptionString
_
s
)
=
s
getAltRhs
(
OptionFixity
mf
)
=
show
mf
mkAlt
po
=
case
lookup_attrib
attrib_name
(
opts
po
)
of
...
...
@@ -675,6 +694,11 @@ ppType (TyF s d) = "(mkFunTy (" ++ ppType s ++ ") (" ++ ppType d ++ "))"
ppType
other
=
error
(
"ppType: can't handle: "
++
show
other
++
"
\n
"
)
pprFixityDir
::
FixityDirection
->
String
pprFixityDir
InfixN
=
"infix"
pprFixityDir
InfixL
=
"infixl"
pprFixityDir
InfixR
=
"infixr"
listify
::
[
String
]
->
String
listify
ss
=
"["
++
concat
(
intersperse
", "
ss
)
++
"]"
...
...
@@ -696,4 +720,3 @@ tyconsIn (TyUTup tys) = foldr union [] $ map tyconsIn tys
arity
::
Ty
->
Int
arity
=
length
.
fst
.
flatTys
utils/genprimopcode/Parser.y
View file @
64efee62
...
...
@@ -43,6 +43,11 @@ import Syntax
monadic { TMonadic }
compare { TCompare }
genprimop { TGenPrimOp }
fixity { TFixity }
infix { TInfixN }
infixl { TInfixL }
infixr { TInfixR }
nothing { TNothing }
thats_all_folks { TThatsAllFolks }
lowerName { TLowerName $$ }
upperName { TUpperName $$ }
...
...
@@ -67,6 +72,14 @@ pOption : lowerName '=' false { OptionFalse $1 }
| lowerName '=' true { OptionTrue $1 }
| lowerName '=' pStuffBetweenBraces { OptionString $1 $3 }
| lowerName '=' integer { OptionInteger $1 $3 }
| fixity '=' pInfix { OptionFixity $3 }
pInfix :: { Maybe Fixity }
pInfix : infix integer { Just $ Fixity $2 InfixN }
| infixl integer { Just $ Fixity $2 InfixL }
| infixr integer { Just $ Fixity $2 InfixR }
| nothing { Nothing }
pEntries :: { [Entry] }
pEntries : pEntry pEntries { $1 : $2 }
...
...
utils/genprimopcode/ParserM.hs
View file @
64efee62
...
...
@@ -84,6 +84,11 @@ data Token = TEOF
|
TString
String
|
TNoBraces
String
|
TInteger
Int
|
TFixity
|
TInfixN
|
TInfixL
|
TInfixR
|
TNothing
deriving
Show
-- Actions
...
...
utils/genprimopcode/Syntax.hs
View file @
64efee62
...
...
@@ -40,6 +40,7 @@ data Option
|
OptionTrue
String
-- name = True
|
OptionString
String
String
-- name = { ... unparsed stuff ... }
|
OptionInteger
String
Int
-- name = <int>
|
OptionFixity
(
Maybe
Fixity
)
-- fixity = infix{,l,r} <int> | Nothing
deriving
Show
-- categorises primops
...
...
@@ -59,6 +60,13 @@ data Ty
type
TyVar
=
String
type
TyCon
=
String
-- Follow definitions of Fixity and FixityDirection in GHC
data
Fixity
=
Fixity
Int
FixityDirection
deriving
(
Eq
,
Show
)
data
FixityDirection
=
InfixN
|
InfixL
|
InfixR
deriving
(
Eq
,
Show
)
------------------------------------------------------------------
-- Sanity checking -----------------------------------------------
...
...
@@ -121,6 +129,7 @@ get_attrib_name (OptionFalse nm) = nm
get_attrib_name
(
OptionTrue
nm
)
=
nm
get_attrib_name
(
OptionString
nm
_
)
=
nm
get_attrib_name
(
OptionInteger
nm
_
)
=
nm
get_attrib_name
(
OptionFixity
_
)
=
"fixity"
lookup_attrib
::
String
->
[
Option
]
->
Maybe
Option
lookup_attrib
_
[]
=
Nothing
...
...
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