[Haskell-beginners] Re: ghci access to .hs functions

Daniel Fischer daniel.is.fischer at web.de
Thu Aug 12 17:15:43 EDT 2010


On Thursday 12 August 2010 22:18:11, prad wrote:
> On Thu, 12 Aug 2010 12:00:44 -0300
>
> MAN <elviotoccalino at gmail.com> wrote:
> > couple of things
> > you could be interested to know.
>
> most definitely! i very much appreciate the help, el.
> thx to you too brent for clearing up the ExitCode problem
>
> > Your main will allways be 'IO ()' , but that doesn't mean you must
> > sparkle 'return ()' all over the place :P
>
> well i have been specializing in random programming => just keep trying
> things randomly and hope it works. :D

That phase shouldn't last long.
Learning to understand the error messages helps getting over it, because 
then most of the time you know from the error message how to fix your code.

>
> putting return() in the "all" worked (no idea why),

Because that gave all branches the same type.

> so i thought it
> must be a good thing and put it in the other two. :D
>
> i'd also used mapM because map didn't work and i figured it had
> something to do with monads and M is the first letter in monad. :D

Good thinking.

mapM :: Monad m => (a -> m b) -> [a] -> m [b]
mapM_ :: Monad m => (a -> m b) -> [a] -> m ()

With map, you go from (a -> m b) and [a] to [m b].
Then you run the monadic actions in that list one after the other and 
either collect the results (mapM) or discard the results (mapM_).

The functions to do that are

sequence :: Monad m => [m b] -> m [b]

and

sequence_ :: Monad m => [m b] -> m ()

mapM fun list = sequence (map fun list)
mapM_ fun list = sequence_ (map fun list)

>
> i really have to get away from this sort of thing and i'm trying to
> figure out the excellent stuff etugrul and kyle provided in the
> = vs <- thread.
>
> now i tried taking the returns out and things are fine for "add" and
> "upd", but even with the changes you suggested for gtKys (mapM to
> mapM_) i'm getting these errors:
>
> ======
> gadit.hs:30:19:
>     Couldn't match expected type `()' against inferred type `[()]'
>       Expected type: IO ()
>       Inferred type: IO [()]
>     In the expression: gtKys conn
>     In a case alternative: "all" -> gtKys conn
>
> gadit.hs:66:4:
>     Couldn't match expected type `[()]' against inferred type `()'
>       Expected type: IO [()]
>       Inferred type: IO ()
>     In the expression: mapM_ (mkPag conn) kL
>     In the expression:
>         do { r <- quickQuery conn "SELECT key from main" [];
>              let kL = concat $ map (map fromSql) r;
>              mapM_ (mkPag conn) kL }
> =======
>
> it want some sort of list and i'm not providing it.
>
> here is the code in question with the line numbers:
>
> =======
>
>  21 main = do
>  22     args <- getArgs
>  23     let act = head args
>  24     conn <- connectPostgreSQL "host=localhost dbname=lohv
>  user=pradmin"


>  25     case act of
>  26          "add"  -> do
>  27              kV1 <- dbDef conn
>  28              upDbs conn (fromSql kV1)
>  29          "upd"  -> upDbs conn (last args)
>  30          "all"  -> gtKys conn
>  31          _      -> putStrLn "add, upd num, all only!!"

In a case expression, all branches must have the same type.
The branches for "add", "upd" and _ have type IO (), so the branch for 
"all" must also have that type.

But the type signature says

gtKys conn :: IO [()]

So GHC can't match the expected type `IO ()' [expected because the other 
branches say it must have that type] against the inferred type `IO [()]' 
['inferred' from the type signature here].

That's the first error message.

But the last statement in gtKys is `mapM_ (mkPag conn) kL'.

mapM_ :: Monad m => (a -> m b) -> [a] -> m ()

so the actual type of gtKys conn is IO () [ and gtKys has the type 
(IConnection conn) => conn -> IO () ]

Fix (or remove) the type signature, and it should work with the old code.

Now to the second error message.
Here the type signature determines the type GHC `expects', IO [()], and the 
code determines the inferred type, IO ().

>  32     commit conn
>  33     disconnect conn
>  34     putStrLn "All Done!"
>
> ...
>
>  61 -- gtKys: gets all key values in database
>  62 gtKys :: (IConnection conn) => conn -> IO [()]
>  63 gtKys conn = do
>  64     r <- quickQuery conn "SELECT key from main" []
>  65     let kL = concat $ map (map fromSql) r
>  66     mapM_ (mkPag conn) kL
>
> ========
>
> now i got to thinking about all this and realized that gtKys really
> shouldn't have
> mapM_ (mkPag conn) kL
> in there anyway because its job is to just get some key values not to
> make Pages (mkPag)
> in fact, i only put it in there because i couldn't figure out how to
> get the stuff out - as kyle says in the other thread:
> "once something is "inside" of a monad (IO in this case), it's very
> difficult, impossible, to get it out again."

That depends on the monad.

>
> so what i did is rewrite the code like this:
> case act of
> ...
>          "all"  -> do
>              kyL <- gtKys conn
>              mapM_ (mkPag conn) kyL
>
> and
>
> gtKys conn = do
>     r <- quickQuery conn "SELECT key from main" []
>     return $ concat $ map (map fromSql) r
>
> it all works now.
>
> gtKys now has the lengthy type:
> gtKys :: (IConnection conn, Data.Convertible.Base.Convertible SqlValue
> a) => conn -> IO [a]
>
> which i'm leaving out since it generates a scope error unless i import
> something else (as brent explained in the above post regarding
> ExitCode).
>
> however, i still don't quite understand what the return is doing beyond
> you seem to need it in order to get things out of a monad associated
> function. whenever i have an IO () i seem to require it.

A common use of `return ()' is to give a monadic computation the correct 
type, e.g.

main = do
    args <- getArgs
    case args of
        [file, limit] -> do somestuff file (read limit)
                            return ()
        _ -> putStrLn usageMessage

if somestuff :: FilePath -> Double -> IO Int

That was what it did here.

Another common use is do nothing, as in

when :: Monad m => Bool -> m () -> m()
when cond action =
    if cond
        then action
        else return ()

>
> there seem to be several ways to ask functions to provide computations
> and require specific ways to get access to them.



More information about the Beginners mailing list