Skip to content
GitLab
Menu
Projects
Groups
Snippets
Help
Help
Support
Community forum
Keyboard shortcuts
?
Submit feedback
Sign in / Register
Toggle navigation
Menu
Open sidebar
Shayne Fletcher
Glasgow Haskell Compiler
Commits
a9c123b7
Commit
a9c123b7
authored
May 26, 2007
by
Isaac Dupree
Browse files
#1318: remove negative-prim-literal old hackish implementation
parent
4a1aca10
Changes
2
Hide whitespace changes
Inline
Side-by-side
compiler/parser/Parser.y.pp
View file @
a9c123b7
...
...
@@ -1270,7 +1270,7 @@ exp10 :: { LHsExpr RdrName }
|
'let'
binds
'in'
exp
{
LL
$
HsLet
(
unLoc
$2
)
$4
}
|
'if'
exp
'then'
exp
'else'
exp
{
LL
$
HsIf
$2
$4
$6
}
|
'case'
exp
'of'
altslist
{
LL
$
HsCase
$2
(
mkMatchGroup
(
unLoc
$4
))
}
|
'-'
fexp
{
LL
$
mkHs
NegApp
$2
}
|
'-'
fexp
{
LL
$
NegApp
$2
noSyntaxExpr
}
|
'do'
stmtlist
{
%
let
loc
=
comb2
$1
$2
in
checkDo
loc
(
unLoc
$2
)
>>=
\
(
stmts
,
body
)
->
...
...
compiler/parser/RdrHsSyn.lhs
View file @
a9c123b7
...
...
@@ -9,7 +9,7 @@ module RdrHsSyn (
extractHsRhoRdrTyVars, extractGenericPatTyVars,
mkHsOpApp, mkClassDecl,
mkHsNegApp,
mkHsIntegral, mkHsFractional, mkHsIsString,
mkHsIntegral, mkHsFractional, mkHsIsString,
mkHsDo, mkHsSplice,
mkTyData, mkPrefixCon, mkRecCon, mkInlineSpec,
mkRecConstrOrUpdate, -- HsExp -> [HsFieldUpdate] -> P HsExp
...
...
@@ -172,18 +172,6 @@ mkTyData new_or_data (context, tname, tyvars, typats) ksig data_cons maybe_deriv
tcdKindSig = ksig, tcdDerivs = maybe_deriv }
\end{code}
\begin{code}
mkHsNegApp :: LHsExpr RdrName -> HsExpr RdrName
-- RdrName If the type checker sees (negate 3#) it will barf, because negate
-- can't take an unboxed arg. But that is exactly what it will see when
-- we write "-3#". So we have to do the negation right now!
mkHsNegApp (L loc e) = f e
where f (HsLit (HsIntPrim i)) = HsLit (HsIntPrim (-i))
f (HsLit (HsFloatPrim i)) = HsLit (HsFloatPrim (-i))
f (HsLit (HsDoublePrim i)) = HsLit (HsDoublePrim (-i))
f expr = NegApp (L loc e) noSyntaxExpr
\end{code}
%************************************************************************
%* *
\subsection[cvBinds-etc]{Converting to @HsBinds@, etc.}
...
...
@@ -656,8 +644,7 @@ checkAPat loc e = case e of
-- Overloaded numeric patterns (e.g. f 0 x = x)
-- Negation is recorded separately, so that the literal is zero or +ve
-- NB. Negative *primitive* literals are already handled by
-- RdrHsSyn.mkHsNegApp
-- NB. Negative *primitive* literals are already handled by the lexer
HsOverLit pos_lit -> return (mkNPat pos_lit Nothing)
NegApp (L _ (HsOverLit pos_lit)) _
-> return (mkNPat pos_lit (Just noSyntaxExpr))
...
...
Write
Preview
Supports
Markdown
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