Why exception is not catching by `catch`? - haskell

Why does not this catch exception of conversion conv B3 ?!
import qualified Control.Monad.Catch as E
data A = A1|A2 deriving (Enum, Show)
data B = B1|B2|B3 deriving (Enum, Show)
conv b = safeConv
where
catchError e = Left e
safeConv = (Right $ (toEnum $ fromEnum b :: A)) `E.catch` catchError
I got:
Right *** Exception: toEnum{A}: tag (2) is outside of enumeration's range (0,1)
CallStack (from HasCallStack):
error, called at xxx.hs:227:26 in main:Main

Haskell exceptions are somewhat different than, say, Java or C++: "true" exceptions work in IO monad, and then there is an imitation of exceptions via pure means, as in ExceptT.
The toEnum function throws the first kind - IO exceptions, - which cannot be caught in pure code. They fly out to the nearest IO place, which in your case is apparently GHCi.
In order to catch such exceptions, you first need to wrap the throwing expression in IO via Control.Exception.evaluate. Then you can catch such exceptions with catch, or, if you just want to convert it to an Either exception A (as you seem to be doing), there is an app for that! - it's called try.
Further, when using either catch or try, you need to specify the specific type of the exception you're trying to catch. But it is possible to catch all exceptions regardless of type by using the existential type SomeException.
So, wrapping up all of that, we get this code:
import qualified Control.Exception as E
data A = A1|A2 deriving (Enum, Show)
data B = B1|B2|B3 deriving (Enum, Show)
conv :: Enum b => b -> IO (Either E.SomeException A)
conv b = E.try . E.evaluate . toEnum $ fromEnum b
NOTE 1: The type annotation on conv is necessary in order to specify E.SomeException as the type of exception to catch. Without it, GHC will complain that the type of exception is ambiguous.
NOTE 2: Because our type annotation on conv already specifies the target type A, the type annotation on toEnum $ fromEnum b is no longer necessary.
NOTE 3: I have replaced your import of Control.Monad.Catch with Control.Exception, because that's where evaluate and SomeException are.

I'll leave it here if someone needs a solution. To keep function pure, conversion should be:
unsafeConvEnum :: (Enum a, Enum b) => a -> b
unsafeConvEnum = toEnum . fromEnum
convEnum :: (Enum a, Enum b) => a -> Maybe b
convEnum e = unsafePerformIO conv'
where onError (_::SomeException) = pure Nothing
conv' = (Just <$> evaluate (unsafeConvEnum e)) `catch` onError
No any IO :)

Related

What is difference between normal functions and typeclass functions?

class (Typeable e, Show e) => Exception e where
toException :: e -> SomeException
fromException :: SomeException -> Maybe e
toException = SomeException
fromException (SomeException e) = cast e
data MyException1 = Exception1A | Exception1B
deriving (Show)
instance Exception MyException1
data MyException2 = Exception2A | Exception2B
deriving (Show)
instance Exception MyException2
It is able to define multiple exceptions. So, multiple fromException functions are able to be defined too. I think it is weird because two functions can have same name and same input.
fromException :: SomeException -> Maybe MyException1
fromException :: SomeException -> Maybe MyException2
Even if the reason why this behavior is ok is "Two functions have different type include return type (and expressions are evaluated based these all types)", it is weird, because I can't define normal functions that way.
f :: Integer -> Maybe Integer
f = cast
f :: Integer -> Maybe Char
f n = cast $ show n
What is difference between normal functions and type class functions?
The fact that you cannot define normal functions that way is the whole difference.
The whole purpose of type classes is to allow overloading - that is, defining multiple different functions with different types, but same name. And have the compiler pick the right one automatically based on types expected in the context.

Does exporting type constructors make a difference?

Let's say I have an internal data type, T a, that is used in the signature of exported functions:
module A (f, g) where
newtype T a = MkT { unT :: (Int, a) }
deriving (Functor, Show, Read) -- for internal use
f :: a -> IO (T a)
f a = fmap (\i -> T (i, a)) randomIO
g :: T a -> a
g = snd . unT
What is the effect of not exporting the type constructor T? Does it prevent consumers from meddling with values of type T a? In other words, is there a difference between the export list (f, g) and (f, g, T()) here?
Prevented
The first thing a consumer will see is that the type doesn't appear in Haddock documentation. In the documentation for f and g, the type Twill not be hyperlinked like an exported type. This may prevent a casual reader from discovering T's class instances.
More importantly, a consumer cannot doing anything with T at the type level. Anything that requires writing a type will be impossible. For instance, a consumer cannot write new class instances involving T, or include T in a type family. (I don't think there's a way around this...)
At the value level, however, the main limitation is that a consumer cannot write a type annotation including T:
> :t (f . read) :: Read b => String -> IO (A.T b)
<interactive>:1:39: Not in scope: type constructor or class `A.T'
Not prevented
The restriction on type signatures is not as significant a limitation as it appears. The compiler can still infer such a type:
> :t f . read
f . read :: Read b => String -> IO (A.T b)
Any value expression within the inferrable subset of Haskell may therefore be expressed regardless of the availability of the type constructor T. If, like me, you're addicted to ScopedTypeVariables and extensive annotations, you may be a little surprised by the definition of unT' below.
Furthermore, because typeclass instances have global scope, a consumer can use any available class functions without additional limitation. Depending on the classes involved, this may allow significant manipulation of values of the unexposed type. With classes like Functor, a consumer can also freely manipulate type parameters, because there's an available function of type T a -> T b.
In the example of T, deriving Show of course exposes the "internal" Int, and gives a consumer enough information to hackishly implement unT:
-- :: (Show a, Read a) => T a -> (Int, a)
unT' = (read . strip . show') `asTypeOf` (mkPair . g)
where
strip = reverse . drop 1 . reverse . drop 9
-- :: T a -> String
show' = show `asTypeOf` (mkString . g)
mkPair :: t -> (Int, t)
mkPair = undefined
mkString :: t -> String
mkString = undefined
> :t unT'
unT' :: (Show b, Read b) => A.T b -> (Int, b)
> x <- f "x"
> unT' x
(-29353, "x")
Implementing mkT' with the Read instance is left as an exercise.
Deriving something like Generic will completely explode any idea of containment, but you'd probably expect that.
Prevented?
In the corners of Haskell where type signatures are necessary or where asTypeOf-style tricks don't work, I guess not exporting the type constructor could actually prevent a consumer from doing something they could with the export list (f, g, T()).
Recommendation
Export all type constructors that are used in the type of any value you export. Here, go ahead and include T() in your export list. Leaving it out doesn't accomplish anything other than muddying the documentation. If you want to expose an purely abstract immutable type, use a newtype with a hidden constructor and no class instances.

Haskell Monads Either

I have a little problem with Data Types in Haskell, I think I should post first some code to help to understand the problem
helper :: (MonadMask a, MonadIO a, Functor a) => Expr -> String -> a (Either InterpreterError Int)
helper x y = ( getEval ( mkCodeString x y ) )
-- Creates Code String
mkCodeString :: (Show a) => a -> String -> String
mkCodeString x y = unpack (replace (pack "Const ") (pack "") (replace (pack "\"") (pack "") (replace (pack "Add") (pack y) (pack (show x) ) ) ) )
-- Calculates String
getEval :: (MonadMask m, MonadIO m, Functor m) => [Char] -> m (Either InterpreterError Int)
getEval str = (runInterpreter (setImports ["Prelude"] >> interpret str (as ::Int)))
-- | A test expression.
testexpression1 :: Expr
testexpression1 = 3 + (4 + 5)
-- | A test expression.
testexpression2 :: Expr
testexpression2 = (3 + 4) + 5
-- | A test expression.
testexpression3 :: Expr
testexpression3 = 2 + 5 + 5
I use the helper Function like this "helper testexpression3 "(+)" and it returns me the value "Right 12" with the typ "Either InterpreterError Int", but I only want to have the "Int" value "12"
I tried the function -> "getValue (Right x) = x" but I dont get that Int value.
After some time of testing I think it is a problem with the Monads I've used.
If I test the typ of the helper function like this: ":t (helper testexpression1 "(+)")" I'll get that: "(... :: (Functor a, MonadIO a, MonadMask a) => a (Either InterpreterError Int)"
How can I make something like that working:
write "getValue (helper testexpression1 "(+)")" and get "12" :: Int
I'll know that the code makes no sence, but its a homework and I wanted to try some things with haskell.Hope you have some more Ideas than I am.
And Sorry for my bad English, I have began to learn English, but I am just starting and Thank you for every Idea and everything.
Edit, here is what was missing on code:
import Test.HUnit (runTestTT,Test(TestLabel,TestList),(~?))
import Data.Function (on)
import Language.Haskell.Interpreter -- Hint package
import Data.Text
import Data.Text.Encoding
import Data.ByteString (ByteString)
import Control.Monad.Catch
-- | A very simple data type for expressions.
data Expr = Const Int | Add Expr Expr deriving Show
-- | 'Expression' is an instance of 'Num'. You will get warnings because
-- many required methods are not implemented.
instance Num Expr where
fromInteger = Const . fromInteger
(+) = Add
-- | Equality of 'Expr's modulo associativity.
instance Eq Expr where
(==) x1 x2 = True --(helper x1 "(+)") == (helper x2 "(+)") && (helper x1 "(*)") == (helper x2 "(*)")
That functions are also in the file ... everything else I have in my file are some Testcases I have created for me.
helper textExpr "(+)" is not of type Either InterpreterError Int it is of type (MonadMask a, MonadIO a, Functor a) => a (Either InterpreterError Int). This later tyoe can be treated as if it was IO (Either InterpreterError Int) for our purposes.
In general something of type IO a (e.g. IO (Either InterpreterError Int)) doesn't contain, in the strictest sense, a value of type a, so you can't just extract a value willy-nilly. Something of type IO a is an action, that when performed, will produce a value of type a. Haskell only performs one action, the one called main. That said, it allows us to easily build larger actions out of smaller actions.
main = helper textExpr "(+)" >>= print
That operator there (>>=) is a monadic bind. For more information about monads in general, see You Could Have Invented Monads!. For an idea of how the IO Monad might be constructed see Free Monads for Less (Part 3 of 3): Yielding IO (under "Who Needs the RealWorld?") or Idris' implementation of IO -- but keep in mind that the IO Monad is opaque and abstract in Haskell; don't expect to be able to get an a value from an IO a value unless you are writing main (an application).

Type Constraints in Typeclass

For fun I'm building a parser library. In this library I have a Parser data type:
data Parser e a = Parser (String -> Either e (a, String))
I'm able to define Functor and Applicative instances of Parser, but I don't think I can make an Alternative instance without constraining the "error" type or the "value" type the parser could return. Originally, this made me create an Applicative instance for when the error types are String messages, but I realized that I should be able to release this constraint to any message data type that has an Alternative (or maybe Monoid instead?) instance as well. With that in mind I wrote this:
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
instance Alternative e => Alternative (Parser e)
where
empty = Parser $ \s -> Left empty
(<|>) (Parser p1) (Parser p2) = Parser $ \s -> tryParser s p2 $ p1 s
where
tryParser s p2 (Left _ ) = p2 s
tryParser _ _ x = x
Unfortunately, this fails to compile. When I load it into ghci I get this error message:
Parsertest.hs:31:47:
Expecting one more argument to `e'
In the instance declaration for `Alternative (Parser e)'
Failed, modules loaded: none.
When I search online, this seems to be the solution, but it doesn't work for me. What am I missing?
The problem is that Alternative is for type constructors of kind * -> *, so if you say
instance Alternative e => ....
then e has to be a type constructor, not a type. So e could be [] or Maybe or something, but not Int.
Alternative's operator is <|> which has type Alternative e => e a -> e a -> e a. This forces e to take an argument to make a type, like Maybe has to take an argument, eg Maybe Int.
Use Monoid instead of Alternative, because it's a type class instead of a constructor class. It's operator mappend has type Monoid e => e -> e -> e which is what you want for combining errors.

Difficulties with 'Either e` instance of `Failure` from "failure" package

This is more or less a simplified version of the issue I'm trying to understand in my own code. I'm working with functions that are polymorphic in the Failure class from this package.
{-# LANGUAGE FlexibleContexts #-}
import Data.Maybe
import Data.Either
import Control.Failure
data FookError = FookError deriving Show
fook :: (Failure FookError m)=> Int -> m Int
fook = undefined
fooks :: (Failure FookError m)=> Int -> m Int
-- DOES NOT TYPE-CHECK:
--fooks n = return $ head $ rights $ map fook [1..]
-- OKAY:
fooks n = return $ head $ catMaybes $ map fook [1..]
You can see in the above code, that when I treat the return type of fook as Maybe Int the module compiles fine, however treating it as Either Fook Int fails.
What is going on here?
This is because, in the non-working definition of fooks, fook's type is ambiguous. When you use catMaybes, it disambiguates as Maybe Int, but when you use rights, it can be Either e Int for any e, and the compiler doesn't necessarily know which. Sure, by default the only Failure instance for Either is instance Failure e (Either e), but there's nothing stopping you defining, e.g. instance Failure String (Either Int).
If you explicitly specify the type by defining fooks as
fooks n =
return $ head $ rights $ map (fook :: Int -> Either FookError Int) [1..]
then it works fine.
However, I suspect that you're not doing what you really want here; fooks never actually uses the failure capability of the underlying monad; indeed, even if there are no non-failing results, the monadic action still succeeds and returns a value. The value just so happens to be an error, but that's still probably not what you want :)
If you want fooks to try a bunch of individual fooks in turn, and return the first one that succeeds, then something like:
fooks :: (Failure FookError m, MonadPlus m) => Int -> m Int
fooks n = foldr mplus (failure FookError) $ map fook [1..]
should do the trick. The plain Failure class by itself offers no way to recover from errors, so you need to require MonadPlus too. Note that the failure FookError here will never actually be used, since [1..] is infinite, but presumably you're planning to change the definition; say to one that actually uses n :)
Unfortunately, that isn't all! Either e doesn't have a MonadPlus instance, presumably because there's no reasonable value of mzero (although another potential problem is that mplus (Left e) (Left e') could be either Left e or Left e').
Thankfully, it's easy to define an instance for our specific type:
instance MonadPlus (Either FookError) where
mzero = failure FookError
mplus a#(Right _) _ = a
mplus (Left _) a = a
You'll need {-# LANGUAGE FlexibleInstances #-} at the top of your file to do this.

Resources