[Haskell-cafe] Help using catch in 6.10
Martijn van Steenbergen
martijn at van.steenbergen.nl
Fri Feb 20 19:18:35 EST 2009
Hi Victor,
You now need to specify the exact type of the exception you wish to
catch. For example, to catch any exception:
action `catch` (\(e :: SomeException) -> handler)
For more information, see:
http://www.haskell.org/~simonmar/papers/ext-exceptions.pdf
HTH,
Martijn.
Victor Nazarov wrote:
> Hello, cafe.
>
> I whant to switch to GHC 6.10
>
> My application compiled fine with 6.8.3, but after switchin to 6.10,
> I've got errors about usage of catch function:
>
> Main.hs:165:14:
> Ambiguous type variable `e2' in the constraint:
> `Exception e2' arising from a use of `catch' at Main.hs:165:14-38
> Probable fix: add a type signature that fixes these type variable(s)
>
> Main.hs:261:17:
> Ambiguous type variable `e' in the constraint:
> `Exception e' arising from a use of `handle' at Main.hs:261:17-118
> Probable fix: add a type signature that fixes these type variable(s)
>
> Relevant places in code are:
>
> ...
> getNSteps f =
> do text <- get entryNSteps entryText
> catch (readIO text >>= f) $ \_e ->
> do msgBox (Just window) [] MessageWarning ButtonsOk $
> "Число шагов указано неверно: " ++ show text
> return ()
> ...
> loadData :: IO ([Term], Map.Map String Term)
> loadData =
> do examples <- handle (\_e -> msgBox Nothing [] MessageWarning
> ButtonsOk "Ошибка чтения файла примеров" >> return []) $
> do examplesLines <- fmap lines $ readFile "examples.txt"
> let parsings :: [Term]
> parsings = concatMap (fromEither . parse) examplesLines
> parse :: String -> Either ParseError Term
> parse = Parsec.parse (Lambda.parser >>= \t -> skipMany
> space >> eof >> return t) ""
> fromEither :: Either ParseError Term -> [Term]
> fromEither = either (const []) (\t -> [t])
> return parsings
> ...
>
>
More information about the Haskell-Cafe
mailing list