6

Given the below program, I am having issues dealing with monads.

module Main 
where
import System.Environment
import System.Directory
import System.IO
import Text.CSV

--------------------------------------------------

exister :: String -> IO Bool
exister path = do
  fileexist <- doesFileExist path 
  direxist  <- doesDirectoryExist path
  return (fileexist || direxist )

--------------------------------------------------
slurp :: String -> IO String 
slurp path = do
  withFile path ReadMode (\handle -> do
                             contents <- hGetContents handle
                             last contents `seq` return contents )
--------------------------------------------------    
main :: IO ()
main = do
  [csv_filename] <- getArgs
  putStrLn (show csv_filename)
  csv_raw <- slurp csv_filename
  let csv_data = parseCSV csv_filename csv_raw

  printCSV csv_data -- unable to compile. 

csv_data is an Either (parseerror) CSV type, and printCSV takes only CSV data.


Here's the ediff between the working version and the broken version.

***************
*** 27,30 ****
    csv_raw <- slurp csv_filename
    let csv_data = parseCSV csv_filename csv_raw

!   printCSV csv_data -- unable to compile. 
\ No newline at end of file
--- 27,35 ----
    csv_raw <- slurp csv_filename
    let csv_data = parseCSV csv_filename csv_raw

!   case csv_data of 
!     Left error -> putStrLn $ show error
!     Right csv_data -> putStrLn $ printCSV csv_data
!     
!   putStrLn "done"
!       

reference: http://hackage.haskell.org/packages/archive/csv/0.1.2/doc/html/Text-CSV.html

Paul Nathan
  • 39,638
  • 28
  • 112
  • 212
  • The question doesn't seem to have anything to do with monads. :) – Rotsor Aug 23 '11 at 01:04
  • @Rotsor I was just going to post a comment reply, but it ballooned into an answer. The question is kinda sorta is about monads, but not really. – Dan Burton Aug 23 '11 at 04:23
  • 1
    Paul, isn't the problem the poor name assigned `printCSV :: CSV -> String`? It is a pure function, not a function to an IO type. If I write `putStrLn $ printCSV csv_data` for the last line, it compiles. – applicative Aug 23 '11 at 05:07
  • @applicative: yeah, I got kicked by the poor name. :-/ – Paul Nathan Aug 23 '11 at 15:42

3 Answers3

17

Regarding monads:

Yes, Either a is a monad. So simplifying the problem, you are basically asking for this:

main = print $ magicMonadUnwrap v

v :: Either String Int
v = Right 3

magicMonadUnwrap :: (Monad m) => m a -> a
magicMonadUnwrap = undefined

How do you define magicMonadUnwrap? Well, you see, it's different for each monad. Each one needs its own unwrapper. Many of these have the word "run" in them, for example, runST, runCont, or runEval. However, for some monads, it might not be safe to unwrap them (hence the need for differing unwrappers).

One implementation for lists would be head. But what if the list is empty? An unwrapper for Maybe is fromJust, but what if it's Nothing?

Similarly, the unwrapper for the Either monad would be something like:

fromRight :: Either a b -> b
fromRight (Right x) = x

But this unwrapper isn't safe: what if you had a Left value instead? (Left usually represents an error state, in your case, a parse error). So the best way to act upon an Either value it is to use the either function, or else use a case statement matching Right and Left, as Daniel Wagner illustrated.

tl;dr: there is no magicMonadUnwrap. If you're inside that same monad, you can use <-, but to truly extract the value from a monad...well...how you do it depends on which monad you're dealing with.

Dan Burton
  • 53,238
  • 27
  • 117
  • 198
  • There is with TH, someone posted an implementation of a generic `Monad m => m a -> a`. Link: http://blog.sigfpe.com/2009/01/rewriting-monadic-expressions-with.html – alternative Aug 23 '11 at 12:33
  • 1
    @monadic: that technique is clever, but it's got a problem. It only allows you to use `extract` within a Template Haskell splice which is then interpreted as some monad. It basically just gives you a fancy `(>>=)`, which could be expected since `extract` is simply replaced by `join`. – John L Aug 23 '11 at 14:35
  • @Dan: Interesting. I see your point, and it coheres better in my mind when I see what's going on. – Paul Nathan Aug 23 '11 at 15:48
7

Use case.

main = do
    ...
    case csv_data of
        Left  err -> {- whatever you're going to do with an error -- print it, throw it as an exception, etc. -}
        Right csv -> printCSV csv

The either function is shorter (syntax-wise), but boils down to the same thing.

main = do
    ...
    either ({- error condition function -}) printCSV csv_data
Daniel Wagner
  • 145,880
  • 9
  • 220
  • 380
3

You must unlearn what you have learned.

Master Yoda.

Instead of thinking about, or searching for ways to "free", "liberate", "release", "unwrap" or "extract" normal Haskell values from effect-centric (usually monadic) contexts, learn how to use one of Haskell's more distinctive features - functions are first-class values:

  • you can use functions like values of other types e.g. like Bool, Char, Int, Integer etc:

    arithOps :: [(String, Int -> Int -> Int)]
    arithOps =  zip ["PLUS","MINUS", "MULT", "QUOT", "REM"]
                    [(+), (-), (*), quot, rem] 
    

For your purposes, what's more important is that functions can also be used as arguments e.g:

map          :: (a -> b) -> [a] -> [b]
map f xs     =  [ f x | x <- xs ]

filter       :: (a -> Bool) -> [a] -> [a]
filter p xs  =  [ x | x <- xs, p x ]

These higher-order functions are even available for use in effect-bearing contexts e.g:

import Control.Monad

liftM  :: Monad m => (a -> b)           -> (m a -> m b)
liftM2 :: Monad m => (a -> b -> c)      -> (m a -> m b -> m c)
liftM3 :: Monad m => (a -> b -> c -> d) -> (m a -> m b -> m c -> m d)

...etc, which you can use to lift your regular Haskell functions:

do     .
       .
       .
   val <- liftM3 calculate this_M that_M other_M
       .
       .
       .

Of course, the direct approach also works:

do     .
       .
       .
   x <- this_M
   y <- that_M
   z <- other_M
   let val =  calculate x y z
       .
       .
       .

As your skills develop, you'll find yourself delegating more and more code to ordinary functions and leaving the effects to a vanishingly-small set of entities defined in terms of functors, applicatives, monads, arrows, etc as you progress towards Haskell mastery.


You're not convinced? Well, here's a brief note of how effects used to be handled in Haskell - there's also a longer description of how Haskell arrived at the monadic interface. Alternately, you could look at Standard ML, OCaml, and other similar languages - who knows, maybe you'll be happier with using them...

atravers
  • 455
  • 4
  • 8