[Haskell-beginners] Handling a MonadError
Christopher Done
chrisdone at googlemail.com
Mon May 30 08:49:51 CEST 2011
On 30 May 2011 05:05, Christopher Howard
<christopher.howard at frigidcode.com>wrote:
> Hi. I'm trying to learn Data.ConfigFile. I want to use the function
> readfile:
>
> [DESCRIPTION]
> readfile :: MonadError CPError m => ConfigParser -> FilePath -> IO (m
> ConfigParser)
>
> I understand that this function returns a monad, and I pull the value
> out of it with (<-). And I believe this is similar to a "Maybe"
> situation where I can do one thing if it provides a syntax error and
> another thing if it provides the ConfigParser. But I'm not sure what
> this would look like in actual code. Could somebody give me a small,
> simple example?
>
It's understandable that actual usage isn't clear, it wasn't clear to me
either when I first encountered it. There are a few ways to use it. It
returns an instance of error Monad, so you can either force it into an
Either value:
λ> do parser <- readfile emptyCP "../confy.conf"; return (get (forceEither
parser) "PATHS" "upload_path") :: IO (Either CPError String)
Right "uploads"
Or you can get it within the monad like everything else:
λ> do parser <- readfile emptyCP "../confy.conf"; return (do config <-
parser; get config "PATHS" "upload_path") :: IO (Either CPError String)
Right "uploads"
Because it returns any MonadError instance, and IO is an instance of
MonadError, you can skip the double level of monadery:
λ> let getUploads :: IO (Either CPError String); getUploads = runErrorT $
do parser <- liftIO $ readfile emptyCP "../confy.conf"; config <- parser;
get config "PATHS" "upload_path" in getUploads
Right "uploads"
Or with join:
λ> :t join
join :: (Monad m) => m (m a) -> m a
λ> let getUploads :: IO (Either CPError String); getUploads = runErrorT $
do cp <- join $ liftIO $ readfile emptyCP "../confy.conf"; get cp "PATHS"
"upload_path" in getUploads
Right "uploads"
Control.Applicative also works nicely for this.
instance Applicative (ErrorT CPError IO) where (<*>) = ap; pure = return
λ> let getCfg :: IO (Either CPError (String,String));
getCfg = runErrorT $ do
cp <- join $ liftIO $ readfile emptyCP "../confy.conf";
(,) <$> get cp "PATHS" "upload_path"
<*> get cp "PATHS" "err_log"
in getCfg
Right ("uploads","errors.log")
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/beginners/attachments/20110530/1c0a4e2d/attachment.htm>
More information about the Beginners
mailing list