Re: [Haskell-cafe] Code review: efficiency question

2006-05-03 Thread Brian Hulley

Bulat Ziganshin wrote:

[ideas including reverseMapM_]
you will laugh, but speed of your two solutions depends on so many
factors (including size of CPU cache) that noone can say that is
better in general. although for small lists reverseMapM_ should be
faster than reverse+mapM. what will be faster - using of higher-order
function or direct recursion, i can't say, it's a really
counter-intuitive area of ghc optimizer :)

of course, i don't think that all that really matters for your program
(drawing should anyway need much more time than looping). just use
higher-level approach (that makes code simpler to write, understand
and maintain) and don't bother your mind :)


Hi Bulat!
Thanks for the suggestions about reverseMapM_ etc.
It seems that since the speeds of the two solutions can be relatively 
faster/slower on different platforms/CPUs I might as well just use the 
combination of existing functions mapM_ and reverse at the moment to get 
readable code with the least amount of effort :-)


Best regards, Brian. 


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


Re: [Haskell-cafe] Code review: efficiency question

2006-05-03 Thread Josef Svenningsson

Brian,

You might also want to take a look at the list fusion functionality in
GHC which often can help optimize your programs when programming with
lists.
http://www.haskell.org/ghc/docs/latest/html/users_guide/rewrite-rules.html#id3153234
It doesn't help in your particular program but it might be usable for
you in the future.

Cheers,

/Josef

On 5/3/06, Brian Hulley [EMAIL PROTECTED] wrote:

Bulat Ziganshin wrote:
 [ideas including reverseMapM_]
 you will laugh, but speed of your two solutions depends on so many
 factors (including size of CPU cache) that noone can say that is
 better in general. although for small lists reverseMapM_ should be
 faster than reverse+mapM. what will be faster - using of higher-order
 function or direct recursion, i can't say, it's a really
 counter-intuitive area of ghc optimizer :)

 of course, i don't think that all that really matters for your program
 (drawing should anyway need much more time than looping). just use
 higher-level approach (that makes code simpler to write, understand
 and maintain) and don't bother your mind :)

Hi Bulat!
Thanks for the suggestions about reverseMapM_ etc.
It seems that since the speeds of the two solutions can be relatively
faster/slower on different platforms/CPUs I might as well just use the
combination of existing functions mapM_ and reverse at the moment to get
readable code with the least amount of effort :-)

Best regards, Brian.

___
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


[Haskell-cafe] Re: Optimizing locking with MVars

2006-05-03 Thread Simon Marlow

This is interesting, thanks.

I propose to add INLINE pragmas to withMVar and friends.

Having an interface for simple locks sounds like a good idea to me. 
Would you like to send a patch?


This won't affect Handle I/O unfortunately, because we need block to 
protect against asynchronous exceptions.  I'm still not certain you 
won't need that in the stream library, too: check any stateful code (eg. 
buffering) and imagine what happens if an exception is raised at an 
arbitrary point.


Cheers,
Simon

Bulat Ziganshin wrote:


Main reason of slowness of existing Handle-based I/O in GHC is locking
around each operation. it is especially bad for simple char-at-a-time
I/O where 99% of time spent on locking and unlocking.

To be exact, on my CPU, hPutChar for 100mb file requires 150 seconds,
while hGetChar for the same file is only 100 seconds long. it seems
that former use 3 locking operations and later 2 ones, because my own
vGetChar/vPutChar implementations both requires 52 seconds, of those
only about one second is real work and rest is just `withMVar`
expenses.

Until now, i thought that this 0.5 ms (about 1000 primitive CPU
operations) on each withMVar is pure time required to perform
takeMVar+putMVar operations. But yesterday i investigated this problem
deeper and results was amazing!

First, i just made local copy of `withMVar` and added INLINE to it:

import Control.Exception as Exception
{-# INLINE inlinedWithMVar #-}
inlinedWithMVar :: MVar a - (a - IO b) - IO b
inlinedWithMVar m io =
  block $ do
a - takeMVar m
b - Exception.catch (unblock (io a))
(\e - do putMVar m a; throw e)
putMVar m a
return b


Second, i've developed my own simplified version of this procedure.
Here i should say that my library uses MVar () field to hold lock
and separate immutable data field with actual data locked:

data WithLocking h = WithLocking h !(MVar ())

This allowed me to omit block/unblock operation and develop the
following faster analog of withMVar:

lock (WithLocking h mvar) action = do
  Exception.catch (do takeMVar mvar
   result - action h   
   putMVar mvar ()  
   return res   
  ) 
  (\e - do tryPutMVar mvar (); throw e)


And as third variant i tried exception-unsafe variant of `withMVar`:

unsafeWithMVar :: MVar a - (a - IO b) - IO b
unsafeWithMVar m io = do
a - takeMVar m
b - io a
putMVar m a
return b


And now are results:

withMVar52 seconds
inlinedWithMVar 38 seconds
lock20 seconds
unsafeWithMVar  10 seconds


So,

1) `withMVar` can be made significantly faster just by attaching
INLINE pragma to it. until GHC includes this patch, you can just make
local copy of this procedure (it's implementation is
compiler-independent) and use INLINE pragma for this local copy

2) if MVar is used only to protect some immutable data from
simultaneous access, it's use can be made significantly faster by
using above-mentioned WithLocking type constructor together with
'lock' function. I hope that this mechanism will go into future
Haskell implementations and in particular it will be used in my own
Streams library and in new DiffArray implementation (that is a part
of ArrayRef library)

3) For simple programs that don't catch exceptions anyway, this
excessive protection is just meaningless. they can use
'unsafeWithMVar' to work as fast as possible. i mean in particular
shootout-like benchmarks. it is also possible to develop fast  safe
routines by using explicit unlocking (with 'tryPutMVar') in
higher-level exception handlers


and a more general conclusion. this case is a good demonstration of
significant performance loss due to using of higher-order functions. i
think that more aggressive inlining of high-order and polymorphic
functions should significantly speed up GHC-compiled programs.




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


RE: [Haskell-cafe] Is it possible to export module aliases?

2006-05-03 Thread Simon Peyton-Jones
Are you asking for the same thing as described under Permit qualified
exports on this Haskell Prime page?


http://haskell.galois.com/cgi-bin/haskell-prime/trac.cgi/wiki/ModuleSyst
em

Simon

| -Original Message-
| From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of
| Brian Hulley
| Sent: 27 April 2006 02:51
| To: Haskell-cafe
| Subject: [Haskell-cafe] Is it possible to export module aliases?
| 
| Hi -
| Given some large list of modules which need to be used qualified, I'd
like
| to be able to make a convenience module that I could use instead, and
which
| would export all these modules also qualified by an alias, ie:
| 
| module Top
|( module qualified Top.First as First
|, module qualified Top.Second as Second
|) where ...
| import qualified Top.First
| 
| so that I could then say:
| 
| import Top
| 
| main = do
|a - First.create ...
|b - Second.create ...
| 
| instead of having to always write:
| 
| import qualified Top.First as First
| import qualified Top.Second as Second
| -- this may be a *very* long list
| 
| in every module that uses the Top API.
| 
| The current workaround for this problem in the standard libraries
seems to
| be to always append the module name to the name of the function or
type or
| constructor (which is unfortunately, like record field names, not
local to
| the type but that's another story) eg by using createFirst,
createSecond
| etc, which seems a bit messy to me.
| 
| An alternative is to use the C preprocessor and #include a file
containing
| all the import declarations, but although ok, I'd prefer to be able
to
| express the code organization purely in Haskell itself.
| 
| This must be a very common issue so I'm wondering if anyone else has
some
| better ideas on how to solve it?
| 
| Thanks, Brian.
| 
| ___
| 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


[Haskell-cafe] Re: Am I lazy enough?

2006-05-03 Thread Spencer Janssen

ByteString's are strict in their contents, so when you do an
hGetContents you'll read the entire file into memory!  This negates
any laziness benefits right off the bat.  The trickiest part is the
lazy IO, you have to use unsafeInterleaveIO or something similar.

Below is a program that does approximately the same as yours.  Note
the getLinesLazily function.  I've only tested that it typechecks, I
haven't run it yet.


Spencer Janssen

-- Program begins here

import System.IO
import System.IO.Unsafe (unsafeInterleaveIO)

import qualified Data.ByteString.Char8 as B
import Data.ByteString.Char8 (ByteString)

main =
   getLinesLazily stdin = mapM B.putStrLn . relines 8

relines :: Int - [ByteString] - [ByteString]
relines n = go . map (\s - (s, B.count ',' s))
where
   go []   = []
   go [(s, _)] = [s]
   go ((s, x) : (t, y) : ss)
| x + y  n = s : go ((t, y) : ss)
| otherwise = go ((B.append s t, x + y) : ss)

getLinesLazily :: Handle - IO [ByteString]
getLinesLazily h = do
   eof - hIsEOF h
   if eof
   then return []
   else do
   l - B.hGetLine h
   ls - unsafeInterleaveIO $ getLinesLazily h
   return (l:ls)

-- Program ends here

On 5/3/06, Joel Reymont [EMAIL PROTECTED] wrote:

Folks,

I'm looking to use the following code to process a multi-GB text
file. I am using ByteStrings but there was a discussion today on IRC
about tail recursion, laziness and accumulators that made me wonder.

Is fixLines below lazy enough? Can it be made lazier?

 Thanks, Joel

---

module Main where

import IO
import System
import Numeric
import Data.Char
import Data.Word
import qualified Data.Map as M
import qualified Data.ByteString.Char8 as B
import Prelude hiding (lines)

grabTableInfo x = (tableId', (tableType, tableStakes))
 where (tableId:tableType:_:tableStakes:_) =
   B.split ',' x
   Just (tableId', _) = B.readInt tableId

lines = B.split '\n'

--- My Oracle ascii dump is 80 characters wide so some lines
--- are split. I need to skip empty lines and join lines
--- containing less than the required number of commas.

fixLines 0 lines = lines
fixLines _ [] = []
fixLines n (line:lines) =
 fixLines' lines line []
 where fixLines' [] str acc
   | B.count ',' str == n
   = acc ++ [str]
   | otherwise
   = acc
   fixLines' (x:xs) str acc
   | B.null str -- skip
   = fixLines' xs x acc
   | B.count ',' str  n -- join with next line
   = fixLines' xs (B.append str x) acc
   | otherwise
   = fixLines' xs x (acc ++ [str])

mkMap = M.fromList . map grabTableInfo . fixLines 20

loadTableInfo = do
   bracket (openFile game_info_tbl.csv ReadMode)
   (hClose)
   (\h - do
  c - B.hGetContents h
  return $ mkMap $ lines c)

--
http://wagerlabs.com/





___
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


[Haskell-cafe] NewBinary/ BinMem and IO monad

2006-05-03 Thread Marc Weber
I'm trying to write some true type library (implementing only the tables
I need at the moment).

When loading a font file it doesn't make sense to parse every table
which isn't needed. So lazyness of haskell would perfectly meet
requirements here.
My problem: NewBinary supports memory buffers. After loading a file to
mem it can't change anymore so I no longer need an IO monad.

It looks like this:

bh - readBinMem file
b::Word8 - get bh

Of cause I can't remove the monad here because bh contains an internal
pointer to the current position... but it might be done returning the
new pointer:
(bh2,b::Word8) = get bh ?

Then I would be able to lazily parse the tables eg: 

getTable1 bh = do
  bh = seek bh offset -- seek to the beginning of the table
  get binary data and build internal representation
  return list of glyph and outlines and ...

of cause this mem should be readonly then..

Would it make sense to implement this? Does it already exist?

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


Re: [Haskell-cafe] Re: Optimizing locking with MVars

2006-05-03 Thread John Meacham
On Wed, May 03, 2006 at 12:07:19PM +0100, Simon Marlow wrote:
 This won't affect Handle I/O unfortunately, because we need block to 
 protect against asynchronous exceptions.  I'm still not certain you 
 won't need that in the stream library, too: check any stateful code (eg. 
 buffering) and imagine what happens if an exception is raised at an 
 arbitrary point.

Is unlocking the lock really the right thing to do on an asynchronous
exception? A lock isn't a resource, it is a primitive needed to enforce
correctness of your program. You use them to protect critical sections
and chances are aborting a critical section at an arbitrary point would
leave your program in an incorrect state, just delaying your deadlock or
hiding the errors silently somewhere where they can bite you later.

hmmm... ever think asynchronous exceptions are more trouble then they
are worth...

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] NewBinary/ BinMem and IO monad

2006-05-03 Thread Bulat Ziganshin
Hello Marc,

Thursday, May 4, 2006, 2:21:58 AM, you wrote:

 getTable1 bh = do
   bh = seek bh offset -- seek to the beginning of the table
   get binary data and build internal representation
   return list of glyph and outlines and ...

just add unsafePerformIO:

getTable1 bh = unsafePerformIO $ do
  seek bh offset -- seek to the beginning of the table
  get binary data and build internal representation
  return list of glyph and outlines and ...


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re[2]: [Haskell-cafe] Re: Optimizing locking with MVars

2006-05-03 Thread Bulat Ziganshin
Hello John,

Thursday, May 4, 2006, 12:33:54 AM, you wrote:

 This won't affect Handle I/O unfortunately, because we need block to
 protect against asynchronous exceptions.  I'm still not certain you 
 won't need that in the stream library, too: check any stateful code (eg. 
 buffering) and imagine what happens if an exception is raised at an 
 arbitrary point.

 Is unlocking the lock really the right thing to do on an asynchronous
 exception? A lock isn't a resource, it is a primitive needed to enforce
 correctness of your program. You use them to protect critical sections
 and chances are aborting a critical section at an arbitrary point would
 leave your program in an incorrect state, just delaying your deadlock or
 hiding the errors silently somewhere where they can bite you later.

after Simon's message i thought about this problem. i found several
situations where restoring of locked file will be useful:

- using stdout and other standard handles. we may need to print error
message or just continue work despite the exception abandoned our
previous writing to stdout

- access to database. despite the exception arrived during previous
operation, we need to go further and just hSeek to the position of
next I/O operation



-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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