testing for exceptions

Hello, I have made this exercise which can be found at the Craft of Functional Programming book. -- exercise 32 -- Suppose we have to raise 2 to the power n. If n is even, 2*m say, then -- 2n = 22*m = (2m)2 -- If n is odd, 2*m+l say, then -- 2n = 22*m+l = (2n)2*2 -- Give a recursive function to compute 2n which uses these insights. f2 :: Integer -> Integer f2 n | n < 0 = error "This will only run for positive numbers" | n == 0 = 1 | even n = f2 ( n `div` 2) ^ 2 | odd n = (f2 ( n `div` 2) ^ 2) * 2 Now I have to make Hunit tests for it, But is there a way I can test if the error message is shown when a negative number is being used ? Roelof

On Sat, Oct 31, 2015, at 11:16 AM, Roelof Wobben wrote:
[...] But is there a way I can test if the error message is shown when a negative number is being used ?
Something like (untested) ``` import qualified Control.Exception as E isErrorCall :: String -> a -> IO Bool isErrorCall s x = (E.evaluate x >> return False) `E.catch` (\(E.ErrorCall e) -> return $ e == s) myTest = isErrorCall "This will only run for positive numbers" . f2 {-
myTest (-1) = return True myTest 100 = return False -}
HTH,
Joachim

Unfrotunately the answer to this is not simple:
http://stackoverflow.com/questions/4243117/how-to-catch-and-ignore-a-call-to...
'error' more or less terminates the program in an unreasonable way.
It would be preferable for f2 to result in a type that can contain the
error result to be parsed.
Cheers,
Darren
On Oct 31, 2015 21:16, "Roelof Wobben"
Hello,
I have made this exercise which can be found at the Craft of Functional Programming book.
-- exercise 32
-- Suppose we have to raise 2 to the power n. If n is even, 2*m say, then -- 2n = 22*m = (2m)2 -- If n is odd, 2*m+l say, then -- 2n = 22*m+l = (2n)2*2 -- Give a recursive function to compute 2n which uses these insights.
f2 :: Integer -> Integer f2 n | n < 0 = error "This will only run for positive numbers" | n == 0 = 1 | even n = f2 ( n `div` 2) ^ 2 | odd n = (f2 ( n `div` 2) ^ 2) * 2
Now I have to make Hunit tests for it,
But is there a way I can test if the error message is shown when a negative number is being used ?
Roelof
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

Op 31-10-2015 om 11:40 schreef Darren Grant:
Unfrotunately the answer to this is not simple:
http://stackoverflow.com/questions/4243117/how-to-catch-and-ignore-a-call-to...
'error' more or less terminates the program in an unreasonable way.
It would be preferable for f2 to result in a type that can contain the error result to be parsed.
Cheers, Darren
Oke, So I have to change the type of f2. To what do I have to change it to make it testable. Roelof

On Sat, Oct 31, 2015 at 11:46:15AM +0100, Roelof Wobben wrote:
Op 31-10-2015 om 11:40 schreef Darren Grant:
Unfrotunately the answer to this is not simple:
http://stackoverflow.com/questions/4243117/how-to-catch-and-ignore-a-call-to...
'error' more or less terminates the program in an unreasonable way.
It would be preferable for f2 to result in a type that can contain the error result to be parsed.
So I have to change the type of f2.
To what do I have to change it to make it testable.
For example, Integer -> Maybe Integer

I'd expect most Haskellers to recommend something like,
f2 :: Integer -> Either Integer ErrorString
where ErrorString is some specific error value type. (String may suffice
for you.)
This is a safe general solution, but there are many potentially more
specific possibilities that might make your program simpler depending on
how this function relates to the context it will be used in.
Cheers,
Darren
On Oct 31, 2015 21:46, "Roelof Wobben"
Op 31-10-2015 om 11:40 schreef Darren Grant:
Unfrotunately the answer to this is not simple:
http://stackoverflow.com/questions/4243117/how-to-catch-and-ignore-a-call-to...
'error' more or less terminates the program in an unreasonable way.
It would be preferable for f2 to result in a type that can contain the error result to be parsed.
Cheers, Darren
Oke,
So I have to change the type of f2.
To what do I have to change it to make it testable.
Roelof
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

Small nitpick, but I would generally put the "exception" or "error" in the
Left part of an Either and a correct result in the Right part.
This has some advantages.
1 - Right is right as opposed to wrong. Easy to remember mnemonic.
2 - It fits neatly with the Monad (Either e) instance.
Roelof, a nice exercise is to first implement your f2 function with the Integer
-> Maybe Integer type and then with Integer -> Either String Integer.
If you realize that both Monad Maybe and Monad (Either e) you can use
almost the same code.
2015-10-31 12:04 GMT+01:00 Darren Grant
I'd expect most Haskellers to recommend something like,
f2 :: Integer -> Either Integer ErrorString
where ErrorString is some specific error value type. (String may suffice for you.)
This is a safe general solution, but there are many potentially more specific possibilities that might make your program simpler depending on how this function relates to the context it will be used in.
Cheers, Darren On Oct 31, 2015 21:46, "Roelof Wobben"
wrote: Op 31-10-2015 om 11:40 schreef Darren Grant:
Unfrotunately the answer to this is not simple:
http://stackoverflow.com/questions/4243117/how-to-catch-and-ignore-a-call-to...
'error' more or less terminates the program in an unreasonable way.
It would be preferable for f2 to result in a type that can contain the error result to be parsed.
Cheers, Darren
Oke,
So I have to change the type of f2.
To what do I have to change it to make it testable.
Roelof
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

You're very close. Take a look at the even clause: Let (k :: Integer), and
consider how the type of the expression producing the error,
Just (f2Maybe k)
differs from the type of the expression,
(f2Maybe k)
Cheers,
Darren
On Sat, Oct 31, 2015 at 11:27 PM, Roelof Wobben
Op 31-10-2015 om 12:10 schreef Roel van Dijk:
Small nitpick, but I would generally put the "exception" or "error" in the Left part of an Either and a correct result in the Right part.
This has some advantages. 1 - Right is right as opposed to wrong. Easy to remember mnemonic. 2 - It fits neatly with the Monad (Either e) instance.
Roelof, a nice exercise is to first implement your f2 function with the Integer -> Maybe Integer type and then with Integer -> Either String Integer. If you realize that both Monad Maybe and Monad (Either e) you can use almost the same code.
2015-10-31 12:04 GMT+01:00 Darren Grant
: I'd expect most Haskellers to recommend something like,
f2 :: Integer -> Either Integer ErrorString
where ErrorString is some specific error value type. (String may suffice for you.)
This is a safe general solution, but there are many potentially more specific possibilities that might make your program simpler depending on how this function relates to the context it will be used in.
Cheers, Darren On Oct 31, 2015 21:46, "Roelof Wobben"
wrote: Op 31-10-2015 om 11:40 schreef Darren Grant:
Unfrotunately the answer to this is not simple:
http://stackoverflow.com/questions/4243117/how-to-catch-and-ignore-a-call-to...
'error' more or less terminates the program in an unreasonable way.
It would be preferable for f2 to result in a type that can contain the error result to be parsed.
Cheers, Darren
Here my try for the Maybe
f2Maybe :: Integer -> Maybe Integer f2Maybe n | n > 0 = Nothing | n == 0 = Just 1 | even n = Just (f2Maybe ( n `div` 2) ^ 2) | odd n = Just ((f2Maybe ( n `div` 2) ^ 2) * 2)
But it will not compile , the clauses for even and odd do not work.
Both maybe and either are not explained in the first 4 chapter of the Craft book.
Roelof
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

Op 31-10-2015 om 13:44 schreef Darren Grant:
You're very close. Take a look at the even clause: Let (k :: Integer), and consider how the type of the expression producing the error,
Just (f2Maybe k)
differs from the type of the expression,
(f2Maybe k)
Cheers, Darren
Just (f2Maybe k) is type Maybe (Maybe Integer) f2Maybe k is type Maybe Integer But when I change the code to this : f2Maybe :: Integer -> Maybe Integer f2Maybe n | n > 0 = Nothing | n == 0 = Just 1 | even n = f2Maybe ( n `div` 2) ^ 2 | odd n = (f2Maybe ( n `div` 2) ^ 2) * 2 Then I see this error message : No instance for (Num (Maybe Integer)) arising from a use of ‘^’ In the expression: f2Maybe (n `div` 2) ^ 2 In an equation for ‘f2Maybe’: f2Maybe n | n > 0 = Nothing | n == 0 = Just 1 | even n = f2Maybe (n `div` 2) ^ 2 | odd n = (f2Maybe (n `div` 2) ^ 2) * 2 Failed, modules loaded: none. No instance for (Num (Maybe Integer)) arising from a use of ‘^’ In the expression: f2Maybe (n `div` 2) ^ 2 In an equation for ‘f2Maybe’: f2Maybe n | n > 0 = Nothing | n == 0 = Just 1 | even n = f2Maybe (n `div` 2) ^ 2 | odd n = (f2Maybe (n `div` 2) ^ 2) * 2 Failed, modules loaded: none. No instance for (Num (Maybe Integer)) arising from a use of ‘^’ In the expression: f2Maybe (n `div` 2) ^ 2 In an equation for ‘f2Maybe’: f2Maybe n | n > 0 = Nothing | n == 0 = Just 1 | even n = f2Maybe (n `div` 2) ^ 2 | odd n = (f2Maybe (n `div` 2) ^ 2) * 2 Failed, modules loaded: none.

You are even closer now! What the type checker is trying to tell you is that it doesn't know how to raise Maybe Integer to some power. You apply the ^ operator to two values, f2Maybe (n `div` 2) and 2. Let us give them names: let a = f2Maybe (n `div` 2) :: Maybe Integer b = 2 :: Int in a ^ b You see that the type of a is Maybe Integer. What does this mean? There are only 2 cases to consider. You have Just an integer or you have Nothing. You can use the case construct to write the code for both cases. f2Maybe :: Integer -> Maybe Integer f2Maybe n | n > 0 = Nothing | n == 0 = Just 1 | even n = case f2Maybe (n `div` 2) of Just x -> <fill in> Nothing -> <fill in> | odd n = case f2Maybe (n `div` 2) of Just x -> <fill in> Nothing -> <fill in>

Simplest hack: f2Maybe :: Integer -> Maybe Integer f2Maybe n = if n < 0 then Nothing else Just (g n) where g 0 = 1 g n = if odd n then x*2 else x where x = (g (n `div` 2))^2 There is no need to *keep* checking for a negative number in the recursive code.
f2Maybe :: Integer -> Maybe Integer f2Maybe n | n > 0 = Nothing | n == 0 = Just 1 | even n = Just (f2Maybe ( n `div` 2) ^ 2) | odd n = Just ((f2Maybe ( n `div` 2) ^ 2) * 2)
Let's try another tack. The recursive calls (f2Maybe (n `div` 2)) give you a value of type Maybe Integer. You want to transform the Integer part. This is an instance of Monad m => m a -> (a -> b) -> m b. There's something almost like that in Control.Monad: liftM :: (a -> b) -> m a -> m b So what you want is liftM (\x -> x^2) (f2Maybe (n `div` 2)) liftM (\x -> x^2*2) (f2Maybe (n `div` 2)) So f2Maybe n | n < 0 = Nothing f2Maybe 0 = Just 1 f2Maybe n = liftM (if odd n then (\x -> x^2*2) else (\x -> x^2)) (f2Maybe (n `div` 2)) Or you could use 'do' notation: f2Maybe n | n < 0 = Nothing f2Maybe 0 = Just 1 f2Maybe n = do x <- f2Maybe (n `div` 2) return (if odd n then x^2*2 else x^2) Whatever you do, the key thing is that you HAVE a value wrapped up in Just and you need to unwrap it, operate on the value, and rewrap it. So you could do something like rewrap _ Nothing = Nothing rewrap f (Just x) = Just (f x) and then f2Maybe n | n < 0 = Nothing f2Maybe 0 = Just 1 f2Maybe n = rewrap (\x -> if odd n then x^2*2 else x^2) (f2Maybe (n `div` 2)) and presto, chango! we've just re-invented liftM under the name 'rewrap'.

On Sat, Oct 31, 2015 at 6:10 PM, Roel van Dijk
Small nitpick, but I would generally put the "exception" or "error" in the Left part of an Either and a correct result in the Right part.
This has some advantages. 1 - Right is right as opposed to wrong. Easy to remember mnemonic. 2 - It fits neatly with the Monad (Either e) instance.
I think you're being modest when you call it a "small nitpick." If code can't get Left and Right right, that code immediately becomes very suspicious. Thus, not f2 :: Integer -> Either Integer ErrorString but f2 :: Integer -> Either ErrorString Integer Nice catch. -- Kim-Ee

Oops yes! :)
On Nov 2, 2015 13:38, "Kim-Ee Yeoh"
On Sat, Oct 31, 2015 at 6:10 PM, Roel van Dijk
wrote: Small nitpick, but I would generally put the "exception" or "error" in the Left part of an Either and a correct result in the Right part.
This has some advantages. 1 - Right is right as opposed to wrong. Easy to remember mnemonic. 2 - It fits neatly with the Monad (Either e) instance.
I think you're being modest when you call it a "small nitpick." If code can't get Left and Right right, that code immediately becomes very suspicious.
Thus, not
f2 :: Integer -> Either Integer ErrorString
but
f2 :: Integer -> Either ErrorString Integer Nice catch.
-- Kim-Ee

I think you misinterpreted that answer. As far as I'm aware, `error`
(except in its type) is no less reasonable than other exceptions, and
you can catch it in IO. So as long as you run a test in IO, you can
test for the call to `error` (as Joachim showed in another reply).
Regards,
Erik
On 31 October 2015 at 11:40, Darren Grant
Unfrotunately the answer to this is not simple:
http://stackoverflow.com/questions/4243117/how-to-catch-and-ignore-a-call-to...
'error' more or less terminates the program in an unreasonable way.
It would be preferable for f2 to result in a type that can contain the error result to be parsed.
Cheers, Darren
On Oct 31, 2015 21:16, "Roelof Wobben"
wrote: Hello,
I have made this exercise which can be found at the Craft of Functional Programming book.
-- exercise 32
-- Suppose we have to raise 2 to the power n. If n is even, 2*m say, then -- 2n = 22*m = (2m)2 -- If n is odd, 2*m+l say, then -- 2n = 22*m+l = (2n)2*2 -- Give a recursive function to compute 2n which uses these insights.
f2 :: Integer -> Integer f2 n | n < 0 = error "This will only run for positive numbers" | n == 0 = 1 | even n = f2 ( n `div` 2) ^ 2 | odd n = (f2 ( n `div` 2) ^ 2) * 2
Now I have to make Hunit tests for it,
But is there a way I can test if the error message is shown when a negative number is being used ?
Roelof
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

Good clarification.
Cheers,
Darren
On Nov 1, 2015 01:09, "Erik Hesselink"
I think you misinterpreted that answer. As far as I'm aware, `error` (except in its type) is no less reasonable than other exceptions, and you can catch it in IO. So as long as you run a test in IO, you can test for the call to `error` (as Joachim showed in another reply).
Regards,
Erik
On 31 October 2015 at 11:40, Darren Grant
wrote: Unfrotunately the answer to this is not simple:
http://stackoverflow.com/questions/4243117/how-to-catch-and-ignore-a-call-to...
'error' more or less terminates the program in an unreasonable way.
It would be preferable for f2 to result in a type that can contain the
result to be parsed.
Cheers, Darren
On Oct 31, 2015 21:16, "Roelof Wobben"
wrote: Hello,
I have made this exercise which can be found at the Craft of Functional Programming book.
-- exercise 32
-- Suppose we have to raise 2 to the power n. If n is even, 2*m say,
error then
-- 2n = 22*m = (2m)2 -- If n is odd, 2*m+l say, then -- 2n = 22*m+l = (2n)2*2 -- Give a recursive function to compute 2n which uses these insights.
f2 :: Integer -> Integer f2 n | n < 0 = error "This will only run for positive numbers" | n == 0 = 1 | even n = f2 ( n `div` 2) ^ 2 | odd n = (f2 ( n `div` 2) ^ 2) * 2
Now I have to make Hunit tests for it,
But is there a way I can test if the error message is shown when a negative number is being used ?
Roelof
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

The ability to express non-termination is a feature, not a bug. If the program truly cannot produce a useful result for some input, it should crash, the earlier the better. Wrapping the return value ONLY to make a non-total program *appear* total is kind of ugly (and commits you to a potentially inappropriate/nonsensical model for the problem at hand). It is cleaner to either constrain the input to values you're prepared to deal with or crash when the implicit invariant is violated.
participants (8)
-
Darren Grant
-
Erik Hesselink
-
joachifm@fastmail.fm
-
Kim-Ee Yeoh
-
Richard A. O'Keefe
-
Roel van Dijk
-
Roelof Wobben
-
Tom Ellis