[Git][ghc/ghc][wip/fix-hadrian-ghci] 3 commits: Derive Ord instance for Extension

Ben Gamari gitlab at gitlab.haskell.org
Mon Apr 20 17:05:44 UTC 2020



Ben Gamari pushed to branch wip/fix-hadrian-ghci at Glasgow Haskell Compiler / GHC


Commits:
36882493 by Shayne Fletcher at 2020-04-20T04:36:43-04:00
Derive Ord instance for Extension

Metric Increase:
   T12150
   T12234

- - - - -
b43365ad by Simon Peyton Jones at 2020-04-20T04:37:20-04:00
Fix a buglet in redundant-constraint warnings

Ticket #18036 pointed out that we were reporting a redundant
constraint when it really really wasn't.

Turned out to be a buglet in the SkolemInfo for the
relevant implication constraint.  Easily fixed!

- - - - -
f6cb3236 by Ben Gamari at 2020-04-20T13:05:37-04:00
hadrian/ghci: Allow arguments to be passed to GHCi

Previously the arguments passed to hadrian/ghci were passed both to
`hadrian` and GHCi. This is rather odd given that there are essentially
not arguments in the intersection of the two. Let's just pass them to
GHCi; this allows `hadrian/ghci -Werror`.

- - - - -


9 changed files:

- compiler/GHC/Tc/TyCl/Instance.hs
- hadrian/ghci
- hadrian/ghci-cabal
- hadrian/ghci-stack
- libraries/ghc-boot-th/GHC/LanguageExtensions/Type.hs
- + testsuite/tests/typecheck/should_compile/T18036.hs
- + testsuite/tests/typecheck/should_compile/T18036a.hs
- + testsuite/tests/typecheck/should_compile/T18036a.stderr
- testsuite/tests/typecheck/should_compile/all.T


Changes:

=====================================
compiler/GHC/Tc/TyCl/Instance.hs
=====================================
@@ -1719,19 +1719,26 @@ tcMethodBodyHelp hs_sig_fn sel_id local_meth_id meth_bind
   | Just hs_sig_ty <- hs_sig_fn sel_name
               -- There is a signature in the instance
               -- See Note [Instance method signatures]
-  = do { let ctxt = FunSigCtxt sel_name True
-       ; (sig_ty, hs_wrap)
+  = do { (sig_ty, hs_wrap)
              <- setSrcSpan (getLoc (hsSigType hs_sig_ty)) $
                 do { inst_sigs <- xoptM LangExt.InstanceSigs
                    ; checkTc inst_sigs (misplacedInstSig sel_name hs_sig_ty)
                    ; sig_ty  <- tcHsSigType (FunSigCtxt sel_name False) hs_sig_ty
                    ; let local_meth_ty = idType local_meth_id
+                         ctxt = FunSigCtxt sel_name False
+                                -- False <=> do not report redundant constraints when
+                                --           checking instance-sig <= class-meth-sig
+                                -- The instance-sig is the focus here; the class-meth-sig
+                                -- is fixed (#18036)
                    ; hs_wrap <- addErrCtxtM (methSigCtxt sel_name sig_ty local_meth_ty) $
                                 tcSubType_NC ctxt sig_ty local_meth_ty
                    ; return (sig_ty, hs_wrap) }
 
        ; inner_meth_name <- newName (nameOccName sel_name)
-       ; let inner_meth_id  = mkLocalId inner_meth_name sig_ty
+       ; let ctxt = FunSigCtxt sel_name True
+                    -- True <=> check for redundant constraints in the
+                    --          user-specified instance signature
+             inner_meth_id  = mkLocalId inner_meth_name sig_ty
              inner_meth_sig = CompleteSig { sig_bndr = inner_meth_id
                                           , sig_ctxt = ctxt
                                           , sig_loc  = getLoc (hsSigType hs_sig_ty) }


=====================================
hadrian/ghci
=====================================
@@ -1,4 +1,4 @@
 #!/usr/bin/env bash
 
 # By default on Linux/MacOS we build Hadrian using Cabal
-(. "hadrian/ghci-cabal" "$@")
+(. "hadrian/ghci-cabal" $@)


=====================================
hadrian/ghci-cabal
=====================================
@@ -3,5 +3,5 @@
 set -e
 
 # Replace newlines with spaces, as these otherwise break the ghci invocation on windows.
-GHC_FLAGS="$GHC_FLAGS $(TERM=dumb CABFLAGS=-v0 "hadrian/build-cabal" tool-args -q --build-root=.hadrian_ghci --flavour=ghc-in-ghci "$@" | tr '\n\r' ' ')"
-ghci $GHC_FLAGS "$@" -fno-code -fwrite-interface -hidir=.hadrian_ghci/interface -O0 ghc/Main.hs +RTS -A128m
+GHC_FLAGS="$GHC_FLAGS $(TERM=dumb CABFLAGS=-v0 "hadrian/build-cabal" tool-args -q --build-root=.hadrian_ghci --flavour=ghc-in-ghci $HADRIAN_ARGS | tr '\n\r' ' ')"
+ghci $GHC_FLAGS $@ -fno-code -fwrite-interface -hidir=.hadrian_ghci/interface -O0 ghc/Main.hs +RTS -A128m


=====================================
hadrian/ghci-stack
=====================================
@@ -3,5 +3,5 @@
 set -e
 
 # Replace newlines with spaces, as these otherwise break the ghci invocation on windows.
-GHC_FLAGS="$GHC_FLAGS $(TERM=dumb CABFLAGS=-v0 "hadrian/build-stack" tool-args -q --build-root=.hadrian_ghci --flavour=ghc-in-ghci "$@" | tr '\n\r' ' ')"
+GHC_FLAGS="$GHC_FLAGS $(TERM=dumb CABFLAGS=-v0 "hadrian/build-stack" tool-args -q --build-root=.hadrian_ghci --flavour=ghc-in-ghci $HADRIAN_ARGS | tr '\n\r' ' ')"
 stack exec -- ghci $GHC_FLAGS "$@" -fno-code -fwrite-interface -hidir=.hadrian_ghci/interface -O0 ghc/Main.hs +RTS -A128m


=====================================
libraries/ghc-boot-th/GHC/LanguageExtensions/Type.hs
=====================================
@@ -145,3 +145,7 @@ data Extension
    | CUSKs
    | StandaloneKindSignatures
    deriving (Eq, Enum, Show, Generic, Bounded)
+-- 'Ord' and 'Bounded' are provided for GHC API users (see discussions
+-- in https://gitlab.haskell.org/ghc/ghc/merge_requests/2707 and
+-- https://gitlab.haskell.org/ghc/ghc/merge_requests/826).
+instance Ord Extension where compare a b = compare (fromEnum a) (fromEnum b)


=====================================
testsuite/tests/typecheck/should_compile/T18036.hs
=====================================
@@ -0,0 +1,13 @@
+{-# LANGUAGE InstanceSigs #-}
+{-# OPTIONS_GHC -Wredundant-constraints #-}
+
+module T18036 where
+
+class Fold f where
+    fold :: Monoid m => f m -> m
+
+newtype Identity a = Identity a
+
+instance Fold Identity where
+    fold :: Identity a -> a
+    fold (Identity a) = a


=====================================
testsuite/tests/typecheck/should_compile/T18036a.hs
=====================================
@@ -0,0 +1,15 @@
+{-# LANGUAGE InstanceSigs #-}
+{-# OPTIONS_GHC -Wredundant-constraints #-}
+
+module T18036 where
+
+class Fold f where
+    fold :: Monoid m => f m -> m
+
+newtype Identity a = Identity a
+
+-- Here we /should/ warn about redundant constraints in the
+-- instance signature, since we can remove them
+instance Fold Identity where
+    fold :: Monoid a => Identity a -> a
+    fold (Identity a) = a


=====================================
testsuite/tests/typecheck/should_compile/T18036a.stderr
=====================================
@@ -0,0 +1,6 @@
+
+T18036a.hs:14:13: warning: [-Wredundant-constraints]
+    • Redundant constraint: Monoid a
+    • In the type signature for:
+           fold :: forall a. Monoid a => Identity a -> a
+      In the instance declaration for ‘Fold Identity’


=====================================
testsuite/tests/typecheck/should_compile/all.T
=====================================
@@ -703,3 +703,5 @@ test('T17024', normal, compile, [''])
 test('T17021a', normal, compile, [''])
 test('T18005', normal, compile, [''])
 test('T18023', normal, compile, [''])
+test('T18036', normal, compile, [''])
+test('T18036a', normal, compile, [''])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7bfb54c815142556c027459241a07c40c964f225...f6cb3236612a2ebc0da7c61e2b528ab8da6ea630

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7bfb54c815142556c027459241a07c40c964f225...f6cb3236612a2ebc0da7c61e2b528ab8da6ea630
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20200420/c5145a94/attachment-0001.html>


More information about the ghc-commits mailing list