Re: [Haskell-cafe] Re: Type classes and definite types

2005-05-11 Thread Krasimir Angelov
Hi Bryn Keller,

The solution for your problem is very simple. You just have to fetch
all values as strings. In this way the library will do all required
conversions for you.

printRow stmt = do
  id <- getFieldValue stmt "ID"
  code <- getFieldValue stmt "Code"
  name <- getFieldValue stmt "Name"
 putStrLn (unwords [id, code, name])


Cheers,
  Krasimir


On 5/6/05, Bryn Keller <[EMAIL PROTECTED]> wrote:
> Max Vasin wrote:
> 
> >Bryn Keller <[EMAIL PROTECTED]> writes:
> >
> >
> >
> >>Hi Max,
> >>
> >>
> >Hello Bryn,
> >
> >
> >
> >>Thanks for pointing this out. It's odd that I don't see that anywhere
> >>in the docs at the HToolkit site:
> >>http://htoolkit.sourceforge.net/doc/hsql/Database.HSQL.html but GHC
> >>certainly believes it exists. However, this doesn't actually solve the
> >>problem. Substituting toSqlValue for show in printRow' gives the same
> >>compile error:
> >>
> >>Main.hs:22:18:
> >>Ambiguous type variable `a' in the constraint:
> >>  `SqlBind a' arising from use of `getFieldValue' at Main.hs:22:18-30
> >>Probable fix: add a type signature that fixes these type variable(s)
> >>
> >>So, like with (show (read s)), we still can't use the function until
> >>we've established a definite type for the value, not just a type
> >>class.
> >>
> >>
> >Yeah...
> >Some more RTFSing shows that we have the
> >
> >getFieldValueType :: Statement -> String -> (SqlType, Bool)
> >
> >which allows us to write
> >
> >printRow stmt = do (id :: Int) <- getFieldValue stmt "ID"
> >   let (codeType, _) = getFieldValueType stmt "Code"
> >   codestr <- case codeType of
> >   SqlChar _ -> do (c :: String) <- 
> > getFieldValue stmt "Code"
> >   return (toSqlValue c)
> >   SqlInteger -> do (i :: Int) <- 
> > getFieldValue stmt "Code"
> >return (toSqlValue i)
> >   -- etc for all SqlType data constructors
> >   putStrLn (unwords [show id, codestr])
> >
> >At least it compiles. But it's ugly :-(
> >
> >
> Ah, good point! Ugly it may be, but at least it works. Thanks for the idea!
> 
> Bryn
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Type classes and definite types

2005-05-06 Thread Bryn Keller
Max Vasin wrote:
Bryn Keller <[EMAIL PROTECTED]> writes:
 

Hi Max,
   

Hello Bryn,
 

Thanks for pointing this out. It's odd that I don't see that anywhere
in the docs at the HToolkit site:
http://htoolkit.sourceforge.net/doc/hsql/Database.HSQL.html but GHC
certainly believes it exists. However, this doesn't actually solve the
problem. Substituting toSqlValue for show in printRow' gives the same
compile error:
Main.hs:22:18:
   Ambiguous type variable `a' in the constraint:
 `SqlBind a' arising from use of `getFieldValue' at Main.hs:22:18-30
   Probable fix: add a type signature that fixes these type variable(s)
So, like with (show (read s)), we still can't use the function until
we've established a definite type for the value, not just a type
class.
   

Yeah... 
Some more RTFSing shows that we have the 

getFieldValueType :: Statement -> String -> (SqlType, Bool)
which allows us to write
printRow stmt = do (id :: Int) <- getFieldValue stmt "ID"
  let (codeType, _) = getFieldValueType stmt "Code"
  codestr <- case codeType of
  SqlChar _ -> do (c :: String) <- getFieldValue stmt 
"Code"
  return (toSqlValue c)
  SqlInteger -> do (i :: Int) <- getFieldValue stmt 
"Code"
   return (toSqlValue i)
  -- etc for all SqlType data constructors
  putStrLn (unwords [show id, codestr])
At least it compiles. But it's ugly :-( 
 

Ah, good point! Ugly it may be, but at least it works. Thanks for the idea!
Bryn
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Type classes and definite types

2005-05-06 Thread Max Vasin
Bryn Keller <[EMAIL PROTECTED]> writes:

> Hi Max,
Hello Bryn,

> Thanks for pointing this out. It's odd that I don't see that anywhere
> in the docs at the HToolkit site:
> http://htoolkit.sourceforge.net/doc/hsql/Database.HSQL.html but GHC
> certainly believes it exists. However, this doesn't actually solve the
> problem. Substituting toSqlValue for show in printRow' gives the same
> compile error:
>
> Main.hs:22:18:
> Ambiguous type variable `a' in the constraint:
>   `SqlBind a' arising from use of `getFieldValue' at Main.hs:22:18-30
> Probable fix: add a type signature that fixes these type variable(s)
>
> So, like with (show (read s)), we still can't use the function until
> we've established a definite type for the value, not just a type
> class.
Yeah... 
Some more RTFSing shows that we have the 

getFieldValueType :: Statement -> String -> (SqlType, Bool)

which allows us to write

printRow stmt = do (id :: Int) <- getFieldValue stmt "ID"
   let (codeType, _) = getFieldValueType stmt "Code"
   codestr <- case codeType of
   SqlChar _ -> do (c :: String) <- 
getFieldValue stmt "Code"
   return (toSqlValue c)
   SqlInteger -> do (i :: Int) <- getFieldValue 
stmt "Code"
return (toSqlValue i)
   -- etc for all SqlType data constructors
   putStrLn (unwords [show id, codestr])

At least it compiles. But it's ugly :-( 

--
WBR,
Max Vasin.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Type classes and definite types

2005-05-05 Thread Bryn Keller

Max Vasin wrote:
Bryn Keller <[EMAIL PROTECTED]> writes:
 

Hi folks,
   

Hello,
[skip]
 

The problem is that getFieldValue returns a value of type (SqlBind a)
=> a. That is, there's no type information associated with this return
value other than it's a valid  SQL value. There are no operations in
the SqlBind class, it's just a marker as near as I can tell. 
   

As of HSQL 1.4 this class has method 
toSqlValue :: a -> String
which probably can help you (I really don't know).

Some RTFSing shows that in most cases toSqlValue is implemented with show.
 

Hi Max,
Thanks for pointing this out. It's odd that I don't see that anywhere in 
the docs at the HToolkit site: 
http://htoolkit.sourceforge.net/doc/hsql/Database.HSQL.html but GHC 
certainly believes it exists. However, this doesn't actually solve the 
problem. Substituting toSqlValue for show in printRow' gives the same 
compile error:

Main.hs:22:18:
   Ambiguous type variable `a' in the constraint:
 `SqlBind a' arising from use of `getFieldValue' at Main.hs:22:18-30
   Probable fix: add a type signature that fixes these type variable(s)
So, like with (show (read s)), we still can't use the function until 
we've established a definite type for the value, not just a type class.

Bryn
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Type classes and definite types

2005-05-05 Thread Max Vasin
Bryn Keller <[EMAIL PROTECTED]> writes:

> Hi folks,
Hello,
[skip]
> The problem is that getFieldValue returns a value of type (SqlBind a)
> => a. That is, there's no type information associated with this return
> value other than it's a valid  SQL value. There are no operations in
> the SqlBind class, it's just a marker as near as I can tell. 
As of HSQL 1.4 this class has method 
toSqlValue :: a -> String
which probably can help you (I really don't know).

Some RTFSing shows that in most cases toSqlValue is implemented with show.

--
WBR,
Max Vasin.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe