Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
        beginners-requ...@haskell.org

You can reach the person managing the list at
        beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1.  database question (Gaius Hammond)
   2. Re:  database question (Daniel Fischer)
   3. Re:  database question (Gaius Hammond)
   4. Re:  database question (Daniel Fischer)
   5. Re:  The cost of generality,      or how expensive is realToFrac?
      (Greg)


----------------------------------------------------------------------

Message: 1
Date: Sat, 18 Sep 2010 19:40:58 +0100
From: Gaius Hammond <ga...@gaius.org.uk>
Subject: [Haskell-beginners] database question
To: Haskell Beginners List <beginners@haskell.org>
Message-ID: <2351cb72-36c6-411d-b0c8-3cc33bb0c...@gaius.org.uk>
Content-Type: text/plain; charset=US-ASCII; format=flowed; delsp=yes

Hi all,



I am trying to write the simplest possible database program in a  
monadic style. The aim of the program is to connect to the database,  
run a query, then print the results. My approach is


- use the Reader monad to pass around the connection handle (lda) to  
the database
- use the Writer monad to store the result set (rs) on its way back  
out - converted into [String] (one String per row)



My code is:



module Main where

import Control.Monad.Reader
import Control.Monad.Writer
import Database.HDBC
import Database.HDBC.Sqlite3

runDbApp lda f =
   do (a, rs) <- runWriterT (runReaderT f lda)
      return rs

doQuery::MonadIO m => ReaderT Connection (WriterT [String] m) ()
doQuery = do
   lda <- ask -- get the database handle from the Reader
   rs <- quickQuery lda "select datetime ('now')" []

   let rs' = map convRow rs
   mapM_ tell rs' -- store the results in the Writer

   where convRow [x] = (fromSql x)::String

main = handleSqlError $ do
   lda <- connectSqlite3 "test.db"
   rs <- runDbApp lda $
              doQuery

   mapM_ putStrLn rs

-- end of file




And the error is




home/gaius/Projects/MonadDb/MonadDb.hs:15:2:
     Couldn't match expected type `IO [[SqlValue]]'
            against inferred type `ReaderT
                                     Connection (WriterT [String] m)  
[[SqlValue]]'
     In a stmt of a 'do' expression:
         rs <- quickQuery lda "select datetime ('now')" []





Why does it think that that is the final expression of the function?  
Any advice greatly appreciated. I have been struggling with this since  
lunchtime!




Thanks,





G






------------------------------

Message: 2
Date: Sat, 18 Sep 2010 22:03:42 +0200
From: Daniel Fischer <daniel.is.fisc...@web.de>
Subject: Re: [Haskell-beginners] database question
To: beginners@haskell.org
Message-ID: <201009182203.42356.daniel.is.fisc...@web.de>
Content-Type: text/plain;  charset="iso-8859-1"

On Saturday 18 September 2010 20:40:58, Gaius Hammond wrote:
> Hi all,
>
>
>
> I am trying to write the simplest possible database program in a
> monadic style. The aim of the program is to connect to the database,
> run a query, then print the results. My approach is
>
>
> - use the Reader monad to pass around the connection handle (lda) to
> the database
> - use the Writer monad to store the result set (rs) on its way back
> out - converted into [String] (one String per row)
>
>
>
> My code is:
>
>
>
> module Main where
>
> import Control.Monad.Reader
> import Control.Monad.Writer
> import Database.HDBC
> import Database.HDBC.Sqlite3
>
> runDbApp lda f =
>    do (a, rs) <- runWriterT (runReaderT f lda)
>       return rs
>
> doQuery::MonadIO m => ReaderT Connection (WriterT [String] m) ()
> doQuery = do
>    lda <- ask -- get the database handle from the Reader
>    rs <- quickQuery lda "select datetime ('now')" []
>
>    let rs' = map convRow rs
>    mapM_ tell rs' -- store the results in the Writer
>
>    where convRow [x] = (fromSql x)::String
>
> main = handleSqlError $ do
>    lda <- connectSqlite3 "test.db"
>    rs <- runDbApp lda $
>               doQuery
>
>    mapM_ putStrLn rs
>
> -- end of file
>
>
>
>
> And the error is
>
>
>
>
> home/gaius/Projects/MonadDb/MonadDb.hs:15:2:
>      Couldn't match expected type `IO [[SqlValue]]'
>             against inferred type `ReaderT
>                                      Connection (WriterT [String] m)
> [[SqlValue]]'
>      In a stmt of a 'do' expression:
>          rs <- quickQuery lda "select datetime ('now')" []
>
>
>
>
>
> Why does it think that that is the final expression of the function?

It doesn't, but you said the do-expression had type
ReaderT Connection (WriterT [String] m) ()
while

quickQuery :: IConnection conn =>
                      conn -> String -> [SqlValue] -> IO [[SqlValue]]

The types don't match, hence the error. But you have a MonadIO constraint, 
so

    rs <- liftIO $ quickQuery ...

should fix it.

> Any advice greatly appreciated. I have been struggling with this since
> lunchtime!
>

Hopefully it didn't stop you from eating.

Cheers,
Daniel



------------------------------

Message: 3
Date: Sat, 18 Sep 2010 21:30:46 +0100
From: Gaius Hammond <ga...@gaius.org.uk>
Subject: Re: [Haskell-beginners] database question
To: Daniel Fischer <daniel.is.fisc...@web.de>
Cc: beginners@haskell.org
Message-ID: <7c43e05f-3480-4e54-a06a-f1f053c3b...@gaius.org.uk>
Content-Type: text/plain; charset=US-ASCII; format=flowed; delsp=yes


On 18 Sep 2010, at 21:03, Daniel Fischer wrote:

>>
>>
>> Why does it think that that is the final expression of the function?
>
> It doesn't, but you said the do-expression had type
> ReaderT Connection (WriterT [String] m) ()
> while
>
> quickQuery :: IConnection conn =>
>                      conn -> String -> [SqlValue] -> IO [[SqlValue]]
>
> The types don't match, hence the error. But you have a MonadIO  
> constraint,
> so
>
>    rs <- liftIO $ quickQuery ...
>
> should fix it.
>


Aha! It does indeed, thanks :-)



I had assumed that with the rs <- quickQuery I was getting the  
[[SqlValue]] "out" of the IO Monad - but I have to lift it into the IO  
Monad first, since I am in a monadic context? This would be the non- 
monadic version




module Main where

import Database.HDBC
import Database.HDBC.Sqlite3

main:: IO ()
main = do lda <- connectSqlite3 "test.db"
           rs <- quickQuery lda "select datetime ('now')" []

           mapM_ putStrLn (map convRow rs)
             where convRow [x] = (fromSql x)::String

-- EOF



Oh, but I am already in the IO monad there aren't I.... And doQuery  
*isn't* but I have declared that it *should be* (e.g. an instance of  
typeclass MonadIO). Is that accurate?




>> Any advice greatly appreciated. I have been struggling with this  
>> since
>> lunchtime!
>>
>
> Hopefully it didn't stop you from eating.



Nothing could do that :-)



Cheers,




G









------------------------------

Message: 4
Date: Sat, 18 Sep 2010 22:49:41 +0200
From: Daniel Fischer <daniel.is.fisc...@web.de>
Subject: Re: [Haskell-beginners] database question
To: Gaius Hammond <ga...@gaius.org.uk>
Cc: beginners@haskell.org
Message-ID: <201009182249.41831.daniel.is.fisc...@web.de>
Content-Type: text/plain;  charset="iso-8859-1"

On Saturday 18 September 2010 22:30:46, Gaius Hammond wrote:
> On 18 Sep 2010, at 21:03, Daniel Fischer wrote:
> >> Why does it think that that is the final expression of the function?
> >
> > It doesn't, but you said the do-expression had type
> > ReaderT Connection (WriterT [String] m) ()
> > while
> >
> > quickQuery :: IConnection conn =>
> >                      conn -> String -> [SqlValue] -> IO [[SqlValue]]
> >
> > The types don't match, hence the error. But you have a MonadIO
> > constraint,
> > so
> >
> >    rs <- liftIO $ quickQuery ...
> >
> > should fix it.
>
> Aha! It does indeed, thanks :-)
>
>
>
> I had assumed that with the rs <- quickQuery I was getting the
> [[SqlValue]] "out" of the IO Monad

Sort of, but only in a do-block of type IO something, you had it in a do-
block of type

ReaderT Connection (WriterT [String] m) something

There it doesn't type-check. Remember,

do a <- act
   otherAct a

is syntactic sugar for

act >>= otherAct

The type of (>>=) says the monads on both sides must be the same.

> - but I have to lift it into the IO
> Monad first, since I am in a monadic context?

No, you have to lift the IO-action (quickQuery args) into the MonadIO
ReaderT Connection (WriterT [String] m),

liftIO :: MonadIO m => IO a -> m a

lifts IO-actions to another monad.

> This would be the non-
> monadic version
>
>
>
>
> module Main where
>
> import Database.HDBC
> import Database.HDBC.Sqlite3
>
> main:: IO ()
> main = do lda <- connectSqlite3 "test.db"
>            rs <- quickQuery lda "select datetime ('now')" []
>
>            mapM_ putStrLn (map convRow rs)
>              where convRow [x] = (fromSql x)::String
>
> -- EOF
>
>
>
> Oh, but I am already in the IO monad there aren't I.

Yup, in main, you're in IO.

> ... And doQuery
> *isn't* but I have declared that it *should be* (e.g. an instance of
> typeclass MonadIO). Is that accurate?
>

No, MonadIO says, you can run IO-actions from inside that monad, but you 
have to lift them in order to run them (except the MonadIO you use is IO 
itself). You said that you wanted to be able to do that, but forgot the 
lifting.

> >> Any advice greatly appreciated. I have been struggling with this
> >> since
> >> lunchtime!
> >
> > Hopefully it didn't stop you from eating.
>
> Nothing could do that :-)

Glad to read that.



------------------------------

Message: 5
Date: Sat, 18 Sep 2010 17:41:36 -0700
From: Greg <gregli...@me.com>
Subject: Re: [Haskell-beginners] The cost of generality,        or how
        expensive is realToFrac?
To: beginners@haskell.org
Message-ID: <4eea6603-57e5-4f1f-a53c-4a87205ba...@me.com>
Content-Type: text/plain; charset="us-ascii"

> It would be interesting to see what core GHC produces for that (you can get 
> the core with the `-ddump-simpl' command line flag [redirect stdout to a 
> file] or with the ghc-core tool [available on hackage]).
> If it runs as fast as realToFrac :: Double -> Float (with optimisations), 
> GHC must have rewritten realToFrac to double2Float# and it should only do 
> that if there are rewrite rules for GLclampf.

I'm not sure if you literally meant you wanted to see the output or not, but 
I've attached a zip of the dump files and my simple source file.  The dump file 
naming is cryptic, but the first letters refer to the definition of 'convert' 
where:

fTF:   use the floatToFloat function in the source file
rTF:   use the standard realToFrac 
fRtR: use (fromRational . toRational)

The next three characters indicate the type signature of convert:

d2f: Double -> Float
d2g: Double -> GL.GLclampf

I'd summarize the results, but apparently I took the blue pill and can't make 
heads or tails of what I'm seeing in the dump format...

> In that case, the problem is probably that GHC doesn't see the realToFrac 
> applications because they're too deeply wrapped in your coordToCoord2D 
> calls.

> If that is the problem, it might help to use {-# INLINE #-} pragmas on 
> coordToCoord2D, fromCartesian2D and toCartesian2D.
> Can you try with realToFrac and the {-# INLINE #-} pragmas?

I tried inlining the functions you suggest with little effect.  The realToFrac 
version (in this case I just set floatToFloat=realToFrac to save the search and 
replace effort) is just too heavily loaded to see any difference at all (98+% 
of CPU is spent in realToFrac).  The same inlining using my definition of 
floatToFloat gave me a 10% improvement from 50% -> 46% of the CPU spent in 
floatToFloat and an inverse change in allocation to match.

Best I can tell, the inlining is being recognized, but just not changing much.

>> 
>> And still ran faster than floatToFloat.  However there's no denying that
>> floatToFloat runs *much* faster than realToFrac in the larger
>> application.  Profiling shows floatToFloat taking about 50% of my CPU
> 
> That's too much for my liking, a simple conversion from Double to Float 
> shouldn't take long, even if the Float is wrapped in newtypes (after all, 
> the newtypes don't exist at runtime).

Agreed.  The rest of the application right now isn't doing a lot of work yet 
though-- I'm generating (pre-calculating, if Haskell is doing it's job) a list 
of 360*180 points on a sphere and dumping that to OpenGL which should be doing 
most of the dirty work in hardware.  I'm not entirely sure why floatToFloat 
recalculates every iteration and isn't just cached, but I'm guessing it's 
because the floatToFloat is being done in an OpenGL callback within the IO 
monad.  Eventually I'll be providing time-varying data anyway, so the 
conversions will have to be continuously recalculated in the end.  

That comes out to 65000 conversions every 30ms, or about 2 million conversions 
a second.  I'd probably just leave it at that except, as you've demonstrated, 
there is at least a factor of 3 or 4 to be gained somehow-- realToFrac can 
provide it under the right conditions.

>> {-# RULES
>> "floatToFloat/id" floatToFloat=id
>> "floatToFloat x2" floatToFloat . floatToFloat = floatToFloat
>>  #-}
>> 
>> Neither of which seems to fires in this application,
> 
> GHC reports fired rules with -ddump-simpl-stats.
> Getting rules to fire is a little brittle, GHC does not try too hard to 
> match expressions with rules, and if several rules match, it chooses one 
> arbitrarily, so your rules may have been missed because the actual code 
> looked different (perhaps because other rewrite rules fired first).

Yeah, I've been looking at the -ddump-simp-stats output.  If I'm reading the 
documentation right, rules are enabled simply by invoking ghc with -O or -O2, 
right?  I'm now not convinced any of my rewrite rules are firing-- or at least 
I can't seem to get them to again.

>> I get a compile time error that I can't make sense of.  It's asking me
>> to put a context on my rule, but I can't find any references on how to
>> do that...
>> 
>> -----------
>> 
>>     Could not deduce (Num a)
>>       from the context (Coord2D (Vertex2 a), Coord2D (a, a))
>>       arising from a use of `pair2vertex'
>>                    at GCB/OpenGL/Geometry.hs:32:40-50
>>     Possible fix:
>>       add (Num a) to the context of the RULE "coordToCoord2D/p2v2"
>>     In the expression: pair2vertex
>>     When checking the transformation rule "coordToCoord2D/p2v2"
> 
> Yes, there's a Num constraint on pair2vertex, but not on coordToCoord2D, so 
> it's not type correct.
> You could try removing the Num constraint from pair2vertex or add the 
> constraint to the rule,
> 
> {-# RULES
> "coordToCoord2D/p2v2" forall a. Num a =>  (coordToCoord2D :: (a,a) -> 
> GL.Vertex2 a) = pair2vertex
>   #-}
> 
> (well, I don't know whether that's the correct way, but you can try).

No, that doesn't do it.  I tried a few variations on that and it always chokes 
on the => symbol or whatever other syntax I try to use.  The Num constraint was 
added because it was needed on related functions (3 element vertices where the 
z was stuffed with 0, for example), so I got rid of those and the Num 
constraint.  Doesn't matter, the rule still doesn't fire...  =(

Cheers--
 Greg


-------------- next part --------------
A non-text attachment was scrubbed...
Name: TypeConversions.zip
Type: application/zip
Size: 8904 bytes
Desc: not available
Url : 
http://www.haskell.org/pipermail/beginners/attachments/20100918/ad811812/TypeConversions.zip

------------------------------

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 27, Issue 43
*****************************************

Reply via email to