Repository : ssh://darcs.haskell.org//srv/darcs/packages/base

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/e7df49e77a0ef55473825c22baccf4d9a88c9cfd

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

commit e7df49e77a0ef55473825c22baccf4d9a88c9cfd
Author: Simon Peyton Jones <[email protected]>
Date:   Wed Oct 31 09:20:10 2012 +0000

    Replace Rank2Types with RankNTypes

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

 Control/Monad/ST/Lazy/Imp.hs    |    2 +-
 Data/Data.hs                    |    2 +-
 GHC/Base.lhs                    |    2 +-
 GHC/Desugar.hs                  |    2 +-
 GHC/IO/Handle/Internals.hs      |    2 +-
 GHC/ST.lhs                      |    2 +-
 Text/ParserCombinators/ReadP.hs |    2 +-
 7 files changed, 7 insertions(+), 7 deletions(-)

diff --git a/Control/Monad/ST/Lazy/Imp.hs b/Control/Monad/ST/Lazy/Imp.hs
index 280723c..702185e 100644
--- a/Control/Monad/ST/Lazy/Imp.hs
+++ b/Control/Monad/ST/Lazy/Imp.hs
@@ -1,5 +1,5 @@
 {-# LANGUAGE Unsafe #-}
-{-# LANGUAGE CPP, MagicHash, UnboxedTuples, Rank2Types #-}
+{-# LANGUAGE CPP, MagicHash, UnboxedTuples, RankNTypes #-}
 {-# OPTIONS_HADDOCK hide #-}
 
 -----------------------------------------------------------------------------
diff --git a/Data/Data.hs b/Data/Data.hs
index 0a29668..708a82a 100644
--- a/Data/Data.hs
+++ b/Data/Data.hs
@@ -1,5 +1,5 @@
 {-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE CPP, Rank2Types, ScopedTypeVariables #-}
+{-# LANGUAGE CPP, RankNTypes, ScopedTypeVariables #-}
 
 -----------------------------------------------------------------------------
 -- |
diff --git a/GHC/Base.lhs b/GHC/Base.lhs
index 42978b1..4810a55 100644
--- a/GHC/Base.lhs
+++ b/GHC/Base.lhs
@@ -70,7 +70,7 @@ Other Prelude modules are much easier with fewer complex 
dependencies.
            , MagicHash
            , UnboxedTuples
            , ExistentialQuantification
-           , Rank2Types
+           , RankNTypes
   #-}
 -- -fno-warn-orphans is needed for things like:
 -- Orphan rule: "x# -# x#" ALWAYS forall x# :: Int# -# x# x# = 0
diff --git a/GHC/Desugar.hs b/GHC/Desugar.hs
index d4da1c8..8c10702 100644
--- a/GHC/Desugar.hs
+++ b/GHC/Desugar.hs
@@ -1,7 +1,7 @@
 {-# LANGUAGE Trustworthy #-}
 {-# LANGUAGE CPP
            , NoImplicitPrelude
-           , Rank2Types
+           , RankNTypes
            , ExistentialQuantification
   #-}
 
diff --git a/GHC/IO/Handle/Internals.hs b/GHC/IO/Handle/Internals.hs
index b77de47..f6c4ef4 100644
--- a/GHC/IO/Handle/Internals.hs
+++ b/GHC/IO/Handle/Internals.hs
@@ -4,7 +4,7 @@
            , BangPatterns
            , PatternGuards
            , NondecreasingIndentation
-           , Rank2Types
+           , RankNTypes
   #-}
 {-# OPTIONS_GHC -fno-warn-unused-matches #-}
 {-# OPTIONS_GHC -fno-warn-name-shadowing #-}
diff --git a/GHC/ST.lhs b/GHC/ST.lhs
index 74a299a..6f2fba1 100644
--- a/GHC/ST.lhs
+++ b/GHC/ST.lhs
@@ -1,6 +1,6 @@
 \begin{code}
 {-# LANGUAGE Unsafe #-}
-{-# LANGUAGE NoImplicitPrelude, MagicHash, UnboxedTuples, Rank2Types #-}
+{-# LANGUAGE NoImplicitPrelude, MagicHash, UnboxedTuples, RankNTypes #-}
 {-# OPTIONS_HADDOCK hide #-}
 -----------------------------------------------------------------------------
 -- |
diff --git a/Text/ParserCombinators/ReadP.hs b/Text/ParserCombinators/ReadP.hs
index cfcb3bd..9412373 100644
--- a/Text/ParserCombinators/ReadP.hs
+++ b/Text/ParserCombinators/ReadP.hs
@@ -1,7 +1,7 @@
 {-# LANGUAGE Trustworthy #-}
 {-# LANGUAGE CPP, NoImplicitPrelude #-}
 #ifndef __NHC__
-{-# LANGUAGE Rank2Types #-}
+{-# LANGUAGE RankNTypes #-}
 #endif
 #ifdef __GLASGOW_HASKELL__
 {-# LANGUAGE MagicHash #-}



_______________________________________________
Cvs-libraries mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-libraries

Reply via email to