diff options
author | lewie <unknown> | 2000-03-02 22:51:30 +0000 |
---|---|---|
committer | lewie <unknown> | 2000-03-02 22:51:30 +0000 |
commit | f0a01a1fc19bfa76aa36fa113942e1c57f3733f4 (patch) | |
tree | 35a2c4c7b95350e99510a1660d5d6d3468b2fdad /ghc/compiler/parser | |
parent | b4e5ee101fab479f2be10b63269536735fce7359 (diff) | |
download | haskell-f0a01a1fc19bfa76aa36fa113942e1c57f3733f4.tar.gz |
[project @ 2000-03-02 22:51:30 by lewie]
Further refine and fix how `with' partitions the LIE. Also moved the
partitioning function from Inst to TcSimplify. Fixed layout bug with
`with'. Fixed another wibble w/ importing defs w/ implicit params.
Make 4-tuples outputable (a convenience in debugging measure).
Diffstat (limited to 'ghc/compiler/parser')
-rw-r--r-- | ghc/compiler/parser/Lex.lhs | 2 | ||||
-rw-r--r-- | ghc/compiler/parser/Parser.y | 12 | ||||
-rw-r--r-- | ghc/compiler/parser/RdrHsSyn.lhs | 1 |
3 files changed, 10 insertions, 5 deletions
diff --git a/ghc/compiler/parser/Lex.lhs b/ghc/compiler/parser/Lex.lhs index aef425f41e..b2f04b04ff 100644 --- a/ghc/compiler/parser/Lex.lhs +++ b/ghc/compiler/parser/Lex.lhs @@ -600,7 +600,7 @@ lexToken cont glaexts buf = cont (ITunknown "\NUL") (stepOn buf) '?'# | flag glaexts && is_lower (lookAhead# buf 1#) -> - lex_ip cont (stepOn buf) + lex_ip cont (incLexeme buf) c | is_digit c -> lex_num cont glaexts 0 buf | is_symbol c -> lex_sym cont buf | is_upper c -> lex_con cont glaexts buf diff --git a/ghc/compiler/parser/Parser.y b/ghc/compiler/parser/Parser.y index 5b839ec15e..bfb325789d 100644 --- a/ghc/compiler/parser/Parser.y +++ b/ghc/compiler/parser/Parser.y @@ -1,6 +1,6 @@ {- ----------------------------------------------------------------------------- -$Id: Parser.y,v 1.26 2000/02/28 21:59:32 lewie Exp $ +$Id: Parser.y,v 1.27 2000/03/02 22:51:30 lewie Exp $ Haskell grammar. @@ -28,6 +28,7 @@ import BasicTypes ( Fixity(..), FixityDirection(..), NewOrData(..) ) import Panic import GlaExts +import FastString ( tailFS ) #include "HsVersions.h" } @@ -514,7 +515,7 @@ ctype :: { RdrNameHsType } type :: { RdrNameHsType } : btype '->' type { MonoFunTy $1 $3 } - | IPVARID '::' type { MonoIParamTy (mkSrcUnqual ipName $1) $3 } + | ipvar '::' type { MonoIParamTy $1 $3 } | btype { $1 } btype :: { RdrNameHsType } @@ -716,7 +717,7 @@ aexp :: { RdrNameHsExpr } aexp1 :: { RdrNameHsExpr } : qvar { HsVar $1 } - | IPVARID { HsIPVar (mkSrcUnqual ipName $1) } + | ipvar { HsIPVar $1 } | gcon { HsVar $1 } | literal { HsLit $1 } | '(' exp ')' { HsPar $2 } @@ -863,7 +864,7 @@ dbinds :: { [(RdrName, RdrNameHsExpr)] } | {- empty -} { [] } dbind :: { (RdrName, RdrNameHsExpr) } -dbind : IPVARID '=' exp { (mkSrcUnqual ipName $1, $3) } +dbind : ipvar '=' exp { ($1, $3) } ----------------------------------------------------------------------------- -- Variables, Constructors and Operators. @@ -882,6 +883,9 @@ qvar :: { RdrName } : qvarid { $1 } | '(' qvarsym ')' { $2 } +ipvar :: { RdrName } + : IPVARID { (mkSrcUnqual ipName (tailFS $1)) } + con :: { RdrName } : conid { $1 } | '(' consym ')' { $2 } diff --git a/ghc/compiler/parser/RdrHsSyn.lhs b/ghc/compiler/parser/RdrHsSyn.lhs index 7fb54425be..41b9fdb0b4 100644 --- a/ghc/compiler/parser/RdrHsSyn.lhs +++ b/ghc/compiler/parser/RdrHsSyn.lhs @@ -163,6 +163,7 @@ extract_ty (MonoTyApp ty1 ty2) acc = extract_ty ty1 (extract_ty ty2 acc extract_ty (MonoListTy ty) acc = extract_ty ty acc extract_ty (MonoTupleTy tys _) acc = foldr extract_ty acc tys extract_ty (MonoFunTy ty1 ty2) acc = extract_ty ty1 (extract_ty ty2 acc) +extract_ty (MonoIParamTy n ty) acc = extract_ty ty acc extract_ty (MonoDictTy cls tys) acc = foldr extract_ty (cls : acc) tys extract_ty (MonoUsgTy usg ty) acc = extract_ty ty acc extract_ty (MonoUsgForAllTy uv ty) acc = extract_ty ty acc |