summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorJose Pedro Magalhaes <jpm@cs.ox.ac.uk>2014-11-04 11:10:27 +0000
committerJose Pedro Magalhaes <jpm@cs.ox.ac.uk>2014-11-04 11:10:27 +0000
commit3744afb5d91ebbe235230b7e9a03e1918ed4aa2c (patch)
treeae953eebc9230a176721b49c64f8a63102b627f6
parentd8e899686d7f3092af54932f46ab122dc8d3d373 (diff)
parentd3a7126ff749d1eff31128ace31bcea26c4eadaa (diff)
downloadhaskell-3744afb5d91ebbe235230b7e9a03e1918ed4aa2c.tar.gz
Merge branch 'master' into wip/GenericsMetaDatawip/GenericsMetaData
-rw-r--r--compiler/simplCore/CallArity.hs4
-rw-r--r--compiler/simplCore/SetLevels.lhs2
-rw-r--r--docs/users_guide/7.10.1-notes.xml22
-rw-r--r--libraries/base/Data/Bool.hs40
-rw-r--r--libraries/base/Data/Char.hs341
-rw-r--r--libraries/base/Data/Fixed.hs25
-rw-r--r--libraries/base/Data/Typeable.hs21
-rw-r--r--libraries/base/Data/Typeable/Internal.hs27
-rw-r--r--libraries/base/GHC/Show.lhs1
-rw-r--r--libraries/base/base.cabal1
-rw-r--r--libraries/base/changelog.md2
-rw-r--r--libraries/base/tests/T9681.hs3
-rw-r--r--libraries/base/tests/T9681.stderr5
-rw-r--r--libraries/base/tests/all.T1
-rw-r--r--testsuite/.gitignore4
-rw-r--r--testsuite/driver/testlib.py10
m---------utils/haddock0
17 files changed, 412 insertions, 97 deletions
diff --git a/compiler/simplCore/CallArity.hs b/compiler/simplCore/CallArity.hs
index bead230bcd..5ee5fe296a 100644
--- a/compiler/simplCore/CallArity.hs
+++ b/compiler/simplCore/CallArity.hs
@@ -33,7 +33,7 @@ Note [Call Arity: The goal]
~~~~~~~~~~~~~~~~~~~~~~~~~~~
The goal of this analysis is to find out if we can eta-expand a local function,
-based on how it is being called. The motivating example is code this this,
+based on how it is being called. The motivating example is this code,
which comes up when we implement foldl using foldr, and do list fusion:
let go = \x -> let d = case ... of
@@ -46,7 +46,7 @@ If we do not eta-expand `go` to have arity 2, we are going to allocate a lot of
partial function applications, which would be bad.
The function `go` has a type of arity two, but only one lambda is manifest.
-Further more, an analysis that only looks at the RHS of go cannot be sufficient
+Furthermore, an analysis that only looks at the RHS of go cannot be sufficient
to eta-expand go: If `go` is ever called with one argument (and the result used
multiple times), we would be doing the work in `...` multiple times.
diff --git a/compiler/simplCore/SetLevels.lhs b/compiler/simplCore/SetLevels.lhs
index 645cf9fc14..b8726d93a4 100644
--- a/compiler/simplCore/SetLevels.lhs
+++ b/compiler/simplCore/SetLevels.lhs
@@ -331,7 +331,7 @@ lvlExpr env expr@(_, AnnApp _ _) = do
-- We don't split adjacent lambdas. That is, given
-- \x y -> (x+1,y)
-- we don't float to give
--- \x -> let v = x+y in \y -> (v,y)
+-- \x -> let v = x+1 in \y -> (v,y)
-- Why not? Because partial applications are fairly rare, and splitting
-- lambdas makes them more expensive.
diff --git a/docs/users_guide/7.10.1-notes.xml b/docs/users_guide/7.10.1-notes.xml
index 3ca5112a9f..fa7ad1a756 100644
--- a/docs/users_guide/7.10.1-notes.xml
+++ b/docs/users_guide/7.10.1-notes.xml
@@ -66,12 +66,6 @@
<itemizedlist>
<listitem>
<para>
- GHC has had its internal Unicode database for
- parsing updated to the Unicode 7.0 standard.
- </para>
- </listitem>
- <listitem>
- <para>
GHC now checks that all the language extensions required for
the inferred type signatures are explicitly enabled. This
means that if any of the type signatures inferred in your
@@ -212,6 +206,22 @@ echo "[]" > package.conf
Version number XXXXX (was 4.7.0.0)
</para>
</listitem>
+ <listitem>
+ <para>
+ GHC has had its internal Unicode database for
+ parsing updated to the Unicode 7.0 standard.
+ </para>
+ </listitem>
+ <listitem>
+ <para>
+ Attempting to access a portion of the result of
+ <literal>System.IO.hGetContents</literal> that was not yet
+ read when the handle was closed now throws an exception.
+ Previously, a lazy read from a closed handle would simply
+ end the result string, leading to silent or delayed
+ failures.
+ </para>
+ </listitem>
</itemizedlist>
</sect3>
diff --git a/libraries/base/Data/Bool.hs b/libraries/base/Data/Bool.hs
index 15371982ea..9f1bef6e7c 100644
--- a/libraries/base/Data/Bool.hs
+++ b/libraries/base/Data/Bool.hs
@@ -28,33 +28,33 @@ module Data.Bool (
import GHC.Base
--- | Case analysis for the 'Bool' type. @bool x y p@ evaluates to @x@
--- when @p@ is @False@, and evaluates to @y@ when @p@ is @True@.
+-- | Case analysis for the 'Bool' type. @'bool' x y p@ evaluates to @x@
+-- when @p@ is 'False', and evaluates to @y@ when @p@ is 'True'.
--
--- This is equivalent to @if p then y else x@; that is, one can
--- think of it as an if-then-else construct with its arguments
--- reordered.
+-- This is equivalent to @if p then y else x@; that is, one can
+-- think of it as an if-then-else construct with its arguments
+-- reordered.
--
--- /Since: 4.7.0.0/
+-- /Since: 4.7.0.0/
--
--- ==== __Examples__
+-- ==== __Examples__
--
--- Basic usage:
+-- Basic usage:
--
--- >>> bool "foo" "bar" True
--- "bar"
--- >>> bool "foo" "bar" False
--- "foo"
+-- >>> bool "foo" "bar" True
+-- "bar"
+-- >>> bool "foo" "bar" False
+-- "foo"
--
--- Confirm that @bool x y p@ and @if p then y else x@ are
--- equivalent:
+-- Confirm that @'bool' x y p@ and @if p then y else x@ are
+-- equivalent:
--
--- >>> let p = True; x = "bar"; y = "foo"
--- >>> bool x y p == if p then y else x
--- True
--- >>> let p = False
--- >>> bool x y p == if p then y else x
--- True
+-- >>> let p = True; x = "bar"; y = "foo"
+-- >>> bool x y p == if p then y else x
+-- True
+-- >>> let p = False
+-- >>> bool x y p == if p then y else x
+-- True
--
bool :: a -> a -> Bool -> a
bool f _ False = f
diff --git a/libraries/base/Data/Char.hs b/libraries/base/Data/Char.hs
index ac708ac0ef..e4e7fbfcb8 100644
--- a/libraries/base/Data/Char.hs
+++ b/libraries/base/Data/Char.hs
@@ -62,10 +62,38 @@ import GHC.Unicode
import GHC.Num
import GHC.Enum
--- | Convert a single digit 'Char' to the corresponding 'Int'.
--- This function fails unless its argument satisfies 'isHexDigit',
--- but recognises both upper and lower-case hexadecimal digits
--- (i.e. @\'0\'@..@\'9\'@, @\'a\'@..@\'f\'@, @\'A\'@..@\'F\'@).
+-- $setup
+-- Allow the use of Prelude in doctests.
+-- >>> import Prelude
+
+-- | Convert a single digit 'Char' to the corresponding 'Int'. This
+-- function fails unless its argument satisfies 'isHexDigit', but
+-- recognises both upper- and lower-case hexadecimal digits (that
+-- is, @\'0\'@..@\'9\'@, @\'a\'@..@\'f\'@, @\'A\'@..@\'F\'@).
+--
+-- ==== __Examples__
+--
+-- Characters @\'0\'@ through @\'9\'@ are converted properly to
+-- @0..9@:
+--
+-- >>> map digitToInt ['0'..'9']
+-- [0,1,2,3,4,5,6,7,8,9]
+--
+-- Both upper- and lower-case @\'A\'@ through @\'F\'@ are converted
+-- as well, to @10..15@.
+--
+-- >>> map digitToInt ['a'..'f']
+-- [10,11,12,13,14,15]
+-- >>> map digitToInt ['A'..'F']
+-- [10,11,12,13,14,15]
+--
+-- Anything else throws an exception:
+--
+-- >>> digitToInt 'G'
+-- *** Exception: Char.digitToInt: not a digit 'G'
+-- >>> digitToInt '♥'
+-- *** Exception: Char.digitToInt: not a digit '\9829'
+--
digitToInt :: Char -> Int
digitToInt c
| (fromIntegral dec::Word) <= 9 = dec
@@ -77,9 +105,61 @@ digitToInt c
hexl = ord c - ord 'a'
hexu = ord c - ord 'A'
--- | Unicode General Categories (column 2 of the UnicodeData table)
--- in the order they are listed in the Unicode standard.
-
+-- | Unicode General Categories (column 2 of the UnicodeData table) in
+-- the order they are listed in the Unicode standard (the Unicode
+-- Character Database, in particular).
+--
+-- ==== __Examples__
+--
+-- Basic usage:
+--
+-- >>> :t OtherLetter
+-- OtherLetter :: GeneralCategory
+--
+-- 'Eq' instance:
+--
+-- >>> UppercaseLetter == UppercaseLetter
+-- True
+-- >>> UppercaseLetter == LowercaseLetter
+-- False
+--
+-- 'Ord' instance:
+--
+-- >>> NonSpacingMark <= MathSymbol
+-- True
+--
+-- 'Enum' instance:
+--
+-- >>> enumFromTo ModifierLetter SpacingCombiningMark
+-- [ModifierLetter,OtherLetter,NonSpacingMark,SpacingCombiningMark]
+--
+-- 'Read' instance:
+--
+-- >>> read "DashPunctuation" :: GeneralCategory
+-- DashPunctuation
+-- >>> read "17" :: GeneralCategory
+-- *** Exception: Prelude.read: no parse
+--
+-- 'Show' instance:
+--
+-- >>> show EnclosingMark
+-- "EnclosingMark"
+--
+-- 'Bounded' instance:
+--
+-- >>> minBound :: GeneralCategory
+-- UppercaseLetter
+-- >>> maxBound :: GeneralCategory
+-- NotAssigned
+--
+-- 'Ix' instance:
+--
+-- >>> import Data.Ix ( index )
+-- >>> index (OtherLetter,Control) FinalQuote
+-- 12
+-- >>> index (OtherLetter,Control) Format
+-- *** Exception: Error in array index
+--
data GeneralCategory
= UppercaseLetter -- ^ Lu: Letter, Uppercase
| LowercaseLetter -- ^ Ll: Letter, Lowercase
@@ -113,15 +193,79 @@ data GeneralCategory
| NotAssigned -- ^ Cn: Other, Not Assigned
deriving (Eq, Ord, Enum, Read, Show, Bounded, Ix)
--- | The Unicode general category of the character.
+-- | The Unicode general category of the character. This relies on the
+-- 'Enum' instance of 'GeneralCategory', which must remain in the
+-- same order as the categories are presented in the Unicode
+-- standard.
+--
+-- ==== __Examples__
+--
+-- Basic usage:
+--
+-- >>> generalCategory 'a'
+-- LowercaseLetter
+-- >>> generalCategory 'A'
+-- UppercaseLetter
+-- >>> generalCategory '0'
+-- DecimalNumber
+-- >>> generalCategory '%'
+-- OtherPunctuation
+-- >>> generalCategory '♥'
+-- OtherSymbol
+-- >>> generalCategory '\31'
+-- Control
+-- >>> generalCategory ' '
+-- Space
+--
generalCategory :: Char -> GeneralCategory
generalCategory c = toEnum $ fromIntegral $ wgencat $ fromIntegral $ ord c
-- derived character classifiers
-- | Selects alphabetic Unicode characters (lower-case, upper-case and
--- title-case letters, plus letters of caseless scripts and modifiers letters).
--- This function is equivalent to 'Data.Char.isAlpha'.
+-- title-case letters, plus letters of caseless scripts and
+-- modifiers letters). This function is equivalent to
+-- 'Data.Char.isAlpha'.
+--
+-- This function returns 'True' if its argument has one of the
+-- following 'GeneralCategory's, or 'False' otherwise:
+--
+-- * 'UppercaseLetter'
+-- * 'LowercaseLetter'
+-- * 'TitlecaseLetter'
+-- * 'ModifierLetter'
+-- * 'OtherLetter'
+--
+-- These classes are defined in the
+-- <http://www.unicode.org/reports/tr44/tr44-14.html#GC_Values_Table Unicode Character Database>,
+-- part of the Unicode standard. The same document defines what is
+-- and is not a \"Letter\".
+--
+-- ==== __Examples__
+--
+-- Basic usage:
+--
+-- >>> isLetter 'a'
+-- True
+-- >>> isLetter 'A'
+-- True
+-- >>> isLetter '0'
+-- False
+-- >>> isLetter '%'
+-- False
+-- >>> isLetter '♥'
+-- False
+-- >>> isLetter '\31'
+-- False
+--
+-- Ensure that 'isLetter' and 'isAlpha' are equivalent.
+--
+-- >>> let chars = [(chr 0)..]
+-- >>> let letters = map isLetter chars
+-- >>> let alphas = map isAlpha chars
+-- >>> letters == alphas
+-- True
+--
isLetter :: Char -> Bool
isLetter c = case generalCategory c of
UppercaseLetter -> True
@@ -131,8 +275,41 @@ isLetter c = case generalCategory c of
OtherLetter -> True
_ -> False
--- | Selects Unicode mark characters, e.g. accents and the like, which
--- combine with preceding letters.
+-- | Selects Unicode mark characters, for example accents and the
+-- like, which combine with preceding characters.
+--
+-- This function returns 'True' if its argument has one of the
+-- following 'GeneralCategory's, or 'False' otherwise:
+--
+-- * 'NonSpacingMark'
+-- * 'SpacingCombiningMark'
+-- * 'EnclosingMark'
+--
+-- These classes are defined in the
+-- <http://www.unicode.org/reports/tr44/tr44-14.html#GC_Values_Table Unicode Character Database>,
+-- part of the Unicode standard. The same document defines what is
+-- and is not a \"Mark\".
+--
+-- ==== __Examples__
+--
+-- Basic usage:
+--
+-- >>> isMark 'a'
+-- False
+-- >>> isMark '0'
+-- False
+--
+-- Combining marks such as accent characters usually need to follow
+-- another character before they become printable:
+--
+-- >>> map isMark "ò"
+-- [False,True]
+--
+-- Puns are not necessarily supported:
+--
+-- >>> isMark '✓'
+-- False
+--
isMark :: Char -> Bool
isMark c = case generalCategory c of
NonSpacingMark -> True
@@ -141,7 +318,41 @@ isMark c = case generalCategory c of
_ -> False
-- | Selects Unicode numeric characters, including digits from various
--- scripts, Roman numerals, etc.
+-- scripts, Roman numerals, et cetera.
+--
+-- This function returns 'True' if its argument has one of the
+-- following 'GeneralCategory's, or 'False' otherwise:
+--
+-- * 'DecimalNumber'
+-- * 'LetterNumber'
+-- * 'OtherNumber'
+--
+-- These classes are defined in the
+-- <http://www.unicode.org/reports/tr44/tr44-14.html#GC_Values_Table Unicode Character Database>,
+-- part of the Unicode standard. The same document defines what is
+-- and is not a \"Number\".
+--
+-- ==== __Examples__
+--
+-- Basic usage:
+--
+-- >>> isNumber 'a'
+-- False
+-- >>> isNumber '%'
+-- False
+-- >>> isNumber '3'
+-- True
+--
+-- ASCII @\'0\'@ through @\'9\'@ are all numbers:
+--
+-- >>> and $ map isNumber ['0'..'9']
+-- True
+--
+-- Unicode Roman numerals are \"numbers\" as well:
+--
+-- >>> isNumber 'Ⅸ'
+-- True
+--
isNumber :: Char -> Bool
isNumber c = case generalCategory c of
DecimalNumber -> True
@@ -151,6 +362,40 @@ isNumber c = case generalCategory c of
-- | Selects Unicode punctuation characters, including various kinds
-- of connectors, brackets and quotes.
+--
+-- This function returns 'True' if its argument has one of the
+-- following 'GeneralCategory's, or 'False' otherwise:
+--
+-- * 'ConnectorPunctuation'
+-- * 'DashPunctuation'
+-- * 'OpenPunctuation'
+-- * 'ClosePunctuation'
+-- * 'InitialQuote'
+-- * 'FinalQuote'
+-- * 'OtherPunctuation'
+--
+-- These classes are defined in the
+-- <http://www.unicode.org/reports/tr44/tr44-14.html#GC_Values_Table Unicode Character Database>,
+-- part of the Unicode standard. The same document defines what is
+-- and is not a \"Punctuation\".
+--
+-- ==== __Examples__
+--
+-- Basic usage:
+--
+-- >>> isPunctuation 'a'
+-- False
+-- >>> isPunctuation '7'
+-- False
+-- >>> isPunctuation '♥'
+-- False
+-- >>> isPunctuation '"'
+-- True
+-- >>> isPunctuation '?'
+-- True
+-- >>> isPunctuation '—'
+-- True
+--
isPunctuation :: Char -> Bool
isPunctuation c = case generalCategory c of
ConnectorPunctuation -> True
@@ -164,6 +409,39 @@ isPunctuation c = case generalCategory c of
-- | Selects Unicode symbol characters, including mathematical and
-- currency symbols.
+--
+-- This function returns 'True' if its argument has one of the
+-- following 'GeneralCategory's, or 'False' otherwise:
+--
+-- * 'MathSymbol'
+-- * 'CurrencySymbol'
+-- * 'ModifierSymbol'
+-- * 'OtherSymbol'
+--
+-- These classes are defined in the
+-- <http://www.unicode.org/reports/tr44/tr44-14.html#GC_Values_Table Unicode Character Database>,
+-- part of the Unicode standard. The same document defines what is
+-- and is not a \"Symbol\".
+--
+-- ==== __Examples__
+--
+-- Basic usage:
+--
+-- >>> isSymbol 'a'
+-- False
+-- >>> isSymbol '6'
+-- False
+-- >>> isSymbol '='
+-- True
+--
+-- The definition of \"math symbol\" may be a little
+-- counter-intuitive depending on one's background:
+--
+-- >>> isSymbol '+'
+-- True
+-- >>> isSymbol '-'
+-- False
+--
isSymbol :: Char -> Bool
isSymbol c = case generalCategory c of
MathSymbol -> True
@@ -173,6 +451,43 @@ isSymbol c = case generalCategory c of
_ -> False
-- | Selects Unicode space and separator characters.
+--
+-- This function returns 'True' if its argument has one of the
+-- following 'GeneralCategory's, or 'False' otherwise:
+--
+-- * 'Space'
+-- * 'LineSeparator'
+-- * 'ParagraphSeparator'
+--
+-- These classes are defined in the
+-- <http://www.unicode.org/reports/tr44/tr44-14.html#GC_Values_Table Unicode Character Database>,
+-- part of the Unicode standard. The same document defines what is
+-- and is not a \"Separator\".
+--
+-- ==== __Examples__
+--
+-- Basic usage:
+--
+-- >>> isSeparator 'a'
+-- False
+-- >>> isSeparator '6'
+-- False
+-- >>> isSeparator ' '
+-- True
+--
+-- Warning: newlines and tab characters are not considered
+-- separators.
+--
+-- >>> isSeparator '\n'
+-- False
+-- >>> isSeparator '\t'
+-- False
+--
+-- But some more exotic characters are (like HTML's @&nbsp;@):
+--
+-- >>> isSeparator '\160'
+-- True
+--
isSeparator :: Char -> Bool
isSeparator c = case generalCategory c of
Space -> True
diff --git a/libraries/base/Data/Fixed.hs b/libraries/base/Data/Fixed.hs
index b499617f32..068eec5f12 100644
--- a/libraries/base/Data/Fixed.hs
+++ b/libraries/base/Data/Fixed.hs
@@ -1,7 +1,6 @@
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE AutoDeriveTypeable #-}
-{-# OPTIONS -Wall -fno-warn-unused-binds #-}
-----------------------------------------------------------------------------
-- |
@@ -37,7 +36,6 @@ module Data.Fixed
E12,Pico
) where
-import Data.Typeable
import Data.Data
import GHC.Read
import Text.ParserCombinators.ReadPrec
@@ -61,7 +59,7 @@ mod' n d = n - (fromInteger f) * d where
-- | The type parameter should be an instance of 'HasResolution'.
newtype Fixed a = MkFixed Integer -- ^ /Since: 4.7.0.0/
- deriving (Eq,Ord,Typeable)
+ deriving (Eq,Ord)
-- We do this because the automatically derived Data instance requires (Data a) context.
-- Our manual instance has the more general (Typeable a) context.
@@ -166,50 +164,43 @@ convertFixed (Number n)
e = ceiling (logBase 10 (fromInteger r) :: Double)
convertFixed _ = pfail
-data E0 = E0
- deriving (Typeable)
+data E0
instance HasResolution E0 where
resolution _ = 1
-- | resolution of 1, this works the same as Integer
type Uni = Fixed E0
-data E1 = E1
- deriving (Typeable)
+data E1
instance HasResolution E1 where
resolution _ = 10
-- | resolution of 10^-1 = .1
type Deci = Fixed E1
-data E2 = E2
- deriving (Typeable)
+data E2
instance HasResolution E2 where
resolution _ = 100
-- | resolution of 10^-2 = .01, useful for many monetary currencies
type Centi = Fixed E2
-data E3 = E3
- deriving (Typeable)
+data E3
instance HasResolution E3 where
resolution _ = 1000
-- | resolution of 10^-3 = .001
type Milli = Fixed E3
-data E6 = E6
- deriving (Typeable)
+data E6
instance HasResolution E6 where
resolution _ = 1000000
-- | resolution of 10^-6 = .000001
type Micro = Fixed E6
-data E9 = E9
- deriving (Typeable)
+data E9
instance HasResolution E9 where
resolution _ = 1000000000
-- | resolution of 10^-9 = .000000001
type Nano = Fixed E9
-data E12 = E12
- deriving (Typeable)
+data E12
instance HasResolution E12 where
resolution _ = 1000000000000
-- | resolution of 10^-12 = .000000000001
diff --git a/libraries/base/Data/Typeable.hs b/libraries/base/Data/Typeable.hs
index f658a9e788..ddb9582092 100644
--- a/libraries/base/Data/Typeable.hs
+++ b/libraries/base/Data/Typeable.hs
@@ -1,20 +1,9 @@
+{-# LANGUAGE GADTs #-}
+{-# LANGUAGE NoImplicitPrelude #-}
+{-# LANGUAGE PolyKinds #-}
+{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE NoImplicitPrelude
- , OverlappingInstances
- , ScopedTypeVariables
- , FlexibleInstances
- , TypeOperators
- , PolyKinds
- , GADTs
- , MagicHash
- #-}
-{-# OPTIONS_GHC -funbox-strict-fields #-}
-
--- The -XOverlappingInstances flag allows the user to over-ride
--- the instances for Typeable given here. In particular, we provide an instance
--- instance ... => Typeable (s a)
--- But a user might want to say
--- instance ... => Typeable (MyType a b)
+{-# LANGUAGE TypeOperators #-}
-----------------------------------------------------------------------------
-- |
diff --git a/libraries/base/Data/Typeable/Internal.hs b/libraries/base/Data/Typeable/Internal.hs
index 140b895509..475f083fba 100644
--- a/libraries/base/Data/Typeable/Internal.hs
+++ b/libraries/base/Data/Typeable/Internal.hs
@@ -1,5 +1,16 @@
-{-# LANGUAGE Unsafe #-}
{-# LANGUAGE BangPatterns #-}
+{-# LANGUAGE CPP #-}
+{-# LANGUAGE ConstraintKinds #-}
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE DeriveDataTypeable #-}
+{-# LANGUAGE FlexibleInstances #-}
+{-# LANGUAGE MagicHash #-}
+{-# LANGUAGE NoImplicitPrelude #-}
+{-# LANGUAGE PolyKinds #-}
+{-# LANGUAGE ScopedTypeVariables #-}
+{-# LANGUAGE StandaloneDeriving #-}
+{-# LANGUAGE UndecidableInstances #-}
+{-# LANGUAGE Unsafe #-}
-----------------------------------------------------------------------------
-- |
@@ -13,20 +24,6 @@
--
-----------------------------------------------------------------------------
-{-# LANGUAGE CPP
- , NoImplicitPrelude
- , OverlappingInstances
- , ScopedTypeVariables
- , FlexibleInstances
- , MagicHash
- , KindSignatures
- , PolyKinds
- , ConstraintKinds
- , DeriveDataTypeable
- , DataKinds
- , UndecidableInstances
- , StandaloneDeriving #-}
-
module Data.Typeable.Internal (
Proxy (..),
TypeRep(..),
diff --git a/libraries/base/GHC/Show.lhs b/libraries/base/GHC/Show.lhs
index 28348171ce..d5ed094646 100644
--- a/libraries/base/GHC/Show.lhs
+++ b/libraries/base/GHC/Show.lhs
@@ -386,6 +386,7 @@ showMultiLineString str
where
go ch s = case break (== '\n') s of
(l, _:s'@(_:_)) -> (ch : showLitString l "\\n\\") : go '\\' s'
+ (l, "\n") -> [ch : showLitString l "\\n\""]
(l, _) -> [ch : showLitString l "\""]
isDec :: Char -> Bool
diff --git a/libraries/base/base.cabal b/libraries/base/base.cabal
index 957053dd15..6277d89e79 100644
--- a/libraries/base/base.cabal
+++ b/libraries/base/base.cabal
@@ -69,7 +69,6 @@ Library
NegativeLiterals
NoImplicitPrelude
NondecreasingIndentation
- OverlappingInstances
OverloadedStrings
ParallelArrays
PolyKinds
diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md
index 76fe87af68..0f892494c3 100644
--- a/libraries/base/changelog.md
+++ b/libraries/base/changelog.md
@@ -87,6 +87,8 @@
* New module `Data.Bifunctor` providing the `Bifunctor(bimap,first,second)`
class (previously defined in `bifunctors` package) (#9682)
+ * Update Unicode class definitions to Unicode version 7.0
+
## 4.7.0.1 *Jul 2014*
* Bundled with GHC 7.8.3
diff --git a/libraries/base/tests/T9681.hs b/libraries/base/tests/T9681.hs
new file mode 100644
index 0000000000..b0fd499780
--- /dev/null
+++ b/libraries/base/tests/T9681.hs
@@ -0,0 +1,3 @@
+module T9681 where
+
+foo = 1 + "\n"
diff --git a/libraries/base/tests/T9681.stderr b/libraries/base/tests/T9681.stderr
new file mode 100644
index 0000000000..7945ff7353
--- /dev/null
+++ b/libraries/base/tests/T9681.stderr
@@ -0,0 +1,5 @@
+
+T9681.hs:3:9:
+ No instance for (Num [Char]) arising from a use of ‘+’
+ In the expression: 1 + "\n"
+ In an equation for ‘foo’: foo = 1 + "\n"
diff --git a/libraries/base/tests/all.T b/libraries/base/tests/all.T
index edb5fc3b16..ee0fb6b708 100644
--- a/libraries/base/tests/all.T
+++ b/libraries/base/tests/all.T
@@ -173,3 +173,4 @@ test('T9111', normal, compile, [''])
test('T9395', normal, compile_and_run, [''])
test('T9532', normal, compile_and_run, [''])
test('T9586', normal, compile, [''])
+test('T9681', normal, compile_fail, [''])
diff --git a/testsuite/.gitignore b/testsuite/.gitignore
index d3dc9cb467..ce5c2c266e 100644
--- a/testsuite/.gitignore
+++ b/testsuite/.gitignore
@@ -29,10 +29,12 @@ Thumbs.db
.hpc.*/
*.genscript
+*.stdout.normalised
+*.stdout-mingw32.normalised
+*.stdout-ghc.normalised
*.stderr.normalised
*.stderr-mingw32.normalised
*.stderr-ghc.normalised
-*.stdout.normalised
*.interp.stdout
*.interp.stderr
*.run.stdout
diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py
index 3093982336..87e37d5ce9 100644
--- a/testsuite/driver/testlib.py
+++ b/testsuite/driver/testlib.py
@@ -920,7 +920,7 @@ def run_command( name, way, cmd ):
def ghci_script_without_flag(flag):
def apply(name, way, script):
- overrides = filter(lambda f: f != flag, getTestOpts().compiler_always_flags)
+ overrides = [f for f in getTestOpts().compiler_always_flags if f != flag]
return ghci_script_override_default_flags(overrides)(name, way, script)
return apply
@@ -933,7 +933,7 @@ def ghci_script_override_default_flags(overrides):
def ghci_script( name, way, script, override_flags = None ):
# Use overriden default flags when given
- if override_flags:
+ if override_flags is not None:
default_flags = override_flags
else:
default_flags = getTestOpts().compiler_always_flags
@@ -973,14 +973,14 @@ def compile_fail_override_default_flags(overrides):
def compile_without_flag(flag):
def apply(name, way, extra_opts):
- overrides = filter(lambda f: f != flag, getTestOpts().compiler_always_flags)
+ overrides = [f for f in getTestOpts().compiler_always_flags if f != flag]
return compile_override_default_flags(overrides)(name, way, extra_opts)
return apply
def compile_fail_without_flag(flag):
def apply(name, way, extra_opts):
- overrides = filter(lambda f: f != flag, getTestOpts().compiler_always_flags)
+ overrides = [f for f in getTestOpts.compiler_always_flags if f != flag]
return compile_fail_override_default_flags(overrides)(name, way, extra_opts)
return apply
@@ -1225,7 +1225,7 @@ def simple_build( name, way, extra_hc_opts, should_fail, top_mod, link, addsuf,
else:
cmd_prefix = getTestOpts().compile_cmd_prefix + ' '
- if override_flags:
+ if override_flags is not None:
comp_flags = copy.copy(override_flags)
else:
comp_flags = copy.copy(getTestOpts().compiler_always_flags)
diff --git a/utils/haddock b/utils/haddock
-Subproject 3fb325a2ca6b6397905116024922d079447a2e0
+Subproject 3937a98afe1bf1a215fd9115051af388e45b729