[Haskell-beginners] Re: ghci access to .hs functions
MAN
elviotoccalino at gmail.com
Thu Aug 12 11:00:44 EDT 2010
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 <byorgey at seas.upenn.edu> 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.
>
>
>
More information about the Beginners
mailing list