On Wed, Dec 21, 2011 at 1:29 PM, Ian Lynagh <ig...@earth.li> wrote: > > We are pleased to announce the first release candidate for GHC 7.4.1: > > http://www.haskell.org/ghc/dist/7.4.1-rc1/ > > This includes the source tarball, installers for OS X and Windows, and > bindists for amd64/Linux, i386/Linux, amd64/FreeBSD and i386/FreeBSD. > > Please test as much as possible; bugs are much cheaper if we find them > before the release! >
Hurrah! The following used to compile with GHC 7.2.1: >>>>> {-# LANGUAGE RankNTypes, TypeFamilies, GADTs #-} import Data.Typeable ( Typeable1, gcast1, typeOf1 ) cast1 :: (Typeable1 f1, Typeable1 f2) => f1 a -> f2 a cast1 val = case gcast1 (Just val) of Just (Just typed_val) -> typed_val `asTypeOf` result Nothing -> error $ "Invalid cast: " ++ tag ++ " -> " ++ show (typeOf1 result) where result = undefined tag = show (typeOf1 val) main = putStrLn "Hello, world!" <<<<< But with GHC 7.4.1 RC 1 I get the error: >>>>> BugDowncast.hs:9:69: Ambiguous type variable `t0' in the constraint: (Typeable1 t0) arising from a use of `typeOf1' Probable fix: add a type signature that fixes these type variable(s) In the first argument of `show', namely `(typeOf1 result)' In the second argument of `(++)', namely `show (typeOf1 result)' In the second argument of `(++)', namely `" -> " ++ show (typeOf1 result)' <<<<< Is this an expected change, or should I create a ticket? Thanks, Antoine > > The release notes are not yet available, but here are some of the > highlights of the 7.4 branch since 7.2 and 7.0: > > * There is a new feature Safe Haskell (-XSafe, -XTrustworthy, -XUnsafe): > > http://www.haskell.org/ghc/dist/stable/docs/html/users_guide/safe-haskell.html > The design has changed since 7.2. > > * There is a new feature kind polymorphism (-XPolyKinds): > > http://www.haskell.org/ghc/dist/stable/docs/html/users_guide/kind-polymorphism-and-promotion.html > A side-effect of this is that, when the extension is not enabled, in > certain circumstances kinds are now defaulted to * rather than being > inferred. > > * There is a new feature constraint kinds (-XConstraintKinds): > > http://www.haskell.org/ghc/dist/stable/docs/html/users_guide/constraint-kind.html > > * It is now possible to give any sort of declaration at the ghci prompt: > > http://www.haskell.org/ghc/dist/stable/docs/html/users_guide/interactive-evaluation.html#ghci-decls > For example, you can now declare datatypes within ghci. > > * The profiling and hpc implementations have been merged and overhauled. > Visible changes include renaming of profiling flags: > > http://www.haskell.org/ghc/dist/stable/docs/html/users_guide/flag-reference.html#id589412 > and the cost-centre stacks have a new semantics, which should in most > cases result in more useful and intuitive profiles. The +RTS -xc flag > now also gives a stack trace. > > * It is now possible to write compiler plugins: > > http://www.haskell.org/ghc/dist/stable/docs/html/users_guide/compiler-plugins.html > > * DPH support has been significantly improved. > > * There is now preliminary support for registerised compilation using > LLVM on the ARM platform. > > > Note: The release candidate accidentally includes the random, primitive, > vector and dph libraries. The final release will not include them. > > > Thanks > Ian, on behalf of the GHC team > > > _______________________________________________ > Glasgow-haskell-users mailing list > Glasgow-haskell-users@haskell.org > http://www.haskell.org/mailman/listinfo/glasgow-haskell-users _______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users