From ac5ec36f9eb9b697be6f4ceb63041a0abdcfd6d0 Mon Sep 17 00:00:00 2001 From: Fendor Date: Wed, 3 Feb 2021 19:10:20 +0100 Subject: Add UnitId to Target record --- haddock-api/src/Haddock/Interface.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/haddock-api/src/Haddock/Interface.hs b/haddock-api/src/Haddock/Interface.hs index 16643d0e..7cc76953 100644 --- a/haddock-api/src/Haddock/Interface.hs +++ b/haddock-api/src/Haddock/Interface.hs @@ -157,7 +157,7 @@ createIfaces verbosity modules flags instIfaceMap = do -- alive to be able to find all the instances. modifySession installHaddockPlugin - targets <- mapM (\filePath -> guessTarget filePath Nothing) modules + targets <- mapM (\filePath -> guessTarget filePath Nothing Nothing) modules setTargets targets loadOk <- withTimingM "load" (const ()) $ -- cgit v1.2.3 From cf7d06b8ac0f47d6ff1c2d3decdb6a50a0fd7502 Mon Sep 17 00:00:00 2001 From: alexbiehl Date: Tue, 9 Feb 2021 12:42:30 +0100 Subject: Stable sort for (data/newtype) instances --- .../src/Haddock/Interface/AttachInstances.hs | 25 +- html-test/ref/Bug1004.html | 1064 ++++++++++---------- html-test/ref/Bug1103.html | 8 +- html-test/ref/Bug548.html | 96 +- html-test/ref/HiddenInstances.html | 8 +- html-test/ref/Instances.html | 354 +++---- html-test/ref/SpuriousSuperclassConstraints.html | 108 +- html-test/ref/TypeFamilies.html | 196 ++-- html-test/ref/TypeFamilies2.html | 68 +- html-test/ref/TypeFamilies3.html | 64 +- hypsrc-test/ref/src/Classes.html | 14 +- hypsrc-test/ref/src/Records.html | 16 +- latex-test/ref/TypeFamilies3/TypeFamilies3.tex | 4 +- 13 files changed, 1017 insertions(+), 1008 deletions(-) diff --git a/haddock-api/src/Haddock/Interface/AttachInstances.hs b/haddock-api/src/Haddock/Interface/AttachInstances.hs index 6ef0ed19..d5b80888 100644 --- a/haddock-api/src/Haddock/Interface/AttachInstances.hs +++ b/haddock-api/src/Haddock/Interface/AttachInstances.hs @@ -179,19 +179,28 @@ findFixity iface ifaceMap instIfaceMap = \name -> -- Collecting and sorting instances -------------------------------------------------------------------------------- +-- | Stable name for stable comparisons. GHC's `Name` uses unstable +-- ordering based on their `Unique`'s. +newtype SName = SName Name + +instance Eq SName where + SName n1 == SName n2 = n1 `stableNameCmp` n2 == EQ + +instance Ord SName where + SName n1 `compare` SName n2 = n1 `stableNameCmp` n2 -- | Simplified type for sorting types, ignoring qualification (not visible -- in Haddock output) and unifying special tycons with normal ones. -- For the benefit of the user (looks nice and predictable) and the -- tests (which prefer output to be deterministic). -data SimpleType = SimpleType Name [SimpleType] +data SimpleType = SimpleType SName [SimpleType] | SimpleTyLit TyLit deriving (Eq,Ord) -instHead :: ([TyVar], [PredType], Class, [Type]) -> ([Int], Name, [SimpleType]) +instHead :: ([TyVar], [PredType], Class, [Type]) -> ([Int], SName, [SimpleType]) instHead (_, _, cls, args) - = (map argCount args, className cls, map simplify args) + = (map argCount args, SName (className cls), map simplify args) argCount :: Type -> Int argCount (AppTy t _) = argCount t + 1 @@ -202,12 +211,12 @@ argCount (CastTy t _) = argCount t argCount _ = 0 simplify :: Type -> SimpleType -simplify (FunTy _ _ t1 t2) = SimpleType funTyConName [simplify t1, simplify t2] +simplify (FunTy _ _ t1 t2) = SimpleType (SName funTyConName) [simplify t1, simplify t2] simplify (ForAllTy _ t) = simplify t simplify (AppTy t1 t2) = SimpleType s (ts ++ maybeToList (simplify_maybe t2)) where (SimpleType s ts) = simplify t1 -simplify (TyVarTy v) = SimpleType (tyVarName v) [] -simplify (TyConApp tc ts) = SimpleType (tyConName tc) +simplify (TyVarTy v) = SimpleType (SName (tyVarName v)) [] +simplify (TyConApp tc ts) = SimpleType (SName (tyConName tc)) (mapMaybe simplify_maybe ts) simplify (LitTy l) = SimpleTyLit l simplify (CastTy ty _) = simplify ty @@ -218,9 +227,9 @@ simplify_maybe (CoercionTy {}) = Nothing simplify_maybe ty = Just (simplify ty) -- Used for sorting -instFam :: FamInst -> ([Int], Name, [SimpleType], Int, SimpleType) +instFam :: FamInst -> ([Int], SName, [SimpleType], Int, SimpleType) instFam FamInst { fi_fam = n, fi_tys = ts, fi_rhs = t } - = (map argCount ts, n, map simplify ts, argCount t, simplify t) + = (map argCount ts, SName n, map simplify ts, argCount t, simplify t) -------------------------------------------------------------------------------- diff --git a/html-test/ref/Bug1004.html b/html-test/ref/Bug1004.html index b4ce3c88..cd959f7f 100644 --- a/html-test/ref/Bug1004.html +++ b/html-test/ref/Bug1004.html @@ -182,135 +182,7 @@ > (Monad f, Monad g) => Monad (Product f g)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

(>>=) :: Product f g a -> (a -> Product f g b) -> Product f g b #

(>>) :: Product f g a -> Product f g b -> Product f g b #

return :: a -> Product f g a #

(Functor f, Functor g) => Functor (Product f g)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

fmap :: (a -> b) -> Product f g a -> Product f g b #

(<$) :: a -> Product f g b -> Product f g a #

(MonadFix
Instance details

(Applicative f, Applicative g) => Applicative (MonadZip f, MonadZip g) => MonadZip (Product f g)

Instance details

Methods

pure :: a -> Product f g a #

(<*>)mzip :: Product f g (a -> b) -> Product f g a -> Product f g b #

liftA2 :: (a -> b -> c) -> Product f g a -> Product f g b -> Product f g c f g (a, b) #

(*>) :: mzipWith :: (a -> b -> c) -> Product f g a -> Product f g b -> Product f g b f g c #

(<*)munzip :: Product f g a -> f g (a, b) -> (Product f g b -> f g a, Product f g a f g b) #

(Foldable
Instance details

(Traversable f, Traversable g) => Traversable (Eq1 f, Eq1 g) => Eq1 (Product f g)

Instance details

Methods

traverse :: Applicative f0 => (a -> f0 b) -> Product f g a -> f0 (Product f g b) #

sequenceA :: Applicative f0 => Product f g (f0 a) -> f0 (Product f g a) #

mapM :: Monad m => (a -> m b) -> Product f g a -> m (Product f g b) #

sequence :: Monad m => liftEq :: (a -> b -> Bool) -> Product f g (m a) -> m ( f g a -> Product f g a) f g b -> Bool #

(Show1Ord1 f, Show1Ord1 g) => Show1Ord1 (Product f g)
Instance details

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Product f g a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [liftCompare :: (a -> b -> Ordering) -> Product f g a] -> ShowS f g a -> Product f g b -> Ordering #

(Read1
Instance details

(Ord1Show1 f, Ord1Show1 g) => Ord1Show1 (Product f g)

Instance details

Methods

liftCompare :: (a -> b -> Ordering) -> Product f g a -> liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Product f g b -> Ordering f g a -> ShowS #

(Eq1 f, Eq1 g) => Eq1 (Product f g)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

liftEq :: (a -> b -> Bool) -> Product f g a -> liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Product f g b -> Bool f g a] -> ShowS #

(MonadZip f, MonadZip g) => MonadZip (Traversable f, Traversable g) => Traversable (Product f g)
Instance details

Methods

mzip :: Product f g a -> traverse :: Applicative f0 => (a -> f0 b) -> Product f g b -> f g a -> f0 (Product f g (a, b) f g b) #

mzipWith :: (a -> b -> c) -> Product f g a -> sequenceA :: Applicative f0 => Product f g b -> f g (f0 a) -> f0 (Product f g c f g a) #

munzip :: Product f g (a, b) -> (mapM :: Monad m => (a -> m b) -> Product f g a, f g a -> m (Product f g b) #

sequence :: Monad m => Product f g (m a) -> m (Product f g a) #

(MonadPlus f, MonadPlus g) => MonadPlus (Alternative f, Alternative g) => Alternative (Product f g)
Instance details

Methods

mzeroempty :: Product f g a

mplus(<|>) :: Product f g a -> f g a #

some :: Product f g a -> Product f g [a] #

many :: Product f g a -> Product f g [a] #

(AlternativeApplicative f, AlternativeApplicative g) => AlternativeApplicative (Product f g)
Instance details

Methods

empty :: pure :: a -> Product f g a #

(<|>)(<*>) :: Product f g (a -> b) -> Product f g a -> Product f g b #

liftA2 :: (a -> b -> c) -> Product f g a -> Product f g a f g b -> Product f g c #

some(*>) :: Product f g a -> Product f g [a] f g b -> Product f g b #

many(<*) :: Product f g a -> Product f g [a] f g b -> Product f g a #

(Eq1 f, Eq1 g, Eq a) => Eq (Functor f, Functor g) => Functor (Product f g a) f g)

Instance details

Methods

(==) :: fmap :: (a -> b) -> Product f g a -> Product f g a -> Bool f g b #

(/=)(<$) :: a -> Product f g b -> Product f g a #

(Monad f, Monad g) => Monad (Product f g)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

(>>=) :: Product f g a -> (a -> Product f g b) -> Product f g b #

(>>) :: Product f g a -> Product f g a -> Bool f g b -> Product f g b #

return :: a -> Product f g a #

(MonadPlus f, MonadPlus g) => MonadPlus (Product f g)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

mzero :: Product f g a #

mplus :: Product f g a -> Product f g a -> Product f g a #

(Typeable
Instance details

(Ord1 f, Ord1 g, Ord a) => Ord (Monoid (f a), Monoid (g a)) => Monoid (Product f g a)

Since: base-4.9.0.0Since: base-4.16.0.0

Instance details

Methods

comparemempty :: Product f g a -> Product f g a -> Ordering f g a #

(<)mappend :: Product f g a -> Product f g a -> Bool f g a -> Product f g a #

(<=) :: mconcat :: [Product f g a -> f g a] -> Product f g a -> Bool f g a #

(Semigroup (f a), Semigroup (g a)) => Semigroup (Product f g a)

Since: base-4.16.0.0

Instance details

Defined in Data.Functor.Product

Methods

(>)(<>) :: Product f g a -> Product f g a -> Bool f g a -> Product f g a #

(>=) :: sconcat :: NonEmpty (Product f g a -> f g a) -> Product f g a -> Bool f g a #

max :: Product f g a -> stimes :: Integral b => b -> Product f g a -> Product f g a #

Generic (Product f g a) 
Instance details

Defined in Data.Functor.Product

Associated Types

type Rep (Product f g a) :: Type -> Type #

Methods

minfrom :: Product f g a -> f g a -> Rep (Product f g a -> f g a) x #

to :: Rep (Product f g a) x -> Product f g a # (Read1

Instance details

(Show1

Instance details

Generic (Eq1 f, Eq1 g, Eq a) => Eq (Product f g a) 

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Associated Types

type Rep (Product f g a) :: Type -> Type #

Methods

from(==) :: Product f g a -> Rep ( f g a -> Product f g a) x f g a -> Bool #

to :: Rep ((/=) :: Product f g a) x -> f g a -> Product f g a f g a -> Bool #

(Semigroup (f a), Semigroup (g a)) => Semigroup (Ord1 f, Ord1 g, Ord a) => Ord (Product f g a)

Since: base-4.16.0.0Since: base-4.9.0.0

Instance details

Methods

(<>)compare :: Product f g a -> Product f g a -> Ordering #

(<) :: Product f g a -> Product f g a f g a -> Bool #

sconcat :: NonEmpty ((<=) :: Product f g a) -> f g a -> Product f g a f g a -> Bool #

stimes :: Integral b => b -> (>) :: Product f g a -> Product f g a f g a -> Bool #

(Monoid (f a), Monoid (g a)) => Monoid (Product f g a)

Since: base-4.16.0.0

Instance details

Defined in Data.Functor.Product

Methods

mempty(>=) :: Product f g a f g a -> Product f g a -> Bool #

mappendmax :: Product f g a ->

mconcat :: [min :: Product f g a] -> f g a -> Product f g a -> Product f g a #Foo3 (a :: Char -> Char) #Foo3 (a :: Char -> Char)

Foo3 (a :: Char -> Char) #Foo3 (a :: Char -> Char)
Arrow a => Functor (ArrowZero a, ArrowPlus a) => Alternative (WrappedArrow a b)
Instance details

Methods

fmap :: (a0 -> b0) -> empty :: WrappedArrow a b a0 #

(<|>) :: WrappedArrow a b a0 -> WrappedArrow a b b0 a b a0 -> WrappedArrow a b a0 #

(<$) :: a0 -> some :: WrappedArrow a b b0 -> a b a0 -> WrappedArrow a b a0 a b [a0] #

many :: WrappedArrow a b a0 -> WrappedArrow a b [a0] #

(ArrowZero a, ArrowPlus a) => Alternative Arrow a => Functor (WrappedArrow a b)
Instance details

Methods

empty :: WrappedArrow a b a0 #

(<|>) :: WrappedArrow a b a0 -> WrappedArrow a b a0 -> WrappedArrow a b a0 #

some :: fmap :: (a0 -> b0) -> WrappedArrow a b a0 -> WrappedArrow a b [a0] a b b0 #

many :: (<$) :: a0 -> WrappedArrow a b a0 -> a b b0 -> WrappedArrow a b [a0] a b a0 #

VisibleClass Int VisibleData # VisibleClass VisibleData Int # Foo [] Maybe #

foo :: [ :: Maybe Int] -> a -> [a] -> a -> Maybe a #

foo' :: [[a]] -> :: Maybe (Maybe a) -> Int -> [[ -> Maybe (Maybe Int]] ) #

Foo Maybe [] #

foo :: Maybe :: [Int -> a -> Maybe a ] -> a -> [a] #

foo' :: Maybe (Maybe a) -> :: [[a]] -> Int -> Maybe (Maybe -> [[Int) ]] #

(Eq a, Foo f) => Foo ((,) (f a)) ((<~~) a) #

foo :: (f a, :: (a <~~ Int) -> a0 -> (f a, a0) ) -> a0 -> a <~~ a0 #

foo' :: (f a, (f a, a0)) -> :: (a <~~ (a <~~ a0)) -> Int -> (f a, (f a, -> a <~~ (a <~~ Int)) ) #

(Eq a, Foo ((<~~) a) f) => Foo ((,) (f a)) #

foo :: (a <~~ :: (f a, Int) -> a0 -> a <~~ a0 ) -> a0 -> (f a, a0) #

foo' :: (a <~~ (a <~~ a0)) -> :: (f a, (f a, a0)) -> Int -> a <~~ (a <~~ -> (f a, (f a, Int) )) #

Foo ((,,) a a) (Quux a b) #

foo :: (a, a, :: Quux a b Int) -> a0 -> (a, a, a0) -> a0 -> Quux a b a0 #

foo' :: (a, a, (a, a, a0)) -> :: Quux a b (Quux a b a0) -> Int -> (a, a, (a, a, -> Quux a b (Quux a b Int)) ) #

Foo (Quux a b) ((,,) a a) #

foo :: Quux a b :: (a, a, Int -> a0 -> Quux a b a0 ) -> a0 -> (a, a, a0) #

foo' :: Quux a b (Quux a b a0) -> :: (a, a, (a, a, a0)) -> Int -> Quux a b (Quux a b -> (a, a, (a, a, Int) )) #

Foo ((,,) a b) => Bar ((,,) a b) (a, b, a) # 
Instance details

Defined in Instances

Methods

bar :: (a, b, (a, b, a)) -> (a, b, Bool) -> (a, b, a) #

bar' :: (a, b, (a, b, (a, b, a))) -> (a, b, (a, b, (a, b, b0))) #

bar0 :: ((a, b, (a, b, a)), (a, b, (a, b, a))) -> ((a, b, b0), (a, b, c)) #

bar1 :: ((a, b, (a, b, a)), (a, b, (a, b, a))) -> ((a, b, b0), (a, b, c)) #

Bar
Instance details

Foo ((,,) a b) => Bar ((,,) a b) (a, b, a) # 
Instance details

Defined in Instances

Methods

bar :: (a, b, (a, b, a)) -> (a, b, Bool) -> (a, b, a) #

bar' :: (a, b, (a, b, (a, b, a))) -> (a, b, (a, b, (a, b, b0))) #

bar0 :: ((a, b, (a, b, a)), (a, b, (a, b, a))) -> ((a, b, b0), (a, b, c)) #

bar1 :: ((a, b, (a, b, a)), (a, b, (a, b, a))) -> ((a, b, b0), (a, b, c)) #

Baz (a, b, c) (Quux a b c) #

baz :: (a, b, c) -> ( :: Quux a b c -> (forall a0. a0 -> a0) -> (b0, forall c0. c0 -> (a, b, c)) -> (b0, c1) c0. c0 -> Quux a b c) -> (b0, c1) #

baz' :: b0 -> (forall b1. b1 -> (a, b, c)) -> ( b1. b1 -> Quux a b c) -> (forall b2. b2 -> (a, b, c)) -> [(b0, (a, b, c))] b2. b2 -> Quux a b c) -> [(b0, Quux a b c)] #

forall b1. (forall b2. b2 -> (a, b, c)) -> c0) -> b2. b2 -> Quux a b c) -> c0) -> forall c1. c1 -> b0 # Baz (Quux a b c) (a, b, c) #

baz :: Quux a b c -> ( :: (a, b, c) -> (forall a0. a0 -> a0) -> (b0, forall c0. c0 -> Quux a b c) -> (b0, c1) c0. c0 -> (a, b, c)) -> (b0, c1) #

baz' :: b0 -> (forall b1. b1 -> Quux a b c) -> ( b1. b1 -> (a, b, c)) -> (forall b2. b2 -> Quux a b c) -> [(b0, Quux a b c)] b2. b2 -> (a, b, c)) -> [(b0, (a, b, c))] #

forall b1. (forall b2. b2 -> Quux a b c) -> c0) -> b2. b2 -> (a, b, c)) -> c0) -> forall c1. c1 -> b0 # Functor (SomeType f) # 

Instance details

Defined in SpuriousSuperclassConstraints

Methods

fmap :: (a -> b) -> SomeType f a -> SomeType f b #

(<$) :: a -> SomeType f b -> SomeType f a #

Applicative
Instance details

Functor (SomeType f) # 
Instance details

Defined in SpuriousSuperclassConstraints

Methods

fmap :: (a -> b) -> SomeType f a -> SomeType f b #

(<$) :: a -> SomeType f b -> SomeType f a #

type X 'XXX <> (a :: Type)
'XX #
type X 'XXX <> (a :: Type) = 'XX = 'X
type 'XXX X <> 'XX (a :: Type) #
type 'XXX X <> 'XX = ' (a :: Type) = X
Test YX
#

Doc for: instance Test Y

Doc for: instance Test X

Test XY #

Doc for: instance Test X

Doc for: instance Test Y

Foo YX #

Doc for: type instance Foo Y = X

Doc for: type instance Foo X = Y

Foo Y = X = Y
Foo XY #

Doc for: type instance Foo X = Y

Doc for: type instance Foo Y = X

Foo X = Y = X
Bat YX
#

Doc for: data instance Bat Y

Doc for: data instance Bat X

Bat Y = BatY YX
Bat XY #

Doc for: data instance Bat X

Doc for: data instance Bat Y

Bat X Y = BatY Y
Assoc YX
#

Doc for: instance Assoc Y

Doc for: instance Assoc X

AssocD YX #

AssocT YX #

Assoc XY
#

Doc for: instance Assoc X

Doc for: instance Assoc Y

AssocD XY #

AssocT XY #

type Y 'XXX <> (a :: Type) 'XX #
type Y 'XXX <> (a :: Type) = a
'XX = 'X
type 'XXX Y <> 'XX (a :: Type) #
type 'XXX Y <> 'XX = 'X
(a :: Type) = a
type Foo W X #

Should be visible, but with a hidden right hand side

External instance

Instance details

Defined in TypeFamilies2TypeFamilies

type Foo W X = Y
type Foo X W #

External instance

Should be visible, but with a hidden right hand side

Instance details

Defined in TypeFamiliesTypeFamilies2

type Foo X = Y W
data
Bar W Y #

Shown because BarX is still exported despite Z being hidden

 Instance details

Defined in TypeFamilies2TypeFamilies

data Bar W = BarX Z
Y
data
Bar Y W # 

Shown because BarX is still exported despite Z being hidden

Instance details

Defined in TypeFamiliesTypeFamilies2

data Bar Y
W = BarX Z
type Bar Int () #type Bar () = Int = ()
type Bar () Int #type Bar () = Int = ()
newtypedata
Baz Double
() #

newtypedata Baz Double = Baz3 Float () = Baz1
datanewtype Baz Int Double #

datanewtype Baz Int = Baz2 Bool Double = Baz3 Float
data
Baz () Int #data Baz () = Baz1 Int = Baz2 Bool
bar :: Int -> Int barbaz :: Int -> (Int, Int) bazbar :: [a] -> Int barbaz :: Int -> ([a], [a]) baznorf :: [Int] -> Int norfquux :: ([a], [a]) -> [a] quuxplugh :: forall a b. Either a a -> Either b b -> Either (a -> b) (b -> a) plughInt -x :: Int x :: Point -> Int +x :: Int xInt -y :: Int y :: Point -> Int +y :: Int yInt -y :: Int -x :: Int -y :: Point -> Int x :: Point -> Int +y :: Point -> Int +x :: Int +y :: Int .. Date: Tue, 9 Feb 2021 12:56:15 +0100 Subject: Also make TyLit deterministic --- haddock-api/src/Haddock/Interface/AttachInstances.hs | 9 +++++++-- 1 file changed, 7 insertions(+), 2 deletions(-) diff --git a/haddock-api/src/Haddock/Interface/AttachInstances.hs b/haddock-api/src/Haddock/Interface/AttachInstances.hs index d5b80888..530c5690 100644 --- a/haddock-api/src/Haddock/Interface/AttachInstances.hs +++ b/haddock-api/src/Haddock/Interface/AttachInstances.hs @@ -28,6 +28,7 @@ import Data.Maybe ( maybeToList, mapMaybe, fromMaybe ) import qualified Data.Map as Map import qualified Data.Set as Set +import GHC.Data.FastString (unpackFS) import GHC.Core.Class import GHC.Driver.Session import GHC.Core (isOrphan) @@ -194,7 +195,9 @@ instance Ord SName where -- For the benefit of the user (looks nice and predictable) and the -- tests (which prefer output to be deterministic). data SimpleType = SimpleType SName [SimpleType] - | SimpleTyLit TyLit + | SimpleIntTyLit Integer + | SimpleStringTyLit String + | SimpleCharTyLit Char deriving (Eq,Ord) @@ -218,7 +221,9 @@ simplify (AppTy t1 t2) = SimpleType s (ts ++ maybeToList (simplify_maybe t2)) simplify (TyVarTy v) = SimpleType (SName (tyVarName v)) [] simplify (TyConApp tc ts) = SimpleType (SName (tyConName tc)) (mapMaybe simplify_maybe ts) -simplify (LitTy l) = SimpleTyLit l +simplify (LitTy (NumTyLit n)) = SimpleIntTyLit n +simplify (LitTy (StrTyLit s)) = SimpleStringTyLit (unpackFS s) +simplify (LitTy (CharTyLit c)) = SimpleCharTyLit c simplify (CastTy ty _) = simplify ty simplify (CoercionTy _) = error "simplify:Coercion" -- cgit v1.2.3 From 23fa3045f14ce0b8e107178e9b7859a66db65910 Mon Sep 17 00:00:00 2001 From: Oleg Grenrus Date: Sun, 14 Feb 2021 15:28:15 +0200 Subject: Add import list to Data.List in Haddock.Interface.Create --- haddock-api/haddock-api.cabal | 1 + haddock-api/src/Haddock/Interface/Create.hs | 2 +- 2 files changed, 2 insertions(+), 1 deletion(-) diff --git a/haddock-api/haddock-api.cabal b/haddock-api/haddock-api.cabal index e6de8b81..e9433d73 100644 --- a/haddock-api/haddock-api.cabal +++ b/haddock-api/haddock-api.cabal @@ -68,6 +68,7 @@ library ghc-options: -funbox-strict-fields -O2 -Wall -Wcompat + -Wcompat-unqualified-imports -Widentities -Wredundant-constraints -Wnoncanonical-monad-instances diff --git a/haddock-api/src/Haddock/Interface/Create.hs b/haddock-api/src/Haddock/Interface/Create.hs index 9a773b6c..c0b9fd46 100644 --- a/haddock-api/src/Haddock/Interface/Create.hs +++ b/haddock-api/src/Haddock/Interface/Create.hs @@ -35,7 +35,7 @@ import Control.Monad.Writer.Strict hiding (tell) import Data.Bitraversable import qualified Data.Map as M import Data.Map (Map) -import Data.List +import Data.List (foldl', find) import Data.Maybe import Data.Traversable import GHC.Stack -- cgit v1.2.3 From 606e3f220d20688c7baff94bef525a13434dc56b Mon Sep 17 00:00:00 2001 From: Joachim Breitner Date: Mon, 22 Feb 2021 10:31:56 +0100 Subject: html-test: Always set language MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit from ghc-9.2 on, the “default” langauge of GHC is expected to change more wildly. To prepare for that (and unblock https://gitlab.haskell.org/ghc/ghc/-/merge_requests/4853), this sets the language for all the test files to `Haskell2010`. This should insolate this test suite against changes to the default. Cherry-picked from https://github.com/haskell/haddock/pull/1341 --- hoogle-test/src/Bug722/Bug722.hs | 1 + hoogle-test/src/Bug806/Bug806.hs | 1 + hoogle-test/src/Bug825/Bug825.hs | 1 + hoogle-test/src/Bug873/Bug873.hs | 1 + hoogle-test/src/Bug946/Bug946.hs | 1 + hoogle-test/src/Bug992/Bug992.hs | 1 + hoogle-test/src/assoc-types/AssocTypes.hs | 1 + hoogle-test/src/classes/Classes.hs | 1 + hoogle-test/src/fixity/Fixity.hs | 1 + hoogle-test/src/modules/Bar.hs | 1 + hoogle-test/src/modules/Foo.hs | 1 + hoogle-test/src/type-sigs/ReaderT.hs | 1 + hoogle-test/src/type-sigs/ReaderTReexport.hs | 1 + html-test/ref/A.html | 6 + html-test/ref/Bold.html | 6 + html-test/ref/Bug1.html | 6 + html-test/ref/Bug1004.html | 6 + html-test/ref/Bug1033.html | 6 + html-test/ref/Bug1035.html | 6 + html-test/ref/Bug1050.html | 6 + html-test/ref/Bug1054.html | 6 + html-test/ref/Bug1063.html | 6 + html-test/ref/Bug1067A.html | 6 + html-test/ref/Bug1067B.html | 6 + html-test/ref/Bug1103.html | 6 + html-test/ref/Bug195.html | 6 + html-test/ref/Bug2.html | 6 + html-test/ref/Bug201.html | 6 + html-test/ref/Bug253.html | 6 + html-test/ref/Bug26.html | 6 + html-test/ref/Bug280.html | 6 + html-test/ref/Bug294.html | 6 + html-test/ref/Bug298.html | 6 + html-test/ref/Bug3.html | 6 + html-test/ref/Bug308.html | 6 + html-test/ref/Bug308CrossModule.html | 6 + html-test/ref/Bug310.html | 6 + html-test/ref/Bug313.html | 6 + html-test/ref/Bug335.html | 6 + html-test/ref/Bug4.html | 6 + html-test/ref/Bug458.html | 6 + html-test/ref/Bug466.html | 6 + html-test/ref/Bug546.html | 6 + html-test/ref/Bug548.html | 6 + html-test/ref/Bug574.html | 6 + html-test/ref/Bug6.html | 6 + html-test/ref/Bug613.html | 6 + html-test/ref/Bug647.html | 6 + html-test/ref/Bug679.html | 6 + html-test/ref/Bug7.html | 6 + html-test/ref/Bug8.html | 6 + html-test/ref/Bug85.html | 6 + html-test/ref/Bug865.html | 6 + html-test/ref/Bug923.html | 6 + html-test/ref/Bug952.html | 6 + html-test/ref/Bug953.html | 6 + html-test/ref/Bug973.html | 6 + html-test/ref/BugDeprecated.html | 6 + html-test/ref/BugExportHeadings.html | 6 + html-test/ref/Bugs.html | 6 + html-test/ref/BundledPatterns.html | 6 + html-test/ref/BundledPatterns2.html | 6 + html-test/ref/ConstructorArgs.html | 6 + html-test/ref/ConstructorPatternExport.html | 6 + html-test/ref/DefaultAssociatedTypes.html | 6 + html-test/ref/DefaultSignatures.html | 6 + html-test/ref/DeprecatedClass.html | 6 + html-test/ref/DeprecatedData.html | 6 + html-test/ref/DeprecatedFunction.html | 6 + html-test/ref/DeprecatedFunction2.html | 6 + html-test/ref/DeprecatedFunction3.html | 6 + html-test/ref/DeprecatedModule.html | 6 + html-test/ref/DeprecatedModule2.html | 6 + html-test/ref/DeprecatedNewtype.html | 6 + html-test/ref/DeprecatedReExport.html | 6 + html-test/ref/DeprecatedRecord.html | 6 + html-test/ref/DeprecatedTypeFamily.html | 6 + html-test/ref/DeprecatedTypeSynonym.html | 6 + html-test/ref/DuplicateRecordFields.html | 6 + html-test/ref/Examples.html | 6 + html-test/ref/FunArgs.html | 6 + html-test/ref/GADTRecords.html | 6 + html-test/ref/GadtConstructorArgs.html | 6 + html-test/ref/Hash.html | 6 + html-test/ref/HiddenInstances.html | 6 + html-test/ref/HiddenInstancesB.html | 6 + html-test/ref/Hyperlinks.html | 6 + html-test/ref/Identifiers.html | 6 + html-test/ref/IgnoreExports.html | 6 + html-test/ref/ImplicitParams.html | 6 + html-test/ref/Instances.html | 6 + html-test/ref/LinearTypes.html | 6 + html-test/ref/Math.html | 6 + html-test/ref/Minimal.html | 6 + html-test/ref/ModuleWithWarning.html | 6 + html-test/ref/NamedDoc.html | 6 + html-test/ref/NamespacedIdentifiers.html | 6 + html-test/ref/Nesting.html | 6 + html-test/ref/NoLayout.html | 6 + html-test/ref/NonGreedy.html | 6 + html-test/ref/Operators.html | 6 + html-test/ref/OrphanInstances.html | 6 + html-test/ref/OrphanInstancesClass.html | 6 + html-test/ref/OrphanInstancesType.html | 6 + html-test/ref/PR643.html | 6 + html-test/ref/PR643_1.html | 6 + html-test/ref/PatternSyns.html | 6 + html-test/ref/PromotedTypes.html | 6 + html-test/ref/Properties.html | 6 + html-test/ref/PruneWithWarning.html | 6 + html-test/ref/QuantifiedConstraints.html | 6 + html-test/ref/QuasiExpr.html | 6 + html-test/ref/QuasiQuote.html | 6 + html-test/ref/SectionLabels.html | 6 + html-test/ref/SpuriousSuperclassConstraints.html | 6 + html-test/ref/TH.html | 6 + html-test/ref/TH2.html | 6 + html-test/ref/Table.html | 6 + html-test/ref/Test.html | 6 + html-test/ref/Threaded.html | 6 + html-test/ref/Threaded_TH.html | 6 + html-test/ref/Ticket112.html | 6 + html-test/ref/Ticket61.html | 6 + html-test/ref/Ticket75.html | 6 + html-test/ref/TitledPicture.html | 6 + html-test/ref/TypeFamilies.html | 6 + html-test/ref/TypeFamilies2.html | 6 + html-test/ref/TypeFamilies3.html | 6 + html-test/ref/TypeOperators.html | 6 + html-test/ref/UnboxedStuff.html | 6 + html-test/ref/Unicode.html | 6 + html-test/ref/Unicode2.html | 6 + html-test/ref/Visible.html | 6 + html-test/src/A.hs | 1 + html-test/src/B.hs | 1 + html-test/src/Bold.hs | 1 + html-test/src/Bug1.hs | 1 + html-test/src/Bug1004.hs | 1 + html-test/src/Bug1033.hs | 1 + html-test/src/Bug1035.hs | 1 + html-test/src/Bug1050.hs | 1 + html-test/src/Bug1054.hs | 1 + html-test/src/Bug1063.hs | 1 + html-test/src/Bug1067A.hs | 1 + html-test/src/Bug1067B.hs | 1 + html-test/src/Bug1103.hs | 1 + html-test/src/Bug195.hs | 1 + html-test/src/Bug2.hs | 1 + html-test/src/Bug201.hs | 1 + html-test/src/Bug253.hs | 1 + html-test/src/Bug26.hs | 1 + html-test/src/Bug280.hs | 1 + html-test/src/Bug294.hs | 1 + html-test/src/Bug298.hs | 1 + html-test/src/Bug3.hs | 1 + html-test/src/Bug308.hs | 1 + html-test/src/Bug308CrossModule.hs | 1 + html-test/src/Bug310.hs | 1 + html-test/src/Bug313.hs | 1 + html-test/src/Bug335.hs | 1 + html-test/src/Bug4.hs | 1 + html-test/src/Bug458.hs | 1 + html-test/src/Bug466.hs | 1 + html-test/src/Bug546.hs | 1 + html-test/src/Bug548.hs | 1 + html-test/src/Bug6.hs | 1 + html-test/src/Bug613.hs | 1 + html-test/src/Bug647.hs | 1 + html-test/src/Bug679.hs | 1 + html-test/src/Bug7.hs | 1 + html-test/src/Bug745.hs | 1 + html-test/src/Bug8.hs | 1 + html-test/src/Bug85.hs | 1 + html-test/src/Bug865.hs | 1 + html-test/src/Bug923.hs | 1 + html-test/src/Bug952.hs | 1 + html-test/src/Bug953.hs | 1 + html-test/src/Bug975.hs | 1 + html-test/src/BugDeprecated.hs | 1 + html-test/src/BugExportHeadings.hs | 1 + html-test/src/Bugs.hs | 1 + html-test/src/BundledPatterns.hs | 1 + html-test/src/BundledPatterns2.hs | 1 + html-test/src/ConstructorArgs.hs | 1 + html-test/src/ConstructorPatternExport.hs | 1 + html-test/src/DefaultAssociatedTypes.hs | 1 + html-test/src/DefaultSignatures.hs | 1 + html-test/src/DeprecatedClass.hs | 1 + html-test/src/DeprecatedData.hs | 1 + html-test/src/DeprecatedFunction.hs | 1 + html-test/src/DeprecatedFunction2.hs | 1 + html-test/src/DeprecatedFunction3.hs | 1 + html-test/src/DeprecatedModule.hs | 1 + html-test/src/DeprecatedModule2.hs | 1 + html-test/src/DeprecatedNewtype.hs | 1 + html-test/src/DeprecatedReExport.hs | 1 + html-test/src/DeprecatedRecord.hs | 1 + html-test/src/DeprecatedTypeFamily.hs | 1 + html-test/src/DeprecatedTypeSynonym.hs | 1 + html-test/src/DuplicateRecordFields.hs | 1 + html-test/src/Examples.hs | 1 + html-test/src/Extensions.hs | 1 + html-test/src/FunArgs.hs | 1 + html-test/src/GADTRecords.hs | 1 + html-test/src/GadtConstructorArgs.hs | 1 + html-test/src/Hash.hs | 1 + html-test/src/Hidden.hs | 1 + html-test/src/HiddenInstances.hs | 1 + html-test/src/HiddenInstancesA.hs | 1 + html-test/src/HiddenInstancesB.hs | 1 + html-test/src/Hyperlinks.hs | 1 + html-test/src/Identifiers.hs | 1 + html-test/src/IgnoreExports.hs | 1 + html-test/src/ImplicitParams.hs | 1 + html-test/src/Instances.hs | 1 + html-test/src/LinearTypes.hs | 1 + html-test/src/Math.hs | 1 + html-test/src/Minimal.hs | 1 + html-test/src/ModuleWithWarning.hs | 1 + html-test/src/NamedDoc.hs | 1 + html-test/src/NamespacedIdentifiers.hs | 1 + html-test/src/Nesting.hs | 1 + html-test/src/NoLayout.hs | 1 + html-test/src/NonGreedy.hs | 1 + html-test/src/Operators.hs | 1 + html-test/src/OrphanInstances.hs | 1 + html-test/src/OrphanInstancesClass.hs | 1 + html-test/src/OrphanInstancesType.hs | 1 + html-test/src/PR643.hs | 1 + html-test/src/PR643_1.hs | 1 + html-test/src/PatternSyns.hs | 1 + html-test/src/PromotedTypes.hs | 1 + html-test/src/Properties.hs | 1 + html-test/src/PruneWithWarning.hs | 1 + html-test/src/QuantifiedConstraints.hs | 1 + html-test/src/QuasiExpr.hs | 1 + html-test/src/QuasiQuote.hs | 1 + html-test/src/SectionLabels.hs | 1 + html-test/src/SpuriousSuperclassConstraints.hs | 1 + html-test/src/TH.hs | 1 + html-test/src/TH2.hs | 1 + html-test/src/Table.hs | 1 + html-test/src/Test.hs | 1 + html-test/src/Threaded.hs | 1 + html-test/src/Threaded_TH.hs | 1 + html-test/src/Ticket112.hs | 1 + html-test/src/Ticket61.hs | 1 + html-test/src/Ticket61_Hidden.hs | 1 + html-test/src/Ticket75.hs | 1 + html-test/src/TitledPicture.hs | 1 + html-test/src/TypeFamilies.hs | 1 + html-test/src/TypeFamilies2.hs | 1 + html-test/src/TypeFamilies3.hs | 1 + html-test/src/TypeOperators.hs | 1 + html-test/src/UnboxedStuff.hs | 1 + html-test/src/Unicode.hs | 1 + html-test/src/Unicode2.hs | 1 + html-test/src/Visible.hs | 1 + hypsrc-test/ref/src/Bug1091.html | 9 +- hypsrc-test/ref/src/CPP.html | 31 +++-- hypsrc-test/ref/src/Classes.html | 79 ++++++------ hypsrc-test/ref/src/Constructors.html | 79 ++++++------ hypsrc-test/ref/src/Identifiers.html | 65 +++++----- hypsrc-test/ref/src/LinkingIdentifiers.html | 37 +++--- hypsrc-test/ref/src/Literals.html | 43 ++++--- hypsrc-test/ref/src/Operators.html | 53 ++++---- hypsrc-test/ref/src/Polymorphism.html | 135 +++++++++++---------- hypsrc-test/ref/src/PositionPragmas.html | 13 +- hypsrc-test/ref/src/Quasiquoter.html | 41 ++++--- hypsrc-test/ref/src/Records.html | 71 ++++++----- .../ref/src/TemplateHaskellQuasiquotes.html | 83 +++++++------ hypsrc-test/ref/src/TemplateHaskellSplices.html | 23 ++-- hypsrc-test/ref/src/Types.html | 87 +++++++------ hypsrc-test/ref/src/UsingQuasiquotes.html | 19 ++- hypsrc-test/src/Bug1091.hs | 1 + hypsrc-test/src/CPP.hs | 1 + hypsrc-test/src/Classes.hs | 1 + hypsrc-test/src/Constructors.hs | 1 + hypsrc-test/src/Identifiers.hs | 1 + hypsrc-test/src/LinkingIdentifiers.hs | 1 + hypsrc-test/src/Literals.hs | 1 + hypsrc-test/src/Operators.hs | 1 + hypsrc-test/src/Polymorphism.hs | 1 + hypsrc-test/src/PositionPragmas.hs | 1 + hypsrc-test/src/Quasiquoter.hs | 1 + hypsrc-test/src/Records.hs | 1 + hypsrc-test/src/TemplateHaskellQuasiquotes.hs | 1 + hypsrc-test/src/TemplateHaskellSplices.hs | 1 + hypsrc-test/src/Types.hs | 1 + hypsrc-test/src/UsingQuasiquotes.hs | 1 + latex-test/src/ConstructorArgs/ConstructorArgs.hs | 1 + .../src/DefaultSignatures/DefaultSignatures.hs | 1 + latex-test/src/Deprecated/Deprecated.hs | 1 + latex-test/src/Example/Example.hs | 1 + .../src/GadtConstructorArgs/GadtConstructorArgs.hs | 1 + latex-test/src/LinearTypes/LinearTypes.hs | 1 + .../NamespacedIdentifier/NamespacedIdentifier.hs | 1 + latex-test/src/Simple/Simple.hs | 1 + latex-test/src/TypeFamilies3/TypeFamilies3.hs | 1 + latex-test/src/UnboxedStuff/UnboxedStuff.hs | 1 + 300 files changed, 1374 insertions(+), 378 deletions(-) diff --git a/hoogle-test/src/Bug722/Bug722.hs b/hoogle-test/src/Bug722/Bug722.hs index a33d5b24..ef7e9a2f 100644 --- a/hoogle-test/src/Bug722/Bug722.hs +++ b/hoogle-test/src/Bug722/Bug722.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} {-# LANGUAGE TypeOperators, TypeFamilies #-} module Bug722 where diff --git a/hoogle-test/src/Bug806/Bug806.hs b/hoogle-test/src/Bug806/Bug806.hs index 45efda77..6deb98c1 100644 --- a/hoogle-test/src/Bug806/Bug806.hs +++ b/hoogle-test/src/Bug806/Bug806.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE UndecidableInstances #-} diff --git a/hoogle-test/src/Bug825/Bug825.hs b/hoogle-test/src/Bug825/Bug825.hs index bfe07139..48c09305 100644 --- a/hoogle-test/src/Bug825/Bug825.hs +++ b/hoogle-test/src/Bug825/Bug825.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE TypeOperators #-} module Bug825 where diff --git a/hoogle-test/src/Bug873/Bug873.hs b/hoogle-test/src/Bug873/Bug873.hs index 3a9a5383..4df1b772 100644 --- a/hoogle-test/src/Bug873/Bug873.hs +++ b/hoogle-test/src/Bug873/Bug873.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} module Bug873 (($), ($$)) where infixr 0 $$ diff --git a/hoogle-test/src/Bug946/Bug946.hs b/hoogle-test/src/Bug946/Bug946.hs index 606b5ac4..ec567d6d 100644 --- a/hoogle-test/src/Bug946/Bug946.hs +++ b/hoogle-test/src/Bug946/Bug946.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} {-# LANGUAGE PatternSynonyms #-} module Bug946 ( AnInt(AnInt, Zero), diff --git a/hoogle-test/src/Bug992/Bug992.hs b/hoogle-test/src/Bug992/Bug992.hs index bd772427..0b03964b 100644 --- a/hoogle-test/src/Bug992/Bug992.hs +++ b/hoogle-test/src/Bug992/Bug992.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} {-# LANGUAGE KindSignatures #-} module Bug992 where diff --git a/hoogle-test/src/assoc-types/AssocTypes.hs b/hoogle-test/src/assoc-types/AssocTypes.hs index ceacc834..3fa5f034 100644 --- a/hoogle-test/src/assoc-types/AssocTypes.hs +++ b/hoogle-test/src/assoc-types/AssocTypes.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE AllowAmbiguousTypes #-} diff --git a/hoogle-test/src/classes/Classes.hs b/hoogle-test/src/classes/Classes.hs index 23f68499..2bd726a2 100644 --- a/hoogle-test/src/classes/Classes.hs +++ b/hoogle-test/src/classes/Classes.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} module Classes where diff --git a/hoogle-test/src/fixity/Fixity.hs b/hoogle-test/src/fixity/Fixity.hs index 3af38117..122bd4f8 100644 --- a/hoogle-test/src/fixity/Fixity.hs +++ b/hoogle-test/src/fixity/Fixity.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} module Fixity where diff --git a/hoogle-test/src/modules/Bar.hs b/hoogle-test/src/modules/Bar.hs index 156a835f..86e2648b 100644 --- a/hoogle-test/src/modules/Bar.hs +++ b/hoogle-test/src/modules/Bar.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} module Bar where diff --git a/hoogle-test/src/modules/Foo.hs b/hoogle-test/src/modules/Foo.hs index 6581fe4c..947da4ce 100644 --- a/hoogle-test/src/modules/Foo.hs +++ b/hoogle-test/src/modules/Foo.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} module Foo where diff --git a/hoogle-test/src/type-sigs/ReaderT.hs b/hoogle-test/src/type-sigs/ReaderT.hs index 009c7ed2..fb09bac0 100644 --- a/hoogle-test/src/type-sigs/ReaderT.hs +++ b/hoogle-test/src/type-sigs/ReaderT.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} module ReaderT where newtype ReaderT r m a = ReaderT { runReaderT :: r -> m a } diff --git a/hoogle-test/src/type-sigs/ReaderTReexport.hs b/hoogle-test/src/type-sigs/ReaderTReexport.hs index 21fa44ee..b995bba8 100644 --- a/hoogle-test/src/type-sigs/ReaderTReexport.hs +++ b/hoogle-test/src/type-sigs/ReaderTReexport.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} module ReaderTReexport (ReaderT(..), runReaderT) where import ReaderT diff --git a/html-test/ref/A.html b/html-test/ref/A.html index c27f1888..d3dc54ff 100644 --- a/html-test/ref/A.html +++ b/html-test/ref/A.html @@ -38,6 +38,12 @@ >Safe-InferredLanguageHaskell2010

A

Safe-InferredLanguageHaskell2010

Bold

Safe-InferredLanguageHaskell2010

Bug1

Safe-InferredLanguageHaskell2010

Bug1004

Safe-InferredLanguageHaskell2010

Bug1033

Safe-InferredLanguageHaskell2010

Bug1035

Safe-InferredLanguageHaskell2010

Bug1050

Safe-InferredLanguageHaskell2010

Bug1054

Safe-InferredLanguageHaskell2010

Bug1063

Safe-InferredLanguageHaskell2010

Bug1067A

Safe-InferredLanguageHaskell2010

Bug1067B

Safe-InferredLanguageHaskell2010

Bug1103

Safe-InferredLanguageHaskell2010

Bug195

Safe-InferredLanguageHaskell2010

Bug2

Safe-InferredLanguageHaskell2010

Bug201

Safe-InferredLanguageHaskell2010

Bug253

Safe-InferredLanguageHaskell2010

Bug26

Safe-InferredLanguageHaskell2010

Bug280

Safe-InferredLanguageHaskell2010

Bug294

Safe-InferredLanguageHaskell2010

Bug298

Safe-InferredLanguageHaskell2010

Bug3

Safe-InferredLanguageHaskell2010

Bug308

Safe-InferredLanguageHaskell2010

Bug308CrossModule

Safe-InferredLanguageHaskell2010

Bug310

Safe-InferredLanguageHaskell2010

Bug313

Safe-InferredLanguageHaskell2010

Bug335

Safe-InferredLanguageHaskell2010

Bug4

Safe-InferredLanguageHaskell2010

Bug458

Safe-InferredLanguageHaskell2010

Bug466

Safe-InferredLanguageHaskell2010

Bug546

Safe-InferredLanguageHaskell2010

Bug548

Safe-InferredLanguageHaskell2010

Bug574

Safe-InferredLanguageHaskell2010

Bug6

Safe-InferredLanguageHaskell2010

Bug613

Safe-InferredLanguageHaskell2010

Bug647

Safe-InferredLanguageHaskell2010

Bug679

Safe-InferredLanguageHaskell2010

Bug7

Safe-InferredLanguageHaskell2010

Bug8

Safe-InferredLanguageHaskell2010

Bug85

Safe-InferredLanguageHaskell2010

Bug865

Safe-InferredLanguageHaskell2010

Bug923

Safe-InferredLanguageHaskell2010

Bug952

Safe-InferredLanguageHaskell2010

Bug953

Safe-InferredLanguageHaskell2010

Bug973

Safe-InferredLanguageHaskell2010

BugDeprecated

Safe-InferredLanguageHaskell2010

BugExportHeadings

Safe-InferredLanguageHaskell2010

Bugs

Safe-InferredLanguageHaskell2010

BundledPatterns

Safe-InferredLanguageHaskell2010

BundledPatterns2

Safe-InferredLanguageHaskell2010

ConstructorArgs

Safe-InferredLanguageHaskell2010

ConstructorPatternExport

Safe-InferredLanguageHaskell2010

DefaultAssociatedTypes

Safe-InferredLanguageHaskell2010

DefaultSignatures

Safe-InferredLanguageHaskell2010

DeprecatedClass

Safe-InferredLanguageHaskell2010

DeprecatedData

Safe-InferredLanguageHaskell2010

DeprecatedFunction

Safe-InferredLanguageHaskell2010

DeprecatedFunction2

Safe-InferredLanguageHaskell2010

DeprecatedFunction3

Safe-InferredLanguageHaskell2010

DeprecatedModule

Safe-InferredLanguageHaskell2010

DeprecatedModule2

Safe-InferredLanguageHaskell2010

DeprecatedNewtype

Safe-InferredLanguageHaskell2010

DeprecatedReExport

Safe-InferredLanguageHaskell2010

DeprecatedRecord

Safe-InferredLanguageHaskell2010

DeprecatedTypeFamily

Safe-InferredLanguageHaskell2010

DeprecatedTypeSynonym

Safe-InferredLanguageHaskell2010

DuplicateRecordFields

Safe-InferredLanguageHaskell2010

Examples

Safe-InferredLanguageHaskell2010

FunArgs

Safe-InferredLanguageHaskell2010

GADTRecords

Safe-InferredLanguageHaskell2010

GadtConstructorArgs

Safe-InferredLanguageHaskell2010

Hash

Safe-InferredLanguageHaskell2010

HiddenInstances

Safe-InferredLanguageHaskell2010

HiddenInstancesB

Safe-InferredLanguageHaskell2010

Hyperlinks

Safe-InferredLanguageHaskell2010

Identifiers

Safe-InferredLanguageHaskell2010

IgnoreExports

Safe-InferredLanguageHaskell2010

ImplicitParams

Safe-InferredLanguageHaskell2010

Instances

Safe-InferredLanguageHaskell2010

LinearTypes

Safe-InferredLanguageHaskell2010

Math

Safe-InferredLanguageHaskell2010

Minimal

Safe-InferredLanguageHaskell2010

ModuleWithWarning

Safe-InferredLanguageHaskell2010

NamedDoc

Safe-InferredLanguageHaskell2010

NamespacedIdentifiers

Safe-InferredLanguageHaskell2010

Nesting

Safe-InferredLanguageHaskell2010

NoLayout

Safe-InferredLanguageHaskell2010

NonGreedy

Safe-InferredLanguageHaskell2010

Operators

Safe-InferredLanguageHaskell2010

OrphanInstances

Safe-InferredLanguageHaskell2010

OrphanInstancesClass

Safe-InferredLanguageHaskell2010

OrphanInstancesType

Safe-InferredLanguageHaskell2010

PR643

Safe-InferredLanguageHaskell2010

PR643_1

Safe-InferredLanguageHaskell2010

PatternSyns

Safe-InferredLanguageHaskell2010

PromotedTypes

Safe-InferredLanguageHaskell2010

Properties

Safe-InferredLanguageHaskell2010

PruneWithWarning

Safe-InferredLanguageHaskell2010

QuantifiedConstraints

Safe-InferredLanguageHaskell2010

QuasiExpr

Safe-InferredLanguageHaskell2010

QuasiQuote

Safe-InferredLanguageHaskell2010

SectionLabels

Safe-InferredLanguageHaskell2010

SpuriousSuperclassConstraints

Safe-InferredLanguageHaskell2010

TH

Safe-InferredLanguageHaskell2010

TH2

Safe-InferredLanguageHaskell2010

Table

Safe-InferredLanguageHaskell2010

Test

Safe-InferredLanguageHaskell2010

Threaded

Safe-InferredLanguageHaskell2010

Threaded_TH

Safe-InferredLanguageHaskell2010

Ticket112

Safe-InferredLanguageHaskell2010

Ticket61

Safe-InferredLanguageHaskell2010

Ticket75

Safe-InferredLanguageHaskell2010

TitledPicture

Safe-InferredLanguageHaskell2010

TypeFamilies

Safe-InferredLanguageHaskell2010

TypeFamilies2

Safe-InferredLanguageHaskell2010

TypeFamilies3

Safe-InferredLanguageHaskell2010

TypeOperators

Safe-InferredLanguageHaskell2010

UnboxedStuff

Safe-InferredLanguageHaskell2010

Unicode

Safe-InferredLanguageHaskell2010

Unicode2

Safe-InferredLanguageHaskell2010

Visible

diff --git a/html-test/src/Bug85.hs b/html-test/src/Bug85.hs index e29b2662..53979aee 100644 --- a/html-test/src/Bug85.hs +++ b/html-test/src/Bug85.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} {-# LANGUAGE GADTs, KindSignatures #-} module Bug85 where diff --git a/html-test/src/Bug865.hs b/html-test/src/Bug865.hs index 71a6add1..86627f8e 100644 --- a/html-test/src/Bug865.hs +++ b/html-test/src/Bug865.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} module Bug865 where -- | An emphasized link [yes /this/ is emphasized while this is diff --git a/html-test/src/Bug923.hs b/html-test/src/Bug923.hs index bb5bca0a..1d24a9f6 100644 --- a/html-test/src/Bug923.hs +++ b/html-test/src/Bug923.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} {-# LANGUAGE KindSignatures, FlexibleInstances, GADTs, DataKinds #-} module Bug923 where diff --git a/html-test/src/Bug952.hs b/html-test/src/Bug952.hs index 09b365e4..0840e46c 100644 --- a/html-test/src/Bug952.hs +++ b/html-test/src/Bug952.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} module Bug952 where -- | See 'case', 'of', '--' compared to 'Q.case', 'Q.of', 'Q.--' diff --git a/html-test/src/Bug953.hs b/html-test/src/Bug953.hs index 63f2c45a..4ff3e8ae 100644 --- a/html-test/src/Bug953.hs +++ b/html-test/src/Bug953.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} module Bug953 where {- | A foo diff --git a/html-test/src/Bug975.hs b/html-test/src/Bug975.hs index 97ebabda..e55385c5 100644 --- a/html-test/src/Bug975.hs +++ b/html-test/src/Bug975.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} {-# LANGUAGE ExplicitForAll #-} module Bug973 where diff --git a/html-test/src/BugDeprecated.hs b/html-test/src/BugDeprecated.hs index 7741786f..9dfef176 100644 --- a/html-test/src/BugDeprecated.hs +++ b/html-test/src/BugDeprecated.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} module BugDeprecated where foo :: Int diff --git a/html-test/src/BugExportHeadings.hs b/html-test/src/BugExportHeadings.hs index a5493a08..b664a448 100644 --- a/html-test/src/BugExportHeadings.hs +++ b/html-test/src/BugExportHeadings.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} -- test for #192 module BugExportHeadings ( -- * Foo diff --git a/html-test/src/Bugs.hs b/html-test/src/Bugs.hs index e60bbe8f..aed716a4 100644 --- a/html-test/src/Bugs.hs +++ b/html-test/src/Bugs.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} module Bugs where data A a = A a (a -> Int) diff --git a/html-test/src/BundledPatterns.hs b/html-test/src/BundledPatterns.hs index 443e64fa..420068ac 100644 --- a/html-test/src/BundledPatterns.hs +++ b/html-test/src/BundledPatterns.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} {-# LANGUAGE DataKinds, GADTs, KindSignatures, PatternSynonyms, TypeOperators, ViewPatterns #-} module BundledPatterns (Vec(Nil,(:>)), RTree (LR,BR)) where diff --git a/html-test/src/BundledPatterns2.hs b/html-test/src/BundledPatterns2.hs index 5e9a83a7..c4123535 100644 --- a/html-test/src/BundledPatterns2.hs +++ b/html-test/src/BundledPatterns2.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} {-# LANGUAGE DataKinds, GADTs, KindSignatures, PatternSynonyms, TypeOperators, ViewPatterns #-} module BundledPatterns2 (Vec((:>), Empty), RTree(..)) where diff --git a/html-test/src/ConstructorArgs.hs b/html-test/src/ConstructorArgs.hs index 6b0da711..c3b848c3 100644 --- a/html-test/src/ConstructorArgs.hs +++ b/html-test/src/ConstructorArgs.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} {-# LANGUAGE GADTs, PatternSynonyms #-} module ConstructorArgs (Foo(..), Boo(Foo, Foa, Fo, Fo'), pattern Bo, pattern Bo') where diff --git a/html-test/src/ConstructorPatternExport.hs b/html-test/src/ConstructorPatternExport.hs index 7897b4bc..aa2971d6 100644 --- a/html-test/src/ConstructorPatternExport.hs +++ b/html-test/src/ConstructorPatternExport.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} {-# LANGUAGE PatternSynonyms #-} {-# LANGUAGE ExistentialQuantification #-} {-# LANGUAGE GADTs #-} diff --git a/html-test/src/DefaultAssociatedTypes.hs b/html-test/src/DefaultAssociatedTypes.hs index 6ad197d3..340742d3 100644 --- a/html-test/src/DefaultAssociatedTypes.hs +++ b/html-test/src/DefaultAssociatedTypes.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} {-# LANGUAGE DefaultSignatures, TypeFamilies #-} module DefaultAssociatedTypes where diff --git a/html-test/src/DefaultSignatures.hs b/html-test/src/DefaultSignatures.hs index 52d68a96..1b1b8257 100644 --- a/html-test/src/DefaultSignatures.hs +++ b/html-test/src/DefaultSignatures.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} {-# LANGUAGE DefaultSignatures #-} module DefaultSignatures where diff --git a/html-test/src/DeprecatedClass.hs b/html-test/src/DeprecatedClass.hs index 018904ab..357f64e4 100644 --- a/html-test/src/DeprecatedClass.hs +++ b/html-test/src/DeprecatedClass.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} module DeprecatedClass where -- | some class diff --git a/html-test/src/DeprecatedData.hs b/html-test/src/DeprecatedData.hs index c40ba122..f2324162 100644 --- a/html-test/src/DeprecatedData.hs +++ b/html-test/src/DeprecatedData.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} {-# LANGUAGE TypeFamilies #-} module DeprecatedData where diff --git a/html-test/src/DeprecatedFunction.hs b/html-test/src/DeprecatedFunction.hs index 8d626435..2c6418d3 100644 --- a/html-test/src/DeprecatedFunction.hs +++ b/html-test/src/DeprecatedFunction.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} module DeprecatedFunction where -- | some documentation for foo diff --git a/html-test/src/DeprecatedFunction2.hs b/html-test/src/DeprecatedFunction2.hs index bdbbf95c..fb4193f2 100644 --- a/html-test/src/DeprecatedFunction2.hs +++ b/html-test/src/DeprecatedFunction2.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} module DeprecatedFunction2 where diff --git a/html-test/src/DeprecatedFunction3.hs b/html-test/src/DeprecatedFunction3.hs index ca719bda..4a286e0a 100644 --- a/html-test/src/DeprecatedFunction3.hs +++ b/html-test/src/DeprecatedFunction3.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} module DeprecatedFunction3 where diff --git a/html-test/src/DeprecatedModule.hs b/html-test/src/DeprecatedModule.hs index 369dba4f..179b5899 100644 --- a/html-test/src/DeprecatedModule.hs +++ b/html-test/src/DeprecatedModule.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} -- | Documentation for "DeprecatedModule". module DeprecatedModule {-# DEPRECATED "Use \"Foo\" instead" #-} where diff --git a/html-test/src/DeprecatedModule2.hs b/html-test/src/DeprecatedModule2.hs index 94185297..ccec1be7 100644 --- a/html-test/src/DeprecatedModule2.hs +++ b/html-test/src/DeprecatedModule2.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} module DeprecatedModule2 {-# DEPRECATED "Use Foo instead" #-} where foo :: Int diff --git a/html-test/src/DeprecatedNewtype.hs b/html-test/src/DeprecatedNewtype.hs index 254f1f55..6aeead44 100644 --- a/html-test/src/DeprecatedNewtype.hs +++ b/html-test/src/DeprecatedNewtype.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} module DeprecatedNewtype where -- | some documentation diff --git a/html-test/src/DeprecatedReExport.hs b/html-test/src/DeprecatedReExport.hs index f851e2ff..061c9c27 100644 --- a/html-test/src/DeprecatedReExport.hs +++ b/html-test/src/DeprecatedReExport.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} -- | -- What is tested here: -- diff --git a/html-test/src/DeprecatedRecord.hs b/html-test/src/DeprecatedRecord.hs index d44499e7..9fe0240d 100644 --- a/html-test/src/DeprecatedRecord.hs +++ b/html-test/src/DeprecatedRecord.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} module DeprecatedRecord where -- | type Foo diff --git a/html-test/src/DeprecatedTypeFamily.hs b/html-test/src/DeprecatedTypeFamily.hs index 70473bb8..3d94cace 100644 --- a/html-test/src/DeprecatedTypeFamily.hs +++ b/html-test/src/DeprecatedTypeFamily.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} {-# LANGUAGE TypeFamilies #-} module DeprecatedTypeFamily where diff --git a/html-test/src/DeprecatedTypeSynonym.hs b/html-test/src/DeprecatedTypeSynonym.hs index 34df47da..05fb9bdc 100644 --- a/html-test/src/DeprecatedTypeSynonym.hs +++ b/html-test/src/DeprecatedTypeSynonym.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} module DeprecatedTypeSynonym where diff --git a/html-test/src/DuplicateRecordFields.hs b/html-test/src/DuplicateRecordFields.hs index 2cf9ff43..59441750 100644 --- a/html-test/src/DuplicateRecordFields.hs +++ b/html-test/src/DuplicateRecordFields.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} {-# LANGUAGE DuplicateRecordFields #-} module DuplicateRecordFields (RawReplay(..)) where diff --git a/html-test/src/Examples.hs b/html-test/src/Examples.hs index c8c450f1..b518ea70 100644 --- a/html-test/src/Examples.hs +++ b/html-test/src/Examples.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} module Examples where -- | Fibonacci number of given 'Integer'. diff --git a/html-test/src/Extensions.hs b/html-test/src/Extensions.hs index 61eac219..bbaa6395 100644 --- a/html-test/src/Extensions.hs +++ b/html-test/src/Extensions.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} {-# LANGUAGE Haskell2010, ExplicitForAll, MonomorphismRestriction #-} {-# OPTIONS_HADDOCK show-extensions #-} module Extensions where diff --git a/html-test/src/FunArgs.hs b/html-test/src/FunArgs.hs index e20bcda7..9d7c19dc 100644 --- a/html-test/src/FunArgs.hs +++ b/html-test/src/FunArgs.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} {-# LANGUAGE RankNTypes, DataKinds, TypeFamilies #-} module FunArgs where diff --git a/html-test/src/GADTRecords.hs b/html-test/src/GADTRecords.hs index dcbbb870..015027d2 100644 --- a/html-test/src/GADTRecords.hs +++ b/html-test/src/GADTRecords.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} {-# LANGUAGE GADTs #-} module GADTRecords (H1(..)) where diff --git a/html-test/src/GadtConstructorArgs.hs b/html-test/src/GadtConstructorArgs.hs index 79ffb4d3..6d742bd7 100644 --- a/html-test/src/GadtConstructorArgs.hs +++ b/html-test/src/GadtConstructorArgs.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} {-# LANGUAGE GADTs, PatternSynonyms #-} module GadtConstructorArgs (Boo(..)) where diff --git a/html-test/src/Hash.hs b/html-test/src/Hash.hs index 1eb8af5b..ce40fdd3 100644 --- a/html-test/src/Hash.hs +++ b/html-test/src/Hash.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} {- | Implementation of fixed-size hash tables, with a type class for constructing hash values for structured types. diff --git a/html-test/src/Hidden.hs b/html-test/src/Hidden.hs index 896da648..2b694e86 100644 --- a/html-test/src/Hidden.hs +++ b/html-test/src/Hidden.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} {-# OPTIONS_HADDOCK hide #-} module Hidden where diff --git a/html-test/src/HiddenInstances.hs b/html-test/src/HiddenInstances.hs index 99a6c2fd..a9124098 100644 --- a/html-test/src/HiddenInstances.hs +++ b/html-test/src/HiddenInstances.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} -- http://trac.haskell.org/haddock/ticket/37 module HiddenInstances (VisibleClass, VisibleData) where diff --git a/html-test/src/HiddenInstancesA.hs b/html-test/src/HiddenInstancesA.hs index f1775208..8879868c 100644 --- a/html-test/src/HiddenInstancesA.hs +++ b/html-test/src/HiddenInstancesA.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} {-# OPTIONS_HADDOCK hide #-} module HiddenInstancesA where diff --git a/html-test/src/HiddenInstancesB.hs b/html-test/src/HiddenInstancesB.hs index eabf0637..0def0ecc 100644 --- a/html-test/src/HiddenInstancesB.hs +++ b/html-test/src/HiddenInstancesB.hs @@ -1,2 +1,3 @@ +{-# LANGUAGE Haskell2010 #-} module HiddenInstancesB (Foo, Bar) where import HiddenInstancesA diff --git a/html-test/src/Hyperlinks.hs b/html-test/src/Hyperlinks.hs index 34e64448..f64a5bb1 100644 --- a/html-test/src/Hyperlinks.hs +++ b/html-test/src/Hyperlinks.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} module Hyperlinks where -- | diff --git a/html-test/src/Identifiers.hs b/html-test/src/Identifiers.hs index 75f12109..13ee3b82 100644 --- a/html-test/src/Identifiers.hs +++ b/html-test/src/Identifiers.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} {-# LANGUAGE TypeOperators #-} module Identifiers where diff --git a/html-test/src/IgnoreExports.hs b/html-test/src/IgnoreExports.hs index edb7c4c1..2016d3d5 100644 --- a/html-test/src/IgnoreExports.hs +++ b/html-test/src/IgnoreExports.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} {-# OPTIONS_HADDOCK ignore-exports #-} module IgnoreExports (Foo, foo) where diff --git a/html-test/src/ImplicitParams.hs b/html-test/src/ImplicitParams.hs index 3ca9157b..8635b2a4 100644 --- a/html-test/src/ImplicitParams.hs +++ b/html-test/src/ImplicitParams.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} {-# LANGUAGE ImplicitParams, RankNTypes #-} module ImplicitParams where diff --git a/html-test/src/Instances.hs b/html-test/src/Instances.hs index 545c8534..e9537a92 100644 --- a/html-test/src/Instances.hs +++ b/html-test/src/Instances.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FlexibleContexts #-} diff --git a/html-test/src/LinearTypes.hs b/html-test/src/LinearTypes.hs index cb4eb138..c4f9c84f 100644 --- a/html-test/src/LinearTypes.hs +++ b/html-test/src/LinearTypes.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} {-# LANGUAGE LinearTypes #-} module LinearTypes where diff --git a/html-test/src/Math.hs b/html-test/src/Math.hs index 75bc513e..375dbc2d 100644 --- a/html-test/src/Math.hs +++ b/html-test/src/Math.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} -- | Math (display) for 'normalDensity' -- -- \[ diff --git a/html-test/src/Minimal.hs b/html-test/src/Minimal.hs index 9df03cca..ec275aec 100644 --- a/html-test/src/Minimal.hs +++ b/html-test/src/Minimal.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} -- | This tests the new MINIMAL pragma present in GHC 7.8 module Minimal ( Foo(..) diff --git a/html-test/src/ModuleWithWarning.hs b/html-test/src/ModuleWithWarning.hs index e64d9d7e..710589bf 100644 --- a/html-test/src/ModuleWithWarning.hs +++ b/html-test/src/ModuleWithWarning.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} -- | Documentation for "ModuleWithWarning". module ModuleWithWarning {-# WARNING "This is an unstable interface. Prefer functions from \"Prelude\" instead!" #-} where diff --git a/html-test/src/NamedDoc.hs b/html-test/src/NamedDoc.hs index 7c04ba72..8ac40921 100644 --- a/html-test/src/NamedDoc.hs +++ b/html-test/src/NamedDoc.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} module NamedDoc where -- $foo bar diff --git a/html-test/src/NamespacedIdentifiers.hs b/html-test/src/NamespacedIdentifiers.hs index 6f59d247..38fb7101 100644 --- a/html-test/src/NamespacedIdentifiers.hs +++ b/html-test/src/NamespacedIdentifiers.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} module NamespacedIdentifiers where -- | A link to: diff --git a/html-test/src/Nesting.hs b/html-test/src/Nesting.hs index f88be87d..fa45e11b 100644 --- a/html-test/src/Nesting.hs +++ b/html-test/src/Nesting.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} module Nesting where {-| diff --git a/html-test/src/NoLayout.hs b/html-test/src/NoLayout.hs index 19b38b1d..e07470a3 100644 --- a/html-test/src/NoLayout.hs +++ b/html-test/src/NoLayout.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} -- Haddock comments are parsed as separate declarations so we -- need to insert a ';' when using them with explicit layout. diff --git a/html-test/src/NonGreedy.hs b/html-test/src/NonGreedy.hs index f51b55f5..b89b0723 100644 --- a/html-test/src/NonGreedy.hs +++ b/html-test/src/NonGreedy.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} module NonGreedy where -- | diff --git a/html-test/src/Operators.hs b/html-test/src/Operators.hs index 0b633c3f..c303c8bd 100644 --- a/html-test/src/Operators.hs +++ b/html-test/src/Operators.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} {-# LANGUAGE PatternSynonyms, TypeOperators, TypeFamilies, MultiParamTypeClasses, GADTs #-} {-# LANGUAGE FunctionalDependencies #-} diff --git a/html-test/src/OrphanInstances.hs b/html-test/src/OrphanInstances.hs index e50327ee..e7a24c45 100644 --- a/html-test/src/OrphanInstances.hs +++ b/html-test/src/OrphanInstances.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} module OrphanInstances where import OrphanInstancesType diff --git a/html-test/src/OrphanInstancesClass.hs b/html-test/src/OrphanInstancesClass.hs index 4b51acfc..d5cbf708 100644 --- a/html-test/src/OrphanInstancesClass.hs +++ b/html-test/src/OrphanInstancesClass.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} module OrphanInstancesClass (AClass(..)) where class AClass a where diff --git a/html-test/src/OrphanInstancesType.hs b/html-test/src/OrphanInstancesType.hs index b3c3145e..8a48b93e 100644 --- a/html-test/src/OrphanInstancesType.hs +++ b/html-test/src/OrphanInstancesType.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} module OrphanInstancesType (AType(..)) where data AType = AType Int diff --git a/html-test/src/PR643.hs b/html-test/src/PR643.hs index 565e5b57..a6ad81ee 100644 --- a/html-test/src/PR643.hs +++ b/html-test/src/PR643.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} module PR643 (test) where import PR643_1 diff --git a/html-test/src/PR643_1.hs b/html-test/src/PR643_1.hs index ecd0db94..67dabee3 100644 --- a/html-test/src/PR643_1.hs +++ b/html-test/src/PR643_1.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} module PR643_1 where infixr 5 `test` diff --git a/html-test/src/PatternSyns.hs b/html-test/src/PatternSyns.hs index bf0f7848..e0da6d6b 100644 --- a/html-test/src/PatternSyns.hs +++ b/html-test/src/PatternSyns.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} {-# LANGUAGE ExistentialQuantification, PatternSynonyms, PolyKinds, TypeOperators #-} -- | Testing some pattern synonyms diff --git a/html-test/src/PromotedTypes.hs b/html-test/src/PromotedTypes.hs index ae3ad375..624f9d5a 100644 --- a/html-test/src/PromotedTypes.hs +++ b/html-test/src/PromotedTypes.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE KindSignatures #-} diff --git a/html-test/src/Properties.hs b/html-test/src/Properties.hs index 05930ece..8b1409f3 100644 --- a/html-test/src/Properties.hs +++ b/html-test/src/Properties.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} module Properties where -- | Fibonacci number of given 'Integer'. diff --git a/html-test/src/PruneWithWarning.hs b/html-test/src/PruneWithWarning.hs index bfa55ea2..c2f746f0 100644 --- a/html-test/src/PruneWithWarning.hs +++ b/html-test/src/PruneWithWarning.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} {-# OPTIONS_HADDOCK prune #-} -- | -- What is tested here: diff --git a/html-test/src/QuantifiedConstraints.hs b/html-test/src/QuantifiedConstraints.hs index 82dd81e5..4f96b322 100644 --- a/html-test/src/QuantifiedConstraints.hs +++ b/html-test/src/QuantifiedConstraints.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} {-# LANGUAGE QuantifiedConstraints #-} module QuantifiedConstraints where diff --git a/html-test/src/QuasiExpr.hs b/html-test/src/QuasiExpr.hs index 970759ba..d81fcf8b 100644 --- a/html-test/src/QuasiExpr.hs +++ b/html-test/src/QuasiExpr.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} {-# LANGUAGE TemplateHaskell #-} -- Used by QuasiQuote. Example taken from the GHC documentation. diff --git a/html-test/src/QuasiQuote.hs b/html-test/src/QuasiQuote.hs index 06762cf9..fe900eb8 100644 --- a/html-test/src/QuasiQuote.hs +++ b/html-test/src/QuasiQuote.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} {-# LANGUAGE TemplateHaskell, QuasiQuotes #-} -- example taken from the GHC documentation diff --git a/html-test/src/SectionLabels.hs b/html-test/src/SectionLabels.hs index 560bafa4..0017bd72 100644 --- a/html-test/src/SectionLabels.hs +++ b/html-test/src/SectionLabels.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} module SectionLabels ( -- * Section heading#custom# diff --git a/html-test/src/SpuriousSuperclassConstraints.hs b/html-test/src/SpuriousSuperclassConstraints.hs index 3e230945..cb204941 100644 --- a/html-test/src/SpuriousSuperclassConstraints.hs +++ b/html-test/src/SpuriousSuperclassConstraints.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} {-# LANGUAGE EmptyDataDecls, KindSignatures #-} -- | -- What is tested here: diff --git a/html-test/src/TH.hs b/html-test/src/TH.hs index f8178bcb..2692ae42 100644 --- a/html-test/src/TH.hs +++ b/html-test/src/TH.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} {-# LANGUAGE TemplateHaskell #-} module TH where diff --git a/html-test/src/TH2.hs b/html-test/src/TH2.hs index ea85e547..f878b1e0 100644 --- a/html-test/src/TH2.hs +++ b/html-test/src/TH2.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} {-# LANGUAGE TemplateHaskell #-} module TH2 where diff --git a/html-test/src/Table.hs b/html-test/src/Table.hs index 2cf0c662..4ffbc9b3 100644 --- a/html-test/src/Table.hs +++ b/html-test/src/Table.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} -- | This tests the table markup module Table ( tableWithHeader diff --git a/html-test/src/Test.hs b/html-test/src/Test.hs index e94cc414..a809f337 100644 --- a/html-test/src/Test.hs +++ b/html-test/src/Test.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} ----------------------------------------------------------------------------- -- | -- Module : Test diff --git a/html-test/src/Threaded.hs b/html-test/src/Threaded.hs index 7f3073ad..afe38c27 100644 --- a/html-test/src/Threaded.hs +++ b/html-test/src/Threaded.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} {-# LANGUAGE TemplateHaskell #-} -- | Ensures haddock built with @-threaded@. diff --git a/html-test/src/Threaded_TH.hs b/html-test/src/Threaded_TH.hs index 53e5a399..8179f090 100644 --- a/html-test/src/Threaded_TH.hs +++ b/html-test/src/Threaded_TH.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} -- | Imported by 'Threaded', since a TH splice can't be used in the -- module where it is defined. module Threaded_TH where diff --git a/html-test/src/Ticket112.hs b/html-test/src/Ticket112.hs index c9cd5117..db7f3ed0 100644 --- a/html-test/src/Ticket112.hs +++ b/html-test/src/Ticket112.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} {-# LANGUAGE MagicHash #-} module Ticket112 where diff --git a/html-test/src/Ticket61.hs b/html-test/src/Ticket61.hs index 26ca287f..c80e1c75 100644 --- a/html-test/src/Ticket61.hs +++ b/html-test/src/Ticket61.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} module Ticket61 (module Ticket61_Hidden) where import Ticket61_Hidden diff --git a/html-test/src/Ticket61_Hidden.hs b/html-test/src/Ticket61_Hidden.hs index 583c10cd..f3654cfc 100644 --- a/html-test/src/Ticket61_Hidden.hs +++ b/html-test/src/Ticket61_Hidden.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} {-# OPTIONS_HADDOCK hide #-} module Ticket61_Hidden where diff --git a/html-test/src/Ticket75.hs b/html-test/src/Ticket75.hs index 5fc704d6..743ffd60 100644 --- a/html-test/src/Ticket75.hs +++ b/html-test/src/Ticket75.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} {-# LANGUAGE TypeOperators #-} module Ticket75 where diff --git a/html-test/src/TitledPicture.hs b/html-test/src/TitledPicture.hs index 7029d98a..69d44397 100644 --- a/html-test/src/TitledPicture.hs +++ b/html-test/src/TitledPicture.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} module TitledPicture where -- | Picture for 'foo' without a title <> diff --git a/html-test/src/TypeFamilies.hs b/html-test/src/TypeFamilies.hs index a79d503e..d759af4f 100644 --- a/html-test/src/TypeFamilies.hs +++ b/html-test/src/TypeFamilies.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} {-# LANGUAGE TypeFamilies, UndecidableInstances, PolyKinds, TypeOperators, DataKinds, MultiParamTypeClasses, GADTs #-} -- | Doc for: module TypeFamilies diff --git a/html-test/src/TypeFamilies2.hs b/html-test/src/TypeFamilies2.hs index b66acbfa..c1211319 100644 --- a/html-test/src/TypeFamilies2.hs +++ b/html-test/src/TypeFamilies2.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} {-# LANGUAGE TypeFamilies #-} -- This tests what happens if we have unexported types -- in type instances. The expected behaviour is diff --git a/html-test/src/TypeFamilies3.hs b/html-test/src/TypeFamilies3.hs index bde05fb8..80279e36 100644 --- a/html-test/src/TypeFamilies3.hs +++ b/html-test/src/TypeFamilies3.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} {-# LANGUAGE TypeFamilies #-} module TypeFamilies3 where diff --git a/html-test/src/TypeOperators.hs b/html-test/src/TypeOperators.hs index e69e89cb..e82d065d 100644 --- a/html-test/src/TypeOperators.hs +++ b/html-test/src/TypeOperators.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} {-# LANGUAGE TypeOperators, GADTs, MultiParamTypeClasses, FlexibleContexts #-} module TypeOperators where diff --git a/html-test/src/UnboxedStuff.hs b/html-test/src/UnboxedStuff.hs index bd1b1302..dfeb7429 100644 --- a/html-test/src/UnboxedStuff.hs +++ b/html-test/src/UnboxedStuff.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} {-# LANGUAGE UnboxedSums, UnboxedTuples #-} module UnboxedStuff where diff --git a/html-test/src/Unicode.hs b/html-test/src/Unicode.hs index d5bbf445..ecd195cf 100644 --- a/html-test/src/Unicode.hs +++ b/html-test/src/Unicode.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} module Unicode where -- | γλώσσα diff --git a/html-test/src/Unicode2.hs b/html-test/src/Unicode2.hs index ca6b18ba..19925a4f 100644 --- a/html-test/src/Unicode2.hs +++ b/html-test/src/Unicode2.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} module Unicode2 where -- | All of the following work with a unicode character ü: diff --git a/html-test/src/Visible.hs b/html-test/src/Visible.hs index cad71931..9440aeef 100644 --- a/html-test/src/Visible.hs +++ b/html-test/src/Visible.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} module Visible where visible :: Int -> Int visible a = a diff --git a/hypsrc-test/ref/src/Bug1091.html b/hypsrc-test/ref/src/Bug1091.html index a9c7d163..3aad9cc8 100644 --- a/hypsrc-test/ref/src/Bug1091.html +++ b/hypsrc-test/ref/src/Bug1091.html @@ -7,12 +7,19 @@ >
{-# LANGUAGE CPP #-}{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE CPP #-}
+module
{-# LANGUAGE CPP #-}{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE CPP #-}
+module
 
 
 
 
 -- " single quotes are fine in line comments
 -- {- unclosed block comments are fine in line comments
 
 -- Multiline CPP is also fine
 
 
 
{-# LANGUAGE Haskell2010 #-}
+module 
 
 
 class
     
     
 
 instance
     
     
 
 instance
 
 
 class
     
     
 
     
     
 
 instance
     
 
 instance
 
 
 class
     
 
 instance
     
     
     
     
 
{-# LANGUAGE Haskell2010 #-}
+module 
 
 
 data
     
     
     
 
 newtype
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
     
   
     
     
 
{-# LANGUAGE Haskell2010 #-}
+module 
 
 
 
 
 
 
 
 
 
 
 
 
     
     
     
     
 
 
 
 
     
     
     
   
     
     
     
 
-- Tests that the identifers/operators are properly linked even when:{-# LANGUAGE Haskell2010 #-}
 ---- Tests that the identifers/operators are properly linked even when:
 --   * backquoted, parenthesized, vanilla--
 --   * qualified, not-qualified--   * backquoted, parenthesized, vanilla
 ----   * qualified, not-qualified
 --
+module
 
 
 
 
 
 
 
 
 
{-# LANGUAGE Haskell2010 #-}
+module 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
{-# LANGUAGE Haskell2010 #-}
+module 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
{-# LANGUAGE RankNTypes #-}{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE ScopedTypeVariables #-}{-# LANGUAGE RankNTypes #-}
 {-# LANGUAGE ScopedTypeVariables #-}
 
+module
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
     
   
     
 
{-# LANGUAGE Haskell2010 #-}
+module 
 
 {-# LINE 8 "hypsrc-test/src/PositionPragmas.hs" #-}
{-# LANGUAGE Haskell2010 #-}
+module 
 
 import
 import
 
 -- | Quoter for constructing multiline string literals
 
 
   
   
   
   
   
   
     
     
 
{-# LANGUAGE NamedFieldPuns #-}{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE RecordWildCards #-}{-# LANGUAGE NamedFieldPuns #-}
 {-# LANGUAGE RecordWildCards #-}
 
+module
 
 
 data
     
     
     
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
     
   
     
     
 
{-# LANGUAGE TemplateHaskell #-}{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE TemplateHaskell #-}
 
+module
 
 import
 
 
 
     
     
   
 
 
 
     
     
     
     
     
   
 
 
 
     
   
 
 
 
     
   
 
 
 
 
     
   
 
 
 
 
{-# LANGUAGE TemplateHaskell #-}{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE TemplateHaskell #-}
+module
 
 import
 
 $
 
 
 
{-# LANGUAGE TypeFamilies #-}{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE TypeFamilies #-}
 
+module
 
 
 data
 
 newtype
 
 type
 type
 
 
 data
 
 data
 data
 
 
 type
 
 type
 type
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
{-# LANGUAGE QuasiQuotes #-}{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE QuasiQuotes #-}
+module
 
 import
 
 
 
Date: Mon, 22 Feb 2021 11:53:07 +0100 Subject: Clean-up of Interface and Interface.Create's imports and pragmata --- haddock-api/src/Haddock/Interface.hs | 23 +++++++------ haddock-api/src/Haddock/Interface/Create.hs | 51 +++++++++++++++++------------ 2 files changed, 41 insertions(+), 33 deletions(-) diff --git a/haddock-api/src/Haddock/Interface.hs b/haddock-api/src/Haddock/Interface.hs index 7cc76953..74dbc9c7 100644 --- a/haddock-api/src/Haddock/Interface.hs +++ b/haddock-api/src/Haddock/Interface.hs @@ -51,26 +51,25 @@ import qualified Data.Map as Map import qualified Data.Set as Set import Text.Printf -import GHC.Unit.Module.Env (mkModuleSet, emptyModuleSet, unionModuleSet, ModuleSet) -import GHC.Unit.Module.ModSummary -import GHC.Unit.Module.Graph -import GHC.Unit.Types -import GHC.Data.Graph.Directed -import GHC.Driver.Session hiding (verbosity) import GHC hiding (verbosity) +import GHC.Data.FastString (unpackFS) +import GHC.Data.Graph.Directed import GHC.Driver.Env import GHC.Driver.Monad -import GHC.Data.FastString (unpackFS) -import GHC.Utils.Error +import GHC.Driver.Session hiding (verbosity) +import GHC.HsToCore.Docs +import GHC.Plugins (Outputable, StaticPlugin(..), Plugin(..), PluginWithArgs(..), defaultPlugin, keepRenamedSource) import GHC.Tc.Types (TcM, TcGblEnv(..)) -import GHC.Tc.Utils.Monad (getTopEnv, setGblEnv) import GHC.Tc.Utils.Env (tcLookupGlobal) +import GHC.Tc.Utils.Monad (getTopEnv, setGblEnv) import GHC.Types.Name (nameIsFromExternalPackage, nameOccName) import GHC.Types.Name.Occurrence (isTcOcc) import GHC.Types.Name.Reader (unQualOK, greMangledName, globalRdrEnvElts) -import GHC.HsToCore.Docs -import GHC.Plugins (Outputable, StaticPlugin(..), Plugin(..), PluginWithArgs(..), - defaultPlugin, keepRenamedSource) +import GHC.Unit.Module.Env (mkModuleSet, emptyModuleSet, unionModuleSet, ModuleSet) +import GHC.Unit.Module.Graph +import GHC.Unit.Module.ModSummary +import GHC.Unit.Types +import GHC.Utils.Error #if defined(mingw32_HOST_OS) import System.IO diff --git a/haddock-api/src/Haddock/Interface/Create.hs b/haddock-api/src/Haddock/Interface/Create.hs index c0b9fd46..a921342e 100644 --- a/haddock-api/src/Haddock/Interface/Create.hs +++ b/haddock-api/src/Haddock/Interface/Create.hs @@ -1,8 +1,17 @@ -{-# LANGUAGE StandaloneDeriving, FlexibleInstances, MultiParamTypeClasses, CPP, TupleSections, BangPatterns, LambdaCase, NamedFieldPuns, ScopedTypeVariables, RecordWildCards #-} -{-# LANGUAGE TypeFamilies #-} -{-# LANGUAGE ViewPatterns #-} +{-# LANGUAGE BangPatterns #-} +{-# LANGUAGE CPP #-} {-# LANGUAGE DerivingStrategies #-} +{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} +{-# LANGUAGE LambdaCase #-} +{-# LANGUAGE MultiParamTypeClasses #-} +{-# LANGUAGE NamedFieldPuns #-} +{-# LANGUAGE RecordWildCards #-} +{-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE StandaloneDeriving #-} +{-# LANGUAGE TupleSections #-} +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE ViewPatterns #-} {-# OPTIONS_GHC -Wwarn #-} ----------------------------------------------------------------------------- -- | @@ -38,33 +47,33 @@ import Data.Map (Map) import Data.List (foldl', find) import Data.Maybe import Data.Traversable -import GHC.Stack -import GHC.Tc.Utils.Monad (finalSafeMode) -import GHC.Types.Avail hiding (avail) -import qualified GHC.Types.Avail as Avail -import qualified GHC.Unit.Module as Module -import GHC.Unit.Module.ModSummary -import qualified GHC.Types.SrcLoc as SrcLoc -import GHC.Types.SourceFile -import GHC.Core.Class -import GHC.Core.ConLike (ConLike(..)) +import GHC.Stack import GHC hiding (lookupName) +import GHC.Core.Class +import GHC.Core.ConLike (ConLike (..)) +import GHC.Data.FastString (bytesFS, unpackFS) import GHC.Driver.Ppr +import GHC.HsToCore.Docs hiding (mkMaps) +import GHC.Parser.Annotation (IsUnicodeSyntax (..)) +import GHC.Tc.Types hiding (IfM) +import GHC.Tc.Utils.Monad (finalSafeMode) +import GHC.Types.Avail hiding (avail) +import qualified GHC.Types.Avail as Avail +import GHC.Types.Basic (PromotionFlag (..)) import GHC.Types.Name -import GHC.Types.Name.Set import GHC.Types.Name.Env -import GHC.Unit.State import GHC.Types.Name.Reader -import GHC.Tc.Types hiding (IfM) -import GHC.Data.FastString ( unpackFS, bytesFS ) -import GHC.Types.Basic ( PromotionFlag(..) ) +import GHC.Types.Name.Set +import GHC.Types.SourceFile import GHC.Types.SourceText +import qualified GHC.Types.SrcLoc as SrcLoc +import qualified GHC.Unit.Module as Module +import GHC.Unit.Module.ModSummary +import GHC.Unit.Module.Warnings +import GHC.Unit.State import qualified GHC.Utils.Outputable as O import GHC.Utils.Panic -import GHC.HsToCore.Docs hiding (mkMaps) -import GHC.Parser.Annotation (IsUnicodeSyntax(..)) -import GHC.Unit.Module.Warnings newtype IfEnv m = IfEnv { -- cgit v1.2.3 From f2bd833fdc6f49bb33ab9df12e18e194453bff03 Mon Sep 17 00:00:00 2001 From: Hécate Moonlight Date: Mon, 22 Feb 2021 18:41:08 +0100 Subject: Explicit imports for Haddock.Interface and Haddock.Interface.Create --- haddock-api/src/Haddock/Interface.hs | 48 ++++++++++++++-------------- haddock-api/src/Haddock/Interface/Create.hs | 49 +++++++++++++++-------------- 2 files changed, 50 insertions(+), 47 deletions(-) diff --git a/haddock-api/src/Haddock/Interface.hs b/haddock-api/src/Haddock/Interface.hs index 74dbc9c7..fd44e58b 100644 --- a/haddock-api/src/Haddock/Interface.hs +++ b/haddock-api/src/Haddock/Interface.hs @@ -34,42 +34,44 @@ module Haddock.Interface ( ) where -import Haddock.GhcUtils -import Haddock.InterfaceFile -import Haddock.Interface.Create -import Haddock.Interface.AttachInstances -import Haddock.Interface.Rename +import Haddock.GhcUtils (moduleString, pretty) +import Haddock.Interface.AttachInstances (attachInstances) +import Haddock.Interface.Create (createInterface1, runIfM) +import Haddock.Interface.Rename (renameInterface) +import Haddock.InterfaceFile (InterfaceFile, ifInstalledIfaces, ifLinkEnv) import Haddock.Options hiding (verbosity) -import Haddock.Types -import Haddock.Utils - -import Control.Monad -import Control.Monad.IO.Class ( MonadIO ) -import Data.IORef +import Haddock.Types (DocOption (..), Documentation (..), ExportItem (..), IfaceMap, InstIfaceMap, Interface, LinkEnv, + expItemDecl, expItemMbDoc, ifaceDoc, ifaceExportItems, ifaceExports, ifaceHaddockCoverage, + ifaceInstances, ifaceMod, ifaceOptions, ifaceVisibleExports, instMod, runWriter, throwE) +import Haddock.Utils (Verbosity (..), normal, out, verbose) + +import Control.Monad (unless, when) +import Control.Monad.IO.Class (MonadIO, liftIO) +import Data.IORef (atomicModifyIORef', newIORef, readIORef) import Data.List (foldl', isPrefixOf, nub) +import Text.Printf (printf) import qualified Data.Map as Map import qualified Data.Set as Set -import Text.Printf import GHC hiding (verbosity) import GHC.Data.FastString (unpackFS) -import GHC.Data.Graph.Directed -import GHC.Driver.Env -import GHC.Driver.Monad +import GHC.Data.Graph.Directed (flattenSCCs) +import GHC.Driver.Env (hsc_dflags, hsc_home_unit, hsc_logger, hsc_static_plugins, hsc_units) +import GHC.Driver.Monad (modifySession, withTimingM) import GHC.Driver.Session hiding (verbosity) import GHC.HsToCore.Docs -import GHC.Plugins (Outputable, StaticPlugin(..), Plugin(..), PluginWithArgs(..), defaultPlugin, keepRenamedSource) -import GHC.Tc.Types (TcM, TcGblEnv(..)) +import GHC.Plugins (Outputable, Plugin (..), PluginWithArgs (..), StaticPlugin (..), defaultPlugin, keepRenamedSource) +import GHC.Tc.Types (TcGblEnv (..), TcM) import GHC.Tc.Utils.Env (tcLookupGlobal) import GHC.Tc.Utils.Monad (getTopEnv, setGblEnv) import GHC.Types.Name (nameIsFromExternalPackage, nameOccName) import GHC.Types.Name.Occurrence (isTcOcc) -import GHC.Types.Name.Reader (unQualOK, greMangledName, globalRdrEnvElts) -import GHC.Unit.Module.Env (mkModuleSet, emptyModuleSet, unionModuleSet, ModuleSet) -import GHC.Unit.Module.Graph -import GHC.Unit.Module.ModSummary -import GHC.Unit.Types -import GHC.Utils.Error +import GHC.Types.Name.Reader (globalRdrEnvElts, greMangledName, unQualOK) +import GHC.Unit.Module.Env (ModuleSet, emptyModuleSet, mkModuleSet, unionModuleSet) +import GHC.Unit.Module.Graph (ModuleGraphNode (..)) +import GHC.Unit.Module.ModSummary (emsModSummary, isBootSummary) +import GHC.Unit.Types (IsBootInterface (..)) +import GHC.Utils.Error (withTiming) #if defined(mingw32_HOST_OS) import System.IO diff --git a/haddock-api/src/Haddock/Interface/Create.hs b/haddock-api/src/Haddock/Interface/Create.hs index a921342e..b039e095 100644 --- a/haddock-api/src/Haddock/Interface/Create.hs +++ b/haddock-api/src/Haddock/Interface/Create.hs @@ -32,48 +32,49 @@ module Haddock.Interface.Create (IfM, runIfM, createInterface1) where import Documentation.Haddock.Doc (metaDocAppend) +import Haddock.Convert (PrintRuntimeReps (..), tyThingToLHsDecl) +import Haddock.GhcUtils (addClassContext, filterSigNames, lHsQTyVarsToTypes, mkEmptySigType, moduleString, parents, + pretty, restrictTo, sigName, unL) +import Haddock.Interface.LexParseRn (processDocString, processDocStringParas, processDocStrings, processModuleHeader) +import Haddock.Options (Flag (..), modulePackageInfo) import Haddock.Types hiding (liftErrMsg) -import Haddock.Options -import Haddock.GhcUtils -import Haddock.Utils -import Haddock.Convert -import Haddock.Interface.LexParseRn +import Haddock.Utils (replace) -import Control.Monad.Reader +import Control.Monad.Reader (MonadReader (..), ReaderT, asks, runReaderT) import Control.Monad.Writer.Strict hiding (tell) -import Data.Bitraversable -import qualified Data.Map as M +import Data.Bitraversable (bitraverse) +import Data.List (find, foldl') import Data.Map (Map) -import Data.List (foldl', find) -import Data.Maybe -import Data.Traversable +import qualified Data.Map as M +import Data.Maybe (catMaybes, fromJust, isJust, mapMaybe, maybeToList) +import Data.Traversable (for) -import GHC.Stack import GHC hiding (lookupName) -import GHC.Core.Class +import GHC.Core.Class (ClassMinimalDef, classMinimalDef) import GHC.Core.ConLike (ConLike (..)) import GHC.Data.FastString (bytesFS, unpackFS) -import GHC.Driver.Ppr +import GHC.Driver.Ppr (showSDoc) import GHC.HsToCore.Docs hiding (mkMaps) import GHC.Parser.Annotation (IsUnicodeSyntax (..)) +import GHC.Stack (HasCallStack) import GHC.Tc.Types hiding (IfM) import GHC.Tc.Utils.Monad (finalSafeMode) import GHC.Types.Avail hiding (avail) import qualified GHC.Types.Avail as Avail import GHC.Types.Basic (PromotionFlag (..)) -import GHC.Types.Name -import GHC.Types.Name.Env -import GHC.Types.Name.Reader -import GHC.Types.Name.Set -import GHC.Types.SourceFile -import GHC.Types.SourceText +import GHC.Types.Name (getOccString, getSrcSpan, isDataConName, isValName, nameIsLocalOrFrom, nameOccName) +import GHC.Types.Name.Env (lookupNameEnv) +import GHC.Types.Name.Reader (GlobalRdrEnv, greMangledName, lookupGlobalRdrEnv) +import GHC.Types.Name.Set (elemNameSet, mkNameSet) +import GHC.Types.SourceFile (HscSource (..)) +import GHC.Types.SourceText (SourceText (..), sl_fs) import qualified GHC.Types.SrcLoc as SrcLoc import qualified GHC.Unit.Module as Module -import GHC.Unit.Module.ModSummary -import GHC.Unit.Module.Warnings -import GHC.Unit.State +import GHC.Unit.Module.ModSummary (msHsFilePath) +import GHC.Unit.Module.Warnings (WarningTxt (..), Warnings (..)) +import GHC.Unit.State (PackageName (..), UnitState, lookupModuleInAllUnits) import qualified GHC.Utils.Outputable as O -import GHC.Utils.Panic +import GHC.Utils.Panic (pprPanic) newtype IfEnv m = IfEnv { -- cgit v1.2.3 From 5a6b3811fe50d0b257e4baa183c9f4ad8e701081 Mon Sep 17 00:00:00 2001 From: Hécate Moonlight Date: Tue, 23 Feb 2021 12:36:12 +0100 Subject: Fix the call-site of guessTarget in Interface.hs Explicit the imports from GHC.HsToCore.Docs --- haddock-api/src/Haddock/Interface.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/haddock-api/src/Haddock/Interface.hs b/haddock-api/src/Haddock/Interface.hs index fd44e58b..b42ae1a3 100644 --- a/haddock-api/src/Haddock/Interface.hs +++ b/haddock-api/src/Haddock/Interface.hs @@ -59,7 +59,7 @@ import GHC.Data.Graph.Directed (flattenSCCs) import GHC.Driver.Env (hsc_dflags, hsc_home_unit, hsc_logger, hsc_static_plugins, hsc_units) import GHC.Driver.Monad (modifySession, withTimingM) import GHC.Driver.Session hiding (verbosity) -import GHC.HsToCore.Docs +import GHC.HsToCore.Docs (getMainDeclBinder) import GHC.Plugins (Outputable, Plugin (..), PluginWithArgs (..), StaticPlugin (..), defaultPlugin, keepRenamedSource) import GHC.Tc.Types (TcGblEnv (..), TcM) import GHC.Tc.Utils.Env (tcLookupGlobal) @@ -158,7 +158,7 @@ createIfaces verbosity modules flags instIfaceMap = do -- alive to be able to find all the instances. modifySession installHaddockPlugin - targets <- mapM (\filePath -> guessTarget filePath Nothing Nothing) modules + targets <- mapM (\filePath -> guessTarget filePath Nothing) modules setTargets targets loadOk <- withTimingM "load" (const ()) $ -- cgit v1.2.3 From b09c80a39e1167c0b48c1a5355f52ecb524e813b Mon Sep 17 00:00:00 2001 From: Sylvain Henry Date: Wed, 24 Feb 2021 11:08:20 +0100 Subject: Fix haddockHypsrcTest output in ghc-head --- hypsrc-test/ref/src/Classes.html | 20 ++++++++++---------- hypsrc-test/ref/src/Records.html | 16 ++++++++-------- 2 files changed, 18 insertions(+), 18 deletions(-) diff --git a/hypsrc-test/ref/src/Classes.html b/hypsrc-test/ref/src/Classes.html index 0acd106d..688b6db6 100644 --- a/hypsrc-test/ref/src/Classes.html +++ b/hypsrc-test/ref/src/Classes.html @@ -194,7 +194,7 @@ >bar :: Int -> Int barbaz :: Int -> (Int, Int) baz bar :: [a] -> Int bar baz :: Int -> ([a], [a]) baznorf :: [Int] -> Int norf quux :: ([a], [a]) -> [a] quuxplugh :: forall a b. Either a a -> Either b b -> Either (a -> b) (b -> a) plughInt -x :: Point -> Int x :: Int +x :: Point -> Int xInt -y :: Point -> Int y :: Int +y :: Point -> Int yInt -x :: Point -> Int -y :: Point -> Int -x :: Int y :: Int +x :: Int +y :: Point -> Int +x :: Point -> Int ..