Reputation: 87
So I'm writing a program in Haskell that receives a number n telling it to return the nth prime number starting at 2 being the 1st prime number. That part of the program works however what I don't understand is how to also have the program throw an exception when the number is 0 or less.
pr :: Int -> Int
pr n = (filter(\x -> (getter) == []) [2..]) !! (n-1)
The getter references another method I wrote that is solving the prime problem. It is working fine.
Upvotes: 1
Views: 1532
Reputation: 64740
Administrivia Other answers have given you some good text so I'm going to be code-heavy and explanation light here. If something still isn't clear then please do comment and I'll try to fill it in (or any of you regular S.O. answerers can beat me to it).
The Answer
You presented a problem where the input of n <= 0
is invalid:
pr :: Int -> Int
pr n = (filter(\x -> (getter) == []) [2..]) !! (n-1)
The easy solution is to match with a pattern or guard and manually throw an exception:
pr :: Int -> Int
pr n | n <= 0 = error "NO!"
| otherwise = ...
But sometimes you want a non-string exception in which case you probably want Control.Exception
:
{-# LANGUAGE DeriveAnyClass #-}
-- ^^^ This is not just a comment, enables a language extension
import Control.Exception as X
data MyException = ZeroOrNegative
deriving (Exception,Show,Eq,Ord)
-- ^^ N.B. you should derive 'Exception' for
-- types you want to 'throw'
pr n | n <= 0 = X.throw ZeroOrNegative
| otherwise = ...
Upvotes: 0
Reputation: 120731
In Haskell, basically everything is just a library function. As such it can easily be found with online search engines. That includes error handling. Thus you may ask Hayoo for error
, or for raise
, or for throw
. All three exist – but raise
only in different flavours, specialised to particular libraries, whereas throw
and error
are part of base
and thus of “Haskell itself”.
throw
can be used to produce properly typed exceptions and is suitable if you may at some point, in your program itself, want to catch / analyse the errors.error
is mostly useful to just crash the program while producing a (hopefully) useful diagnostic message on the terminal, which seems to be what you want here.The type of error
is†, as of GHC-8,
error :: HasCallStack => String -> a
The HasCallStack
is a recent addition which allows the program to tell you where in your code the error occured. This doesn't change the way you use the function though; in older versions of GHC the type was simply
error :: String -> a
That means, you just give error
some error message and then use it as “the result” of any function, no matter what the result type of that function is actually supposed to be. In your case,
pr n | n >= 0 = ...
| otherwise = error "Table flip"
If you give this function a negative number, it will then not give any actual result but crash the program with the message Table flip
and, in GHC>=8, also tell you that this error happened within pr
.
You'll probably want to also know where pr
was called, to actually debug the problem. You can yourself use the GHC call-stack simulation for this:
import GHC.Stack
pr :: HasCallStack => Int -> Int
pr n | n >= 0 = ...
| otherwise = error "Table flip"
Note that I didn't need to change the implementation in any way, I just added the HasCallStack
constraint.
error :: forall (r :: RuntimeRep). forall (a :: TYPE r). HasCallStack => [Char] -> a
...don't worry about that, these are just implementation details raising of meanigful errors throwing is in fact not so naturally supported by the Haskell language.
Upvotes: 0
Reputation: 29193
By default, if no equation for a function matches the given arguments, you get a runtime error:
fromJust :: Maybe a -> a
fromJust (Just a) = a
-- No case for Nothing
-- fromJust Nothing throws error at runtime
However, this doesn't work for numbers. Instead, guards will do a similar thing:
assertOver0 :: Int -> ()
assertOver0 n | n > 0 = ()
-- No case for n <= 0
-- assertOver0 (-1) throws error at runtime
While this is the default behavior, it is bad style to have incomplete patterns/guards. Instead, explicitly cause an error with error
or undefined
:
pr n | n >= 0 = filter (null . getter) [2..] !! n
| otherwise = error "Table flip"
-- undefined is just like error, except that error lets you give an error message
-- and undefined doesn't (undefined is more useful when you know it will never
-- be evaluated, and you don't need to give an error message)
-- undefined :: a; error :: String -> a
-- That is, they can take on any type you want them to have, because whatever code
-- is after them will never be executed anyway
-- I took liberties with your definition of pr. Your filtering function didn't use
-- x, so I wrote what I think you meant. I also made it 0-indexed.
-- Prelude.null checks for [], but doesn't incur an Eq constraint, so I replaced
-- (== []) with it.
-- Parens are not needed around the filter, because function application has
-- the highest precedence.
Haskell also has a more sophisticated exception mechanism in Control.Exception
, but you probably don't need that here. In general, exceptions and partial functions are looked down upon, (because you can only handle them in IO
) and you should strive for monads like Maybe
or Either
instead.
import Control.Monad
pr n = do guard $ n >= 0 -- guard True = Just (); guard False = Nothing (in this case)
return $ filter (null . getter) [2..] !! n
pr 2 = Just 5
pr (-1) = Nothing
All this is unnecessary, though. (!!)
already errors on negative indices
ghci> "abc" !! -1
*** Exception: Prelude.!!: negative index
So we're back to where we started:
pr n = filter (null . getter) [2..] !! n
There's also a library that redefines list operations (including (!!)
) to be monadic instead of partial.
Upvotes: 6