Repository : ssh://darcs.haskell.org//srv/darcs/ghc

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/984676d51291ea900cec289599e647de38645405

>---------------------------------------------------------------

commit 984676d51291ea900cec289599e647de38645405
Author: Simon Peyton Jones <simo...@microsoft.com>
Date:   Fri Oct 19 00:54:59 2012 +0100

    Deprecate Rank2Types and PolymorphicComponents, in favour of RankNTypes
    
    We agreed that it's not worth the bother of trying to maintain all
    these distinct flags; RankNTypes will do the job fine.  Trac #6032.

>---------------------------------------------------------------

 compiler/main/DynFlags.hs        |   11 ++++-------
 compiler/prelude/PrelRules.lhs   |    2 +-
 compiler/simplCore/OccurAnal.lhs |    2 +-
 compiler/typecheck/TcMType.lhs   |   13 +++----------
 4 files changed, 9 insertions(+), 19 deletions(-)

diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs
index 35821b0..8498d48 100644
--- a/compiler/main/DynFlags.hs
+++ b/compiler/main/DynFlags.hs
@@ -504,7 +504,6 @@ data ExtensionFlag
    | Opt_MultiParamTypeClasses
    | Opt_FunctionalDependencies
    | Opt_UnicodeSyntax
-   | Opt_PolymorphicComponents
    | Opt_ExistentialQuantification
    | Opt_MagicHash
    | Opt_EmptyDataDecls
@@ -518,7 +517,6 @@ data ExtensionFlag
    | Opt_TupleSections
    | Opt_PatternGuards
    | Opt_LiberalTypeSynonyms
-   | Opt_Rank2Types
    | Opt_RankNTypes
    | Opt_ImpredicativeTypes
    | Opt_TypeOperators
@@ -2412,7 +2410,6 @@ xFlags = [
   ( "PatternGuards",                    Opt_PatternGuards, nop ),
   ( "UnicodeSyntax",                    Opt_UnicodeSyntax, nop ),
   ( "MagicHash",                        Opt_MagicHash, nop ),
-  ( "PolymorphicComponents",            Opt_PolymorphicComponents, nop ),
   ( "ExistentialQuantification",        Opt_ExistentialQuantification, nop ),
   ( "KindSignatures",                   Opt_KindSignatures, nop ),
   ( "EmptyDataDecls",                   Opt_EmptyDataDecls, nop ),
@@ -2425,7 +2422,10 @@ xFlags = [
   ( "CApiFFI",                          Opt_CApiFFI, nop ),
   ( "GHCForeignImportPrim",             Opt_GHCForeignImportPrim, nop ),
   ( "LiberalTypeSynonyms",              Opt_LiberalTypeSynonyms, nop ),
-  ( "Rank2Types",                       Opt_Rank2Types, nop ),
+  ( "PolymorphicComponents",            Opt_RankNTypes, 
+     deprecatedForExtension "RankNTypes" ),
+  ( "Rank2Types",                       Opt_RankNTypes, 
+     deprecatedForExtension "RankNTypes" ),
   ( "RankNTypes",                       Opt_RankNTypes, nop ),
   ( "ImpredicativeTypes",               Opt_ImpredicativeTypes, nop),
   ( "TypeOperators",                    Opt_TypeOperators, nop ),
@@ -2540,11 +2540,9 @@ defaultFlags settings
 impliedFlags :: [(ExtensionFlag, TurnOnFlag, ExtensionFlag)]
 impliedFlags
   = [ (Opt_RankNTypes,                turnOn, Opt_ExplicitForAll)
-    , (Opt_Rank2Types,                turnOn, Opt_ExplicitForAll)
     , (Opt_ScopedTypeVariables,       turnOn, Opt_ExplicitForAll)
     , (Opt_LiberalTypeSynonyms,       turnOn, Opt_ExplicitForAll)
     , (Opt_ExistentialQuantification, turnOn, Opt_ExplicitForAll)
-    , (Opt_PolymorphicComponents,     turnOn, Opt_ExplicitForAll)
     , (Opt_FlexibleInstances,         turnOn, Opt_TypeSynonymInstances)
     , (Opt_FunctionalDependencies,    turnOn, Opt_MultiParamTypeClasses)
 
@@ -2693,7 +2691,6 @@ glasgowExtsFlags = [
            , Opt_MultiParamTypeClasses
            , Opt_FunctionalDependencies
            , Opt_MagicHash
-           , Opt_PolymorphicComponents
            , Opt_ExistentialQuantification
            , Opt_UnicodeSyntax
            , Opt_PostfixOperators
diff --git a/compiler/prelude/PrelRules.lhs b/compiler/prelude/PrelRules.lhs
index d1a2efd..86a9844 100644
--- a/compiler/prelude/PrelRules.lhs
+++ b/compiler/prelude/PrelRules.lhs
@@ -12,7 +12,7 @@ ToDo:
    (i1 + i2) only if it results in a valid Float.
 
 \begin{code}
-{-# LANGUAGE Rank2Types #-}
+{-# LANGUAGE RankNTypes #-}
 {-# OPTIONS -optc-DNON_POSIX_SOURCE #-}
 
 module PrelRules ( primOpRules, builtinRules ) where
diff --git a/compiler/simplCore/OccurAnal.lhs b/compiler/simplCore/OccurAnal.lhs
index 5a204f4..692b971 100644
--- a/compiler/simplCore/OccurAnal.lhs
+++ b/compiler/simplCore/OccurAnal.lhs
@@ -436,7 +436,7 @@ We are in an infinite loop.
 
 A more elaborate example (that I actually saw in practice when I went to
 mark GHC.List.filter as INLINABLE) is as follows. Say I have this module:
-  {-# LANGUAGE Rank2Types #-}
+  {-# LANGUAGE RankNTypes #-}
   module GHCList where
   
   import Prelude hiding (filter)
diff --git a/compiler/typecheck/TcMType.lhs b/compiler/typecheck/TcMType.lhs
index 7a3db58..afc575c 100644
--- a/compiler/typecheck/TcMType.lhs
+++ b/compiler/typecheck/TcMType.lhs
@@ -993,21 +993,16 @@ checkValidType :: UserTypeCtxt -> Type -> TcM ()
 -- Not used for instance decls; checkValidInstance instead
 checkValidType ctxt ty 
   = do { traceTc "checkValidType" (ppr ty <+> text "::" <+> ppr (typeKind ty))
-       ; rank2_flag      <- xoptM Opt_Rank2Types
-       ; rankn_flag      <- xoptM Opt_RankNTypes
-       ; polycomp        <- xoptM Opt_PolymorphicComponents
+       ; rankn_flag  <- xoptM Opt_RankNTypes
        ; let gen_rank :: Rank -> Rank
              gen_rank r | rankn_flag = ArbitraryRank
-                       | rank2_flag = r2
                        | otherwise  = r
 
-             rank2 = gen_rank r2
              rank1 = gen_rank r1
              rank0 = gen_rank r0
 
              r0 = rankZeroMonoType
              r1 = LimitedRank True r0
-             r2 = LimitedRank True r1
 
              rank
               = case ctxt of
@@ -1021,10 +1016,8 @@ checkValidType ctxt ty
                 ExprSigCtxt    -> rank1
                 FunSigCtxt _   -> rank1
                 InfSigCtxt _   -> ArbitraryRank        -- Inferred type
-                ConArgCtxt _   | polycomp -> rank2
-                                     -- We are given the type of the entire
-                                     -- constructor, hence rank 1
-                               | otherwise -> rank1
+                ConArgCtxt _   -> rank1 -- We are given the type of the entire
+                                         -- constructor, hence rank 1
 
                 ForSigCtxt _   -> rank1
                 SpecInstCtxt   -> rank1



_______________________________________________
Cvs-ghc mailing list
Cvs-ghc@haskell.org
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to