Hello community,

here is the log from the commit of package ghc-hint for openSUSE:Factory 
checked in at 2017-08-31 20:56:15
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
Comparing /work/SRC/openSUSE:Factory/ghc-hint (Old)
 and      /work/SRC/openSUSE:Factory/.ghc-hint.new (New)
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++

Package is "ghc-hint"

Thu Aug 31 20:56:15 2017 rev:2 rq:513380 version:0.7.0

Changes:
--------
--- /work/SRC/openSUSE:Factory/ghc-hint/ghc-hint.changes        2017-05-16 
14:38:47.764738601 +0200
+++ /work/SRC/openSUSE:Factory/.ghc-hint.new/ghc-hint.changes   2017-08-31 
20:56:16.816961054 +0200
@@ -1,0 +2,5 @@
+Thu Jul 27 14:06:03 UTC 2017 - [email protected]
+
+- Update to version 0.7.0.
+
+-------------------------------------------------------------------

Old:
----
  hint-0.6.0.tar.gz

New:
----
  hint-0.7.0.tar.gz

++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++

Other differences:
------------------
++++++ ghc-hint.spec ++++++
--- /var/tmp/diff_new_pack.zDgNuP/_old  2017-08-31 20:56:17.708835743 +0200
+++ /var/tmp/diff_new_pack.zDgNuP/_new  2017-08-31 20:56:17.712835181 +0200
@@ -19,7 +19,7 @@
 %global pkg_name hint
 %bcond_with tests
 Name:           ghc-%{pkg_name}
-Version:        0.6.0
+Version:        0.7.0
 Release:        0
 Summary:        Runtime Haskell interpreter (GHC API wrapper)
 License:        BSD-3-Clause

++++++ hint-0.6.0.tar.gz -> hint-0.7.0.tar.gz ++++++
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/hint-0.6.0/CHANGELOG.md new/hint-0.7.0/CHANGELOG.md
--- old/hint-0.6.0/CHANGELOG.md 2016-06-05 15:15:50.000000000 +0200
+++ new/hint-0.7.0/CHANGELOG.md 2017-06-13 11:27:30.000000000 +0200
@@ -1,3 +1,10 @@
+### 0.7.0
+
+* Support for GHC 8.2
+* Support use in a dynamically-linked executable
+* Add `normalizeType`, like ghci's :kind!
+* Drop support for GHC 7.6
+
 ### 0.6.0
 
 * Support for GHC 8.0
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/hint-0.6.0/hint.cabal new/hint-0.7.0/hint.cabal
--- old/hint-0.6.0/hint.cabal   2016-06-05 15:15:50.000000000 +0200
+++ new/hint-0.7.0/hint.cabal   2017-06-13 11:27:30.000000000 +0200
@@ -1,5 +1,5 @@
 name:         hint
-version:      0.6.0
+version:      0.7.0
 description:
         This library defines an Interpreter monad. It allows to load Haskell
         modules, browse them, type-check and evaluate strings with Haskell
@@ -30,7 +30,7 @@
   type:     git
   location: https://github.com/mvdan/hint
 
-Test-Suite unit-tests
+test-suite unit-tests
   type:           exitcode-stdio-1.0
   hs-source-dirs: unit-tests
   main-is:        run-unit-tests.hs
@@ -43,9 +43,9 @@
                   extensible-exceptions,
                   exceptions
 
-Library
+library
   build-depends: base == 4.*,
-                 ghc >= 7.6 && < 8.2,
+                 ghc >= 7.6 && < 8.4,
                  ghc-paths,
                  mtl,
                  filepath,
@@ -63,7 +63,6 @@
   other-modules:   Hint.GHC
                    Hint.Base
                    Hint.InterpreterT
-                   Hint.Compat
                    Hint.CompatPlatform
                    Hint.Configuration
                    Hint.Extension
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/hint-0.6.0/src/Control/Monad/Ghc.hs 
new/hint-0.7.0/src/Control/Monad/Ghc.hs
--- old/hint-0.6.0/src/Control/Monad/Ghc.hs     2016-06-05 15:15:50.000000000 
+0200
+++ new/hint-0.7.0/src/Control/Monad/Ghc.hs     2017-06-13 11:27:30.000000000 
+0200
@@ -38,12 +38,6 @@
 instance MTL.MonadIO m => MTL.MonadIO (GhcT m) where
     liftIO = GhcT . GHC.liftIO
 
-#if __GLASGOW_HASKELL__ < 708
-  -- ghc started using transformers at some point
-instance MTL.MonadIO m => GHC.MonadIO (GhcT m) where
-    liftIO = MTL.liftIO
-#endif
-
 instance MonadCatch m => MonadThrow (GhcT m) where
     throwM = lift . throwM
 
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/hint-0.6.0/src/Hint/Base.hs 
new/hint-0.7.0/src/Hint/Base.hs
--- old/hint-0.6.0/src/Hint/Base.hs     2016-06-05 15:15:50.000000000 +0200
+++ new/hint-0.7.0/src/Hint/Base.hs     2017-06-13 11:27:30.000000000 +0200
@@ -34,10 +34,10 @@
 
 -- | Version of the underlying ghc api. Values are:
 --
--- * @708@ for GHC 7.8.x
---
 -- * @710@ for GHC 7.10.x
 --
+-- * @800@ for GHC 8.0.x
+--
 -- * etc...
 ghcVersion :: Int
 ghcVersion = __GLASGOW_HASKELL__
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/hint-0.6.0/src/Hint/Compat.hs 
new/hint-0.7.0/src/Hint/Compat.hs
--- old/hint-0.6.0/src/Hint/Compat.hs   2016-06-05 15:15:50.000000000 +0200
+++ new/hint-0.7.0/src/Hint/Compat.hs   1970-01-01 01:00:00.000000000 +0100
@@ -1,34 +0,0 @@
-module Hint.Compat where
-
-import qualified Hint.GHC as GHC
-
--- Kinds became a synonym for Type in GHC 6.8. We define this wrapper
--- to be able to define a FromGhcRep instance for both versions
-newtype Kind = Kind GHC.Kind
-
-supportedExtensions :: [String]
-supportedExtensions = map f GHC.xFlags
-    where
-#if (__GLASGOW_HASKELL__ >= 710)
-      f = GHC.flagSpecName
-#else
-      f (e,_,_) = e
-#endif
-
-configureDynFlags :: GHC.DynFlags -> GHC.DynFlags
-configureDynFlags dflags = dflags{GHC.ghcMode    = GHC.CompManager,
-                                  GHC.hscTarget  = GHC.HscInterpreted,
-                                  GHC.ghcLink    = GHC.LinkInMemory,
-                                  GHC.verbosity  = 0}
-
-parseDynamicFlags :: GHC.GhcMonad m
-                  => GHC.DynFlags -> [String] -> m (GHC.DynFlags, [String])
-parseDynamicFlags d = fmap firstTwo . GHC.parseDynamicFlags d . map GHC.noLoc
-    where firstTwo (a,b,_) = (a, map GHC.unLoc b)
-
-pprType :: GHC.Type -> GHC.SDoc
-#if __GLASGOW_HASKELL__ < 708
-pprType = GHC.pprTypeForUser False -- False means drop explicit foralls
-#else
-pprType = GHC.pprTypeForUser
-#endif
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/hint-0.6.0/src/Hint/Configuration.hs 
new/hint-0.7.0/src/Hint/Configuration.hs
--- old/hint-0.6.0/src/Hint/Configuration.hs    2016-06-05 15:15:50.000000000 
+0200
+++ new/hint-0.7.0/src/Hint/Configuration.hs    2017-06-13 11:27:30.000000000 
+0200
@@ -8,7 +8,10 @@
       languageExtensions, availableExtensions, Extension(..),
       installedModulesInScope,
 
-      searchPath
+      searchPath,
+
+      configureDynFlags, parseDynamicFlags,
+
 ) where
 
 import Control.Monad
@@ -17,7 +20,6 @@
 import Data.List (intercalate)
 
 import qualified Hint.GHC as GHC
-import qualified Hint.Compat as Compat
 import Hint.Base
 import Hint.Util (quote)
 
@@ -26,7 +28,7 @@
 setGhcOptions :: MonadInterpreter m => [String] -> m ()
 setGhcOptions opts =
     do old_flags <- runGhc GHC.getSessionDynFlags
-       (new_flags,not_parsed) <- runGhc2 Compat.parseDynamicFlags old_flags 
opts
+       (new_flags,not_parsed) <- runGhc2 parseDynamicFlags old_flags opts
        unless (null not_parsed) $
             throwM $ UnknownError
                             $ concat ["flags: ", unwords $ map quote 
not_parsed,
@@ -127,3 +129,16 @@
        => (InterpreterConfiguration -> InterpreterConfiguration)
        -> m ()
 onConf f = onState $ \st -> st{configuration = f (configuration st)}
+
+configureDynFlags :: GHC.DynFlags -> GHC.DynFlags
+configureDynFlags dflags =
+    (if GHC.dynamicGhc then GHC.addWay' GHC.WayDyn else id)
+                           dflags{GHC.ghcMode    = GHC.CompManager,
+                                  GHC.hscTarget  = GHC.HscInterpreted,
+                                  GHC.ghcLink    = GHC.LinkInMemory,
+                                  GHC.verbosity  = 0}
+
+parseDynamicFlags :: GHC.GhcMonad m
+                  => GHC.DynFlags -> [String] -> m (GHC.DynFlags, [String])
+parseDynamicFlags d = fmap firstTwo . GHC.parseDynamicFlags d . map GHC.noLoc
+    where firstTwo (a,b,_) = (a, map GHC.unLoc b)
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/hint-0.6.0/src/Hint/Conversions.hs 
new/hint-0.7.0/src/Hint/Conversions.hs
--- old/hint-0.6.0/src/Hint/Conversions.hs      2016-06-05 15:15:50.000000000 
+0200
+++ new/hint-0.7.0/src/Hint/Conversions.hs      2017-06-13 11:27:30.000000000 
+0200
@@ -5,7 +5,6 @@
 import qualified Hint.GHC as GHC
 
 import Hint.Base
-import qualified Hint.Compat as Compat
 
 -- --------- Types / Kinds -----------------------
 
@@ -15,12 +14,12 @@
       -- (i.e., do not expose internals)
       unqual <- runGhc GHC.getPrintUnqual
       withDynFlags $ \df ->
-        return $ GHC.showSDocForUser df unqual (Compat.pprType t)
+        return $ GHC.showSDocForUser df unqual (GHC.pprTypeForUser t)
 
-kindToString :: MonadInterpreter m => Compat.Kind -> m String
-kindToString (Compat.Kind k)
+kindToString :: MonadInterpreter m => GHC.Kind -> m String
+kindToString k
  = withDynFlags $ \df ->
-     return $ GHC.showSDoc df (Compat.pprType k)
+     return $ GHC.showSDoc df (GHC.pprTypeForUser k)
 
 -- ---------------- Modules --------------------------
 
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/hint-0.6.0/src/Hint/Extension.hs 
new/hint-0.7.0/src/Hint/Extension.hs
--- old/hint-0.6.0/src/Hint/Extension.hs        2016-06-05 15:15:50.000000000 
+0200
+++ new/hint-0.7.0/src/Hint/Extension.hs        2017-06-13 11:27:30.000000000 
+0200
@@ -1,14 +1,23 @@
 -- this module was automatically generated. do not edit!
 -- edit util/mk_extensions_mod.hs instead
 module Hint.Extension (
-    Extension(..), availableExtensions, asExtension
+    Extension(..), supportedExtensions, availableExtensions, asExtension
 ) where
 
-import Hint.Compat as Compat
+import qualified Hint.GHC as GHC
+
+supportedExtensions :: [String]
+supportedExtensions = map f GHC.xFlags
+    where
+#if (__GLASGOW_HASKELL__ >= 710)
+      f = GHC.flagSpecName
+#else
+      f (e,_,_) = e
+#endif
 
 -- | List of the extensions known by the interpreter.
 availableExtensions :: [Extension]
-availableExtensions = map asExtension Compat.supportedExtensions
+availableExtensions = map asExtension supportedExtensions
 
 asExtension :: String -> Extension
 asExtension s = if isKnown s
@@ -139,6 +148,7 @@
                | MonadFailDesugaring
                | TemplateHaskellQuotes
                | OverloadedLabels
+               | TypeFamilyDependencies
                | NoOverlappingInstances
                | NoUndecidableInstances
                | NoIncoherentInstances
@@ -257,6 +267,7 @@
                | NoMonadFailDesugaring
                | NoTemplateHaskellQuotes
                | NoOverloadedLabels
+               | NoTypeFamilyDependencies
                | UnknownExtension String
         deriving (Eq, Show, Read)
 
@@ -379,6 +390,7 @@
                    MonadFailDesugaring,
                    TemplateHaskellQuotes,
                    OverloadedLabels,
+                   TypeFamilyDependencies,
                    NoOverlappingInstances,
                    NoUndecidableInstances,
                    NoIncoherentInstances,
@@ -496,5 +508,6 @@
                    NoUndecidableSuperClasses,
                    NoMonadFailDesugaring,
                    NoTemplateHaskellQuotes,
-                   NoOverloadedLabels
+                   NoOverloadedLabels,
+                   NoTypeFamilyDependencies
                    ]
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/hint-0.6.0/src/Hint/GHC.hs 
new/hint-0.7.0/src/Hint/GHC.hs
--- old/hint-0.6.0/src/Hint/GHC.hs      2016-06-05 15:15:50.000000000 +0200
+++ new/hint-0.7.0/src/Hint/GHC.hs      2017-06-13 11:27:30.000000000 +0200
@@ -25,11 +25,15 @@
 import DynFlags as X (xFlags, xopt, LogAction)
 #endif
 
+#if __GLASGOW_HASKELL__ >= 800
+import DynFlags as X (WarnReason(NoReason))
+#endif
+
 import PprTyThing as X (pprTypeForUser)
 import SrcLoc as X (mkRealSrcLoc)
 
-#if __GLASGOW_HASKELL__ >= 708
 import ConLike as X (ConLike(RealDataCon))
-#endif
+
+import DynFlags as X (addWay', Way(..), dynamicGhc)
 
 type Message = MsgDoc
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/hint-0.6.0/src/Hint/InterpreterT.hs 
new/hint-0.7.0/src/Hint/InterpreterT.hs
--- old/hint-0.6.0/src/Hint/InterpreterT.hs     2016-06-05 15:15:50.000000000 
+0200
+++ new/hint-0.7.0/src/Hint/InterpreterT.hs     2017-06-13 11:27:30.000000000 
+0200
@@ -25,7 +25,6 @@
 import qualified GHC.Paths
 
 import qualified Hint.GHC as GHC
-import qualified Hint.Compat as Compat
 
 type Interpreter = InterpreterT IO
 
@@ -84,8 +83,8 @@
        -- Set a custom log handler, to intercept error messages :S
        df0 <- runGhc GHC.getSessionDynFlags
 
-       let df1 = Compat.configureDynFlags df0
-       (df2, extra) <- runGhc2 Compat.parseDynamicFlags df1 args
+       let df1 = configureDynFlags df0
+       (df2, extra) <- runGhc2 parseDynamicFlags df1 args
        unless (null extra) $
             throwM $ UnknownError (concat [ "flags: '"
                                           , unwords extra
@@ -103,7 +102,7 @@
        let toOpt e     = let err = error ("init error: unknown ext:" ++ show e)
                          in fromMaybe err (lookup e extMap)
        let getOptVal e = (asExtension e, GHC.xopt (toOpt e) df2)
-       let defExts = map  getOptVal Compat.supportedExtensions
+       let defExts = map  getOptVal supportedExtensions
 
        onState (\s -> s{defaultExts = defExts})
 
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/hint-0.6.0/src/Hint/Parsers.hs 
new/hint-0.7.0/src/Hint/Parsers.hs
--- old/hint-0.6.0/src/Hint/Parsers.hs  2016-06-05 15:15:50.000000000 +0200
+++ new/hint-0.7.0/src/Hint/Parsers.hs  2017-06-13 11:27:30.000000000 +0200
@@ -8,10 +8,6 @@
 
 import qualified Hint.GHC as GHC
 
-#if __GLASGOW_HASKELL__ >= 800
-import qualified DynFlags as GHC
-#endif
-
 data ParseResult = ParseOk | ParseError GHC.SrcSpan GHC.Message
 
 parseExpr :: MonadInterpreter m => String -> m ParseResult
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/hint-0.6.0/src/Hint/Reflection.hs 
new/hint-0.7.0/src/Hint/Reflection.hs
--- old/hint-0.6.0/src/Hint/Reflection.hs       2016-06-05 15:15:50.000000000 
+0200
+++ new/hint-0.7.0/src/Hint/Reflection.hs       2017-06-13 11:27:30.000000000 
+0200
@@ -47,11 +47,7 @@
            (
              [asModElem df c | c@(GHC.ATyCon c') <- xs, GHC.isClassTyCon c'],
              [asModElem df t | t@(GHC.ATyCon c') <- xs, (not . 
GHC.isClassTyCon) c'],
-#if __GLASGOW_HASKELL__ < 708
-             [asModElem df d | [email protected]{} <- xs],
-#else
              [asModElem df d | d@(GHC.AConLike (GHC.RealDataCon{})) <- xs],
-#endif
              [asModElem df f | [email protected]{} <- xs]
            )
           cs' = [Class n $ filter (alsoIn fs) ms  | Class n ms  <- cs]
@@ -60,11 +56,7 @@
 
 asModElem :: GHC.DynFlags -> GHC.TyThing -> ModuleElem
 asModElem df (GHC.AnId f)      = Fun $ getUnqualName df f
-#if __GLASGOW_HASKELL__ < 708
-asModElem df (GHC.ADataCon dc) = Fun $ getUnqualName df dc
-#else
 asModElem df (GHC.AConLike (GHC.RealDataCon dc)) = Fun $ getUnqualName df dc
-#endif
 asModElem df (GHC.ATyCon tc)   =
   if GHC.isClassTyCon tc
   then Class (getUnqualName df tc) (map (getUnqualName df) $ (GHC.classMethods 
. fromJust . GHC.tyConClass_maybe) tc)
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/hint-0.6.0/src/Hint/Typecheck.hs 
new/hint-0.7.0/src/Hint/Typecheck.hs
--- old/hint-0.6.0/src/Hint/Typecheck.hs        2016-06-05 15:15:50.000000000 
+0200
+++ new/hint-0.7.0/src/Hint/Typecheck.hs        2017-06-13 11:27:30.000000000 
+0200
@@ -1,5 +1,5 @@
 module Hint.Typecheck (
-      typeOf, typeChecks, kindOf,
+      typeOf, typeChecks, kindOf, normalizeType
 ) where
 
 import Control.Monad.Catch
@@ -8,7 +8,6 @@
 import Hint.Parsers
 import Hint.Conversions
 
-import qualified Hint.Compat as Compat
 import qualified Hint.GHC as GHC
 
 -- | Returns a string representation of the type of the expression.
@@ -37,17 +36,34 @@
        -- kind of errors
        failOnParseError parseType type_expr
        --
-       kind <- mayFail $ runGhc1 typeKind type_expr
+       (_, kind) <- mayFail $ runGhc1 typeKind type_expr
        --
-       kindToString (Compat.Kind kind)
+       kindToString kind
+
+-- | Returns a string representation of the normalized type expression.
+-- This is what the @:kind!@ GHCi command prints after @=@.
+normalizeType :: MonadInterpreter m => String -> m String
+normalizeType type_expr =
+    do -- First, make sure the expression has no syntax errors,
+       -- for this is the only way we have to "intercept" this
+       -- kind of errors
+       failOnParseError parseType type_expr
+       --
+       (ty, _) <- mayFail $ runGhc1 typeKind type_expr
+       --
+       typeToString ty
 
 -- add a bogus Maybe, in order to use it with mayFail
 exprType :: GHC.GhcMonad m => String -> m (Maybe GHC.Type)
+#if __GLASGOW_HASKELL__ < 802
 exprType = fmap Just . GHC.exprType
+#else
+exprType = fmap Just . GHC.exprType GHC.TM_Inst
+#endif
 
 -- add a bogus Maybe, in order to use it with mayFail
-typeKind :: GHC.GhcMonad m => String -> m (Maybe GHC.Kind)
-typeKind = fmap (Just . snd) . GHC.typeKind True
+typeKind :: GHC.GhcMonad m => String -> m (Maybe (GHC.Type, GHC.Kind))
+typeKind = fmap Just . GHC.typeKind True
 
 onCompilationError :: MonadInterpreter m
                    => ([GhcError] -> m a)
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' 
old/hint-0.6.0/src/Language/Haskell/Interpreter/Unsafe.hs 
new/hint-0.7.0/src/Language/Haskell/Interpreter/Unsafe.hs
--- old/hint-0.6.0/src/Language/Haskell/Interpreter/Unsafe.hs   2016-06-05 
15:15:50.000000000 +0200
+++ new/hint-0.7.0/src/Language/Haskell/Interpreter/Unsafe.hs   2017-06-13 
11:27:30.000000000 +0200
@@ -38,7 +38,7 @@
 --   containers, etc.) can be found. This allows you to run hint on
 --   a machine in which GHC is not installed.
 --
---   A typical libdir value would be "/opt/ghc/7.10.3/lib/ghc-7.10.3".
+--   A typical libdir value could be "/usr/lib/ghc-8.0.1/ghc-8.0.1".
 unsafeRunInterpreterWithArgsLibdir :: (MonadIO m, MonadMask m
 #if __GLASGOW_HASKELL__ < 800
                                  , Functor m
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/hint-0.6.0/src/Language/Haskell/Interpreter.hs 
new/hint-0.7.0/src/Language/Haskell/Interpreter.hs
--- old/hint-0.6.0/src/Language/Haskell/Interpreter.hs  2016-06-05 
15:15:50.000000000 +0200
+++ new/hint-0.7.0/src/Language/Haskell/Interpreter.hs  2017-06-13 
11:27:30.000000000 +0200
@@ -34,7 +34,7 @@
     -- pragmas inline in the code since GHC scarfs them up.
     getModuleAnnotations, getValAnnotations,
     -- ** Type inference
-     typeOf, typeChecks, kindOf,
+     typeOf, typeChecks, kindOf, normalizeType,
     -- ** Evaluation
      interpret, as, infer, eval,
     -- * Error handling
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/hint-0.6.0/unit-tests/run-unit-tests.hs 
new/hint-0.7.0/unit-tests/run-unit-tests.hs
--- old/hint-0.6.0/unit-tests/run-unit-tests.hs 2016-06-05 15:15:50.000000000 
+0200
+++ new/hint-0.7.0/unit-tests/run-unit-tests.hs 2017-06-13 11:27:30.000000000 
+0200
@@ -200,6 +200,19 @@
         _ <- forkIO $ Control.Monad.void concurrent
         readMVar r @?  "concurrent instance did not fail"
 
+test_normalize_type :: TestCase
+test_normalize_type = TestCase "normalize_type" [mod_file] $ do
+        liftIO $ writeFile mod_file mod_text
+        loadModules [mod_file]
+        setTopLevelModules ["T"]
+        normalizeType "Foo Int" @@?= "()"
+
+    where mod_text = unlines ["{-# LANGUAGE TypeFamilies #-}"
+                             ,"module T where"
+                             ,"type family Foo x"
+                             ,"type instance Foo x = ()"]
+          mod_file = "TEST_NormalizeType.hs"
+
 tests :: [TestCase]
 tests = [test_reload_modified
         ,test_lang_exts
@@ -215,6 +228,7 @@
         ,test_search_path_dot
         ,test_catch
         ,test_only_one_instance
+        ,test_normalize_type
         ]
 
 main :: IO ()


Reply via email to