Hi all,

What's the recommended way to get hint[0] to play nice with type synonyms[1]?

A problem occurs with in scope type synonyms involving types not in scope.

I came up with this after looking at the source[2], but it makes me feel ill:

--8<--
-- hint and type synonyms don't play nice
module Main where

import Language.Haskell.Interpreter

import Data.Typeable as T
import Data.Typeable.Internal
import GHC.Fingerprint.Type

main = failure >> success

test t = (print =<<) . runInterpreter $ do
  setImports [ "Prelude" ]
  interpret "1/5" t

failure = test (as :: Rational)
-- Left (WontCompile [GhcError {errMsg = "Not in scope: type constructor or class `Ratio'"}])

success = test (as :: Q)
-- Right (1 % 5)

newtype Q = Q Rational

instance Show Q where
  show (Q a) = show a
  showsPrec n (Q a) = showsPrec n a

instance Typeable Q where
  typeOf _ = TypeRep (Fingerprint 0 0) (T.mkTyCon "Rational") []
--8<--

Thanks,


Claude

[0] http://hackage.haskell.org/package/hint
[1] http://www.haskell.org/onlinereport/decls.html#type-synonym-decls
[2] http://hackage.haskell.org/packages/archive/hint/0.3.3.4/doc/html/src/Hint-Eval.html#interpret

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to