On 01 Dec 2015, at 20:44, Jeffrey Brown <jeffbrown.the@gmail.com> wrote:I spoke too soon; I'm seeing the same problem with MonadError.Prelude> :set -XFlexibleContextsPrelude> import Control.Monad.ExceptPrelude Control.Monad.Except> let f = (fail "be Left!" :: (MonadError String m) => m ())Loading package transformers-0.4.2.0 ... linking ... done.Loading package mtl-2.2.1 ... linking ... done.Prelude Control.Monad.Except> f :: Either String ()*** Exception: be Left!Prelude Control.Monad.Except>On Mon, Nov 30, 2015 at 6:18 PM, Jeffrey Brown <jeffbrown.the@gmail.com> wrote:Oleg's suggestion works! I just had to add these two lines in order to use it:{-# LANGUAGE FlexibleContexts #-}import Control.Monad.Except -- mtl libraryThanks, everybody!--On Mon, Nov 30, 2015 at 2:38 PM, Oleg Grenrus <oleg.grenrus@iki.fi> wrote:On 01 Dec 2015, at 00:34, Oleg Grenrus <oleg.grenrus@iki.fi> wrote:Hi, Jeffreyin short: `fail` of `Either e` throws an exception (i.e. is not overriden, default implementation is `fail s = error s`) [1, 2]For `Maybe`, fail is defined as `fail _ = Nothing`; which is good default. [3]You probably want to use for example `throwError from `mtl` package [4]:I haven’t still tested it, but less wrong context is `MonadError String m`:gelemM :: (MonadError String m) => MyGraph -> Node -> m ()gelemM g n = if gelem n g -- FGL's gelem function returnsthen return () -- True if the node is in the graphelse throwError "Node not in Graph" -- False otherwise_______________________________________________- OlegOn 01 Dec 2015, at 00:25, Jeffrey Brown <jeffbrown.the@gmail.com> wrote:_______________________________________________I've written a monadic function which in a Maybe context produces a Nothing when it fails (as intended), but in an Either context produces an Exception rather than a Left.Here's a tiny demonstration. "tinyGraph" below has one Node, 0, with the label "dog". If I try to change the label at Node 0 to "cat", it works. If I try to change the label at Node 1 to "cat", it fails, because Node 1 is not in the graph.type MyGraph = Gr String StringtinyGraph = mkGraph [(0, "dog")] [] :: MyGraphmaybeSucceed = replaceStringAtNodeM tinyGraph 0 "cat" :: Maybe MyGraph-- == Just (mkGraph [(0,"cat")] [])maybeFail = replaceStringAtNodeM tinyGraph 1 "cat" :: Maybe MyGraph-- == NothingeitherSucceed = replaceStringAtNodeM tinyGraph 0 "cat" :: Either String MyGraph-- == Right (mkGraph [(0,"cat")] [])eitherFail = replaceStringAtNodeM tinyGraph 1 "cat" :: Either String MyGraph-- *** Exception: Node not in GraphHere's the code:import Data.Graph.Inductive -- FGL, the Functional Graph LibrarygelemM :: (Monad m) => MyGraph -> Node -> m ()gelemM g n = if gelem n g -- FGL's gelem function returnsthen return () -- True if the node is in the graphelse fail "Node not in Graph" -- False otherwisereplaceStringAtNode :: MyGraph -> Node -> String -> MyGraphreplaceStringAtNode g n e = let (Just (a,b,c,d),g') = match n gin (a,b,e,d) & g'replaceStringAtNodeM :: (Monad m) => MyGraph -> Node -> String -> m MyGraphreplaceStringAtNodeM g n s = dogelemM g nreturn $ replaceStringAtNode g n s-- if evaluated, the pattern match in replaceStringAtNode must succeed,-- because gelemM catches the case where n is not in the graph[1] https://github.com/JeffreyBenjaminBrown/digraphs-with-text/blob/master/test/monad_fail_problems.hs--Jeffrey Benjamin Brown
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-cafeJeffrey Benjamin Brown--Jeffrey Benjamin Brown