runghc -fdefer-type-errors

Richard Eisenberg eir at cis.upenn.edu
Mon Mar 11 14:27:52 CET 2013


When I ran this code (ghc 7.6.1), I did get the Hello, world! printout. That line was sandwiched between the compile-time warning from the type error and the run-time exception from the type error, but the output was there:

09:24:28 ~/temp> runghc Scratch.hs

Scratch.hs:5:12: Warning:
    No instance for (Num String) arising from the literal `1'
    Possible fix: add an instance declaration for (Num String)
    In the first argument of `putStrLn', namely `1'
    In a stmt of a 'do' block: putStrLn 1
    In the expression:
      do { putStrLn "Hello, world";
           putStrLn 1 }
Hello, world
Scratch.hs: Scratch.hs:5:12:
    No instance for (Num String) arising from the literal `1'
    Possible fix: add an instance declaration for (Num String)
    In the first argument of `putStrLn', namely `1'
    In a stmt of a 'do' block: putStrLn 1
    In the expression:
      do { putStrLn "Hello, world";
           putStrLn 1 }
(deferred type error)


It's easier to see with `runghc Scratch.hs 2> /dev/null` which prints only the Hello, world! Oddly, passing flag "-w" doesn't suppress the warning, so I don't think there's a way to turn it off.

Richard

On Mar 11, 2013, at 3:45 AM, Kazu Yamamoto (山本和彦) <kazu at iij.ad.jp> wrote:

> Hello,
> 
> Doesn't runghc support the -fdefer-type-errors option?
> 
> Consider this code:
> 
> ----
> module Main where
> 
> main :: IO ()
> main = do
>    -- putStrLn は文字列を取る
>    putStrLn "Hello, world!" 
>    putStrLn 1               -- 型エラー
> ----
> 
> If I use runghc with -fdefer-type-errors, "Hello, world!" is not
> printed. Is this a bug?
> 
> If this behavior is intended, I would like to change it. If GHC can
> run code like dynamically typed languages, it would be appealing to
> new Haskell programmers from their community.
> 
> --Kazu
> 
> _______________________________________________
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users at haskell.org
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users




More information about the Glasgow-haskell-users mailing list