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

Hartmut Pfarr hartmut0407 at googlemail.com
Sat Aug 17 19:35:17 CEST 2013


Hello,

I've a problem connecting to my postgresql database.
Can You help me fix the ambigious type signature?

(The example is identical to the first 5-liner-example in the package 
documentation)

http://hackage.haskell.org/packages/archive/postgresql-simple/0.3.5.0/doc/html/Database-PostgreSQL-Simple.html

Kind regards
Hartmut

------------------------------------------------------------------------
{-# LANGUAGE OverloadedStrings #-}

import Database.PostgreSQL.Simple

main = do
   conn <- connect defaultConnectInfo
   query conn "select 2 + 2"
   return ()
------------------------------------------------------------------------
But this leads to error:
------------------------------------------------------------------------
Line 9: 1 error(s), 0 warning(s)

Couldn't match expected type `IO a0'
             with actual type `q0 -> IO [r0]'
In the return type of a call of `query'
Probable cause: `query' is applied to too few arguments
In a stmt of a 'do' block: query conn "select 2 + 2"
In the expression:
   do { conn <- connect defaultConnectInfo;
        query conn "select 2 + 2";
        return () }
------------------------------------------------------------------------
OK, I see, that a parameter q is missing.
I change the source code to

{-# LANGUAGE OverloadedStrings #-}

import Database.PostgreSQL.Simple

main = do
   conn <- connect defaultConnectInfo
   query conn "select 2 + 2" ( )      {- added ( ) here  -}
   return ()
------------------------------------------------------------------------
Now, I run into next error:
------------------------------------------------------------------------
Line 9: 1 error(s), 0 warning(s)

No instance for (FromRow r0) arising from a use of `query'
The type variable `r0' is ambiguous
Possible fix: add a type signature that fixes these type variable(s)
Note: there are several potential instances:
   instance (FromField a, FromField b) => FromRow (a, b)
     -- Defined in `Database.PostgreSQL.Simple.FromRow'
   instance (FromField a, FromField b, FromField c) =>
            FromRow (a, b, c)
     -- Defined in `Database.PostgreSQL.Simple.FromRow'
   instance (FromField a, FromField b, FromField c, FromField d) =>
            FromRow (a, b, c, d)
     -- Defined in `Database.PostgreSQL.Simple.FromRow'
   ...plus 10 others
In a stmt of a 'do' block: query conn "select 2 + 2" ()
In the expression:
   do { conn <- connect defaultConnectInfo;
        query conn "select 2 + 2" ();
        return () }
In an equation for `main':
     main
       = do { conn <- connect defaultConnectInfo;
              query conn "select 2 + 2" ();
              return () }





More information about the Haskell-Cafe mailing list