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
Tobias Decking
GHC
Commits
d876992c
Commit
d876992c
authored
Nov 05, 2003
by
simonpj
Browse files
[project @ 2003-11-05 14:51:53 by simonpj]
Fixes to derivable type classes; should work now
parent
6959a665
Changes
2
Hide whitespace changes
Inline
Side-by-side
ghc/compiler/typecheck/TcDeriv.lhs
View file @
d876992c
...
...
@@ -19,7 +19,7 @@ import CmdLineOpts ( DynFlag(..) )
import Generics ( mkTyConGenericBinds )
import TcRnMonad
import TcEnv ( newDFunName,
InstInfo(..),
pprInstInfo,
InstBindings(..),
InstInfo(..), InstBindings(..),
pprInstInfoDetails, tcLookupTyCon, tcExtendTyVarEnv
)
import TcGenDeriv -- Deriv stuff
...
...
@@ -215,8 +215,10 @@ tcDeriving tycl_decls
; let inst_info = newtype_inst_info ++ ordinary_inst_info
-- Rename these extra bindings, discarding warnings about unused bindings etc
-- Set -fglasgow exts so that we can have type signatures in patterns,
-- which is used in the generic binds
; (rn_binds, gen_bndrs)
<- discardWarnings $ do
<- discardWarnings $
setOptM Opt_GlasgowExts $
do
{ (rn_deriv, _dus1) <- rnTopMonoBinds deriv_binds []
; (rn_gen, dus_gen) <- rnTopMonoBinds gen_binds []
; return (rn_deriv `ThenBinds` rn_gen, duDefs dus_gen) }
...
...
ghc/compiler/typecheck/TcRnMonad.lhs
View file @
d876992c
...
...
@@ -38,7 +38,7 @@ import Bag ( emptyBag )
import Outputable
import UniqSupply ( UniqSupply, mkSplitUniqSupply, uniqFromSupply, splitUniqSupply )
import Unique ( Unique )
import CmdLineOpts ( DynFlags, DynFlag(..), dopt, opt_PprStyle_Debug )
import CmdLineOpts ( DynFlags, DynFlag(..), dopt, opt_PprStyle_Debug
, dopt_set
)
import Bag ( snocBag, unionBags )
import Panic ( showException )
...
...
@@ -226,6 +226,10 @@ getDOpts = do { env <- getTopEnv; return (hsc_dflags env) }
doptM :: DynFlag -> TcRnIf gbl lcl Bool
doptM flag = do { dflags <- getDOpts; return (dopt flag dflags) }
setOptM :: DynFlag -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a
setOptM flag = updEnv (\ env@(Env { env_top = top }) ->
env { env_top = top { hsc_dflags = dopt_set (hsc_dflags top) flag}} )
ifOptM :: DynFlag -> TcRnIf gbl lcl () -> TcRnIf gbl lcl () -- Do it flag is true
ifOptM flag thing_inside = do { b <- doptM flag;
if b then thing_inside else return () }
...
...
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