
in an effort to figure out type declarations i thought i'd let ghci do the work. so i wrote a program: import ... main = do ... func1 func2 now when i load this into ghci i can't to :t func1 etc and get a not in scope error however, if i put a return () onto the end of main: import ... main = do ... return () func1 func2 the functions are in scope of ghci and i can find out the types. so what is happening here? i understand that return is different in haskell than in other languages, but i don't understand just what it is doing. :( -- In friendship, prad ... with you on your journey Towards Freedom http://www.towardsfreedom.com (website) Information, Inspiration, Imagination - truly a site for soaring I's

It's hard to tell just looking at what you have given. Can you show us the exact contents of your .hs file? On Wed, Aug 11, 2010 at 01:17:09PM -0700, prad wrote:
in an effort to figure out type declarations i thought i'd let ghci do the work.
so i wrote a program:
import ... main = do ... func1 func2
now when i load this into ghci i can't to :t func1 etc and get a not in scope error
however, if i put a return () onto the end of main:
import ... main = do ... return () func1 func2
the functions are in scope of ghci and i can find out the types.
so what is happening here? i understand that return is different in haskell than in other languages, but i don't understand just what it is doing. :(
-- In friendship, prad
... with you on your journey Towards Freedom http://www.towardsfreedom.com (website) Information, Inspiration, Imagination - truly a site for soaring I's _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

On Thu, 12 Aug 2010 09:01:42 +0100
Brent Yorgey
Can you show us the exact contents of your .hs file? certainly! but now i take it all back! :( it's working fine without the return().
it compiles main when i :l or when i ghci the file from the command line. so now i think i'm delusional. :D :D anyway, here's some of the code below and i'll ask another question. in the function: -- edFil: edits a file with vim -- edFil :: String -> IO GHC.IO.Exception.ExitCode (not in scope error) edFil kV = rawSystem "vim" ["+source ~/.vim/ftplugin/html/HTML.vim",kV] i got the type from ghci, but if i actually put it in i get error: Not in scope: type constructor or class `GHC.IO.Exception.ExitCode' if i don't do the type definition that ghci gives me, everything compiles fine. so i don't understand the type definition, much less what's happening here. ====== import System (getArgs) import System.Cmd (rawSystem) import Data.List(elemIndices) import Database.HDBC import Database.HDBC.PostgreSQL (connectPostgreSQL) main = do args <- getArgs let act = head args conn <- connectPostgreSQL "host=localhost dbname=lohv user=pradmin" case act of "add" -> do kV1 <- dbDef conn upDbs conn (fromSql kV1) return () "upd" -> do upDbs conn (last args) return () "all" -> do gtKys conn return () _ -> putStrLn "add, upd num, all only!!" commit conn disconnect conn putStrLn "All Done!" return () -- bkS2L: break a string into a list of strings -- dC char delimiter; oS original string bkS2L :: (Char -> Bool) -> String -> [String] bkS2L dC [] = [] bkS2L dC oS = let (h,t) = break dC oS in h : case t of [] -> [] _:t -> bkS2L dC t -- dbDef: adds a default entry to db dbDef :: (IConnection conn) => conn -> IO SqlValue dbDef conn = do run conn "INSERT INTO main DEFAULT VALUES" [] ((r:z):zs) <- quickQuery conn "SELECT last_value from main_key_seq" [] return r -- edFil: edits a file with vim -- edFil :: String -> IO GHC.IO.Exception.ExitCode (not in scope error) edFil kV = rawSystem "vim" ["+source ~/.vim/ftplugin/html/HTML.vim",kV] -- gtInx: gets indices for each element of substring in string gtInx :: (Eq a) => [a] -> [a] -> [(a,[Int])] gtInx hL nL = map (\x -> (x,elemIndices x hL)) nL -- gtKys: gets all key values in database gtKys :: (IConnection conn) => conn -> IO [()] gtKys conn = do r <- quickQuery conn "SELECT key from main" [] let kL = concat $ map (map fromSql) r mapM (mkPag conn) kL ... ======= there are more functions, but it is all working fine. -- In friendship, prad ... with you on your journey Towards Freedom http://www.towardsfreedom.com (website) Information, Inspiration, Imagination - truly a site for soaring I's

On Thu, Aug 12, 2010 at 01:42:58AM -0700, prad wrote:
On Thu, 12 Aug 2010 09:01:42 +0100 Brent Yorgey
wrote: Can you show us the exact contents of your .hs file? certainly! but now i take it all back! :( it's working fine without the return().
it compiles main when i :l or when i ghci the file from the command line.
so now i think i'm delusional. :D :D
anyway, here's some of the code below and i'll ask another question. in the function:
-- edFil: edits a file with vim -- edFil :: String -> IO GHC.IO.Exception.ExitCode (not in scope error) edFil kV = rawSystem "vim" ["+source ~/.vim/ftplugin/html/HTML.vim",kV]
i got the type from ghci, but if i actually put it in i get error: Not in scope: type constructor or class `GHC.IO.Exception.ExitCode'
In order to be able to refer to a type you must import a module which exports it. However you are free to *use* a type without importing it, as long as you do not actually refer to it in a type signature. This is why your code works without the type signature. Just add import GHC.IO.Exception and then you will be able to give the type signature edFil :: String -> ExitCode -Brent

Hey prad, I was checking out your code and noticed a couple of things you could be interested to know. Your main will allways be 'IO ()' , but that doesn't mean you must sparkle 'return ()' all over the place :P Check this out: main = do args <- getArgs let act = head args conn <- connectPostgreSQL "host=localhost dbname=lohv user=pradmin" case act of "add" -> do kV1 <- dbDef conn upDbs conn (fromSql kV1) "upd" -> upDbs conn (last args) "all" -> gtKys conn _ -> putStrLn "add, upd num, all only!!" commit conn disconnect conn putStrLn "All Done!" I took the liberty of modifying your gtKys function: -- gtKys: gets all key values in database [NOTICE mapM_ for mapM] gtKys :: (IConnection conn) => conn -> IO () gtKys conn = do r <- quickQuery conn "SELECT key from main" [] let kL = concat $ map (map fromSql) r mapM_ (mkPag conn) kL Only if 'upDbs' return some value inside IO you'd replace their calls for " upDbs conn some >> return () ". Although I assume those statements are simple 'IO ()', just like 'putStrLn string' El jue, 12-08-2010 a las 01:42 -0700, prad escribió:
On Thu, 12 Aug 2010 09:01:42 +0100 Brent Yorgey
wrote: Can you show us the exact contents of your .hs file? certainly! but now i take it all back! :( it's working fine without the return().
it compiles main when i :l or when i ghci the file from the command line.
so now i think i'm delusional. :D :D
anyway, here's some of the code below and i'll ask another question. in the function:
-- edFil: edits a file with vim -- edFil :: String -> IO GHC.IO.Exception.ExitCode (not in scope error) edFil kV = rawSystem "vim" ["+source ~/.vim/ftplugin/html/HTML.vim",kV]
i got the type from ghci, but if i actually put it in i get error: Not in scope: type constructor or class `GHC.IO.Exception.ExitCode'
if i don't do the type definition that ghci gives me, everything compiles fine.
so i don't understand the type definition, much less what's happening here.
====== import System (getArgs) import System.Cmd (rawSystem) import Data.List(elemIndices) import Database.HDBC import Database.HDBC.PostgreSQL (connectPostgreSQL)
main = do args <- getArgs let act = head args conn <- connectPostgreSQL "host=localhost dbname=lohv user=pradmin" case act of "add" -> do kV1 <- dbDef conn upDbs conn (fromSql kV1) return () "upd" -> do upDbs conn (last args) return () "all" -> do gtKys conn return () _ -> putStrLn "add, upd num, all only!!" commit conn disconnect conn putStrLn "All Done!" return ()
-- bkS2L: break a string into a list of strings -- dC char delimiter; oS original string bkS2L :: (Char -> Bool) -> String -> [String] bkS2L dC [] = [] bkS2L dC oS = let (h,t) = break dC oS in h : case t of [] -> [] _:t -> bkS2L dC t
-- dbDef: adds a default entry to db dbDef :: (IConnection conn) => conn -> IO SqlValue dbDef conn = do run conn "INSERT INTO main DEFAULT VALUES" [] ((r:z):zs) <- quickQuery conn "SELECT last_value from main_key_seq" [] return r
-- edFil: edits a file with vim -- edFil :: String -> IO GHC.IO.Exception.ExitCode (not in scope error) edFil kV = rawSystem "vim" ["+source ~/.vim/ftplugin/html/HTML.vim",kV]
-- gtInx: gets indices for each element of substring in string gtInx :: (Eq a) => [a] -> [a] -> [(a,[Int])] gtInx hL nL = map (\x -> (x,elemIndices x hL)) nL
-- gtKys: gets all key values in database gtKys :: (IConnection conn) => conn -> IO [()] gtKys conn = do r <- quickQuery conn "SELECT key from main" [] let kL = concat $ map (map fromSql) r mapM (mkPag conn) kL
...
=======
there are more functions, but it is all working fine.

On Thu, 12 Aug 2010 12:00:44 -0300
MAN
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 putting return() in the "all" worked (no idea why), 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 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!!" 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." 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. there seem to be several ways to ask functions to provide computations and require specific ways to get access to them. -- In friendship, prad ... with you on your journey Towards Freedom http://www.towardsfreedom.com (website) Information, Inspiration, Imagination - truly a site for soaring I's

The problem in the "all" case branch is that, although you applied the mapM-to-mapM_ modification, you didn't change the type signature of gtKys accordingly: mapM :: (a -> m b) -> m a -> m [b] mapM_ :: (a -> m b) -> m a -> m () In your case 'a' above is whatever 'fromSql' returns for your program (I can't infer it... which might explain the lengthy type signature), and 'b' is simply '()'. So 'b=()' which means the type of 'gtKys' is no longer: gtKys :: (IConnection conn) => conn -> IO [()] -- using 'mapM' gtKys :: (IConnection conn) => conn -> IO () -- using 'mapM_' Two more things to say: You should know that '()' is both a type AND a value... kind of strange. '()' designates a type of "things" (like 'Int' and 'Double' do for integers and double-precision numbers), but the kink is that the only "thing" of such type is a value known as 'unit' which is written (for good or bad) '()'. As a mental help... all functions in Control.Monad (and several other modules as well) that end in '_' "throw away" their results; meaning that they return 'unit' regardless of their action. "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." Pan, I think It's time for you to get serious with the monads XD I can't suggest anything, 'cause I read a whole lot before my brain started to understand any of it... but maybe you should check out articles, looking for real monad-related answers to your more general questions (in particular you seem to be getting hit by "getting a value out of a monad"). Try the en.wikibooks.org/wiki/Haskell or learnyouahaskell.org and skip to the sections where do-notation and monadic computations are discussed. Just rememeber: "Don't Panic". El jue, 12-08-2010 a las 13:18 -0700, prad escribió:
On Thu, 12 Aug 2010 12:00:44 -0300 MAN
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
putting return() in the "all" worked (no idea why), 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
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!!" 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."
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.
there seem to be several ways to ask functions to provide computations and require specific ways to get access to them.
-- In friendship, prad
... with you on your journey Towards Freedom http://www.towardsfreedom.com (website) Information, Inspiration, Imagination - truly a site for soaring I's _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

On Thursday 12 August 2010 22:18:11, prad wrote:
On Thu, 12 Aug 2010 12:00:44 -0300
MAN
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.
participants (4)
-
Brent Yorgey
-
Daniel Fischer
-
MAN
-
prad