[Haskell-cafe] Database.postgreSQL.Simple - ambigious type

Hartmut Pfarr hartmut0407 at googlemail.com
Sun Aug 18 02:12:25 CEST 2013


... thx all for helping. Now the coding works: it puts the following out.
Kind regards
Hartmut


*Main> main
Only {fromOnly = 4}
------------------------------
Only {fromOnly = 101}
Only {fromOnly = 102}
Only {fromOnly = 103}
------------------------------
blub 101 51
blub 102 52
blub 103 53


The Coding is:

-- PostgreSQL-Simple test

{-# LANGUAGE OverloadedStrings #-}

import Database.PostgreSQL.Simple
import Data.Foldable
import qualified Data.Text as Text

myconn :: ConnectInfo
myconn = defaultConnectInfo {
             connectUser = "test",
             connectPassword = "test",
             connectDatabase = "test"}

db_calc :: (FromRow a) => IO [a]
db_calc = do
   conn <- connect myconn
   query_ conn "select 2 + 2"

hr :: IO ()
hr = putStrLn "------------------------------"

main :: IO ()
main = do
   conn <- connect myconn

   -- Let Database calculate 2+2
   x1 <- db_calc
   forM_ x1 $ \h ->
     putStrLn $ show (h :: Only Int)

   -- Select single integer column
   hr; x2 <- query_ conn "select aaa from aaa"
   forM_ x2 $ \(col1) ->
     putStrLn $ show (col1 :: Only Int)

   -- select integer and text columns together
   hr; x3 <- query_ conn "select aaa,bbb,textcol from aaa"
   forM_ x3 $ \(int_col_1,int_col_2,text_col_3) ->
     putStrLn $
       Text.unpack text_col_3 ++ " "
       ++ show (int_col_1 :: Int) ++ " "
       ++ show (int_col_2 :: Int)

   return ()



On 08/18/2013 12:12 AM, Brandon Allbery wrote:
> On Sat, Aug 17, 2013 at 5:59 PM, Hartmut Pfarr
> <hartmut0407 at googlemail.com <mailto:hartmut0407 at googlemail.com>> wrote:
>
>        query_ conn "select 2 + 2"
>
>     I've no errors any more.
>     But: I don't see any result (for sure, it is not coeded yet)
>
>
> Yes, because you're not capturing it; it's the return value from
> `query_`, which you are throwing away above instead of capturing with
> some kind of `res <- query_ ...`. Again, see that section of the
> documentation I pointed to for how to get results.
>
> --
> brandon s allbery kf8nh                               sine nomine associates
> allbery.b at gmail.com <mailto:allbery.b at gmail.com> ballbery at sinenomine.net
> <mailto:ballbery at sinenomine.net>
> unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net





More information about the Haskell-Cafe mailing list