diff options
author | Tom Ellis <tom.ellis@microsoft.com> | 2019-12-02 11:06:11 +0000 |
---|---|---|
committer | tomjaguarpaw1 <tom-github.com@jaguarpaw.co.uk> | 2020-01-27 12:30:46 -0500 |
commit | 4bada77d5882974514d85d4bd0fd4e1801dad755 (patch) | |
tree | f429f57d48400892ad0a5c91bb2e03f9115c2c5a | |
parent | 97d0b0a367e4c6a52a17c3299439ac7de129da24 (diff) | |
download | haskell-4bada77d5882974514d85d4bd0fd4e1801dad755.tar.gz |
Disable two warnings for files that trigger them
incomplete-uni-patterns and incomplete-record-updates will be in -Wall at a
future date, so prepare for that by disabling those warnings on files that
trigger them.
126 files changed, 238 insertions, 0 deletions
diff --git a/compiler/GHC/Cmm/ContFlowOpt.hs b/compiler/GHC/Cmm/ContFlowOpt.hs index 7765972d02..1e5459f460 100644 --- a/compiler/GHC/Cmm/ContFlowOpt.hs +++ b/compiler/GHC/Cmm/ContFlowOpt.hs @@ -1,6 +1,7 @@ {-# LANGUAGE GADTs #-} {-# LANGUAGE BangPatterns #-} {-# OPTIONS_GHC -fno-warn-incomplete-patterns #-} +{-# OPTIONS_GHC -Wno-incomplete-record-updates #-} module GHC.Cmm.ContFlowOpt ( cmmCfgOpts , cmmCfgOptsProc diff --git a/compiler/GHC/Cmm/DebugBlock.hs b/compiler/GHC/Cmm/DebugBlock.hs index 70fc08ee94..6b940c9867 100644 --- a/compiler/GHC/Cmm/DebugBlock.hs +++ b/compiler/GHC/Cmm/DebugBlock.hs @@ -1,6 +1,8 @@ {-# LANGUAGE GADTs #-} {-# LANGUAGE MultiWayIf #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} + ----------------------------------------------------------------------------- -- -- Debugging data diff --git a/compiler/GHC/Cmm/MachOp.hs b/compiler/GHC/Cmm/MachOp.hs index 234001545c..a887477028 100644 --- a/compiler/GHC/Cmm/MachOp.hs +++ b/compiler/GHC/Cmm/MachOp.hs @@ -1,3 +1,5 @@ +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} + module GHC.Cmm.MachOp ( MachOp(..) , pprMachOp, isCommutableMachOp, isAssociativeMachOp diff --git a/compiler/GHC/Cmm/Node.hs b/compiler/GHC/Cmm/Node.hs index bb74647910..0764d6d8a3 100644 --- a/compiler/GHC/Cmm/Node.hs +++ b/compiler/GHC/Cmm/Node.hs @@ -9,6 +9,8 @@ {-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE ScopedTypeVariables #-} +{-# OPTIONS_GHC -Wno-incomplete-record-updates #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} -- CmmNode type for representation using Hoopl graphs. diff --git a/compiler/GHC/Cmm/ProcPoint.hs b/compiler/GHC/Cmm/ProcPoint.hs index 00a7a73d89..1e4b70bd23 100644 --- a/compiler/GHC/Cmm/ProcPoint.hs +++ b/compiler/GHC/Cmm/ProcPoint.hs @@ -1,4 +1,5 @@ {-# LANGUAGE GADTs, DisambiguateRecordFields, BangPatterns #-} +{-# OPTIONS_GHC -Wno-incomplete-record-updates #-} module GHC.Cmm.ProcPoint ( ProcPointSet, Status(..) diff --git a/compiler/GHC/Cmm/Switch.hs b/compiler/GHC/Cmm/Switch.hs index e89fadfd2e..ea7932ca17 100644 --- a/compiler/GHC/Cmm/Switch.hs +++ b/compiler/GHC/Cmm/Switch.hs @@ -1,4 +1,5 @@ {-# LANGUAGE GADTs #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} module GHC.Cmm.Switch ( SwitchTargets, mkSwitchTargets, diff --git a/compiler/GHC/Cmm/Utils.hs b/compiler/GHC/Cmm/Utils.hs index d879c7b82f..02d64da936 100644 --- a/compiler/GHC/Cmm/Utils.hs +++ b/compiler/GHC/Cmm/Utils.hs @@ -1,6 +1,8 @@ {-# LANGUAGE GADTs, RankNTypes #-} {-# LANGUAGE BangPatterns #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} + ----------------------------------------------------------------------------- -- -- Cmm utilities. diff --git a/compiler/GHC/CoreToStg/Prep.hs b/compiler/GHC/CoreToStg/Prep.hs index 4dd1822a5e..14716081d4 100644 --- a/compiler/GHC/CoreToStg/Prep.hs +++ b/compiler/GHC/CoreToStg/Prep.hs @@ -7,6 +7,8 @@ Core pass to saturate constructors and PrimOps {-# LANGUAGE BangPatterns, CPP, MultiWayIf #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} + module GHC.CoreToStg.Prep ( corePrepPgm, corePrepExpr, cvtLitInteger, cvtLitNatural, lookupMkIntegerName, lookupIntegerSDataConName, diff --git a/compiler/GHC/Hs/Decls.hs b/compiler/GHC/Hs/Decls.hs index c2e517f901..827f26bedc 100644 --- a/compiler/GHC/Hs/Decls.hs +++ b/compiler/GHC/Hs/Decls.hs @@ -13,6 +13,8 @@ {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE TypeFamilies #-} +{-# OPTIONS_GHC -Wno-incomplete-record-updates #-} + -- | Abstract syntax of global declarations. -- -- Definitions for: @SynDecl@ and @ConDecl@, @ClassDecl@, diff --git a/compiler/GHC/Hs/Expr.hs b/compiler/GHC/Hs/Expr.hs index 373c459cdb..d37c8ed914 100644 --- a/compiler/GHC/Hs/Expr.hs +++ b/compiler/GHC/Hs/Expr.hs @@ -15,6 +15,8 @@ {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE ViewPatterns #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} + -- | Abstract Haskell syntax for expressions. module GHC.Hs.Expr where diff --git a/compiler/GHC/Hs/Utils.hs b/compiler/GHC/Hs/Utils.hs index a6c70574d0..76101a73cb 100644 --- a/compiler/GHC/Hs/Utils.hs +++ b/compiler/GHC/Hs/Utils.hs @@ -25,6 +25,8 @@ just attach noSrcSpan to everything. {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE ViewPatterns #-} +{-# OPTIONS_GHC -Wno-incomplete-record-updates #-} + module GHC.Hs.Utils( -- * Terms mkHsPar, mkHsApp, mkHsAppType, mkHsAppTypes, mkHsCaseAlt, diff --git a/compiler/GHC/HsToCore/PmCheck/Ppr.hs b/compiler/GHC/HsToCore/PmCheck/Ppr.hs index 81c7bd74bd..a3b5cbede4 100644 --- a/compiler/GHC/HsToCore/PmCheck/Ppr.hs +++ b/compiler/GHC/HsToCore/PmCheck/Ppr.hs @@ -1,5 +1,7 @@ {-# LANGUAGE CPP, ViewPatterns #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} + -- | Provides factilities for pretty-printing 'Delta's in a way appropriate for -- user facing pattern match warnings. module GHC.HsToCore.PmCheck.Ppr ( diff --git a/compiler/GHC/Iface/Ext/Ast.hs b/compiler/GHC/Iface/Ext/Ast.hs index 50d5d8e3e7..893966d3eb 100644 --- a/compiler/GHC/Iface/Ext/Ast.hs +++ b/compiler/GHC/Iface/Ext/Ast.hs @@ -12,6 +12,9 @@ Main functions for .hie file generation {-# LANGUAGE AllowAmbiguousTypes #-} {-# LANGUAGE ViewPatterns #-} {-# LANGUAGE DeriveDataTypeable #-} + +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} + module GHC.Iface.Ext.Ast ( mkHieFile ) where import GhcPrelude diff --git a/compiler/GHC/Iface/Rename.hs b/compiler/GHC/Iface/Rename.hs index 94a7dbc06e..693f9068c4 100644 --- a/compiler/GHC/Iface/Rename.hs +++ b/compiler/GHC/Iface/Rename.hs @@ -1,6 +1,8 @@ {-# LANGUAGE CPP #-} {-# LANGUAGE LambdaCase #-} +{-# OPTIONS_GHC -Wno-incomplete-record-updates #-} + -- | This module implements interface renaming, which is -- used to rewrite interface files on the fly when we -- are doing indefinite typechecking and need instantiations diff --git a/compiler/GHC/Iface/Tidy.hs b/compiler/GHC/Iface/Tidy.hs index 1a7f9f0026..6f3a104925 100644 --- a/compiler/GHC/Iface/Tidy.hs +++ b/compiler/GHC/Iface/Tidy.hs @@ -6,6 +6,8 @@ {-# LANGUAGE CPP, DeriveFunctor, ViewPatterns #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} + module GHC.Iface.Tidy ( mkBootModDetailsTc, tidyProgram ) where diff --git a/compiler/GHC/IfaceToCore.hs b/compiler/GHC/IfaceToCore.hs index 6b7b623389..5c58ac90c0 100644 --- a/compiler/GHC/IfaceToCore.hs +++ b/compiler/GHC/IfaceToCore.hs @@ -9,6 +9,8 @@ Type checking of type signatures in interface files {-# LANGUAGE CPP #-} {-# LANGUAGE NondecreasingIndentation #-} +{-# OPTIONS_GHC -Wno-incomplete-record-updates #-} + module GHC.IfaceToCore ( tcLookupImported_maybe, importDecl, checkWiredInTyCon, tcHiBootIface, typecheckIface, diff --git a/compiler/GHC/Rename/Binds.hs b/compiler/GHC/Rename/Binds.hs index f4c8e0effd..6cf0a55fc6 100644 --- a/compiler/GHC/Rename/Binds.hs +++ b/compiler/GHC/Rename/Binds.hs @@ -1,6 +1,9 @@ {-# LANGUAGE ScopedTypeVariables, BangPatterns #-} {-# LANGUAGE TypeFamilies #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} +{-# OPTIONS_GHC -Wno-incomplete-record-updates #-} + {- (c) The GRASP/AQUA Project, Glasgow University, 1992-1998 diff --git a/compiler/GHC/Rename/Expr.hs b/compiler/GHC/Rename/Expr.hs index 0cae30b1f7..a084bff71e 100644 --- a/compiler/GHC/Rename/Expr.hs +++ b/compiler/GHC/Rename/Expr.hs @@ -16,6 +16,9 @@ free variables. {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE ViewPatterns #-} +{-# OPTIONS_GHC -Wno-incomplete-record-updates #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} + module GHC.Rename.Expr ( rnLExpr, rnExpr, rnStmts ) where diff --git a/compiler/GHC/Rename/Names.hs b/compiler/GHC/Rename/Names.hs index e23191bf0c..ecf82fffa0 100644 --- a/compiler/GHC/Rename/Names.hs +++ b/compiler/GHC/Rename/Names.hs @@ -10,6 +10,9 @@ Extracting imported and top-level names in scope {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} +{-# OPTIONS_GHC -Wno-incomplete-record-updates #-} + module GHC.Rename.Names ( rnImports, getLocalNonValBinders, newRecordSelector, extendGlobalRdrEnvRn, diff --git a/compiler/GHC/Rename/Pat.hs b/compiler/GHC/Rename/Pat.hs index 9b03c83681..ae509867b3 100644 --- a/compiler/GHC/Rename/Pat.hs +++ b/compiler/GHC/Rename/Pat.hs @@ -18,6 +18,9 @@ free variables. {-# LANGUAGE ViewPatterns #-} {-# LANGUAGE DeriveFunctor #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} +{-# OPTIONS_GHC -Wno-incomplete-record-updates #-} + module GHC.Rename.Pat (-- main entry points rnPat, rnPats, rnBindPat, rnPatAndThen, diff --git a/compiler/GHC/Rename/Source.hs b/compiler/GHC/Rename/Source.hs index 6a84e30936..934c346971 100644 --- a/compiler/GHC/Rename/Source.hs +++ b/compiler/GHC/Rename/Source.hs @@ -10,6 +10,9 @@ Main pass of renamer {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE ViewPatterns #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} +{-# OPTIONS_GHC -Wno-incomplete-record-updates #-} + module GHC.Rename.Source ( rnSrcDecls, addTcgDUs, findSplice ) where diff --git a/compiler/GHC/Rename/Splice.hs b/compiler/GHC/Rename/Splice.hs index 5211834c0e..5115052718 100644 --- a/compiler/GHC/Rename/Splice.hs +++ b/compiler/GHC/Rename/Splice.hs @@ -2,6 +2,8 @@ {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE ViewPatterns #-} +{-# OPTIONS_GHC -Wno-incomplete-record-updates #-} + module GHC.Rename.Splice ( rnTopSpliceDecls, rnSpliceType, rnSpliceExpr, rnSplicePat, rnSpliceDecl, diff --git a/compiler/GHC/Rename/Utils.hs b/compiler/GHC/Rename/Utils.hs index b2d8fad31c..29705c56f0 100644 --- a/compiler/GHC/Rename/Utils.hs +++ b/compiler/GHC/Rename/Utils.hs @@ -7,6 +7,8 @@ This module contains miscellaneous functions related to renaming. {-# LANGUAGE ViewPatterns #-} {-# LANGUAGE TypeFamilies #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} + module GHC.Rename.Utils ( checkDupRdrNames, checkShadowedRdrNames, checkDupNames, checkDupAndShadowedNames, dupNamesErr, diff --git a/compiler/GHC/Stg/Unarise.hs b/compiler/GHC/Stg/Unarise.hs index bc2ce4cb87..4ed88255c1 100644 --- a/compiler/GHC/Stg/Unarise.hs +++ b/compiler/GHC/Stg/Unarise.hs @@ -194,6 +194,8 @@ STG programs after unarisation have these invariants: {-# LANGUAGE CPP, TupleSections #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} + module GHC.Stg.Unarise (unarise) where #include "HsVersions.h" diff --git a/compiler/GHC/StgToCmm/Expr.hs b/compiler/GHC/StgToCmm/Expr.hs index 0c2d9b8ae5..1befdd7d3a 100644 --- a/compiler/GHC/StgToCmm/Expr.hs +++ b/compiler/GHC/StgToCmm/Expr.hs @@ -1,5 +1,7 @@ {-# LANGUAGE CPP, BangPatterns #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} + ----------------------------------------------------------------------------- -- -- Stg to C-- code generation: expressions diff --git a/compiler/GHC/StgToCmm/Heap.hs b/compiler/GHC/StgToCmm/Heap.hs index 492a4460f8..0ac573314a 100644 --- a/compiler/GHC/StgToCmm/Heap.hs +++ b/compiler/GHC/StgToCmm/Heap.hs @@ -6,6 +6,8 @@ -- ----------------------------------------------------------------------------- +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} + module GHC.StgToCmm.Heap ( getVirtHp, setVirtHp, setRealHp, getHpRelOffset, diff --git a/compiler/GHC/StgToCmm/Prim.hs b/compiler/GHC/StgToCmm/Prim.hs index 06264099df..4354814751 100644 --- a/compiler/GHC/StgToCmm/Prim.hs +++ b/compiler/GHC/StgToCmm/Prim.hs @@ -7,6 +7,8 @@ {-# OPTIONS_GHC -fmax-pmcheck-iterations=4000000 #-} #endif +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} + ---------------------------------------------------------------------------- -- -- Stg to C--: primitive operations diff --git a/compiler/GHC/ThToHs.hs b/compiler/GHC/ThToHs.hs index 298bc6660a..7d970ed570 100644 --- a/compiler/GHC/ThToHs.hs +++ b/compiler/GHC/ThToHs.hs @@ -12,6 +12,9 @@ This module converts Template Haskell syntax into Hs syntax {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE ViewPatterns #-} +{-# OPTIONS_GHC -Wno-incomplete-record-updates #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} + module GHC.ThToHs ( convertToHsExpr , convertToPat diff --git a/compiler/basicTypes/BasicTypes.hs b/compiler/basicTypes/BasicTypes.hs index dc545ea838..046b208983 100644 --- a/compiler/basicTypes/BasicTypes.hs +++ b/compiler/basicTypes/BasicTypes.hs @@ -15,6 +15,7 @@ types that -} {-# LANGUAGE DeriveDataTypeable #-} +{-# OPTIONS_GHC -Wno-incomplete-record-updates #-} module BasicTypes( Version, bumpVersion, initialVersion, diff --git a/compiler/basicTypes/Demand.hs b/compiler/basicTypes/Demand.hs index b64663b970..edb91734d2 100644 --- a/compiler/basicTypes/Demand.hs +++ b/compiler/basicTypes/Demand.hs @@ -6,6 +6,7 @@ -} {-# LANGUAGE CPP, FlexibleInstances, TypeSynonymInstances, RecordWildCards #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} module Demand ( StrDmd, UseDmd(..), Count, diff --git a/compiler/basicTypes/IdInfo.hs b/compiler/basicTypes/IdInfo.hs index b2ec6acb5a..b768a0cbcf 100644 --- a/compiler/basicTypes/IdInfo.hs +++ b/compiler/basicTypes/IdInfo.hs @@ -11,6 +11,8 @@ Haskell. [WDP 94/11]) {-# LANGUAGE CPP #-} {-# LANGUAGE FlexibleContexts #-} +{-# OPTIONS_GHC -Wno-incomplete-record-updates #-} + module IdInfo ( -- * The IdDetails type IdDetails(..), pprIdDetails, coVarDetails, isCoVarDetails, diff --git a/compiler/basicTypes/Literal.hs b/compiler/basicTypes/Literal.hs index bea0478d5c..526115d5ef 100644 --- a/compiler/basicTypes/Literal.hs +++ b/compiler/basicTypes/Literal.hs @@ -6,6 +6,7 @@ -} {-# LANGUAGE CPP, DeriveDataTypeable, ScopedTypeVariables #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} module Literal ( diff --git a/compiler/basicTypes/MkId.hs b/compiler/basicTypes/MkId.hs index 7a3d71cb7b..49e5115097 100644 --- a/compiler/basicTypes/MkId.hs +++ b/compiler/basicTypes/MkId.hs @@ -14,6 +14,8 @@ have a standard form, namely: {-# LANGUAGE CPP #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} + module MkId ( mkDictFunId, mkDictFunTy, mkDictSelId, mkDictSelRhs, diff --git a/compiler/basicTypes/Var.hs b/compiler/basicTypes/Var.hs index f5142caf3c..e9926d799d 100644 --- a/compiler/basicTypes/Var.hs +++ b/compiler/basicTypes/Var.hs @@ -6,6 +6,8 @@ -} {-# LANGUAGE CPP, FlexibleContexts, MultiWayIf, FlexibleInstances, DeriveDataTypeable #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} +{-# OPTIONS_GHC -Wno-incomplete-record-updates #-} -- | -- #name_types# diff --git a/compiler/coreSyn/CoreArity.hs b/compiler/coreSyn/CoreArity.hs index 56ce0fdff5..3c5d2e96c6 100644 --- a/compiler/coreSyn/CoreArity.hs +++ b/compiler/coreSyn/CoreArity.hs @@ -8,6 +8,8 @@ {-# LANGUAGE CPP #-} +{-# OPTIONS_GHC -Wno-incomplete-record-updates #-} + -- | Arity and eta expansion module CoreArity ( manifestArity, joinRhsArity, exprArity, typeArity, diff --git a/compiler/coreSyn/CoreSubst.hs b/compiler/coreSyn/CoreSubst.hs index 904e9eec04..669026c641 100644 --- a/compiler/coreSyn/CoreSubst.hs +++ b/compiler/coreSyn/CoreSubst.hs @@ -7,6 +7,7 @@ Utility functions on @Core@ syntax -} {-# LANGUAGE CPP #-} +{-# OPTIONS_GHC -Wno-incomplete-record-updates #-} module CoreSubst ( -- * Main data types Subst(..), -- Implementation exported for supercompiler's Renaming.hs only diff --git a/compiler/coreSyn/CoreSyn.hs b/compiler/coreSyn/CoreSyn.hs index 53824737a1..bc04d4ee22 100644 --- a/compiler/coreSyn/CoreSyn.hs +++ b/compiler/coreSyn/CoreSyn.hs @@ -6,6 +6,8 @@ {-# LANGUAGE CPP, DeriveDataTypeable, FlexibleContexts #-} {-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE BangPatterns #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} +{-# OPTIONS_GHC -Wno-incomplete-record-updates #-} -- | CoreSyn holds all the main data types for use by for the Glasgow Haskell Compiler midsection module CoreSyn ( diff --git a/compiler/coreSyn/CoreTidy.hs b/compiler/coreSyn/CoreTidy.hs index 5183d26622..9c19f3667b 100644 --- a/compiler/coreSyn/CoreTidy.hs +++ b/compiler/coreSyn/CoreTidy.hs @@ -8,6 +8,7 @@ The code for *top-level* bindings is in GHC.Iface.Tidy. -} {-# LANGUAGE CPP #-} +{-# OPTIONS_GHC -Wno-incomplete-record-updates #-} module CoreTidy ( tidyExpr, tidyRules, tidyUnfolding ) where diff --git a/compiler/coreSyn/CoreUnfold.hs b/compiler/coreSyn/CoreUnfold.hs index 260530bc55..1b02878bd8 100644 --- a/compiler/coreSyn/CoreUnfold.hs +++ b/compiler/coreSyn/CoreUnfold.hs @@ -17,6 +17,8 @@ find, unsurprisingly, a Core expression. {-# LANGUAGE CPP #-} +{-# OPTIONS_GHC -Wno-incomplete-record-updates #-} + module CoreUnfold ( Unfolding, UnfoldingGuidance, -- Abstract types diff --git a/compiler/coreSyn/MkCore.hs b/compiler/coreSyn/MkCore.hs index 7e5bbe548c..a261a98451 100644 --- a/compiler/coreSyn/MkCore.hs +++ b/compiler/coreSyn/MkCore.hs @@ -1,5 +1,7 @@ {-# LANGUAGE CPP #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} + -- | Handy functions for creating much Core syntax module MkCore ( -- * Constructing normal syntax diff --git a/compiler/deSugar/Coverage.hs b/compiler/deSugar/Coverage.hs index d94f640f84..178372a567 100644 --- a/compiler/deSugar/Coverage.hs +++ b/compiler/deSugar/Coverage.hs @@ -8,6 +8,8 @@ {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE DeriveFunctor #-} +{-# OPTIONS_GHC -Wno-incomplete-record-updates #-} + module Coverage (addTicksToBinds, hpcInitCode) where import GhcPrelude as Prelude diff --git a/compiler/deSugar/DsArrows.hs b/compiler/deSugar/DsArrows.hs index 0cbf3dae39..bab9a60cad 100644 --- a/compiler/deSugar/DsArrows.hs +++ b/compiler/deSugar/DsArrows.hs @@ -10,6 +10,8 @@ Desugaring arrow commands {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE ViewPatterns #-} +{-# OPTIONS_GHC -Wno-incomplete-record-updates #-} + module DsArrows ( dsProcExpr ) where #include "HsVersions.h" diff --git a/compiler/deSugar/DsBinds.hs b/compiler/deSugar/DsBinds.hs index ef6f72e780..ac3a41a8fb 100644 --- a/compiler/deSugar/DsBinds.hs +++ b/compiler/deSugar/DsBinds.hs @@ -15,6 +15,8 @@ lower levels it is preserved with @let@/@letrec@s). {-# LANGUAGE ViewPatterns #-} {-# LANGUAGE FlexibleContexts #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} + module DsBinds ( dsTopLHsBinds, dsLHsBinds, decomposeRuleLhs, dsSpec, dsHsWrapper, dsTcEvBinds, dsTcEvBinds_s, dsEvBinds, dsMkUserRule ) where diff --git a/compiler/deSugar/DsCCall.hs b/compiler/deSugar/DsCCall.hs index 3df8ee11e0..fc5f10eb4b 100644 --- a/compiler/deSugar/DsCCall.hs +++ b/compiler/deSugar/DsCCall.hs @@ -7,6 +7,8 @@ Desugaring foreign calls -} {-# LANGUAGE CPP #-} + +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} module DsCCall ( dsCCall , mkFCall diff --git a/compiler/deSugar/DsExpr.hs b/compiler/deSugar/DsExpr.hs index 1271bcbe7b..0f1386d76d 100644 --- a/compiler/deSugar/DsExpr.hs +++ b/compiler/deSugar/DsExpr.hs @@ -10,6 +10,9 @@ Desugaring expressions. {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE ViewPatterns #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} +{-# OPTIONS_GHC -Wno-incomplete-record-updates #-} + module DsExpr ( dsExpr, dsLExpr, dsLExprNoLP, dsLocalBinds , dsValBinds, dsLit, dsSyntaxExpr , dsHandleMonadicFailure ) where diff --git a/compiler/deSugar/DsForeign.hs b/compiler/deSugar/DsForeign.hs index cdf58e709e..5c2b1a8a22 100644 --- a/compiler/deSugar/DsForeign.hs +++ b/compiler/deSugar/DsForeign.hs @@ -11,6 +11,8 @@ Desugaring foreign declarations (see also DsCCall). {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE ViewPatterns #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} + module DsForeign ( dsForeigns ) where #include "HsVersions.h" diff --git a/compiler/deSugar/DsMeta.hs b/compiler/deSugar/DsMeta.hs index cdb049cc87..9dcbc8faaa 100644 --- a/compiler/deSugar/DsMeta.hs +++ b/compiler/deSugar/DsMeta.hs @@ -5,6 +5,8 @@ {-# LANGUAGE DataKinds #-} {-# LANGUAGE UndecidableInstances #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} + ----------------------------------------------------------------------------- -- -- (c) The University of Glasgow 2006 diff --git a/compiler/deSugar/DsUsage.hs b/compiler/deSugar/DsUsage.hs index 811e5f9b07..8d3517410e 100644 --- a/compiler/deSugar/DsUsage.hs +++ b/compiler/deSugar/DsUsage.hs @@ -2,6 +2,8 @@ {-# LANGUAGE TupleSections #-} {-# LANGUAGE ViewPatterns #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} + module DsUsage ( -- * Dependency/fingerprinting code (used by GHC.Iface.Utils) mkUsageInfo, mkUsedNames, mkDependencies diff --git a/compiler/deSugar/ExtractDocs.hs b/compiler/deSugar/ExtractDocs.hs index ec5238ae4b..8612a05cb9 100644 --- a/compiler/deSugar/ExtractDocs.hs +++ b/compiler/deSugar/ExtractDocs.hs @@ -4,6 +4,8 @@ {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE ViewPatterns #-} +{-# OPTIONS_GHC -Wno-incomplete-record-updates #-} + module ExtractDocs (extractDocs) where import GhcPrelude diff --git a/compiler/deSugar/Match.hs b/compiler/deSugar/Match.hs index d5518aa870..ac277893f6 100644 --- a/compiler/deSugar/Match.hs +++ b/compiler/deSugar/Match.hs @@ -12,6 +12,9 @@ The @match@ function {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE ViewPatterns #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} +{-# OPTIONS_GHC -Wno-incomplete-record-updates #-} + module Match ( match, matchEquations, matchWrapper, matchSimply , matchSinglePat, matchSinglePatVar ) where diff --git a/compiler/deSugar/MatchCon.hs b/compiler/deSugar/MatchCon.hs index d27e1b37af..b5d5807592 100644 --- a/compiler/deSugar/MatchCon.hs +++ b/compiler/deSugar/MatchCon.hs @@ -10,6 +10,8 @@ Pattern-matching constructors {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE ViewPatterns #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} + module MatchCon ( matchConFamily, matchPatSyn ) where #include "HsVersions.h" diff --git a/compiler/deSugar/MatchLit.hs b/compiler/deSugar/MatchLit.hs index 14d5b942b1..a6ec151bfd 100644 --- a/compiler/deSugar/MatchLit.hs +++ b/compiler/deSugar/MatchLit.hs @@ -9,6 +9,8 @@ Pattern-matching literal patterns {-# LANGUAGE CPP, ScopedTypeVariables #-} {-# LANGUAGE ViewPatterns #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} + module MatchLit ( dsLit, dsOverLit, hsLitKey , tidyLitPat, tidyNPat , matchLiterals, matchNPlusKPats, matchNPats diff --git a/compiler/ghci/ByteCodeGen.hs b/compiler/ghci/ByteCodeGen.hs index 186d094bff..5d5b2990e6 100644 --- a/compiler/ghci/ByteCodeGen.hs +++ b/compiler/ghci/ByteCodeGen.hs @@ -2,6 +2,7 @@ {-# LANGUAGE DeriveFunctor #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# OPTIONS_GHC -fprof-auto-top #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} -- -- (c) The University of Glasgow 2002-2006 -- diff --git a/compiler/iface/BuildTyCl.hs b/compiler/iface/BuildTyCl.hs index 1ea61cf0c5..d9959f339f 100644 --- a/compiler/iface/BuildTyCl.hs +++ b/compiler/iface/BuildTyCl.hs @@ -5,6 +5,8 @@ {-# LANGUAGE CPP #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} + module BuildTyCl ( buildDataCon, buildPatSyn, diff --git a/compiler/llvmGen/LlvmCodeGen/Base.hs b/compiler/llvmGen/LlvmCodeGen/Base.hs index 165f733af4..41b7fcc562 100644 --- a/compiler/llvmGen/LlvmCodeGen/Base.hs +++ b/compiler/llvmGen/LlvmCodeGen/Base.hs @@ -1,6 +1,8 @@ {-# LANGUAGE CPP #-} {-# LANGUAGE DeriveFunctor #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} + -- ---------------------------------------------------------------------------- -- | Base LLVM Code Generation module -- diff --git a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs index f9b10679ef..e46e0f787f 100644 --- a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs +++ b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs @@ -1,5 +1,6 @@ {-# LANGUAGE CPP, GADTs #-} {-# OPTIONS_GHC -fno-warn-type-defaults #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} -- ---------------------------------------------------------------------------- -- | Handle conversion of CmmProc to LLVM code. -- diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs index d212722d8d..830135b7c8 100644 --- a/compiler/main/DriverPipeline.hs +++ b/compiler/main/DriverPipeline.hs @@ -1,5 +1,7 @@ {-# LANGUAGE CPP, NamedFieldPuns, NondecreasingIndentation, BangPatterns, MultiWayIf #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} + ----------------------------------------------------------------------------- -- -- GHC Driver diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs index 61f83c6437..c5fd66e1f7 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/main/DynFlags.hs @@ -17,6 +17,7 @@ {-# OPTIONS_GHC -fno-cse #-} -- -fno-cse is needed for GLOBAL_VAR's to behave properly +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} module DynFlags ( -- * Dynamic flags and associated configuration types diff --git a/compiler/main/GhcMake.hs b/compiler/main/GhcMake.hs index 6525163608..6bcb256561 100644 --- a/compiler/main/GhcMake.hs +++ b/compiler/main/GhcMake.hs @@ -1,6 +1,8 @@ {-# LANGUAGE BangPatterns, CPP, NondecreasingIndentation, ScopedTypeVariables #-} {-# LANGUAGE RecordWildCards, NamedFieldPuns #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} + -- ----------------------------------------------------------------------------- -- -- (c) The University of Glasgow, 2011 diff --git a/compiler/main/InteractiveEval.hs b/compiler/main/InteractiveEval.hs index 5d67a9a39c..badb746718 100644 --- a/compiler/main/InteractiveEval.hs +++ b/compiler/main/InteractiveEval.hs @@ -1,6 +1,8 @@ {-# LANGUAGE CPP, MagicHash, NondecreasingIndentation, RecordWildCards, BangPatterns #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} + -- ----------------------------------------------------------------------------- -- -- (c) The University of Glasgow, 2005-2007 diff --git a/compiler/nativeGen/AsmCodeGen.hs b/compiler/nativeGen/AsmCodeGen.hs index 021fbae195..4a38909e65 100644 --- a/compiler/nativeGen/AsmCodeGen.hs +++ b/compiler/nativeGen/AsmCodeGen.hs @@ -13,6 +13,8 @@ {-# LANGUAGE UnboxedTuples #-} #endif +{-# OPTIONS_GHC -Wno-incomplete-record-updates #-} + module AsmCodeGen ( -- * Module entry point nativeCodeGen diff --git a/compiler/nativeGen/PPC/Instr.hs b/compiler/nativeGen/PPC/Instr.hs index d19282fee6..f149c92c9d 100644 --- a/compiler/nativeGen/PPC/Instr.hs +++ b/compiler/nativeGen/PPC/Instr.hs @@ -1,5 +1,7 @@ {-# LANGUAGE CPP #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} + ----------------------------------------------------------------------------- -- -- Machine-dependent assembly language diff --git a/compiler/nativeGen/RegAlloc/Graph/Stats.hs b/compiler/nativeGen/RegAlloc/Graph/Stats.hs index 152e813515..2159548437 100644 --- a/compiler/nativeGen/RegAlloc/Graph/Stats.hs +++ b/compiler/nativeGen/RegAlloc/Graph/Stats.hs @@ -1,5 +1,7 @@ {-# LANGUAGE BangPatterns, CPP #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} + -- | Carries interesting info for debugging / profiling of the -- graph coloring register allocator. module RegAlloc.Graph.Stats ( diff --git a/compiler/nativeGen/RegAlloc/Linear/JoinToTargets.hs b/compiler/nativeGen/RegAlloc/Linear/JoinToTargets.hs index c21ab1bea1..d0710cb65f 100644 --- a/compiler/nativeGen/RegAlloc/Linear/JoinToTargets.hs +++ b/compiler/nativeGen/RegAlloc/Linear/JoinToTargets.hs @@ -1,3 +1,4 @@ +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} -- | Handles joining of a jump instruction to its targets. diff --git a/compiler/nativeGen/RegAlloc/Linear/Main.hs b/compiler/nativeGen/RegAlloc/Linear/Main.hs index bccffb208c..7a3b1ef902 100644 --- a/compiler/nativeGen/RegAlloc/Linear/Main.hs +++ b/compiler/nativeGen/RegAlloc/Linear/Main.hs @@ -1,5 +1,7 @@ {-# LANGUAGE BangPatterns, CPP, ScopedTypeVariables #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} + ----------------------------------------------------------------------------- -- -- The register allocator diff --git a/compiler/nativeGen/RegAlloc/Liveness.hs b/compiler/nativeGen/RegAlloc/Liveness.hs index c39ee4895a..44a7b359a8 100644 --- a/compiler/nativeGen/RegAlloc/Liveness.hs +++ b/compiler/nativeGen/RegAlloc/Liveness.hs @@ -3,6 +3,8 @@ {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} + ----------------------------------------------------------------------------- -- -- The register liveness determinator diff --git a/compiler/nativeGen/SPARC/CodeGen/Expand.hs b/compiler/nativeGen/SPARC/CodeGen/Expand.hs index ba7577602f..a384e498d2 100644 --- a/compiler/nativeGen/SPARC/CodeGen/Expand.hs +++ b/compiler/nativeGen/SPARC/CodeGen/Expand.hs @@ -1,3 +1,5 @@ +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} + -- | Expand out synthetic instructions into single machine instrs. module SPARC.CodeGen.Expand ( expandTop diff --git a/compiler/nativeGen/X86/CodeGen.hs b/compiler/nativeGen/X86/CodeGen.hs index 14e7cb56ce..8811385965 100644 --- a/compiler/nativeGen/X86/CodeGen.hs +++ b/compiler/nativeGen/X86/CodeGen.hs @@ -9,6 +9,8 @@ {-# OPTIONS_GHC -fmax-pmcheck-iterations=10000000 #-} #endif +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} + ----------------------------------------------------------------------------- -- -- Generating machine code (instruction selection) diff --git a/compiler/parser/HaddockUtils.hs b/compiler/parser/HaddockUtils.hs index d1d41a3d29..b8e0c564a6 100644 --- a/compiler/parser/HaddockUtils.hs +++ b/compiler/parser/HaddockUtils.hs @@ -1,3 +1,4 @@ +{-# OPTIONS_GHC -Wno-incomplete-record-updates #-} module HaddockUtils where diff --git a/compiler/parser/Lexer.x b/compiler/parser/Lexer.x index efae29e84e..5e7270be01 100644 --- a/compiler/parser/Lexer.x +++ b/compiler/parser/Lexer.x @@ -47,6 +47,7 @@ {-# LANGUAGE MultiWayIf #-} {-# OPTIONS_GHC -funbox-strict-fields #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} module Lexer ( Token(..), lexer, lexerDbg, pragState, mkPState, mkPStatePure, PState(..), diff --git a/compiler/prelude/PrelNames.hs b/compiler/prelude/PrelNames.hs index 8c0d25de46..17aee23fab 100644 --- a/compiler/prelude/PrelNames.hs +++ b/compiler/prelude/PrelNames.hs @@ -143,6 +143,7 @@ Note [Wired-in packages] in Module. This is done in Packages.findWiredInPackages -} {-# LANGUAGE CPP #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} module PrelNames ( Unique, Uniquable(..), hasKey, -- Re-exported for convenience diff --git a/compiler/prelude/TysPrim.hs b/compiler/prelude/TysPrim.hs index a25540290a..acf71c999a 100644 --- a/compiler/prelude/TysPrim.hs +++ b/compiler/prelude/TysPrim.hs @@ -6,6 +6,7 @@ -} {-# LANGUAGE CPP #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} -- | This module defines TyCons that can't be expressed in Haskell. -- They are all, therefore, wired-in TyCons. C.f module TysWiredIn diff --git a/compiler/prelude/TysWiredIn.hs b/compiler/prelude/TysWiredIn.hs index a1f9f267fe..bec29ebc76 100644 --- a/compiler/prelude/TysWiredIn.hs +++ b/compiler/prelude/TysWiredIn.hs @@ -7,6 +7,8 @@ {-# LANGUAGE CPP #-} {-# LANGUAGE OverloadedStrings #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} + -- | This module is about types that can be defined in Haskell, but which -- must be wired into the compiler nonetheless. C.f module TysPrim module TysWiredIn ( diff --git a/compiler/simplCore/CSE.hs b/compiler/simplCore/CSE.hs index 70e530c294..9a0945e290 100644 --- a/compiler/simplCore/CSE.hs +++ b/compiler/simplCore/CSE.hs @@ -6,6 +6,9 @@ {-# LANGUAGE CPP #-} +{-# OPTIONS_GHC -Wno-incomplete-record-updates #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} + module CSE (cseProgram, cseOneExpr) where #include "HsVersions.h" diff --git a/compiler/simplCore/CoreMonad.hs b/compiler/simplCore/CoreMonad.hs index 9832445b09..45ed5d19c1 100644 --- a/compiler/simplCore/CoreMonad.hs +++ b/compiler/simplCore/CoreMonad.hs @@ -7,6 +7,8 @@ {-# LANGUAGE CPP #-} {-# LANGUAGE DeriveFunctor #-} +{-# OPTIONS_GHC -Wno-incomplete-record-updates #-} + module CoreMonad ( -- * Configuration of the core-to-core passes CoreToDo(..), runWhen, runMaybe, diff --git a/compiler/simplCore/FloatIn.hs b/compiler/simplCore/FloatIn.hs index 216e848889..ab66a43a04 100644 --- a/compiler/simplCore/FloatIn.hs +++ b/compiler/simplCore/FloatIn.hs @@ -14,6 +14,7 @@ then discover that they aren't needed in the chosen branch. {-# LANGUAGE CPP #-} {-# OPTIONS_GHC -fprof-auto #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} module FloatIn ( floatInwards ) where diff --git a/compiler/simplCore/OccurAnal.hs b/compiler/simplCore/OccurAnal.hs index f6300edef4..96ee9623c3 100644 --- a/compiler/simplCore/OccurAnal.hs +++ b/compiler/simplCore/OccurAnal.hs @@ -13,6 +13,8 @@ core expression with (hopefully) improved usage information. {-# LANGUAGE CPP, BangPatterns, MultiWayIf, ViewPatterns #-} +{-# OPTIONS_GHC -Wno-incomplete-record-updates #-} + module OccurAnal ( occurAnalysePgm, occurAnalyseExpr, occurAnalyseExpr_NoBinderSwap ) where diff --git a/compiler/simplCore/SetLevels.hs b/compiler/simplCore/SetLevels.hs index 84f7147195..7cf0b9d524 100644 --- a/compiler/simplCore/SetLevels.hs +++ b/compiler/simplCore/SetLevels.hs @@ -50,6 +50,8 @@ -} {-# LANGUAGE CPP, MultiWayIf #-} + +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} module SetLevels ( setLevels, diff --git a/compiler/simplCore/Simplify.hs b/compiler/simplCore/Simplify.hs index e9bce31a62..01d802c30b 100644 --- a/compiler/simplCore/Simplify.hs +++ b/compiler/simplCore/Simplify.hs @@ -6,6 +6,7 @@ {-# LANGUAGE CPP #-} +{-# OPTIONS_GHC -Wno-incomplete-record-updates #-} module Simplify ( simplTopBinds, simplExpr, simplRules ) where #include "HsVersions.h" diff --git a/compiler/specialise/SpecConstr.hs b/compiler/specialise/SpecConstr.hs index a5f05cac50..6a6900123d 100644 --- a/compiler/specialise/SpecConstr.hs +++ b/compiler/specialise/SpecConstr.hs @@ -12,6 +12,8 @@ ToDo [Oct 2013] {-# LANGUAGE CPP #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} + module SpecConstr( specConstrProgram, SpecConstrAnnotation(..) diff --git a/compiler/specialise/Specialise.hs b/compiler/specialise/Specialise.hs index 1dcf76b8ea..7ec40138c5 100644 --- a/compiler/specialise/Specialise.hs +++ b/compiler/specialise/Specialise.hs @@ -7,6 +7,8 @@ {-# LANGUAGE CPP #-} {-# LANGUAGE DeriveFunctor #-} {-# LANGUAGE ViewPatterns #-} + +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} module Specialise ( specProgram, specUnfolding ) where #include "HsVersions.h" diff --git a/compiler/typecheck/ClsInst.hs b/compiler/typecheck/ClsInst.hs index 74c232c80d..bcb6971f2c 100644 --- a/compiler/typecheck/ClsInst.hs +++ b/compiler/typecheck/ClsInst.hs @@ -1,5 +1,7 @@ {-# LANGUAGE CPP #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} + module ClsInst ( matchGlobalInst, ClsInstResult(..), diff --git a/compiler/typecheck/Constraint.hs b/compiler/typecheck/Constraint.hs index 657734370e..29a8700b77 100644 --- a/compiler/typecheck/Constraint.hs +++ b/compiler/typecheck/Constraint.hs @@ -7,6 +7,8 @@ as used in the type-checker and constraint solver. {-# LANGUAGE CPP, GeneralizedNewtypeDeriving #-} +{-# OPTIONS_GHC -Wno-incomplete-record-updates #-} + module Constraint ( -- QCInst QCInst(..), isPendingScInst, diff --git a/compiler/typecheck/Inst.hs b/compiler/typecheck/Inst.hs index 47d7ff68a9..fa6558e943 100644 --- a/compiler/typecheck/Inst.hs +++ b/compiler/typecheck/Inst.hs @@ -9,6 +9,9 @@ The @Inst@ type: dictionaries or method instances {-# LANGUAGE CPP, MultiWayIf, TupleSections #-} {-# LANGUAGE FlexibleContexts #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} +{-# OPTIONS_GHC -Wno-incomplete-record-updates #-} + module Inst ( deeplySkolemise, topInstantiate, topInstantiateInferred, deeplyInstantiate, diff --git a/compiler/typecheck/TcArrows.hs b/compiler/typecheck/TcArrows.hs index 38ea5ade59..7bdcac865d 100644 --- a/compiler/typecheck/TcArrows.hs +++ b/compiler/typecheck/TcArrows.hs @@ -8,6 +8,8 @@ Typecheck arrow notation {-# LANGUAGE RankNTypes, TupleSections #-} {-# LANGUAGE TypeFamilies #-} +{-# OPTIONS_GHC -Wno-incomplete-record-updates #-} + module TcArrows ( tcProc ) where import GhcPrelude diff --git a/compiler/typecheck/TcClassDcl.hs b/compiler/typecheck/TcClassDcl.hs index fe93b785c1..58af3647c6 100644 --- a/compiler/typecheck/TcClassDcl.hs +++ b/compiler/typecheck/TcClassDcl.hs @@ -9,6 +9,8 @@ Typechecking class declarations {-# LANGUAGE CPP #-} {-# LANGUAGE TypeFamilies #-} +{-# OPTIONS_GHC -Wno-incomplete-record-updates #-} + module TcClassDcl ( tcClassSigs, tcClassDecl2, findMethodBind, instantiateMethod, tcClassMinimalDef, diff --git a/compiler/typecheck/TcDeriv.hs b/compiler/typecheck/TcDeriv.hs index 8b33dd4a63..8fef838de1 100644 --- a/compiler/typecheck/TcDeriv.hs +++ b/compiler/typecheck/TcDeriv.hs @@ -10,6 +10,8 @@ Handles @deriving@ clauses on @data@ declarations. {-# LANGUAGE MultiWayIf #-} {-# LANGUAGE TypeFamilies #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} + module TcDeriv ( tcDeriving, DerivInfo(..) ) where #include "HsVersions.h" diff --git a/compiler/typecheck/TcErrors.hs b/compiler/typecheck/TcErrors.hs index d531ced95f..b20fb55e11 100644 --- a/compiler/typecheck/TcErrors.hs +++ b/compiler/typecheck/TcErrors.hs @@ -2,6 +2,9 @@ {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE ViewPatterns #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} +{-# OPTIONS_GHC -Wno-incomplete-record-updates #-} + module TcErrors( reportUnsolved, reportAllUnsolved, warnAllUnsolved, warnDefaulting, diff --git a/compiler/typecheck/TcExpr.hs b/compiler/typecheck/TcExpr.hs index fd986cb2d1..845b81bb23 100644 --- a/compiler/typecheck/TcExpr.hs +++ b/compiler/typecheck/TcExpr.hs @@ -10,6 +10,8 @@ {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE TypeFamilies #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} + module TcExpr ( tcPolyExpr, tcMonoExpr, tcMonoExprNC, tcInferSigma, tcInferSigmaNC, tcInferRho, tcInferRhoNC, tcSyntaxOp, tcSyntaxOpGen, SyntaxOpType(..), synKnownType, diff --git a/compiler/typecheck/TcFlatten.hs b/compiler/typecheck/TcFlatten.hs index 5d5589df9a..73c354ef73 100644 --- a/compiler/typecheck/TcFlatten.hs +++ b/compiler/typecheck/TcFlatten.hs @@ -1,5 +1,7 @@ {-# LANGUAGE CPP, DeriveFunctor, ViewPatterns, BangPatterns #-} +{-# OPTIONS_GHC -Wno-incomplete-record-updates #-} + module TcFlatten( FlattenMode(..), flatten, flattenKind, flattenArgsNom, diff --git a/compiler/typecheck/TcGenDeriv.hs b/compiler/typecheck/TcGenDeriv.hs index ff58da474d..9c41abb6f1 100644 --- a/compiler/typecheck/TcGenDeriv.hs +++ b/compiler/typecheck/TcGenDeriv.hs @@ -16,6 +16,8 @@ This is where we do all the grimy bindings' generation. {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE TypeFamilies #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} + module TcGenDeriv ( BagDerivStuff, DerivStuff(..), diff --git a/compiler/typecheck/TcGenGenerics.hs b/compiler/typecheck/TcGenGenerics.hs index 3f59cb08fd..640010d45f 100644 --- a/compiler/typecheck/TcGenGenerics.hs +++ b/compiler/typecheck/TcGenGenerics.hs @@ -10,6 +10,8 @@ The deriving code for the Generic class {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE TypeFamilies #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} + module TcGenGenerics (canDoGenerics, canDoGenerics1, GenericKind(..), gen_Generic_binds, get_gen1_constrained_tys) where diff --git a/compiler/typecheck/TcHoleErrors.hs b/compiler/typecheck/TcHoleErrors.hs index f6b71c8378..ba8fa30eb1 100644 --- a/compiler/typecheck/TcHoleErrors.hs +++ b/compiler/typecheck/TcHoleErrors.hs @@ -1,5 +1,6 @@ {-# LANGUAGE RecordWildCards #-} {-# LANGUAGE ExistentialQuantification #-} +{-# OPTIONS_GHC -Wno-incomplete-record-updates #-} module TcHoleErrors ( findValidHoleFits, tcFilterHoleFits , tcCheckHoleFit, tcSubsumes , withoutUnification diff --git a/compiler/typecheck/TcHsSyn.hs b/compiler/typecheck/TcHsSyn.hs index 0729b81df6..3d060191eb 100644 --- a/compiler/typecheck/TcHsSyn.hs +++ b/compiler/typecheck/TcHsSyn.hs @@ -14,6 +14,8 @@ checker. {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE ViewPatterns #-} +{-# OPTIONS_GHC -Wno-incomplete-record-updates #-} + module TcHsSyn ( -- * Extracting types from HsSyn hsLitType, hsPatType, hsLPatType, diff --git a/compiler/typecheck/TcHsType.hs b/compiler/typecheck/TcHsType.hs index 038871a27f..32fbae7a14 100644 --- a/compiler/typecheck/TcHsType.hs +++ b/compiler/typecheck/TcHsType.hs @@ -11,6 +11,8 @@ {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE ViewPatterns #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} + module TcHsType ( -- Type signatures kcClassSigType, tcClassSigType, diff --git a/compiler/typecheck/TcInstDcls.hs b/compiler/typecheck/TcInstDcls.hs index 30a2816d76..62edfae0ed 100644 --- a/compiler/typecheck/TcInstDcls.hs +++ b/compiler/typecheck/TcInstDcls.hs @@ -10,6 +10,9 @@ TcInstDecls: Typechecking instance declarations {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE TypeFamilies #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} +{-# OPTIONS_GHC -Wno-incomplete-record-updates #-} + module TcInstDcls ( tcInstDecls1, tcInstDeclsDeriv, tcInstDecls2 ) where #include "HsVersions.h" diff --git a/compiler/typecheck/TcInteract.hs b/compiler/typecheck/TcInteract.hs index e594b10895..2a77c6226d 100644 --- a/compiler/typecheck/TcInteract.hs +++ b/compiler/typecheck/TcInteract.hs @@ -1,5 +1,8 @@ {-# LANGUAGE CPP #-} +{-# OPTIONS_GHC -Wno-incomplete-record-updates #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} + module TcInteract ( solveSimpleGivens, -- Solves [Ct] solveSimpleWanteds, -- Solves Cts diff --git a/compiler/typecheck/TcMType.hs b/compiler/typecheck/TcMType.hs index 753a2d6642..ef75635994 100644 --- a/compiler/typecheck/TcMType.hs +++ b/compiler/typecheck/TcMType.hs @@ -11,6 +11,8 @@ mutable type variables. {-# LANGUAGE CPP, TupleSections, MultiWayIf #-} +{-# OPTIONS_GHC -Wno-incomplete-record-updates #-} + module TcMType ( TcTyVar, TcKind, TcType, TcTauType, TcThetaType, TcTyVarSet, diff --git a/compiler/typecheck/TcMatches.hs b/compiler/typecheck/TcMatches.hs index 96772f5dc0..e373fe6b8f 100644 --- a/compiler/typecheck/TcMatches.hs +++ b/compiler/typecheck/TcMatches.hs @@ -14,6 +14,8 @@ TcMatches: Typecheck some @Matches@ {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE RecordWildCards #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} + module TcMatches ( tcMatchesFun, tcGRHS, tcGRHSsPat, tcMatchesCase, tcMatchLambda, TcMatchCtxt(..), TcStmtChecker, TcExprStmtChecker, TcCmdStmtChecker, tcStmts, tcStmtsAndThen, tcDoStmts, tcBody, diff --git a/compiler/typecheck/TcOrigin.hs b/compiler/typecheck/TcOrigin.hs index 0ad9a6cc51..6cf1dbb8d8 100644 --- a/compiler/typecheck/TcOrigin.hs +++ b/compiler/typecheck/TcOrigin.hs @@ -7,6 +7,9 @@ The datatypes here are mainly used for error message generation. {-# LANGUAGE CPP #-} +{-# OPTIONS_GHC -Wno-incomplete-record-updates #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} + module TcOrigin ( -- UserTypeCtxt UserTypeCtxt(..), pprUserTypeCtxt, isSigMaybe, diff --git a/compiler/typecheck/TcPat.hs b/compiler/typecheck/TcPat.hs index c9d9125774..97664e9526 100644 --- a/compiler/typecheck/TcPat.hs +++ b/compiler/typecheck/TcPat.hs @@ -11,6 +11,8 @@ TcPat: Typechecking patterns {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE ViewPatterns #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} + module TcPat ( tcLetPat, newLetBndr, LetBndrSpec(..) , tcPat, tcPat_O, tcPats , addDataConStupidTheta, badFieldCon, polyPatSig ) where diff --git a/compiler/typecheck/TcPatSyn.hs b/compiler/typecheck/TcPatSyn.hs index 45147cd048..21f20c552d 100644 --- a/compiler/typecheck/TcPatSyn.hs +++ b/compiler/typecheck/TcPatSyn.hs @@ -10,6 +10,8 @@ {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE ViewPatterns #-} +{-# OPTIONS_GHC -Wno-incomplete-record-updates #-} + module TcPatSyn ( tcPatSynDecl, tcPatSynBuilderBind , tcPatSynBuilderOcc, nonBidirectionalErr ) where diff --git a/compiler/typecheck/TcRnDriver.hs b/compiler/typecheck/TcRnDriver.hs index c4afb5d891..99cbcf1578 100644 --- a/compiler/typecheck/TcRnDriver.hs +++ b/compiler/typecheck/TcRnDriver.hs @@ -17,6 +17,8 @@ https://gitlab.haskell.org/ghc/ghc/wikis/commentary/compiler/type-checker {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE ViewPatterns #-} +{-# OPTIONS_GHC -Wno-incomplete-record-updates #-} + module TcRnDriver ( tcRnStmt, tcRnExpr, TcRnExprMode(..), tcRnType, tcRnImportDecls, diff --git a/compiler/typecheck/TcRnMonad.hs b/compiler/typecheck/TcRnMonad.hs index e7e7e6efc4..4bf9ad90cf 100644 --- a/compiler/typecheck/TcRnMonad.hs +++ b/compiler/typecheck/TcRnMonad.hs @@ -8,6 +8,7 @@ Functions for working with the typechecker environment (setters, getters...). {-# LANGUAGE CPP, ExplicitForAll, FlexibleInstances, BangPatterns #-} {-# LANGUAGE RecordWildCards #-} {-# OPTIONS_GHC -fno-warn-orphans #-} +{-# OPTIONS_GHC -Wno-incomplete-record-updates #-} {-# LANGUAGE ViewPatterns #-} diff --git a/compiler/typecheck/TcSMonad.hs b/compiler/typecheck/TcSMonad.hs index 01df5df46e..aa5b283f9d 100644 --- a/compiler/typecheck/TcSMonad.hs +++ b/compiler/typecheck/TcSMonad.hs @@ -1,5 +1,7 @@ {-# LANGUAGE CPP, DeriveFunctor, TypeFamilies #-} +{-# OPTIONS_GHC -Wno-incomplete-record-updates #-} + -- Type definitions for the constraint solver module TcSMonad ( diff --git a/compiler/typecheck/TcSplice.hs b/compiler/typecheck/TcSplice.hs index 5ff4c314b3..566db1c1df 100644 --- a/compiler/typecheck/TcSplice.hs +++ b/compiler/typecheck/TcSplice.hs @@ -18,6 +18,8 @@ TcSplice: Template Haskell splices {-# LANGUAGE TupleSections #-} {-# OPTIONS_GHC -fno-warn-orphans #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} + module TcSplice( tcSpliceExpr, tcTypedBracket, tcUntypedBracket, -- runQuasiQuoteExpr, runQuasiQuotePat, diff --git a/compiler/typecheck/TcTyClsDecls.hs b/compiler/typecheck/TcTyClsDecls.hs index 6b49eeda68..bceb901c8a 100644 --- a/compiler/typecheck/TcTyClsDecls.hs +++ b/compiler/typecheck/TcTyClsDecls.hs @@ -10,6 +10,8 @@ TcTyClsDecls: Typecheck type and class declarations {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE ViewPatterns #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} + module TcTyClsDecls ( tcTyAndClassDecls, diff --git a/compiler/typecheck/TcTyDecls.hs b/compiler/typecheck/TcTyDecls.hs index e5df9daff8..9aee045c7e 100644 --- a/compiler/typecheck/TcTyDecls.hs +++ b/compiler/typecheck/TcTyDecls.hs @@ -14,6 +14,8 @@ files for imported data types. {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE ViewPatterns #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} + module TcTyDecls( RolesInfo, inferRoles, diff --git a/compiler/typecheck/TcType.hs b/compiler/typecheck/TcType.hs index 0ae70e8c1e..9faa4bb44e 100644 --- a/compiler/typecheck/TcType.hs +++ b/compiler/typecheck/TcType.hs @@ -16,6 +16,7 @@ is the principal client. -} {-# LANGUAGE CPP, ScopedTypeVariables, MultiWayIf, FlexibleContexts #-} +{-# OPTIONS_GHC -Wno-incomplete-record-updates #-} module TcType ( -------------------------------- diff --git a/compiler/typecheck/TcUnify.hs b/compiler/typecheck/TcUnify.hs index af83536f00..b5bffb3bf2 100644 --- a/compiler/typecheck/TcUnify.hs +++ b/compiler/typecheck/TcUnify.hs @@ -9,6 +9,9 @@ Type subsumption and unification {-# LANGUAGE CPP, DeriveFunctor, MultiWayIf, TupleSections, ScopedTypeVariables #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} +{-# OPTIONS_GHC -Wno-incomplete-record-updates #-} + module TcUnify ( -- Full-blown subsumption tcWrapResult, tcWrapResultO, tcSkolemise, tcSkolemiseET, diff --git a/compiler/typecheck/TcValidity.hs b/compiler/typecheck/TcValidity.hs index 990c86ee6f..a4074afe96 100644 --- a/compiler/typecheck/TcValidity.hs +++ b/compiler/typecheck/TcValidity.hs @@ -5,6 +5,9 @@ {-# LANGUAGE CPP, TupleSections, ViewPatterns #-} +{-# OPTIONS_GHC -Wno-incomplete-record-updates #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} + module TcValidity ( Rank, UserTypeCtxt(..), checkValidType, checkValidMonoType, checkValidTheta, diff --git a/compiler/types/FamInstEnv.hs b/compiler/types/FamInstEnv.hs index 275387e91b..56183e1495 100644 --- a/compiler/types/FamInstEnv.hs +++ b/compiler/types/FamInstEnv.hs @@ -5,6 +5,8 @@ {-# LANGUAGE CPP, GADTs, ScopedTypeVariables, BangPatterns, TupleSections, DeriveFunctor #-} +{-# OPTIONS_GHC -Wno-incomplete-record-updates #-} + module FamInstEnv ( FamInst(..), FamFlavor(..), famInstAxiom, famInstTyCon, famInstRHS, famInstsRepTyCons, famInstRepTyCon_maybe, dataFamInstRepTyCon, diff --git a/compiler/types/TyCoSubst.hs b/compiler/types/TyCoSubst.hs index 7c1a811ae3..27e2ab9f77 100644 --- a/compiler/types/TyCoSubst.hs +++ b/compiler/types/TyCoSubst.hs @@ -6,6 +6,7 @@ Type and Coercion - friends' interface {-# LANGUAGE CPP #-} {-# LANGUAGE BangPatterns #-} +{-# OPTIONS_GHC -Wno-incomplete-record-updates #-} -- | Substitution into types and coercions. module TyCoSubst diff --git a/compiler/types/TyCoTidy.hs b/compiler/types/TyCoTidy.hs index b6f87c2230..649a7dee11 100644 --- a/compiler/types/TyCoTidy.hs +++ b/compiler/types/TyCoTidy.hs @@ -1,4 +1,6 @@ {-# LANGUAGE BangPatterns #-} +{-# OPTIONS_GHC -Wno-incomplete-record-updates #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} -- | Tidying types and coercions for printing in error messages. module TyCoTidy diff --git a/compiler/types/Type.hs b/compiler/types/Type.hs index c0964fd79e..a318725f3b 100644 --- a/compiler/types/Type.hs +++ b/compiler/types/Type.hs @@ -5,6 +5,7 @@ {-# LANGUAGE CPP, FlexibleContexts #-} {-# OPTIONS_GHC -fno-warn-orphans #-} +{-# OPTIONS_GHC -Wno-incomplete-record-updates #-} -- | Main functions for manipulating types and type-related things module Type ( diff --git a/compiler/utils/Fingerprint.hs b/compiler/utils/Fingerprint.hs index 0d4499079f..21f6a93c77 100644 --- a/compiler/utils/Fingerprint.hs +++ b/compiler/utils/Fingerprint.hs @@ -1,4 +1,5 @@ {-# LANGUAGE CPP #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} -- ---------------------------------------------------------------------------- -- diff --git a/compiler/utils/GraphColor.hs b/compiler/utils/GraphColor.hs index 82ec522357..9ab2ad22af 100644 --- a/compiler/utils/GraphColor.hs +++ b/compiler/utils/GraphColor.hs @@ -3,6 +3,8 @@ -- the node keys, nodes and colors. -- +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} + module GraphColor ( module GraphBase, module GraphOps, diff --git a/compiler/utils/GraphOps.hs b/compiler/utils/GraphOps.hs index cc8668ea45..c7161f0e32 100644 --- a/compiler/utils/GraphOps.hs +++ b/compiler/utils/GraphOps.hs @@ -1,6 +1,8 @@ -- | Basic operations on graphs. -- +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} + module GraphOps ( addNode, delNode, getNode, lookupNode, modNode, size, diff --git a/compiler/utils/Util.hs b/compiler/utils/Util.hs index 1837b13e97..a8eb5ea471 100644 --- a/compiler/utils/Util.hs +++ b/compiler/utils/Util.hs @@ -6,6 +6,8 @@ {-# LANGUAGE BangPatterns #-} {-# LANGUAGE TupleSections #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} + -- | Highly random utility functions -- module Util ( diff --git a/libraries/base/GHC/Event/IntTable.hs b/libraries/base/GHC/Event/IntTable.hs index 7ae2e1a8dc..56993d18b3 100644 --- a/libraries/base/GHC/Event/IntTable.hs +++ b/libraries/base/GHC/Event/IntTable.hs @@ -1,6 +1,7 @@ {-# LANGUAGE Trustworthy #-} {-# LANGUAGE BangPatterns, NoImplicitPrelude, RecordWildCards #-} {-# OPTIONS_GHC -Wno-name-shadowing #-} +{-# OPTIONS_GHC -Wno-incomplete-record-updates #-} module GHC.Event.IntTable ( diff --git a/libraries/base/GHC/Float.hs b/libraries/base/GHC/Float.hs index 1e870e0c49..03e232c190 100644 --- a/libraries/base/GHC/Float.hs +++ b/libraries/base/GHC/Float.hs @@ -11,6 +11,7 @@ -- around, but we haven't got there yet: {-# OPTIONS_GHC -Wno-orphans #-} {-# OPTIONS_HADDOCK not-home #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} ----------------------------------------------------------------------------- -- | diff --git a/libraries/base/GHC/IO/Handle/Internals.hs b/libraries/base/GHC/IO/Handle/Internals.hs index 21284a776c..c0b7e35a11 100644 --- a/libraries/base/GHC/IO/Handle/Internals.hs +++ b/libraries/base/GHC/IO/Handle/Internals.hs @@ -7,6 +7,7 @@ #-} {-# OPTIONS_GHC -Wno-unused-matches #-} {-# OPTIONS_GHC -Wno-name-shadowing #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} {-# OPTIONS_HADDOCK not-home #-} ----------------------------------------------------------------------------- diff --git a/libraries/base/GHC/List.hs b/libraries/base/GHC/List.hs index ba5229f9cb..2cd24515d1 100644 --- a/libraries/base/GHC/List.hs +++ b/libraries/base/GHC/List.hs @@ -1,6 +1,7 @@ {-# LANGUAGE Trustworthy #-} {-# LANGUAGE CPP, NoImplicitPrelude, ScopedTypeVariables, MagicHash #-} {-# LANGUAGE BangPatterns #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} ----------------------------------------------------------------------------- -- | diff --git a/libraries/base/GHC/StaticPtr.hs b/libraries/base/GHC/StaticPtr.hs index dcffbad701..f478bad8cd 100644 --- a/libraries/base/GHC/StaticPtr.hs +++ b/libraries/base/GHC/StaticPtr.hs @@ -2,6 +2,7 @@ {-# LANGUAGE ExistentialQuantification #-} {-# LANGUAGE MagicHash #-} {-# LANGUAGE UnboxedTuples #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} ----------------------------------------------------------------------------- -- | -- Module : GHC.StaticPtr diff --git a/libraries/base/Text/Printf.hs b/libraries/base/Text/Printf.hs index a97a0fd4f0..f8d3f02281 100644 --- a/libraries/base/Text/Printf.hs +++ b/libraries/base/Text/Printf.hs @@ -1,5 +1,6 @@ {-# LANGUAGE Safe #-} {-# LANGUAGE GADTs #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} ----------------------------------------------------------------------------- -- | diff --git a/utils/ghc-cabal/Main.hs b/utils/ghc-cabal/Main.hs index b83ad63aba..92587971e7 100644 --- a/utils/ghc-cabal/Main.hs +++ b/utils/ghc-cabal/Main.hs @@ -1,4 +1,5 @@ {-# OPTIONS_GHC -fno-warn-warnings-deprecations #-} +{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} module Main (main) where |