Re: [Haskell-cafe] operating on a hundred files at once

2007-04-09 Thread Jefferson Heard
Thanks for the advice.  I'm not so much interested in performance here,
as this is just a one-off.  Disk thrashing or not, these files are only
a few hundred K apiece, and I can't imagine that the whole computation
will take more than a few minutes.  

My question is more about how to deal with the IO monad "pollution" of
all the data in a situation where you have N instances of IO [a] at step
1, and you have M computations to perform on those instances, which are
all monad-free.

-- Jeff

On Mon, 2007-04-09 at 22:24 +0400, Bulat Ziganshin wrote:
> Hello Jefferson,
> 
> Monday, April 9, 2007, 9:34:12 PM, you wrote:
> 
> if you have enough memory available, the fastest way is to read file
> to memory using bytestring, convert it into array of doubles,
> repeating this step for all files. then perform your computations. if
> you will try to read 100 files simultaneously, this may lead to
> extensive disk seeking or cpu cache trashing
> 
> ... even better, you should read one file, add its values to the
> accumulators, then read next file...
> 
> 
> > I have a series of NxM numeric tables I'm doing a quick
> > mean/variance/t-test etcetera on.  The cell t1 [i,j] corresponds exactly
> > to the cells t2..N [i,j], and so it's perfectly possible to read one
> > item at a time from each of the 100 files and compute the mean/variance
> > etcetera on all cells that way.  So what I propose to do is something
> > along the lines of:
> 
> > openAndProcess filename = 
> > f <- readFile filename
> > return (map (L.split ',') . lines $ f)
> 
> > main = do 
> > fs <- getArgs
> > let items = map (map read) . map openAndProcess fs 
> > in do print . map (map $ mean) items
> >   print . map (map $ variance) items
> 
> > How close am I to doing the right thing here? As I understand it, this
> > will result in one hundred IO [String] instances being returned by the
> > call to (map openAndProcess $ filenames).  Do I need to do something
> > special to lift (read), (mean), and (variance), or even (map) into the
> > IO monad so they can process the input as needed?
> 
> > Thanks in advance,
> > -- Jeff
> 
> > ___
> > 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] operating on a hundred files at once

2007-04-09 Thread Jefferson Heard
It is indeed!  Is that to be found in Control.Monad, I take it?

On Tue, 2007-04-10 at 08:50 +1000, Duncan Coutts wrote:
> On Mon, 2007-04-09 at 14:40 -0400, Jefferson Heard wrote:
> > Thanks for the advice.  I'm not so much interested in performance here,
> > as this is just a one-off.  Disk thrashing or not, these files are only
> > a few hundred K apiece, and I can't imagine that the whole computation
> > will take more than a few minutes.  
> > 
> > My question is more about how to deal with the IO monad "pollution" of
> > all the data in a situation where you have N instances of IO [a] at step
> > 1, and you have M computations to perform on those instances, which are
> > all monad-free.
> 
> Perhaps you want one of these functions:
> 
> sequence :: Monad m => [m a] -> m [a]
> 
> sequence_ :: Monad m => [m a] -> m ()
> 
> for example in the case of IO it's:
> 
> sequence :: [IO a] -> IO [a]
> sequence_ :: [IO a] -> IO ()
> 
> ie it takes a pure list of IO actions and sticks them together into one
> IO action, or to put it another way, it performs all the actions in
> sequence.
> 
> 
> Is this what you meant?
> 
> Duncan

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


Re: [Haskell-cafe] operating on a hundred files at once

2007-04-10 Thread Jefferson Heard
Thanks, Ketil.  I knew I could calcuate the mean in constant space, but
I didn't think about the variance.  Much appreciated.

On Tue, 2007-04-10 at 08:30 +0200, Ketil Malde wrote:
> On Tue, 2007-04-10 at 13:16 +1000, Duncan Coutts wrote:
> 
> > Note, that like in your original we read each file twice, once for the
> > mean and once for the variance. 
> 
> As an aside, you can calculate both mean and variance in one pass (and
> constant space) by calculating the sum of elements 'x', the sum of
> squared elements 'x2', and keeping track of the number of elements 'n'.
> 
>   mean = x/n
>   var  = (x2-mean*mean*n)/(n-1)
> 
> If you track the sum of cubed elements (x3) and the powers of four (x4),
> you also get kurtosis and skew in a similar manner.
> 
> -k

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


[Haskell-cafe] Reading/writing packed bytes from file

2007-06-19 Thread Jefferson Heard
I've read the documentation for some of the marshalling packages out
there for Haskell, and I'm left confused as to which one I should be
using and how to actually do what I want to do.   I have a file, a
little over 2gb, of packed data in the format

(recordcount) records of:

4-byte int (count),
(count) 2-byte unsigned shorts,
(count) 4-byte floats

all in little-endian order.  What I want to do is read each record
(lazily), and unpack it into Data.IntMap.IntMap Float where the unsigned
shorts become the keys and the 4-byte floats become the values.

Then I want to do a lot of interesting processing which we'll skip here,
and write back out packed data to a file in the format of

4-byte float,
4-byte float,
4-byte float

for each record. I need these output records to be four-byte C floats.
I've gotten as far as datatypes and a couple of signatures, but I can't
figure out the functions themselves that go with the signatures, and
then again, maybe I have the signatures wrong.  

-- 
import qualified Data.IntMap as M
import qualified Data.ByteString.Lazy.Char8 as B

data InputRecord = M.IntMap Float
data OutputRecord = (Float, Float, Float)

-- open a file as a lazy ByteString and break up the individual records
-- by reading the count variable, reading that many bytes times 
-- sizeof short + sizeof float into a lazy ByteString.
readRawRecordsFromFile :: String -> IO [B.ByteString] 


-- take a bytestring as returned by readRawRecordsFromFile and turn it
-- into a map.
decodeRawRecord :: B.ByteString -> M.IntMap Float
--

Can anyone help with how to construct these functions?  I'm going to
have to make a few passes over this file, so I'd like the IO to be as
fast as Haskelly possible.

-- Jeff




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


Re: [Haskell-cafe] Reading/writing packed bytes from file

2007-06-20 Thread Jefferson Heard
What about the Data.Binary module from the Hackage database?  I can call
C, no problem, but I hate to do something that's already been done.

On Wed, 2007-06-20 at 12:02 +1000, Donald Bruce Stewart wrote:
> jeff:
> > I've read the documentation for some of the marshalling packages out
> > there for Haskell, and I'm left confused as to which one I should be
> > using and how to actually do what I want to do.   I have a file, a
> > little over 2gb, of packed data in the format
> > 
> > (recordcount) records of:
> > 
> > 4-byte int (count),
> > (count) 2-byte unsigned shorts,
> > (count) 4-byte floats
> > 
> > all in little-endian order.  What I want to do is read each record
> > (lazily), and unpack it into Data.IntMap.IntMap Float where the unsigned
> > shorts become the keys and the 4-byte floats become the values.
> > 
> > Then I want to do a lot of interesting processing which we'll skip here,
> > and write back out packed data to a file in the format of
> > 
> > 4-byte float,
> > 4-byte float,
> > 4-byte float
> > 
> > for each record. I need these output records to be four-byte C floats.
> > I've gotten as far as datatypes and a couple of signatures, but I can't
> > figure out the functions themselves that go with the signatures, and
> > then again, maybe I have the signatures wrong.  
> > 
> > -- 
> > import qualified Data.IntMap as M
> > import qualified Data.ByteString.Lazy.Char8 as B
> > 
> > data InputRecord = M.IntMap Float
> > data OutputRecord = (Float, Float, Float)
> > 
> > -- open a file as a lazy ByteString and break up the individual records
> > -- by reading the count variable, reading that many bytes times 
> > -- sizeof short + sizeof float into a lazy ByteString.
> > readRawRecordsFromFile :: String -> IO [B.ByteString] 
> > 
> > 
> > -- take a bytestring as returned by readRawRecordsFromFile and turn it
> > -- into a map.
> > decodeRawRecord :: B.ByteString -> M.IntMap Float
> > --
> > 
> > Can anyone help with how to construct these functions?  I'm going to
> > have to make a few passes over this file, so I'd like the IO to be as
> > fast as Haskelly possible.
> > 
> > -- Jeff
> 
> Data.ByteString.Lazy.Char8.readFile should suffice for the IO.
> then use drop/take to split up the file in pieces if you know the length
> of each field.
> 
> For converting ByteString chunks to Floats, I'd probably call C for that.
> 
> -- Don

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


[Haskell-cafe] Odd lack of laziness

2007-06-21 Thread Jefferson Heard
Alright, I've been hacking away at what I posted the other day, and I
have something that works for files that will fit entirely into memory.
And then I figured out why I've been restricted to files that fit
entirely into memory...  One of my functions is causing the entire thing
to be read in, when, in the way I analyze the program, only a very small
portion of the file should be read in.  Here are the functions I've used
to test this problem...

import Data.Bits
import qualified Data.ByteString.Lazy as BS
import Foreign.C.Types
...

{-# INLINE decodeLengthBits #-}
decodeLengthBits :: BS.ByteString -> CInt
decodeLengthBits doc = (shift (pieces !! 3) 24) .|.
   (shift (pieces !! 2) 16) .|.
   (shift (pieces !! 1) 8) .|.
   (pieces !! 0)
   where pieces::[CInt] = map fromIntegral . BS.unpack . BS.take 4 $ doc

breakIntoDocuments :: RawDocument -> [RawDocument]
breakIntoDocuments f | BS.length f > 0 = if len > 0
 then (BS.take bytes f) :
  (breakIntoDocuments
 (BS.drop bytes f))
 else (breakIntoDocuments
 (BS.drop bytes f))
 | otherwise  = []
 where len = decodeLengthBits f
   bytes = fromIntegral (len * 2 + len * 4 + 4)


and a main function of:

main = do
 f <- B.readFile "Documents.bin"
 print (take 1 (breakIntoDocuments f))


Shouldn't the program only read in enough of the lazy byte-string to
create the first return value of breakIntoDocuments?  The return value
of decodeLengthBits is only 277.  I watched it, and it's reading in my
whole 2gb file...

-- Jeff


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


[Haskell-cafe] Allocating enormous amounts of memory and wondering why

2007-07-08 Thread Jefferson Heard
I'm using the Data.AltBinary package to read in a list of 4.8 million
floats and 1.6 million ints.  Doing so caused the memory footprint to
blow up to more than 2gb, which on my laptop simply causes the program
to crash.  I can do it on my workstation, but I'd really rather not,
because I want my program to be fairly portable.  

The file that I wrote out in packing the data structure was only 28MB,
so I assume I'm just using the wrong data structure, or I'm using full
laziness somewhere I shouldn't be.

I've tried compiling with profiling enabled, but I wasn't able to,
because the Streams package doesn't seem to have an option for compiling
with profiling.  I'm also a newbie to Cabal, so I'm probably just
missing something.  

The fundamental question, though is "Is there something wrong with how I
wrote the following function?"

binaryLoadDocumentCoordinates :: String -> IO (Ptr CFloat, [Int])
binaryLoadDocumentCoordinates path = do
  pointsH <- openBinaryFile (path ++ "/Clusters.bin") ReadMode
  coordinates <- get pointsH :: IO [Float]
  galaxies <- get pointsH :: IO [Int]
  coordinatesArr <- mallocArray (length coordinates)
  pokeArray coordinatesArr (map (fromRational . toRational) coordinates)
  return (coordinatesArr, galaxies)

I suppose in a pinch I could write a C function that serializes the
data, but I'd really rather not.  What I'm trying to do is load a bunch
of coordinates into a vertex array for OpenGL.  I did this for a small
30,000 item vertex array, but I need to be able to handle several
million vertices in the end.  

If I serialize an unboxed array instead of a list or if I do repeated
"put_" and "get" calls, will that help with the memory problem?

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


Re: [Haskell-cafe] Allocating enormous amounts of memory and wondering why

2007-07-08 Thread Jefferson Heard
By the way, I've confirmed it doesn't even make it past the call to 

coordinates <- get pointsH :: IO [Float]

It just runs for about 15 seconds and then all the memory is consumed.
I'm using a laptop with 2gb of RAM and a 2.0gHz processor, so I assume
the read shouldn't take that long, since on the wiki, AltBinary says it
can run at around 20-50MB/sec.  I assume I'm doing something *way* wrong
here...

On Sun, 2007-07-08 at 17:26 -0400, Jefferson Heard wrote:
> I'm using the Data.AltBinary package to read in a list of 4.8 million
> floats and 1.6 million ints.  Doing so caused the memory footprint to
> blow up to more than 2gb, which on my laptop simply causes the program
> to crash.  I can do it on my workstation, but I'd really rather not,
> because I want my program to be fairly portable.  
> 
> The file that I wrote out in packing the data structure was only 28MB,
> so I assume I'm just using the wrong data structure, or I'm using full
> laziness somewhere I shouldn't be.
> 
> I've tried compiling with profiling enabled, but I wasn't able to,
> because the Streams package doesn't seem to have an option for compiling
> with profiling.  I'm also a newbie to Cabal, so I'm probably just
> missing something.  
> 
> The fundamental question, though is "Is there something wrong with how I
> wrote the following function?"
> 
> binaryLoadDocumentCoordinates :: String -> IO (Ptr CFloat, [Int])
> binaryLoadDocumentCoordinates path = do
>   pointsH <- openBinaryFile (path ++ "/Clusters.bin") ReadMode
>   coordinates <- get pointsH :: IO [Float]
>   galaxies <- get pointsH :: IO [Int]
>   coordinatesArr <- mallocArray (length coordinates)
>   pokeArray coordinatesArr (map (fromRational . toRational) coordinates)
>   return (coordinatesArr, galaxies)
> 
> I suppose in a pinch I could write a C function that serializes the
> data, but I'd really rather not.  What I'm trying to do is load a bunch
> of coordinates into a vertex array for OpenGL.  I did this for a small
> 30,000 item vertex array, but I need to be able to handle several
> million vertices 
> in the end.  
> 
> If I serialize an unboxed array instead of a list or if I do repeated
> "put_" and "get" calls, will that help with the memory problem?
> 
> ___
> 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] Allocating enormous amounts of memory and wondering why

2007-07-10 Thread Jefferson Heard
I switched to Data.Binary, which dropped me from 2.6GB to 1.5GB, and
then I switched this afternoon to unboxed arrays from lists of floats,
and that dropped me again from 1.5GB to 475MB.  I think, all told, that
I'm in an acceptable range now, and thank you for pointing out the
library mistake.  I'm also down from 1.5 minutes load time to under 10
seconds of load time, which is also very very nice.  Incidentally, the
code I'm now using is:

binaryLoadDocumentCoordinates :: 
  String -> IO (Ptr Float, Array.UArray Int Int)
binaryLoadDocumentCoordinates path = do
  putStrLn "File opened"
  coordinates <- decodeFile (path ++ "/Clusters.bin") :: IO
(Array.UArray Int Float)
  print . Array.bounds $ coordinates
  putStrLn "Got coordinates"
  galaxies <- decodeFile (path ++ "/Galaxies.bin") :: IO (Array.UArray
Int Int)
  putStrLn "Got galaxies"
  coordinatesArr <- mallocArray . snd . Array.bounds $ coordinates
  putStrLn "Allocated array"
  pokeArray coordinatesArr . Array.elems $ coordinates
  return (coordinatesArr, galaxies)

binarySaveDocumentCoordinates :: String -> [Point] -> IO ()
binarySaveDocumentCoordinates path points = do
  let len = length points
  encodeFile (path ++ "Clusters.bin") . (Array.listArray (0,len*3) :: 
[Float] -> Array.UArray Int Float) . coordinateList . solve $ points
  encodeFile (path ++ "Galaxies.bin") . (Array.listArray (0,len) :: 
[Int] -> Array.UArray Int Int) . galaxyList $ points




On Sun, 2007-07-08 at 14:37 -0700, Stefan O'Rear wrote:
> On Sun, Jul 08, 2007 at 05:26:18PM -0400, Jefferson Heard wrote:
> > I'm using the Data.AltBinary package to read in a list of 4.8 million
> > floats and 1.6 million ints.  Doing so caused the memory footprint to
> > blow up to more than 2gb, which on my laptop simply causes the program
> > to crash.  I can do it on my workstation, but I'd really rather not,
> > because I want my program to be fairly portable.  
> > 
> > The file that I wrote out in packing the data structure was only 28MB,
> > so I assume I'm just using the wrong data structure, or I'm using full
> > laziness somewhere I shouldn't be.
> > 
> > I've tried compiling with profiling enabled, but I wasn't able to,
> > because the Streams package doesn't seem to have an option for compiling
> > with profiling.  I'm also a newbie to Cabal, so I'm probably just
> > missing something.  
> > 
> > The fundamental question, though is "Is there something wrong with how I
> > wrote the following function?"
> > 
> > binaryLoadDocumentCoordinates :: String -> IO (Ptr CFloat, [Int])
> > binaryLoadDocumentCoordinates path = do
> >   pointsH <- openBinaryFile (path ++ "/Clusters.bin") ReadMode
> >   coordinates <- get pointsH :: IO [Float]
> >   galaxies <- get pointsH :: IO [Int]
> >   coordinatesArr <- mallocArray (length coordinates)
> >   pokeArray coordinatesArr (map (fromRational . toRational) coordinates)
> >   return (coordinatesArr, galaxies)
> > 
> > I suppose in a pinch I could write a C function that serializes the
> > data, but I'd really rather not.  What I'm trying to do is load a bunch
> > of coordinates into a vertex array for OpenGL.  I did this for a small
> > 30,000 item vertex array, but I need to be able to handle several
> > million vertices in the end.  
> > 
> > If I serialize an unboxed array instead of a list or if I do repeated
> > "put_" and "get" calls, will that help with the memory problem?
> 
> Why are you using AltBinary instead of the (much newer and faster)
> Binary?  Binary *does* work with profiling and does not depend on
> streams.
> 
> (To compile Binary with profiling support, add -p to the Cabal
> configuration line.  This is documented in the --help message!)
> 
> Yes, using unboxed arrays will help.  Also try using the -c RTS option
> (that is, run your program as ./myprogram +RTS -c -RTS) - this tells the
> garbage collector to use a mark-compact system, which is slower than the
> default copying collector but uses roughly half as much memory.
> 
> Stefan

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


[Haskell-cafe] Strange memory consumption problems in something that should be tail-recursive

2007-02-13 Thread Jefferson Heard
Hi, I am running the following code against a 210 MB file in an attempt to 
determine whether I should use alex or whether, since my needs are very 
performance oriented, I should write a lexer of my own.  I thought that 
everything I'd written here was tail-recursive, but after compiling this with 
GHC 2.4.6, and running it, I eat up 2GB of RAM in less than a second.  So 
far, I have tried token and character oriented Parsec parsers and alex and 
alex is winning by a factor of 2.  I would like to be able to tokenize the 
entirety of a 1TB collection in less than 36 hours on my current machine, 
which is where alex has gotten me so far.  Thanks in advance!

 -- Jeff

---

module Main 
where


import qualified FileReader
import qualified Data.Set as Set

punct = foldl (flip Set.insert) Set.empty "<,>.?/:;\"'{[}]|\\_-+=)
(*&[EMAIL PROTECTED]"

stripTagOrComment [] = []
stripTagOrComment ('>':rest) = rest
stripTagOrCOmment (c:rest) = stripTagOrComment rest

pass1 :: String -> String -> String
pass1 left [] = left
pass1 left ('<':right) = pass1 left (stripTagOrComment right)
pass1 left (' ':right) = pass1 left right
pass1 left (c:right) 
| Set.member c punct = pass1 (' ':c:' ':left) right
| otherwise  = pass1 (c:left) right


pass2 :: [String] -> String -> Char -> String -> [String]
pass2 left word ' ' [] = word:left
pass2 left word c [] = (c:word):left
pass2 left word ' ' (' ':right) = pass2 left word ' ' right
pass2 left word ' ' (c:right) = pass2 (word:left) "" c right
pass2 left word l (c:right) = pass2 left (l:word) c right

tokenize = (pass2 [] "" ' ') . (pass1 [])

main = do
  file <- do FileReader.trecReadFile "trecfile"
  print (tokenize (head (tail file))) 


--  print (length (map (runParser tokenizeDoc [] "") file))
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Strange memory consumption problems in something that should be tail-recursive

2007-02-13 Thread Jefferson Heard
On Tuesday 13 February 2007 15:59, Duncan Coutts wrote:
> On Tue, 2007-02-13 at 15:27 -0500, Jefferson Heard wrote:
> > Hi, I am running the following code against a 210 MB file in an attempt
> > to determine whether I should use alex or whether, since my needs are
> > very performance oriented, I should write a lexer of my own.  I thought
> > that everything I'd written here was tail-recursive
>
> Isn't that exactly the problem - that it's tail recursive? You do not
> want it to be tail recursive since then it must consume the whole input
> before producing any output. You want it to be as lazy as possible so
> that it can start producing tokens as soon as possible without having to
> consume everything.
>
> If performance is really important to you then you may also want to
> investigate lexing from a lazy ByteString. Alex can now do that (darcs
> version) or you can do it by hand as you're trying now.
>
> Duncan

Argh, bitten by the scheme bug! Right -- NO tail recursion...  So that leaves 
me with some rather non-intuitive strategies for achieving execution time 
efficiency.  Anyone care to point me in the direction of a document on 
efficiency in Haskell?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Strange memory consumption problems in something that should be tail-recursive

2007-02-13 Thread Jefferson Heard
Didn't think it was overly slow, just that I could do better :-).


On Tuesday 13 February 2007 16:30, [EMAIL PROTECTED] wrote:
> Jefferson Heard wrote:
> > Argh, bitten by the scheme bug! Right -- NO tail recursion...  So that
> > leaves me with some rather non-intuitive strategies for achieving
> > execution time efficiency.  Anyone care to point me in the direction of a
> > document on efficiency in Haskell?
>
> Besides, proper tail recursion in Haskell needs strictness annotations,
> but the best way is to forget the two words "tail recursive" altogether :)
>
> It always helps to do a rough calculation of how much time you have to
> expect it to run. Processing 1TB with a 1GHz processor and 16=2^4
> machine instruction in the inner loop (must be quite short, the loop) takes
>
>  2^40 / (2^30 / 16) = 2^14 seconds ~ 4.5 hours
>
> Of course, these 4.5 hours are quite sensitive to the 2^4 factor and
> might well be 3 or 9 hours. Assuming that you ran alex on a String, the
> reported 36 hours are entirely reasonable, in the sense of alex not
> being overly slow.
>
> Regards,
> apfelmus
>
> ___
> 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] Strange memory consumption problems in something that should be tail-recursive

2007-02-13 Thread Jefferson Heard
Ha!  You're right!  I didn't think about the laziness aspect of it.  Anyway, 
the non tail-recursive version fixed the problem.  Thanks!

On Tuesday 13 February 2007 16:32, Bernie Pope wrote:
> Creighton Hogg wrote:
> > On 2/13/07, *Duncan Coutts* <[EMAIL PROTECTED]
> > <mailto:[EMAIL PROTECTED]>> wrote:
> >
> > On Tue, 2007-02-13 at 15:27 -0500, Jefferson Heard wrote:
> > > Hi, I am running the following code against a 210 MB file in an
> >
> > attempt to
> >
> > > determine whether I should use alex or whether, since my needs
> >
> > are very
> >
> > > performance oriented, I should write a lexer of my own.  I
> >
> > thought that
> >
> > > everything I'd written here was tail-recursive
> >
> > Isn't that exactly the problem - that it's tail recursive? You do not
> > want it to be tail recursive since then it must consume the whole
> > input
> > before producing any output. You want it to be as lazy as possible so
> > that it can start producing tokens as soon as possible without
> > having to
> > consume everything.
> >
> >
> > This may be silly of me, but I feel like this is an important point:
> > so you're saying that tail recursion, without strictness, doesn't run
> > in constant space?
>
> It is an important point, and a classic space bug (see foldl in the
> Prelude).
>
> It it not the fault of tail recursion per se, in fact tail recursion is
> often important in Haskell too.
>
> > So for example in the case of,
> > facTail 1 n' = n'
> > facTail n n' = facTail (n-1) (n*n')
>
> The problem with this example is that it will build up an expression of
> the form:
>
>(n1 * n2 * n3 .)
>
> in the second argument. It's size will be proportional to the number of
> recursive calls made (n).
>
> > You'll just be building a bunch of unevaluated thunks until you hit
> > the termination condition?
>
> To fix it you will want the function to evaluate its second argument
> eagerly:
>
> facTail n n' = facTail (n-1) $! (n*n')
> Cheers,
> Bernie.
>
>
> ___
> 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] Difference between Lazy ByteStrings and Strings in alex

2007-02-13 Thread Jefferson Heard
It was suggested that I might derive some performance benefit from using lazy 
bytestrings in my tokenizer instead of regular strings.  Here's the code that 
I've tried.  Note that I've hacked the "basic" wrapper code in the Lazy 
version, so the code should be all but the same.  The only thing I had to do 
out of the ordinary was write my own 'take' function instead of using the 
substring function provided by Data.Lazy.ByteString.Char8.  The take function 
I used was derived from the one GHC uses in GHC.List and produces about the 
same code.  

The non-lazy version runs in 38 seconds on a 211MB file versus the lazy 
versions 41 seconds.  That of course doesn't seem like that much, and in the 
non-lazy case, I have to break the input up into multiple files, whereas I 
don't have to in the lazy version -- this does not take any extra time.  The 
seconds do add up to a couple of hours for me, though once I'm done, and so 
I'd like to understand why, when the consensus was that Data.ByteString.Lazy 
might give me better performance in the end, it doesn't do so here.  

I am running GHC 2.6 now, and am using -O3 as my optimization parameter.  I'm 
profiling the code now, but was wondering if there was any insight...

-- Jeff 

Non-lazy version

{
module Main
where

import qualified FileReader

}

%wrapper "basic"

$letter = [a-zA-Z]
$digit = 0-9
$alphanum = [a-zA-Z0-9]
$punct = [\! \@ \# \$ \% \^ \& \* \( \) \_ \- \+ \= \{ \[ \} \] \\ \| \; \: \' 
\" \, \. \? \/ \` \~]
$dec = \.
$posneg = [\- \+]

@date1 = jan($punct|uary)?\ $digit{1,2}(\,\ $digit{2,4})?
   | feb($punct|ruary)?\ $digit{1,2}(\,\ $digit{2,4})?
   | mar($punct|ch)?\ $digit{1,2}(\,\ $digit{2,4})?
   | apr($punct|il)?\ $digit{1,2}(\,\ $digit{2,4})?
   | may?\ $digit{1,2}(\,\ $digit{2,4})?
   | jun($punct|e)?\ $digit{1,2}(\,\ $digit{2,4})?
   | jul($punct|y)?\ $digit{1,2}(\,\ $digit{2,4})?
   | aug($punct|ust)?\ $digit{1,2}(\,\ $digit{2,4})?
   | sep($punct|tember)?\ $digit{1,2}(\,\ $digit{2,4})?
   | sept($punct)?\ $digit{1,2}(\,\ $digit{2,4})?
   | oct($punct|ober)?\ $digit{1,2}(\,\ $digit{2,4})?
   | nov($punct|ember)?\ $digit{1,2}(\,\ $digit{2,4})?
   | dec($punct|ember)?\ $digit{1,2}(\,\ $digit{2,4})?

@date2 = $digit{1,2} $punct $digit{1,2} $punct $digit{2,4}

@time = $digit{1,2} \: $digit{2} (am|pm)?

@word = $alphanum+

@number = $posneg? $digit+ 
| $posneg? $digit+ $dec $digit+
| $posneg? $digit+ (\,$digit{3})+
| $posneg? $digit? (\,$digit{3})+ $dec $digit+

$white = [\t\r\n\v\f\ ]

@doc = \< DOC \>
@tag = \< $alphanum+ \>
 | \<\/ $alphanum+ \>

tokens :- 
  @doc{ \s -> "" }
  @tag;
  $white+ ; 
  @time   { \s -> s }
  @number { \s -> s } 
  @word   { \s -> s }
  $punct  ; 
  .   ;

{

printCount c [] = print c
printCount c (l:ls) = if l == "" then printCount (c+1) ls else printCount c ls

main = do
file <- readFile "trecfile1" 
printCount 0 (alexScanTokens file) 
 
}

-- 

Version depending on ByteString.Lazy -- note that the grammar is the same, so 
it has been omitted
-- 


... grammar ...

{
type AlexInput = (Char, -- previous char
  B.ByteString)   -- current input string

takebytes :: Int -> B.ByteString -> String
takebytes (0) _ =  ""
takebytes n s = c : takebytes (n-1) cs
where c = B.index s 0
  cs = B.drop 1 s

alexGetChar :: AlexInput -> Maybe (Char,AlexInput)
alexGetChar (_, bytestring) 
| bytestring == B.empty = Nothing
| otherwise = Just (c , (c,cs))
where c = B.index bytestring 0
  cs = B.drop 1 bytestring

alexInputPrevChar :: AlexInput -> Char
alexInputPrevChar (c,_) = c

alexScanTokens :: B.ByteString -> [String]
alexScanTokens str = go ('\n',str)
  where go inp@(_,str) =
  case alexScan inp 0 of
AlexToken inp' len act -> act (takebytes len str) : go inp'
AlexSkip  inp' len -> go inp'
AlexEOF -> []
AlexError _ -> error "lexical error"




printCount :: Int -> [String] -> IO ()
printCount c [] = print c
printCount c (l:ls) = if l == "" then printCount (c+1) ls else printCount c ls

main = do
file <- B.readFile "trecfile1" 
printCount 0 (alexScanTokens file) 
 
}
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Difference between Lazy ByteStrings and Strings in alex

2007-02-13 Thread Jefferson Heard
Yes, that was a typo :-)

On Tuesday 13 February 2007 22:54, Stefan O'Rear wrote:
> On Tue, Feb 13, 2007 at 10:43:11PM -0500, Jefferson Heard wrote:
> > I am running GHC 2.6 now, and am using -O3 as my optimization parameter. 
> > I'm
>
> I think you will get much better performance with GHC 6.6.  The optimizer
> has been improved a *lot* in the last 10 years.
>
> (I hope that was a typo!!)
>
> > Non-lazy version
> >
> > {
> > module Main
> > where
> >
> > import qualified FileReader
> >
> > }
> >
> > %wrapper "basic"
> >
> > $letter = [a-zA-Z]
> > $digit = 0-9
> > $alphanum = [a-zA-Z0-9]
> > $punct = [\! \@ \# \$ \% \^ \& \* \( \) \_ \- \+ \= \{ \[ \} \] \\ \| \;
> > \: \' \" \, \. \? \/ \` \~]
> > $dec = \.
> > $posneg = [\- \+]
> >
> > @date1 = jan($punct|uary)?\ $digit{1,2}(\,\ $digit{2,4})?
> >
> >| feb($punct|ruary)?\ $digit{1,2}(\,\ $digit{2,4})?
> >| mar($punct|ch)?\ $digit{1,2}(\,\ $digit{2,4})?
> >| apr($punct|il)?\ $digit{1,2}(\,\ $digit{2,4})?
> >| may?\ $digit{1,2}(\,\ $digit{2,4})?
> >| jun($punct|e)?\ $digit{1,2}(\,\ $digit{2,4})?
> >| jul($punct|y)?\ $digit{1,2}(\,\ $digit{2,4})?
> >| aug($punct|ust)?\ $digit{1,2}(\,\ $digit{2,4})?
> >| sep($punct|tember)?\ $digit{1,2}(\,\ $digit{2,4})?
> >| sept($punct)?\ $digit{1,2}(\,\ $digit{2,4})?
> >| oct($punct|ober)?\ $digit{1,2}(\,\ $digit{2,4})?
> >| nov($punct|ember)?\ $digit{1,2}(\,\ $digit{2,4})?
> >| dec($punct|ember)?\ $digit{1,2}(\,\ $digit{2,4})?
> >
> > @date2 = $digit{1,2} $punct $digit{1,2} $punct $digit{2,4}
> >
> > @time = $digit{1,2} \: $digit{2} (am|pm)?
> >
> > @word = $alphanum+
> >
> > @number = $posneg? $digit+
> >
> > | $posneg? $digit+ $dec $digit+
> > | $posneg? $digit+ (\,$digit{3})+
> > | $posneg? $digit? (\,$digit{3})+ $dec $digit+
> >
> > $white = [\t\r\n\v\f\ ]
> >
> > @doc = \< DOC \>
> > @tag = \< $alphanum+ \>
> >
> >  | \<\/ $alphanum+ \>
> >
> > tokens :-
> >   @doc{ \s -> "" }
> >   @tag;
> >   $white+ ;
> >   @time   { \s -> s }
> >   @number { \s -> s }
> >   @word   { \s -> s }
> >   $punct  ;
> >   .   ;
> >
> > {
> >
> > printCount c [] = print c
> > printCount c (l:ls) = if l == "" then printCount (c+1) ls else printCount
> > c ls
> >
> > main = do
> > file <- readFile "trecfile1"
> > printCount 0 (alexScanTokens file)
> >
> > }
>
> FTR, regular strings are lazy - too lazy, which is where the performance
> problems come from.
>
> > --
> > -
> >--- Version depending on ByteString.Lazy
> > -- note that the grammar is the same, so it has been omitted
> > --
> > -
> >---
> >
> > ... grammar ...
> >
> > {
> > type AlexInput = (Char, -- previous char
> >   B.ByteString)   -- current input string
> >
> > takebytes :: Int -> B.ByteString -> String
> > takebytes (0) _ =  ""
> > takebytes n s = c : takebytes (n-1) cs
> > where c = B.index s 0
> >   cs = B.drop 1 s
> >
> > alexGetChar :: AlexInput -> Maybe (Char,AlexInput)
> > alexGetChar (_, bytestring)
> >
> > | bytestring == B.empty = Nothing
> > | otherwise = Just (c , (c,cs))
> >
> > where c = B.index bytestring 0
> >   cs = B.drop 1 bytestring
>
> Hm, you might do better with more specialized functions.
>
> > alexGetChar :: AlexInput -> Maybe (Char,AlexInput)
> > alexGetChar (_, bytestring)
> >
> > | B.null bytestring = Nothing
> > | otherwise = Just (c , (c,cs))
> >
> > where c = B.head bytestring
> >   cs = B.tail bytestring
>
> or even:
> > alexGetChar :: AlexInput -> Maybe (Char,AlexInput)
> > alexGetChar (_, bytestring)
> >
> > | B.null bytestring = Nothing
> > | otherwise = Just (c , (c,cs))
> >
> > where c = B.unsafeHead bytestring
> >   cs = B.unsafeTail bytestring
> >
> > alexInputPrevChar 

[Haskell-cafe] Looking for documentation on Control.Parallel.Strategies

2007-02-16 Thread Jefferson Heard
Is there anything that documents this further than the Haddock documentation 
available from Haskell.org or the GHC pages?  I've gotten some basic 
parallelism to work using parMap and using >|| and >|, but I had a fold and a 
map that I could logically compute at the same time.  

I found this example for quicksort using GPH:

import Strategies


main = print (quicksort ([999,998..0]::[Int]))

quicksort :: (Ord a, NFData a) => [a] -> [a]
quicksort [] = []
quicksort [x] = [x]
quicksort (x:xs) = (lo ++ (x:hi)) `using` strategy
where
lo = quicksort [ y | y <- xs, y < x]
hi = quicksort [ y | y <- xs, y >= x]
strategy result = rnf lo `par`
rnf hi `par`
rnf result

Is the syntax the same for GHC using Control.Parallel.Strategies?  If so, does 
the following execute the two computations from the where clause in parallel?

import Control.Parallel
import Control.Parallel.Strategies

stats bigList summation mean = (stddev, proportions) `using` strategy
where 
stddev = sqrt (fold ((+) . (^2) . (-mean)) 0 bigList)
proportions = map (/summation) bigList
strategy result = rnf stddev >|| 
rnf proportions >|| 
rnf result

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


Re: [Haskell-cafe] Looking for documentation on Control.Parallel.Strategies

2007-02-16 Thread Jefferson Heard
That's MUCH better, thanks.  That's not what's directly available from 
haskell.org.  It still doesn't give anything more general about using the 
combinators in actual programs, you know, like examples, but it's at least 
some clear documentation as to what each strategy does.  

Maybe one day, when I have a parallel program actually working, I could 
document that...

On Friday 16 February 2007 16:26, Bjorn Bringert wrote:
> On Feb 16, 2007, at 21:16 , Jefferson Heard wrote:
> > Is there anything that documents this further than the Haddock
> > documentation
> > available from Haskell.org or the GHC pages?  I've gotten some basic
> > parallelism to work using parMap and using >|| and >|, but I had a
> > fold and a
> > map that I could logically compute at the same time.
> >
> > ...
>
> Maybe that's what you're looking at, but the darcs version has some
> more Haddock comments, see http://www.haskell.org/ghc/dist/current/
> docs/libraries/base/Control-Parallel-Strategies.html
>
> /Björn
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Leaves of a Tree

2007-02-21 Thread Jefferson Heard
Alternatively, the definition of your tree could include a list of linked 
lists, one for each level of the tree.  Then you could just select the last 
list and it's the same as saving only the leaves from a complete inorder walk 
of the tree.

data AltTree a = AltTree { tree_structure :: Tree a, nodes :: [[a]] }

On Wednesday 21 February 2007 14:31, Tom Hawkins wrote:
> Hello,
>
> Any recommendations for speeding up extracting the set of leaves from a
> tree?
>
> data Tree = Branch Tree Tree | Leaf Int deriving (Eq, Ord)
>
> My slow, naive function:
>
> leaves :: Tree -> Set Int
> leaves (Leaf n) = singleton n
> leaves (Branch left right) = union (leaves left) (leaves right)
>
> In my case, many of the branches in the tree are the same.  I suspect
> the fixed point operation mentioned in the thread "speeding up
> fibonacci with memoizing" is applicable, but I'm having a tough time
> making the connection.
>
> -Tom
> ___
> 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] Is anyone using CUDA with haskell yet?

2007-02-21 Thread Jefferson Heard
I don't want to duplicate anyone's work, and I'm not sure that NDA would allow 
me to release the code in any case (have to check on it carefully), but is 
anyone currently using the CUDA framework from nVidia inside of Haskell for 
highly parallel programming?

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


Re: [Haskell-cafe] A "real" Haskell Cookbook

2007-02-21 Thread Jefferson Heard
I second this plea.

-- Jeff

On Wednesday 21 February 2007 22:34, P. R. Stanley wrote:
> and can I please ask anyone thinking of using special symbols to
> resist the temptation.
> Symbols such as the &160 used liberally in the Haskell wikibook are
> totally invisible to screen readers.
> I would be happy to proof read any document before it goes to the
> wikibook to ensure it's fully accessible to screen readers.
>
> Regards,
> Paul
>
> At 03:17 22/02/2007, you wrote:
> >I made a preliminary page, and fleshed out some of the
> >headers/sub-headers on the wiki page for a good Haskell Cookbook
> >(aka NOT a PLEAC clone).  Please contribute and/or fix the examples
> >and explanations so we can make a really nice Cookbook for newbies. :)
> >
> >  http://haskell.org/haskellwiki/Cookbook
> >
> >___
> >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 mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Recursion

2007-03-06 Thread Jefferson Heard
Bryan, 

The code here does not take advantage of laziness, which is probably what you 
want to do, as it is much cleaner to look at and more Haskell like.  In 
answer to your question it is tail recursive, and strict, which means that in 
some compilers, with some optimization flags (i.e. GHC) you will get an 
iteration instead of a recursion, but consider instead this:

main = do 
input = readFile stdin
let r = map processit (lines input)
putStrLn (unlines s)

For more details, see: 
http://blogs.nubgames.com/code/?p=22

On Tuesday 06 March 2007 11:52, Bryan Burgers wrote:
> On 3/6/07, [EMAIL PROTECTED] <[EMAIL PROTECTED]> wrote:
> > Does the following code increase the level of recursion
> > once for each input line or is the recursive construct
> > converted to an iteration?
> >
> > Thanks,
> > Dave Feustel
> >
> > main :: IO ()
> > main = do
> >   line <- getLine
> >   processIt line
> >   main
> >
> > processIt   :: String -> IO ()
> > processIt s = do
> >   print (length s)
>
> Dave,
>
> I would imagine it does not, but I will let somebody more
> knowledgeable tell you for sure. My thought, though, is that if this
> is your whole code and not a simplified version (eg, one that
> terminates on certain input), then you could consider using the
> Prelude's 'interact'[1] function, which performs a transformation on
> standard input. In your case, the code would simplify to:
>
> main = interact (unlines . map (show . length) . lines)
>
> The unlines/lines combo breaks up the whole input into a list of lines
> of input, and the (show . length) is the heart of your 'processIt'
> function.
>
> Alternately, you could also use something like:
>
> main = getContents >>= mapM_ processIt . lines
>
> Which takes everything from standard in, splits it up into lines, and
> then performs processIt for each line.
>
> [1]
> http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v%3Aint
>eract
>
> Bryan
> ___
> 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] Usage of . and $

2007-03-06 Thread Jefferson Heard
Usually, I can do this, but today, my brain is weak, and I'm just trying to 
get this piece of code out the door.  My code looks like this:

weight = sum (IntMap.elems (IntMap.intersectionWith 
 (\x y -> x*y) queryVector rationalProjection)) 

I know that this will work (ignoring indentation):

sum $ IntMap.elems $ IntMap.intersectionWith (\x y -> x*y) queryVector 
rationalProjection

But why won't this?:

sum . IntMap.elems . IntMap.IntersectionWith ...

Is there a difference between the "elegance" of function composition versus 
application?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Usage of . and $

2007-03-06 Thread Jefferson Heard
Nope, I'm asking why 

um . IntMap.elems . IntMap.IntersectionWith (\x y -> x*y) queryVector 
rationalProjection

won't work.




On Tuesday 06 March 2007 15:14, Jeff Polakow wrote:
> [EMAIL PROTECTED] wrote on 03/06/2007 02:43:03 PM:
> > Usually, I can do this, but today, my brain is weak, and I'm just trying
>
> to
>
> > get this piece of code out the door.  My code looks like this:
> >
> > weight = sum (IntMap.elems (IntMap.intersectionWith
> >(\x y -> x*y) queryVector rationalProjection))
> >
> > I know that this will work (ignoring indentation):
> >
> > sum $ IntMap.elems $ IntMap.intersectionWith (\x y -> x*y) queryVector
> > rationalProjection
> >
> > But why won't this?:
> >
> > sum . IntMap.elems . IntMap.IntersectionWith ...
> >
> > Is there a difference between the "elegance" of function composition
>
> versus
>
> > application?
>
> I assume your really asking why something like:
>
> (*) $ 2 $ 3
>
> won't work? If so, the reason is that $ associates to the right. So you
> should write:
>
> ((*) $ 2) $ 3
>
> If not, could you give the full expression which doesn't work?
>
> -Jeff
>
>
>
> ---
>
> This e-mail may contain confidential and/or privileged information. If you
> are not the intended recipient (or have received this e-mail in error)
> please notify the sender immediately and destroy this e-mail. Any
> unauthorized copying, disclosure or distribution of the material in this
> e-mail is strictly forbidden.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] literate Haskell newbie question

2007-03-09 Thread Jefferson Heard
ghc handles lhs files based on their extension.  You don't need to translate 
it to a different format.  If you want to translate > notation lhs to hs on 
your own (I dunno why, just if you did), the sed/grep combo 

cat foo.lhs | grep -e "^>" | sed "s/^> //"

would work just fine.

On Friday 09 March 2007 09:23, Immanuel Normann wrote:
> I am a newbie to literate Haskell and these are my two simple questions:
>
> How do I compile a literate haskell file foo.lhs (using ghc-6.6)?
> Is there a tool that translates foo.lhs to foo.hs?
>
> Surprisingly I don't find the answer in
> http://haskell.org/haskellwiki/Literate_programming
> whereas a lot about translation into tex-files can be found.
>
> Thanks,
> Immanuel
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Parallelism on concurrent?

2007-03-13 Thread Jefferson Heard
Simon will probably chime in on it as well, but his paper on the subject is 
the best there is:  

http://research.microsoft.com/~simonpj/Papers/strategies.ps.gz

If you have questions about the paper, I'd be happy to help, too.  I worked 
through it myself fairly recently.

-- Jeff

On Tuesday 13 March 2007 12:26, Dusan Kolar wrote:
> Hello all,
>
>   I'm googling around haskell.org to get some deeper knowledge about
> Control.Parallel.Strategies than it is presented on
> http://www.haskell.org/ghc/docs/latest/html/libraries/base/Control-Parallel
>-Strategies.html BTW, could someone point me to some more deeper doc. about
> it?
>
>   During googling I've discovered that since GHC 6.6, par, forkIO, and
> forkOS should make the stuff run in parallel if I have more than one CPU
> core. Is that right? I think not, because on my machine only par makes
> the things run in parallel and only during the computation (GC runs in a
> single thread). If it should work, how can I verify that my installation
> is correct? If it should not work, will it be working someday?
>
>   Thanks for your patience, responses, and tips
>
> Dusan
>
> ___
> 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] Parallelism on concurrent?

2007-03-13 Thread Jefferson Heard
forkOS should work as well, assuming you have OS threads, like in linux 2.6.  
You should probably be using the -smp compiler flag and not the -threaded 
compiler flag, I'm guessing, and make sure that your +RTS arguments indicate 
that you want to use X total concurrent threads...

-- Jeff

On Tuesday 13 March 2007 13:10, Dusan Kolar wrote:
> Yes, it works for operator /par/. That's what I've reported. But should
> it work for forkIO and forkOS? Could anybody give more detailed answer
> than yes, no? :-) (Link to the Web is OK.)
>
> BTW, thanks for the link to the paper (moreover, I can see, that
> googling over haskell.org is not sufficient ;-) ).
>
> Regards,
>
>   Dusan
>
> Pepe Iborra wrote:
> > On 13/03/2007, at 17:46, Jefferson Heard wrote:
> >> Simon will probably chime in on it as well, but his paper on the
> >> subject is
> >> the best there is:
> >>
> >> http://research.microsoft.com/~simonpj/Papers/strategies.ps.gz
> >
> > It does work in GHC 6.6 very nicely.
> > You can try it with the following naive fib function, extracted from
> > the paper mentioned above:
> >
> > \begin{code}
> > import Control.Parallel
> > import System.Environment
> > import Fib
> >
> > main = do
> >(x:_) <- getArgs
> >print$ pfib (read x)
> >
> > pfib 0 = 1
> > pfib 1 = 1
> > pfib n = n1 `par` n2 `seq` n1+n2+1
> >   where (n1,n2) = (pfib(n-1), pfib(n-2))
> > \end{code}
> >
> > pep:~/code/snippets/Parallelism$ ghc --make -O Main -threaded
> >
> > pep:~/code/snippets/Parallelism$ time src/Main 33
> > 11405773
> >
> > real0m1.444s
> > user0m1.343s
> > sys 0m0.020s
> >
> > pep:~/code/snippets/Parallelism$ time src/Main 33 +RTS -N2
> > 11405773
> >
> > real0m0.764s
> > user0m1.367s
> > sys 0m0.030s
> >
> >
> >
> > Got a speedup of 100%, and didn't use threads at all. Yay!
> >
> > pepe
> >
> > ___
> > 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] Haskell beginner

2007-03-15 Thread Jefferson Heard
Yet another Haskell Tutorial is the way I learned it.  I find that subscribing 
to the mailing lists and reading the tutorial material is generally speaking 
enough.

On Thursday 15 March 2007 14:30:03 arnuld wrote:
> i want to start learning Haskell and willing to master it :-)  i have
> done some Common Lisp from http://www.gigamonkeys.com/book/. so i know
> what are functions, variables, etc. BUT i have never done any real
> life programmming or any kind of software development.
>
> in my country no Haskell books are available :-( , hence i can only
> use online Tutorials. my main purpose is to learn real-life
> programming by contributing some "Haskell coding" to a GPLed Software
> written using Haskell.
>
> i have found "Yet Another Haskell Tutorial" after searching the archives.
>
> is it really a good idea to learn Haskell using only Online material ?
> (when one does not have any offline resources)


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


[Haskell-cafe] operating on a hundred files at once

2007-04-09 Thread Jefferson Heard
I have a series of NxM numeric tables I'm doing a quick
mean/variance/t-test etcetera on.  The cell t1 [i,j] corresponds exactly
to the cells t2..N [i,j], and so it's perfectly possible to read one
item at a time from each of the 100 files and compute the mean/variance
etcetera on all cells that way.  So what I propose to do is something
along the lines of:

openAndProcess filename = 
f <- readFile filename
return (map (L.split ',') . lines $ f)

main = do 
fs <- getArgs
let items = map (map read) . map openAndProcess fs 
in do print . map (map $ mean) items
  print . map (map $ variance) items

How close am I to doing the right thing here? As I understand it, this
will result in one hundred IO [String] instances being returned by the
call to (map openAndProcess $ filenames).  Do I need to do something
special to lift (read), (mean), and (variance), or even (map) into the
IO monad so they can process the input as needed?

Thanks in advance,
-- Jeff

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


Re: [Haskell-cafe] Drawing an existing image into a cairo surface?

2008-09-21 Thread Jefferson Heard
Sorry.  In a hurry, and I don't have a lot of time to read the
message, so if I'm offering a lot of info you already have, I
apologize.  The best thing to do is to allocate either a pixmap or
Gtk.DrawingArea -- you can then use widgetGetDrawable to get the
drawing context from it and newGC to take drawing context and get a
graphics context.  After you have a drawing and graphics context, you
can use drawPixbuf to draw or update any image you want, then use the
same DrawngArea for Cairo after you've drawing the image.

If you need more help with it, let me know, and I can send some code
that will do it later today.

-- Jeff

On Sun, Sep 21, 2008 at 10:09 AM, Rafal Kolanski <[EMAIL PROTECTED]> wrote:
>
> Bulat Ziganshin wrote:
>>
>> afair, Render is a super-IO monad so you can just lift any IO
>> operation to Render:
>>
>> x <- liftIO$ imageSurfaceCreateFromPNG file
>
> You are indeed correct.
>
> I feel really silly now, using unsafePerformIO in the IO monad. D'oh!
>
> Thank you very much!
>
> Rafal Kolanski.
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>



-- 
I try to take things like a crow; war and chaos don't always ruin a
picnic, they just mean you have to be careful what you swallow.

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


[Haskell-cafe] Cairo and dialog oddities on Windows using glade.

2008-10-15 Thread Jefferson Heard
Maybe I'm doing something wrong.  I've created several dialog boxes in
Glade, and I'm calling Gtk.runDialog on them when a user clicks the
mouse in my main window.  On Linux, they work mostly right, but the
insertion point never shows in the Gtk.Entry areas and the dialog
itself comes up without any decoration.  In Windows, I cannot edit the
Entry areas at all.  I can click on the action buttons I added with
Gtk.Dialog.addButton.

Also, I'm getting an (Invalid matrix (matrix not invertible)) error
from Cairo in WIndows that I'm not getting in Linux, and all I can
think is that occasionally a rectangle width could be negative.  Would
that cause the error?


-- 
I try to take things like a crow; war and chaos don't always ruin a
picnic, they just mean you have to be careful what you swallow.

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


[Haskell-cafe] How to deal with pointers to pointers in the FFI

2008-10-17 Thread Jefferson Heard
I have the following functions in C:

OGRErr  OGR_G_CreateFromWkb (unsigned char *, OGRSpatialReferenceH,
OGRGeometryH *, int)
OGRErr  OGR_G_CreateFromWkt (char **, OGRSpatialReferenceH, OGRGeometryH *)
voidOGR_G_DestroyGeometry (OGRGeometryH)
OGRGeometryHOGR_G_CreateGeometry (OGRwkbGeometryType)

The normal sequence of calls is

OGRGeometryH handle = OGR_G_CreateGeometry(SOME_TYPE);
// do stuff
OGR_G_DestroyGeometry(handle);

OR

OGR_G_CreateFromWkb(blob, ref, &handle, 0);
// do stuff
OGR_G_DestroyGeometry(handle);

As you can see, in one case, I have to pass in a pointer to the
returned handle, and not just the handle.  How can I accomplish this
feat using a single type?

I had

data OGRGeometryH
type Geometry = Ptr OGRGeometryH

but then can I declare that a function returns a

Ptr (Geometry)

?



-- 
I try to take things like a crow; war and chaos don't always ruin a
picnic, they just mean you have to be careful what you swallow.

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


Re: [Haskell-cafe] How to deal with pointers to pointers in the FFI

2008-10-17 Thread Jefferson Heard
Sadly, nothing so awesome...  OGR is part of GDAL, an open-source
geographic information system suite.

On Fri, Oct 17, 2008 at 3:22 PM, Jake McArthur <[EMAIL PROTECTED]> wrote:
> -BEGIN PGP SIGNED MESSAGE-
> Hash: SHA1
>
> Jefferson Heard wrote:
>> I have the following functions in C:
>>
>> OGRErrOGR_G_CreateFromWkb (unsigned char *, OGRSpatialReferenceH,
>> OGRGeometryH *, int)
>> OGRErrOGR_G_CreateFromWkt (char **, OGRSpatialReferenceH, 
>> OGRGeometryH *)
>> void  OGR_G_DestroyGeometry (OGRGeometryH)
>> OGRGeometryH  OGR_G_CreateGeometry (OGRwkbGeometryType)
>
> Are these Ogre3D functions? If so, I hope you are planning on releasing
> these bindings!
>
> But I don't have an answer to your question, sorry. :\
>
> - - Jake
> -BEGIN PGP SIGNATURE-
> Version: GnuPG v1.4.9 (MingW32)
> Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org
>
> iEYEARECAAYFAkj45dwACgkQye5hVyvIUKmRoQCfTOnlxfRCUY/9SY9qA29NNIJL
> AvYAn1m6h8b36amu+DBqd/r1dT5iXb/H
> =Smjr
> -END PGP SIGNATURE-
>



-- 
I try to take things like a crow; war and chaos don't always ruin a
picnic, they just mean you have to be careful what you swallow.

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


Re: [Haskell-cafe] Memory efficiency questions for real-time graphics

2008-10-27 Thread Jefferson Heard
By the way, T, feel free to lean on me if you run into any problems.
I did something along the lines of what you were describing some time
ago, my particular non-linear transform being converting a vertex
array to/from polar coordinates and updating in realtime.

-- Jeff

On Tue, Oct 28, 2008 at 12:00 AM, T Willingham <[EMAIL PROTECTED]> wrote:
> On Mon, Oct 27, 2008 at 11:04 PM, Don Stewart <[EMAIL PROTECTED]> wrote:
>> It depends on the operations (safe indexing or unsafe indexing).
>> Being strict or unboxed doesn't determine the safety.
>
> OK, that makes sense.
>
> This is a huge load off my conscience.  I can now dig into Real World
> Haskell without hesitation, knowing that what I want in the end is
> actually possible.
>
> Thanks again,
> TW
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>



-- 
I try to take things like a crow; war and chaos don't always ruin a
picnic, they just mean you have to be careful what you swallow.

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


Re: [Haskell-cafe] Re: ghc-6.11 + OpenGL/GLUT crashes on WinXP

2008-10-28 Thread Jefferson Heard
Conal, are you using display lists at all?  I've had problems with
allocating lists, but you seem to be able to leave off the allocation
step in Windows on nVidia cards so long as you're careful not to
conflict names yourself.

On Tue, Oct 28, 2008 at 4:03 PM, Matti Niemenmaa
<[EMAIL PROTECTED]> wrote:
> Conal Elliott wrote:
>> I am using glut32 rather than freeglut (and no need for patching the darcs
>> GLUT).  I wonder if glut32-vs-freeglut could account for crash-vs-nocrash on
>> 6.10 and 6.11 but not 6.9.  I'd love to hear from someone on Windows and
>> glut32.
>
> Windows XP with SP3
> ghc-6.10.20081007
> glut32
>
> Works fine for me.
>
> Taking a look at my GL headers, I did have to mess with at least glut.h to get
> something to work---whether it was to build HOpenGL, to make programs 
> linkable,
> or to make them runnable, I'm not sure. In any case, what I did was force
> GLUTAPIENTRY to be #defined as __stdcall.
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>



-- 
I try to take things like a crow; war and chaos don't always ruin a
picnic, they just mean you have to be careful what you swallow.

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


Re: [Haskell-cafe] Re: ghc-6.11 + OpenGL/GLUT crashes on WinXP

2008-10-29 Thread Jefferson Heard
Conal, I tried this today on a VirtualBox VM running the same versions
as Mark Wassell, and it worked for me...  I wonder, though, if perhaps
GLUT is not getting a GLX (or direct) video context on your machine
for some reason.  That has caused some of my GLUT programs to die in
the past, no matter the language.  Have you tried using the GLUT
library from a C program to see if you get the same error?

On Wed, Oct 29, 2008 at 4:49 AM, Mark Wassell <[EMAIL PROTECTED]> wrote:
> Hi,
>
> Works here:
>
> Windows XP SP 3
> ghc-6.10.20081007
> glut32 from http://www.xmission.com/~nate/glut.html
>
> Don't know if this will help:
>
> DLLS loaded
>
> glut32.dll0x10000x38000C:\WINDOWS\glut32.dll
> opengl32.dll0x5ed00xcc000C:\WINDOWS\system32\opengl32.dll
> glu32.dll0x68b20x2C:\WINDOWS\system32\glu32.dll
> ddraw.dll0x73760x4b000C:\WINDOWS\system32\ddraw.dll
> dciman32.dll0x73bc0x6000C:\WINDOWS\system32\dciman32.dll
> msvcrt.dll0x77c10x58000C:\WINDOWS\system32\msvcrt.dll
> advapi32.dll0x77dd0x9b000C:\WINDOWS\system32\advapi32.dll
> rpcrt4.dll0x77e70x92000C:\WINDOWS\system32\rpcrt4.dll
> gdi32.dll0x77f10x49000C:\WINDOWS\system32\gdi32.dll
> secur32.dll0x77fe0x11000C:\WINDOWS\system32\secur32.dll
> kernel32.dll0x7c800xf6000C:\WINDOWS\system32\kernel32.dll
> ntdll.dll0x7c900xaf000C:\WINDOWS\system32\ntdll.dll
> user32.dll0x7e410x91000C:\WINDOWS\system32\user32.dll
>
> Some of the versions
>
> opengl32.dll OpenGL DLL (Microsoft) Version 5.01.2600.5512
> glu32.dll OpenGL Utility Library DLL (Microsoft) Version 5.01.2600.5512
> ddraw.dll - DirectDraw (Microsoft) 5.03.2600.5512
> dciman32.dll - DCI Manage (Microsft) 5.01.2600.5512.
> glut32 had no version info.
>
> DirectX 9.0c (always thought OpenGL and DirectX were orthogonal but
> ddraw.dll  is being used).
>
> Mark
>
>
> Conal Elliott wrote:
>>
>> No display lists.  The crash happens during the GLUT call "initialize".  I
>> can trigger it from ghci with the following simple incantation:
>>
>> Prelude> import Graphics.UI.GLUT
>>     Prelude Graphics.UI.GLUT> initialize "foo" []
>>
>> And no trouble under ghc 6.9.20080622.
>>
>> Stumped.  :(
>>
>>- Conal
>>
>> On Tue, Oct 28, 2008 at 3:14 PM, Jefferson Heard
>> <[EMAIL PROTECTED] <mailto:[EMAIL PROTECTED]>> wrote:
>>
>>Conal, are you using display lists at all?  I've had problems with
>>allocating lists, but you seem to be able to leave off the allocation
>>step in Windows on nVidia cards so long as you're careful not to
>>conflict names yourself.
>>
>>On Tue, Oct 28, 2008 at 4:03 PM, Matti Niemenmaa
>><[EMAIL PROTECTED]
>><mailto:[EMAIL PROTECTED]>> wrote:
>>> Conal Elliott wrote:
>>>> I am using glut32 rather than freeglut (and no need for
>>patching the darcs
>>>> GLUT).  I wonder if glut32-vs-freeglut could account for
>>crash-vs-nocrash on
>>>> 6.10 and 6.11 but not 6.9.  I'd love to hear from someone on
>>Windows and
>>>> glut32.
>>>
>>> Windows XP with SP3
>>> ghc-6.10.20081007
>>> glut32
>>>
>>> Works fine for me.
>>>
>>> Taking a look at my GL headers, I did have to mess with at least
>>glut.h to get
>>> something to work---whether it was to build HOpenGL, to make
>>programs linkable,
>>> or to make them runnable, I'm not sure. In any case, what I did
>>was force
>>> GLUTAPIENTRY to be #defined as __stdcall.
>>>
>>> ___
>>> Haskell-Cafe mailing list
>>> Haskell-Cafe@haskell.org <mailto:Haskell-Cafe@haskell.org>
>>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>>
>>
>>
>>
>>--
>>I try to take things like a crow; war and chaos don't always ruin a
>>picnic, they just mean you have to be careful what you swallow.
>>
>>-- Jessica Edwards
>>___
>>Haskell-Cafe mailing list
>>Haskell-Cafe@haskell.org <mailto: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 mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>



-- 
I try to take things like a crow; war and chaos don't always ruin a
picnic, they just mean you have to be careful what you swallow.

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


[Haskell-cafe] Cairo build fail on OS X Leapord

2008-10-31 Thread Jefferson Heard
Installing gtk2hs from MacPorts on a clean mac:

2 -I/usr/X11R6/include

svgcairo/Graphics/Rendering/Cairo/SVG.chs:201:2:
Couldn't match expected type `()' against inferred type `CInt'
  Expected type: Render ()
  Inferred type: Render CInt
In the expression:
  liftIO
$ (\ (SVG arg1) (Cairo arg2)
   -> withForeignPtr arg1
$ \ argPtr1 -> rsvg_handle_render_cairo argPtr1 arg2)
svg cr
In the expression:
do cr <- ask
 liftIO
   $ (\ (SVG arg1) (Cairo arg2)
  -> withForeignPtr arg1
   $ \ argPtr1 -> rsvg_handle_render_cairo argPtr1 arg2)
   svg cr
make[1]: *** [svgcairo/Graphics/Rendering/Cairo/SVG.o] Error 1
rm svgcairo/Graphics/Rendering/Cairo/SVG.hs
make: *** [all] Error 2

Error: Status 1 encountered during processing.


-- 
I try to take things like a crow; war and chaos don't always ruin a
picnic, they just mean you have to be careful what you swallow.

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


Re: [Haskell-cafe] Cairo build fail on OS X Leapord

2008-11-03 Thread Jefferson Heard
how can we use those from MacPorts?  Is it possible?

On Mon, Nov 3, 2008 at 5:59 AM, Duncan Coutts
<[EMAIL PROTECTED]> wrote:
> On Fri, 2008-10-31 at 14:55 -0400, Jefferson Heard wrote:
>> Installing gtk2hs from MacPorts on a clean mac:
>
>> svgcairo/Graphics/Rendering/Cairo/SVG.chs:201:2:
>> Couldn't match expected type `()' against inferred type `CInt'
>
> The latest major release of the cairo C lib changed the API to return an
> int status code for a C function that previously returned void.
>
> c2hs guarantees us some degree of cross-language type safety and caught
> this api change for us (by turning it into a Haskell type error).
>
> I expect the updates to work with the new cairo api are in the gtk2hs
> darcs version.
>
> Duncan
>
>



-- 
I try to take things like a crow; war and chaos don't always ruin a
picnic, they just mean you have to be careful what you swallow.

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


[Haskell-cafe] HOpenGL wiki link to documentation is broken

2008-11-05 Thread Jefferson Heard
I suspect this has to do with the latest GHC not including it by
default, but the HOpenGL wiki's documentation links are broken.

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


[Haskell-cafe] Anyone know why this always returns invalid texture objects?

2008-11-06 Thread Jefferson Heard
import Graphics.UI.Gtk
import Graphics.UI.Gtk.Glade
import Graphics.UI.Gtk.OpenGL
import qualified Graphics.Rendering.OpenGL as GL
import Graphics.Rendering.OpenGL (($=))

main = do
  initGUI
  initGL
  GL.shadeModel $= GL.Flat
  GL.depthFunc $= Just GL.Less
  (window1,gui,dlgs) <- constructGUIObject
  (sX, sY) <- liftM (mapPair fromIntegral) . widgetGetSize .
drawing_canvas $ gui -- get the canvas size for determining the part
of the widget to repaint
  pb <- pixbufNew ColorspaceRgb False 8 (round pbWidth) (round pbHeight)
  pixbufFill pb 0 0 0 255
  pxbufs <- initSubpixbufs pb texRows texCols
  textures <- GL.genObjectNames (texRows*texCols)
  print textures


-- 
I try to take things like a crow; war and chaos don't always ruin a
picnic, they just mean you have to be careful what you swallow.

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


Re: [Gtk2hs-users] [Haskell-cafe] Anyone know why this always returns invalid texture objects?

2008-11-06 Thread Jefferson Heard
Ah, that's good to know.  I thought initGL would create the context.
Sorry to be unclear in the code I posted, but part of createGUIObject
is a glDrawingAreaNew.  It creates a drawing area, which is then
stored in a giant UserInterface record.

data UserInterface = MainWindow {
  ...
  , drawing_canvas :: GLDrawingArea
  }

createGUIObject = do
  ...
  config <- glConfigNew ...
  canvas <- glDrawingAreaNew config

  return $ MainWindow { ... drawing_canvas = canvas .. }

It seems that won't create the context?  do I have to show the window
first, or can I just do...

withGLDrawingArea $ glGenObjects n

?

Thanks!

-- Jeff

On Thu, Nov 6, 2008 at 9:15 PM, Bertram Felgenhauer
<[EMAIL PROTECTED]> wrote:
> [CCing gtk2hs-users]
>
> Jefferson Heard wrote:
>> import Graphics.UI.Gtk
>> import Graphics.UI.Gtk.Glade
>> import Graphics.UI.Gtk.OpenGL
>> import qualified Graphics.Rendering.OpenGL as GL
>> import Graphics.Rendering.OpenGL (($=))
>>
>> main = do
>>   initGUI
>>   initGL
>
> "initGL" may be slightly misleading - it initialises the
> gtkglext gtk+ extension. It does not create a GL context.
>
>>   GL.shadeModel $= GL.Flat
>>   GL.depthFunc $= Just GL.Less
>>   (window1,gui,dlgs) <- constructGUIObject
>>   (sX, sY) <- liftM (mapPair fromIntegral) . widgetGetSize .
>> drawing_canvas $ gui -- get the canvas size for determining the part
>> of the widget to repaint
>>   pb <- pixbufNew ColorspaceRgb False 8 (round pbWidth) (round pbHeight)
>>   pixbufFill pb 0 0 0 255
>>   pxbufs <- initSubpixbufs pb texRows texCols
>>   textures <- GL.genObjectNames (texRows*texCols)
>>   print textures
>
> There is no active GL context at this point. GtkGLExt creates
> new GL contexts for GL enabled widgets when they're realized -
> I think. I'm a bit fuzzy about the exact life time of the GL
> context. [1]
>
> After the context was created, you have to activate it before
> doing any GL operations.
>
> In Gtk2hs you can use the GLDrawingArea widget, which provides
> withGLDrawingArea for easy activation of the GL context.
>
> There's an example in the gtk2hs sources, in examples/opengl.
>
> Enabling GL for other widgets is not supported well at the moment.
> (There are low level bindings (using DrawWindow), but no generic
> binding to the higher level gtk_widget_set_gl_capability() call.
> Such support wouldn't be too hard to add, I think.)
>
> HTH,
>
> Bertram
>
> [1] see 
> http://gtkglext.sourceforge.net/reference/gtkglext/gtkglext-gtkglwidget.html#gtk-widget-get-gl-context
>
> -
> This SF.Net email is sponsored by the Moblin Your Move Developer's challenge
> Build the coolest Linux based applications with Moblin SDK & win great prizes
> Grand prize is a trip for two to an Open Source event anywhere in the world
> http://moblin-contest.org/redirect.php?banner_id=100&url=/
> ___
> Gtk2hs-users mailing list
> [EMAIL PROTECTED]
> https://lists.sourceforge.net/lists/listinfo/gtk2hs-users
>



-- 
I try to take things like a crow; war and chaos don't always ruin a
picnic, they just mean you have to be careful what you swallow.

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


Re: [Haskell-cafe] Re: What *not* to use Haskell for

2008-11-11 Thread Jefferson Heard
Actually, one language you mention there *is* worse than the others
for writing wrappable library code: C++.  Admittedly, they've got a
Python interface now via boost, but the main problem with writing
wrappable C++ code is the template system and the inheritence systems
getting in the way.  Symbol names aren't predictable and not
standardized, so it becomes impossible to write a portable system for
finding and binding to functions in a library.  I've not yet found a
good way to do it in FFI code, and I would love to, as one library in
particular I hold near and dear -- OpenSceneGraph -- is entirely
written in C++.

-- Jeff

On Tue, Nov 11, 2008 at 6:35 AM, Bulat Ziganshin
<[EMAIL PROTECTED]> wrote:
> Hello Mauricio,
>
> Tuesday, November 11, 2008, 2:26:21 PM, you wrote:
>
> imho, Haskell isn't worse here than any other compiled language - C++,
> ML, Eiffel and beter tnan Java or C#.every language has its own object
> model and GC. the only ay is to provide C-typed interfaces between
> languages (or use COM, IDL and other API-describing languages)
>
>> I think Haskell is not nice to write general purpouse libraries
>> that could be easily and completly wrapped by other languages.
>> You can wrap gtk, sqlite3, gsl, opengl etc., but you can't write
>> python bindings for Data.Graph.
>
>> But, then, if you claim there's nothing else Haskell can't do,
>> what do you need those bindings for ? :)
>
>> Best,
>> Mauricio
>
>>> Hi everyone
>>>
>>> So I should clarify I'm not a troll and do "see the Haskell light". But
>>> one thing I can never answer when preaching to others is "what does
>>> Haskell not do well?"
>>>
>>> Usually I'll avoid then question and explain that it is a 'complete'
>>> language and we do have more than enough libraries to make it useful and
>>> productive. But I'd be keen to know if people have any anecdotes,
>>> ideally ones which can subsequently be twisted into an argument for
>>> Haskell ;)
>>>
>>> Cheers,
>>>
>>> Dave
>
>> ___
>> Haskell-Cafe mailing list
>> Haskell-Cafe@haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
> --
> Best regards,
>  Bulatmailto:[EMAIL PROTECTED]
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>



-- 
I try to take things like a crow; war and chaos don't always ruin a
picnic, they just mean you have to be careful what you swallow.

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


Re: [Haskell-cafe] What *not* to use Haskell for

2008-11-11 Thread Jefferson Heard
Kyle, I would say that most apps don't actually require that you write
a mutation heavy inner loop.   They can be written either way, and
Haskell gives you the facility to do both. Even my field, which is
visualization can be written either way.  I write with a mutation
heavy inner loop myself, because it's how I started out, and I haven't
had any trouble with performance.  OpenGL is always my upper bound.
Even 2D code, which I've written on occasion seems not to suffer.

On Tue, Nov 11, 2008 at 5:23 PM, Kyle Consalus <[EMAIL PROTECTED]> wrote:
> On Tue, Nov 11, 2008 at 1:51 PM, Don Stewart <[EMAIL PROTECTED]> wrote:
>> consalus:
>>> On Tue, Nov 11, 2008 at 2:38 AM, Dave Tapley <[EMAIL PROTECTED]> wrote:
>>> > Hi everyone
>>> >
>>> > So I should clarify I'm not a troll and do "see the Haskell light". But
>>> > one thing I can never answer when preaching to others is "what does
>>> > Haskell not do well?"
>>> >
>>> > Usually I'll avoid then question and explain that it is a 'complete'
>>> > language and we do have more than enough libraries to make it useful and
>>> > productive. But I'd be keen to know if people have any anecdotes,
>>> > ideally ones which can subsequently be twisted into an argument for
>>> > Haskell ;)
>>> >
>>> > Cheers,
>>> >
>>> > Dave
>>> >
>>> > ___
>>> > Haskell-Cafe mailing list
>>> > Haskell-Cafe@haskell.org
>>> > http://www.haskell.org/mailman/listinfo/haskell-cafe
>>> >
>>>
>>> I think some would disagree with me, but I would advise against using
>>> haskell for a task that necessarily requires a lot of mutable state
>>> and IO and for which serious performance is a big factor.  I'm not
>>> talking about stuff that can be approximated by zippers and whatnot,
>>> but rather situations where IORefs abound and data has identity.
>>> Haskell can quite capably do mutable state and IO, but if your task is
>>> all mutable state and IO, I'd lean toward a language that makes it
>>> easier (OCaml, perhaps).
>>
>> Do you have an example of a mutable state/ IO bound application, like,
>> hmm, a window manager or a revision control system or a file system...?
>>
>> -- Don
>>
>
> Of course, with a lot of skill, good design, and a pile of language
> extensions state/io-heavy
> Haskell code can be clean and flexible. Performance can be pretty
> good, and for complex algorithmic
> code arguably a better choice than most other languages. Still,
> neither of the projects you reference (to my knowledge)
> have a mutation-heavy inner computation loop. XMonad does all of its
> mutation in a custom monad that is ReaderT StateT IO or something
> similar, and it apparently works beautifully. However, my
> understanding is that stack of monad transformers tend not to be
> particularly efficient, and while that usually isn't an issue, the
> case that I'm talking about is that where mutation
> performance is a major concern.
> Other languages offer similar expressive power, minus the joys of
> laziness and referential transparency.
> Persistent data structures are great, but if you're not using the
> persistence it is less convenient and less efficient.
> So again, Haskell _can_ do mutation and IO just fine, but if laziness,
> purity, and immutability will be the rare exception
> rather than the rule, might be easier to use a language that makes
> strictness and impurity easier.
> (Unless you're a Haskell guru, in which case I imagine Haskell is
> always the most convenient language to use).
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>



-- 
I try to take things like a crow; war and chaos don't always ruin a
picnic, they just mean you have to be careful what you swallow.

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


[Haskell-cafe] HAPPS on a major hosting provider?

2008-11-16 Thread Jefferson Heard
I was wondering if anyone's ever tried to run Haaps on a major hosting
provider, like oh, say Site5?  I have an app I'd otherwise use Rails
for and I thought I'd give Haaps a try...

-- Jeff


I try to take things like a crow; war and chaos don't always ruin a
picnic, they just mean you have to be careful what you swallow.

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


[Haskell-cafe] Why is this so inefficient?

2008-02-05 Thread Jefferson Heard
I thought this was fairly straightforward, but where the marked line
finishes in 0.31 seconds on my machine, the actual transpose takes
more than 5 minutes.  I know it must be possible to read data in
haskell faster than this.  I'm trying to read a 100MB comma delimited
file.  I've tried both CSV modules, and these take even longer to read
the file.  Is there some general best-practice for reading and parsing
large amounts of data that I'm not aware of?

I have tried, by the way, a couple of things, including putting a bang
(!) before row in transposeRow and using foldr instead of foldl', but
that didn't change anything other than force me to increase the stack
size to 100M on the command line.

I'm running in the profiler now, and I'll update this, but I thought I
would check and see if my head was on remotely straight to begin with.

-- Jeff

---
module ColumnMajorCSV where

import qualified Data.ByteString.Char8 as S
import qualified Data.Map as M
import qualified Data.List as L

transposeRow cols row = zipWith (:) row cols

transposeCSV :: [[S.ByteString]] -> M.Map String [S.ByteString]
transposeCSV (header:rows) = M.fromList (zip (map S.unpack header) spreadsheet)
where spreadsheet = L.foldl' transposeRow emptySheet rows
  emptySheet = take (length header) $ repeat []

dataFromFile :: String -> IO (M.Map String [S.ByteString])
dataFromFile filename = do
f <- S.readFile filename
print . length . map (S.split ',' $!) . S.lines $ f
 -- finishes in 0.31 seconds
return . transposeCSV . map (S.split ',' $!) . S.lines $ f  --
this takes 5 minutes and 6 seconds
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why is this so inefficient?

2008-02-05 Thread Jefferson Heard
I've switched to this, which gets rid of the ByteString instances
fairly quickly.  None of them make it into the final map.  I'm still
not getting any faster response out of it, and it also complains that
my stack size is too small for anything about 128K records or more.

import qualified Data.ByteString.Char8 as S
import qualified Data.Map as M
import qualified Data.List as L

transposeRow cols row = zipWith (:) (map (read . S.unpack) $ row) cols

transposeCSV :: [[S.ByteString]] -> M.Map String [Float]
transposeCSV (header:rows) = M.fromList (zip (map S.unpack header) spreadsheet)
where spreadsheet = L.foldl' transposeRow emptySheet rows
  emptySheet = take (length header) $ repeat []

dataFromFile :: String -> IO (M.Map String [Float])
dataFromFile filename = do
f <- S.readFile filename
return . transposeCSV . map (S.split ',' $!) . S.lines $ f

On Tue, Feb 5, 2008 at 1:15 PM, Don Stewart <[EMAIL PROTECTED]> wrote:
> If the  strings are relatively short, there can be a bottleneck
>  in the current Ord instance for Bytestrings. When lots of them
>  are in a map, the ffi calls to memcmp dominate.
>
>  I've a fix for this (do it all in Haskell for small strings), and
>  can push it if someone complains some more.
>
>  jefferson.r.heard:
>
>
> > I thought this was fairly straightforward, but where the marked line
>  > finishes in 0.31 seconds on my machine, the actual transpose takes
>  > more than 5 minutes.  I know it must be possible to read data in
>  > haskell faster than this.  I'm trying to read a 100MB comma delimited
>  > file.  I've tried both CSV modules, and these take even longer to read
>  > the file.  Is there some general best-practice for reading and parsing
>  > large amounts of data that I'm not aware of?
>  >
>  > I have tried, by the way, a couple of things, including putting a bang
>  > (!) before row in transposeRow and using foldr instead of foldl', but
>  > that didn't change anything other than force me to increase the stack
>  > size to 100M on the command line.
>  >
>  > I'm running in the profiler now, and I'll update this, but I thought I
>  > would check and see if my head was on remotely straight to begin with.
>  >
>  > -- Jeff
>  >
>  > ---
>  > module ColumnMajorCSV where
>  >
>  > import qualified Data.ByteString.Char8 as S
>  > import qualified Data.Map as M
>  > import qualified Data.List as L
>  >
>  > transposeRow cols row = zipWith (:) row cols
>  >
>  > transposeCSV :: [[S.ByteString]] -> M.Map String [S.ByteString]
>  > transposeCSV (header:rows) = M.fromList (zip (map S.unpack header) 
> spreadsheet)
>  > where spreadsheet = L.foldl' transposeRow emptySheet rows
>  >   emptySheet = take (length header) $ repeat []
>  >
>  > dataFromFile :: String -> IO (M.Map String [S.ByteString])
>  > dataFromFile filename = do
>  > f <- S.readFile filename
>  > print . length . map (S.split ',' $!) . S.lines $ f
>  >  -- finishes in 0.31 seconds
>  > return . transposeCSV . map (S.split ',' $!) . S.lines $ f  --
>  > this takes 5 minutes and 6 seconds
>  > ___
>  > Haskell-Cafe mailing list
>  > Haskell-Cafe@haskell.org
>  > http://www.haskell.org/mailman/listinfo/haskell-cafe
>



-- 
I try to take things like a crow; war and chaos don't always ruin a
picnic, they just mean you have to be careful what you swallow.

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


Re: [Haskell-cafe] Doubting Haskell

2008-02-16 Thread Jefferson Heard
  Since everyone's been focusing on the IO so far, I wanted to take a
quick stab at his mention of "green" vs. OS threads...  I like the
term "green", actually, as it's what my grandmother calls
decaffeinated coffee, owing to the fact that decaf taster's choice has
a big green plastic lid.  Distrust all coffee that comes in a plastic
lid, folks.  Life is better that way...

However, Haskell very much has real, caffeinated parallelism
mechanisms.  There is explicit concurrency, which says that things can
happen at the same time (see Control.Concurrent) and there is the
whole question of Glasgow Parallel Haskell and Data Parallel Haskell,
which I won't really begin to cover, as Manuel Chakravarty and Simon
Peyton Jones will do TONS better at explaining these than I can.  I
will however mention Control.Parallel and Control.Parallel.Strategies,
because they're my personal favorite way of being parallel.

The Haskell thread is semantically much like the Java thread, it's
green, in other words, but you can control the number of real OS
threads that Haskell threads are executed on at the command line.
Thus you might call them "half caffeinated"  But, at least with
Control.Parallel.Strategies, they're SO much easier to use.  There are
a couple of caveats, but I'll give an example first.  Let's say you're
doing some heavy computer graphics, but you're doing it all in
spherical coordinates (I do this all the time, which is why I'm using
it as an example) and before you go to OpenGL, you need to transform
everything into Carteisan coordinates.

vertices :: [GL.Vertex3] -- a list of oh, say, 150,000 vertices or so
in spherical coordinates

sphericalToCart :: GL.Vertex3 -> GL.Vertex3
sphericalToCart (GL.Vertex3 r a z) = (GL.Vertex3 (r * cos a * sin z)
(r * sin a * sin z) (r * cos a))

Now to convert them all, you'd just do a

map sphericalToCart vertices

and that would do a lazy conversion of everything, but since you know
you're going to use all the vertices, strictness is just as well, and
you can do strict things in parallel this way:

parMap rwhnf sphericalToCart vertices

or even more efficiently,

map rwhnf sphericalToCart vertices `using` parListChunk 1024

That'll execute on all cores of your processor and do the same
operation much faster, if you were going to have to do the entire
operation anyway.

-- Jeff

On Sat, Feb 16, 2008 at 5:05 PM, Alan Carter <[EMAIL PROTECTED]> wrote:
> Greetings Haskellers,
>
>  I'm a Haskell newbie, and this post began as a scream for help. Having
>  slept on it I find myself thinking of Simon Peyton-Jones' recent
>  request for good use cases. Perhaps a frustrated - and doubting -
>  newbie can also provide a data point. If my worries are unfounded (and
>  I hope they are), I think it's significant that to me, today, they
>  seem real enough. Please understand that I'm not being negative for
>  the sake of it - rather I'm describing what Haskell looks like from
>  the outside.
>
>  Let me put it this way. Imagine that two weeks ago my forward-thinking
>  and risk-embracing boss asked me to evaluate Haskell for the upcoming
>  Project X. Further imagine that she ensured I was able to sit in the
>  corner emitting curses for the whole two weeks, and on Monday I have
>  to provide my report.
>
>  At this point, two weeks in, I would be forced to say that I have no
>  reason to believe that Haskell is useful for real world tasks. ghc is
>  an industrial strength compiler for a toy language. While remarkable
>  claims are made for it, in practice even the experts are often unable
>  to implement the most basic behaviours, and where they are able to
>  implement, they find that their program has become so complex that
>  they are unable to describe or discuss the result. Likely this is a
>  deep problem, not a shallow one. The Haskell community is in denial
>  over this, leading to phenomenal time wasting as one goes round and
>  round in circles playing word games with documentation. This risks a
>  return of the chronic embuggerance that we thought we'd escaped when
>  Vista appeared and the set of people who would have to write Windows
>  device drivers reduced to Hewlett Packard employees, Joanna Rutkowska
>  and criminals. When people enthuse about Haskell, we should run a
>  program called Cat.hs from the haskell.org website, throw fruit at
>  them and laugh.
>
>  Strong words, but in all honesty I *want* to believe, and if I would
>  make such a report I imagine hundreds if not thousands would say the
>  same thing. I'm hoping I'm wrong about this, and what's actually
>  needed is some work on communication (perhaps from a production
>  programming point of view, which I'd be keen to help with).
>
>  What got me started with Haskell was the video of an Intel employee
>  holding a Teraflops in his hand. I still remember the very silly
>  September 1991 edition of Scientific American, which asked if a
>  Teraflops would *ever* be built. What a stupid question! Stack up
>  enough

[Haskell-cafe] Rendering TTF fonts in Haskell and OpenGL

2008-02-17 Thread Jefferson Heard
In C and in Java, I can use truetype fonts in Haskell using select
libraries, and I'd like to be able to do the same in Haskell.  Are
there any portable libraries out there for loading fonts into OpenGL
geometry for Haskell?  I can use the vector fonts from GLUT is
absolutely neccessary, but I'd like something that looks a little more
professional.  Are there any suggestions?

-- Jeff

-- 
I try to take things like a crow; war and chaos don't always ruin a
picnic, they just mean you have to be careful what you swallow.

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


Re: [Haskell-cafe] Rendering TTF fonts in Haskell and OpenGL

2008-02-17 Thread Jefferson Heard
Thanks.  that's certainly a thought...  doesn't make the text 3d,
though, does it?  I'd ideally like to have something that turns the
text into geometry, but this'll do in a pinch...

On Sun, Feb 17, 2008 at 8:26 PM, Luke Palmer <[EMAIL PROTECTED]> wrote:
> On Feb 18, 2008 12:20 AM, Brandon S. Allbery KF8NH <[EMAIL PROTECTED]> wrote:
>  >
>  > On Feb 17, 2008, at 19:13 , Jefferson Heard wrote:
>  >
>  > > In C and in Java, I can use truetype fonts in Haskell using select
>  > > libraries, and I'd like to be able to do the same in Haskell.  Are
>  > > there any portable libraries out there for loading fonts into OpenGL
>  > > geometry for Haskell?  I can use the vector fonts from GLUT is
>  > > absolutely neccessary, but I'd like something that looks a little more
>  > > professional.  Are there any suggestions?
>  >
>  > Can't speak to OpenGL per se, but have a look at:
>  > http://hackage.haskell.org/cgi-bin/hackage-scripts/package/SDL-ttf-0.4.0
>  > http://hackage.haskell.org/cgi-bin/hackage-scripts/package/X11-xft-0.2
>
>  I have an immature, but precise and picky implementation that renders text in
>  a ttf font to an OpenGL texture (using SDL-ttf) here:
>  http://svn.luqui.org/svn/misc/luke/work/code/haskell/frp/Fregl/Draw.hs
>  (It may have some dependencies in the same directory).  Text support is
>  way at the bottom.
>
>  Good Luck,
>
>  Luke
>



-- 
I try to take things like a crow; war and chaos don't always ruin a
picnic, they just mean you have to be careful what you swallow.

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


[Haskell-cafe] Tutorial for using the state monad or a better suggestion?

2008-02-22 Thread Jefferson Heard
So the reason I keep pinging the list so much of late is I'm currently
writing a GLUT program to visualize a heirarchical clustering of
18,000+ protein-protein interaction pairs (and associated
gene-ontology terms).  Thanks for the help on reading CSVs, those who
wrote me back...  my program intitializes and displays its first image
within 6 seconds, about 10 times faster and in 10 times less memory
than the Java program the guy was using.

Now I'm to the point of making this thing interactive, and I I'm
trying to figure out the Haskell way of doing this.  Last time I wrote
a program like this, I made a record data type with all the state and
placed it into an IORef and curried it into the GLUT callback
functions.  I'm going to do the same thing now if there aren't cringes
and wailings from people with a better sense of pure-functional
aesthetics out there on the list with a willingness to either point me
towards a tutorial that would help me do this better.  Keep in mind
that Graphics.UI.GLUT callbacks all want to return an IO (), and thus
leftover state monads at ends of functions aren't going to be
acceptable to the standard library...

Any ideas?  Oh, currently my program state includes:

The geometry I'm rendering (Ptr GLfloat vertex and color arrays),
The same geometry as a display list for rendering into the selection buffer
An indexed and named tree that represents the clustering
A tree of text containing tooltips to display
The previous current mouse position (for dragging purposes)
A couple of histograms as Array.IArray.Diff.DiffArrays
Various parameters for constructing rendered data out of the indexed
tree (for reconstruction after a node is collapsed/expanded)

So I'm carrying around some pretty bulky state; should give you some
understanding as to why I thougt the record data type would be the
sanest way to do this without polluting my parameter list with
individual IORrefs.

Oh, and again, it's not that I don't know that I can make the IORef
solution work, I can and I've done it before.  It's just that I
thought there might be a prettier way to do this.

Thanks in advance!

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


Re: [Haskell-cafe] Tutorial for using the state monad or a better suggestion?

2008-02-22 Thread Jefferson Heard
Thanks.  There seems to be some consensus developing around using
IORefs to hold all the program state.

-- Jeff

On Fri, Feb 22, 2008 at 12:11 PM, Brandon S. Allbery KF8NH
<[EMAIL PROTECTED]> wrote:
>
>  On Feb 22, 2008, at 9:15 , Jefferson Heard wrote:
>
>  > Now I'm to the point of making this thing interactive, and I I'm
>  > trying to figure out the Haskell way of doing this.  Last time I wrote
>  > a program like this, I made a record data type with all the state and
>  > placed it into an IORef and curried it into the GLUT callback
>  > functions.  I'm going to do the same thing now if there aren't cringes
>  > and wailings from people with a better sense of pure-functional
>  > aesthetics out there on the list with a willingness to either point me
>  > towards a tutorial that would help me do this better.  Keep in mind
>  > that Graphics.UI.GLUT callbacks all want to return an IO (), and thus
>  > leftover state monads at ends of functions aren't going to be
>  > acceptable to the standard library...
>
>  What I do (with gtk2hs) is visible at http://hpaste.org/3137 ---
>  MWPState is a fairly large record.
>
>  I will note that this code stores the mutable data in separate
>  IORefs, whereas I'm told that it's better to use a single IORef with
>  all the mutable state inside it.  (For some reason I had assumed that
>  the overhead would be higher.)  That said, the wrappers make it
>  fairly easy to refactor it.  Since the IORef(s) and much of the
>  remaining state is read-only, I use a ReaderT IO instead of StateT
>  IO; this also turned out to be convenient for what turned out to be a
>  significant optimization (in response to a timer firing, it collects
>  a bunch of data and feeds it into a TreeView, and it turned out to be
>  useful to collect it all at the front and use local to roll a
>  modified record with the cached values).
>
>  (The code in that paste is rather out of date, probably I should
>  update it.)
>
>  --
>  brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
>  system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
>  electrical and computer engineering, carnegie mellon universityKF8NH
>
>
>



-- 
I try to take things like a crow; war and chaos don't always ruin a
picnic, they just mean you have to be careful what you swallow.

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


[Haskell-cafe] Error I haven't seen before

2008-02-28 Thread Jefferson Heard
I'm getting this error when I try to render the text contained in a record
structure in the Protein module.  Does this mean that the thunk that could
calculate go_terms is being evaluated for the first time in the program?
go_terms is calculated by a Data.Map.! lookup operation.

Main: No match in record selector Protein.go_terms
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Error I haven't seen before

2008-02-28 Thread Jefferson Heard
It does.  Thank you...

On Thu, Feb 28, 2008 at 5:00 PM, Albert Y. C. Lai <[EMAIL PROTECTED]> wrote:

> Jefferson Heard wrote:
> > Main: No match in record selector Protein.go_terms
>
> data R = A { sa :: Int } | B { sb :: Int }
>
> sa (A 0) works (as expected). sa (B 0) gives
>
> *** Exception: No match in record selector Main.sa
>
> I think that explains your problem.
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>



-- 
I try to take things like a crow; war and chaos don't always ruin a picnic,
they just mean you have to be careful what you swallow.

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


[Haskell-cafe] Failing to make `par`

2008-03-03 Thread Jefferson Heard
I've used Control.Parallel and Control.Parallel.Strategies extensively in
the past, and I thought I knew what I was doing.  I declared the following
function:

findSupernodes' :: S.Set Name -> Int -> Tree -> Protein.Tree -> S.Set Name
findSupernodes' set size (Node i _ _ s il ir) (Protein.Node _ pl pr _ g)
| S.size g > size = (Name (fromIntegral i)) `S.insert` set
| otherwise   =  leftNodes `S.union` rightNodes
where leftNodes =  (findSupernodes' set size il pl)
  rightNodes = (findSupernodes' set size il pl)
findSupernodes' set size (Leaf _ _) (Protein.Gene _ _ _) = set

and then simply wrote the following as an initial stab at parallelizing it,
because actually calling this function causes the program to execute an
absurd number of string comparisons:

findSupernodes = findSupernodes' S.empty
findSupernodes' :: S.Set Name -> Int -> Tree -> Protein.Tree -> S.Set Name
findSupernodes' set size (Node i _ _ s il ir) (Protein.Node _ pl pr _ g)
| S.size g > size = (Name (fromIntegral i)) `S.insert` set
| otherwise   =  leftNodes `par` rightNodes `seq` leftNodes
`S.union` rightNodes
where leftNodes =  (findSupernodes' set size il pl)
  rightNodes = (findSupernodes' set size il pl)
findSupernodes' set size (Leaf _ _) (Protein.Gene _ _ _) = set

The thing is, these two functions don't return the same thing.  The parallel
version is returning an empty set, while the sequential version returns what
it should return.  Any clue what I did wrong?

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


[Haskell-cafe] Thanks for the help: image of draft visualization

2008-03-07 Thread Jefferson Heard
Thanks for everyone's help on the list re my Haskell woes with the latest
visualization effort. I've been making my code more generic for the last
week, and I plan on releasing a visualization framework back to the
community at some point.  Gotta get approval from my boss before releasing
code back to the wild, but here's an image of the draft of the visualization
I've been working on:

http://vizdata.renci.org/projects/jeff/ProteinViz/ProteinViz.png

Basically, what you're seeing is 18,500 genes arranged in a full
heirarchical clustering (the clustering technique uses a metric I'm
unfamiliar with, and I got the dataset pre-packaged from the guy who's using
it).  The final visualization is fully interactive and runs fine under
Linux, dies a miserable death under windows (runs out of RAM, and I can't
figure out why, nor do I particularly care), and primarily runs on our 14
foot by 9 foot (4.5x3 metres for those of us in metric) linux display wall.
The full program is about 800 linux of Haskell code using nothing but the
standard library under GHC 6.8.

Again, thanks for all your help!

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


[Haskell-cafe] BUG: genObjectNames dies on Win32

2008-03-24 Thread Jefferson Heard
Could this get forwarded on to another more appropriate maling list?

Confirmed on GHC and GHCi 6.6 and 6.8,

Graphics.Rendering.OpenGL.GL.genObjectNames n is dying if I ask it to
return an IO :: [DisplayList]

For an example, just open GHCI and change context to
Graphics.Rendering.OpenGL.GL and do

genObjectNames 4 :: IO [DisplayList]

GHCi will merely die.  Compiled with GHC, I'm simply running out of
memory.  It eats RAM indefinitely.

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


Re: [Haskell-cafe] Functional board games

2008-04-21 Thread Jefferson Heard
Ralph Glass has a Xiang Qi board:  http://xiangqiboard.blogspot.com/

On Mon, Apr 21, 2008 at 11:22 AM, Dougal Stanton <[EMAIL PROTECTED]>
wrote:

> I'm having a go at making a functional board game (the back-end logic
> for one, at least) and as with all good projects it raises lots of
> questions. But I'll keep it to one this time.
>
> Does anyone know of functional-style implementations of
> chess/draughts/go/anything else that might give me ideas? I am writing
> a game of Thud (yes, from the Terry Pratchett book...) but I don't
> hold much hope of their being a functional-style Thud game already in
> existence!
>
> Cheers,
>
> D.
>
> --
> Dougal Stanton
> [EMAIL PROTECTED] // http://www.dougalstanton.net
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>



-- 
I try to take things like a crow; war and chaos don't always ruin a picnic,
they just mean you have to be careful what you swallow.

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


Re: [Haskell-cafe] Trying to build a stand-alone executable GLUT app with ghc, Windows XP

2008-04-25 Thread Jefferson Heard
Google "download glut32.dll" and pull that file down and put it in the
directory with your executable.  I'd attach it myself, but gmail won't let
me.  I use that all the time, though.

2008/4/25 Peter Schmitz <[EMAIL PROTECTED]>:

> Problem summary
>
> Trying to build a stand-alone executable GLUT app with ghc, Windows XP
>
> Problem description
>
> I compile and link (without errors) a simple GLUT application under Windows
> XP.
> When I run it, XP pops an error window saying the app cannot start due to a
> missing "glut32.dll".
>
> I want to do a static build to create a stand-alone executable GLUT app
> under Windows XP,
> without using DLL files, or placing any files in the Windows system dir.
> This is my first GUI code in Haskell, and I chose GLUT because it is a
> standard library.
>
> Following are some details.
> Thanks much for any advice.
>
> Source code
>
> -- Simple GLUT app to create a window
> module Main(main) where
>
> import Graphics.Rendering.OpenGL
> import Graphics.UI.GLUT
>
> main = do
>(progname, _) <- getArgsAndInitialize
>createWindow "Hello World"
>mainLoop
>
>  Compile/run Environment
>
> ghc-6.8.2 on a USB flashdrive under a non-admin Windows XP account
>
> ghc dir is not on C:
>
> E:\apps\ghc\ghc-6.8.2
>
> XP shell used: cmd.exe
>
> shell path
>
> E:\ghcTest>path
>
> PATH=C:\WINDOWS\system32;C:\WINDOWS;E:\apps\ghc\ghc-6.8.2\bin;.\
>
> ghc library path
>
> E:\ghcTest>ghc --print-libdir
>
> E:/apps/ghc/ghc-6.8.2
>
> compile/link output
>
> E:\ghcTest>ghc --make x  -package GLUT
>
> [1 of 1] Compiling Main ( x.hs, x.o )
>
> Linking x.exe ...
>
> E:\ghcTest>
>
> files (sizes in bytes)
>
>186 x.hs
>387 x.hi
> 3,184 x.o
>498 x.exe.manifest
> 609,222 x.exe
>
>  When application is run
>
> Error dialog window pops up
>
> window title
>
> a.exe - Unable To Locate Component
>
> window text
>
> The application has failed to start because glut32.dll was not found.
> Re-installing the application may fix this problem.
>
> No output in shell; no glut window is created.
>
>
>
> Other builds tried; same runtime error
>
> ghc  --make x  -package GLUT  -static
>
> ghc -package GLUT  x.hs  -o x
>
> ghc --make x  -package GLUT  -LE:\apps\ghc\ghc-6.8.2\lib\GLUT-2.1.1.1
>
> ghc --make x  -LE:\apps\ghc\ghc-6.8.2\lib\GLUT-2.1.1.1
>
> --
>
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>


-- 
I try to take things like a crow; war and chaos don't always ruin a picnic,
they just mean you have to be careful what you swallow.

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


Re: [Haskell-cafe] Copying Arrays

2008-05-29 Thread Jefferson Heard
Define too slow, time-consuming?  I've dealt with this problem a lot
at this point, and I've been able to slurp up CSV files of several
gigabytes in the same amount of time as I generally do in C.  I have a
feeling an array solution is just going to bog you down more, however
if you insist, I would also suggest writing your I/O in C and
returning a ForeignPtr to something and work from there.

-- Jeff

On Thu, May 29, 2008 at 12:21 PM, Tom Harper
<[EMAIL PROTECTED]> wrote:
> I'm trying to implement some file I/O where I can read in a file to an
> array, but do so without having to know how much space I will need.
> (Before you suggest it, lists are too slow/space consuming.)  I was
> thinking that one possible solution is to use a strategy used in
> dynamic arrays, where everytime you run out of space you double the
> capacity of the array.  Trouble is, most arrays in Haskell would
> require you to traverse the entire array and copy each individual
> cell, which would make it worthless.
>
> Are there any low-level array types (MutableByteArray#, for example)
> that support a memcpy-like function where I could copy the entire
> array into the new one instead of copying it one value at a time?  Is
> there another solution that I'm missing?
>
>
> --
> Tom Harper
> MSc Computer Science '08
> University of Oxford
> Mobile: +44 (0)7533 998 591
> Skype: +1 949 273 4627 (harpertom)
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>



-- 
I try to take things like a crow; war and chaos don't always ruin a
picnic, they just mean you have to be careful what you swallow.

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


Re: [Haskell-cafe] Copying Arrays

2008-05-29 Thread Jefferson Heard
Exactly.  Someone on the list gave me this example awhile back for
reading CSV files.  I can process a gigabyte (simple unpack and print
to dev/null for IO testing purposes) in about two and a half seconds
using this code.

import Data.ByteString.Lazy.Char8 as C

-- | Read a datafile and turn it into lists of columns
readDatafileAndTranspose name = do
sheet <- (transpose . map (C.split '\t') . C.lines) `fmap` C.readFile name
return $ foldl' go M.empty sheet
  where go m (x:xs) = M.insert (C.unpack x) xs m


2008/5/29 Adrian Neumann <[EMAIL PROTECTED]>:
> Isn't fast IO what ByteStrings where invented for?
>
> Adrian
>
> Tom Harper schrieb:
>>
>> I'm trying to implement some file I/O where I can read in a file to an
>> array, but do so without having to know how much space I will need.
>> (Before you suggest it, lists are too slow/space consuming.)  I was
>> thinking that one possible solution is to use a strategy used in
>> dynamic arrays, where everytime you run out of space you double the
>> capacity of the array.  Trouble is, most arrays in Haskell would
>> require you to traverse the entire array and copy each individual
>> cell, which would make it worthless.
>>
>> Are there any low-level array types (MutableByteArray#, for example)
>> that support a memcpy-like function where I could copy the entire
>> array into the new one instead of copying it one value at a time?  Is
>> there another solution that I'm missing?
>>
>>
>
>
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>



-- 
I try to take things like a crow; war and chaos don't always ruin a
picnic, they just mean you have to be careful what you swallow.

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


[Haskell-cafe] Wrapping FTGL in FFI calls

2008-06-19 Thread Jefferson Heard
I've been looking for awhile now for a simple way to get truetype fonts into
my visualizations so I can abandon the hideous GLUT fonts and make things
that look like they were developed in the 1990s instead of back in the days
of TRON.  I found FTGL, but I'm mostly a Haskell developer these days, and
resent having to go back to C just to write a simple application.

So I was wondering if anyone had ever wrapped the FTGL library in Haskel FFI
or whether those out there who are experts on the FFI think at first glance
it should be readily wrappable by a rank amateur at FFI such as myself.

http://ftgl.sourceforge.net/docs/html/

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


[Haskell-cafe] Wrapping FTGL in FFI calls

2008-06-19 Thread Jefferson Heard
I've been looking for awhile now for a simple way to get truetype fonts into
my visualizations so I can abandon the hideous GLUT fonts and make things
that look like they were developed in the 1990s instead of back in the days
of TRON.  I found FTGL, but I'm mostly a Haskell developer these days, and
resent having to go back to C just to write a simple application.

So I was wondering if anyone had ever wrapped the FTGL library in Haskel FFI
or whether those out there who are experts on the FFI think at first glance
it should be readily wrappable by a rank amateur at FFI such as myself.

http://ftgl.sourceforge.net/docs/html/

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


Re: [Haskell-cafe] Re: Wrapping FTGL in FFI calls

2008-06-20 Thread Jefferson Heard
Well, Achim you were almost exactly correct.  I have a functional function
interface in about half an hour's worth of work.  I have one question, which
is how to create a Ptr to four CFloats on the fly, pass them to the bounding
box functions, and then come back out with a [Float]

My prototype looks like this:
foreign import ccall unsafe "ftglGetFontBBox" fgetFontBBox :: Font ->
CString -> Ptr CFloat -> IO ()

the ptr to cfloat should be a float[4], which is modified inside the
original C function.

On Fri, Jun 20, 2008 at 1:16 AM, Achim Schneider <[EMAIL PROTECTED]> wrote:

> "Jefferson Heard" <[EMAIL PROTECTED]> wrote:
>
> > I've been looking for awhile now for a simple way to get truetype
> > fonts into my visualizations so I can abandon the hideous GLUT fonts
> > and make things that look like they were developed in the 1990s
> > instead of back in the days of TRON.  I found FTGL, but I'm mostly a
> > Haskell developer these days, and resent having to go back to C just
> > to write a simple application.
> >
> > So I was wondering if anyone had ever wrapped the FTGL library in
> > Haskel FFI or whether those out there who are experts on the FFI
> > think at first glance it should be readily wrappable by a rank
> > amateur at FFI such as myself.
> >
> > http://ftgl.sourceforge.net/docs/html/
> >
> Using the FFI is generally straight forward, as long as you can live
> with using the IO monad and the C code uses objects (well,
> pointers to structs passed as first argument, where's the
> difference...).
>
> Things only depend on the purity of the C code and how high-level you
> want your interface to be. In this case, I estimate half an hour if
> you're a fast typist. That includes the time needed to read the FFI
> docs.
>
> --
> (c) this sig last receiving data processing entity. Inspect headers for
> past copyright information. All rights reserved. Unauthorised copying,
> hiring, renting, public performance and/or broadcasting of this
> signature prohibited.
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>



-- 
I try to take things like a crow; war and chaos don't always ruin a picnic,
they just mean you have to be careful what you swallow.

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


Re: [Haskell-cafe] Re: Wrapping FTGL in FFI calls

2008-06-20 Thread Jefferson Heard
Oh, and I should say the function I want to implement is

getFontBBox :: Font -> String -> IO [Float]

I do know how to marhsal/unmarshal the String.  Just not the CFloat array to
Haskell [Float]

On Fri, Jun 20, 2008 at 2:25 PM, Jefferson Heard <
[EMAIL PROTECTED]> wrote:

> Well, Achim you were almost exactly correct.  I have a functional function
> interface in about half an hour's worth of work.  I have one question, which
> is how to create a Ptr to four CFloats on the fly, pass them to the bounding
> box functions, and then come back out with a [Float]
>
> My prototype looks like this:
> foreign import ccall unsafe "ftglGetFontBBox" fgetFontBBox :: Font ->
> CString -> Ptr CFloat -> IO ()
>
> the ptr to cfloat should be a float[4], which is modified inside the
> original C function.
>
>
> On Fri, Jun 20, 2008 at 1:16 AM, Achim Schneider <[EMAIL PROTECTED]> wrote:
>
>> "Jefferson Heard" <[EMAIL PROTECTED]> wrote:
>>
>> > I've been looking for awhile now for a simple way to get truetype
>> > fonts into my visualizations so I can abandon the hideous GLUT fonts
>> > and make things that look like they were developed in the 1990s
>> > instead of back in the days of TRON.  I found FTGL, but I'm mostly a
>> > Haskell developer these days, and resent having to go back to C just
>> > to write a simple application.
>> >
>> > So I was wondering if anyone had ever wrapped the FTGL library in
>> > Haskel FFI or whether those out there who are experts on the FFI
>> > think at first glance it should be readily wrappable by a rank
>> > amateur at FFI such as myself.
>> >
>> > http://ftgl.sourceforge.net/docs/html/
>> >
>> Using the FFI is generally straight forward, as long as you can live
>> with using the IO monad and the C code uses objects (well,
>> pointers to structs passed as first argument, where's the
>> difference...).
>>
>> Things only depend on the purity of the C code and how high-level you
>> want your interface to be. In this case, I estimate half an hour if
>> you're a fast typist. That includes the time needed to read the FFI
>> docs.
>>
>> --
>> (c) this sig last receiving data processing entity. Inspect headers for
>> past copyright information. All rights reserved. Unauthorised copying,
>> hiring, renting, public performance and/or broadcasting of this
>> signature prohibited.
>>
>> ___
>> Haskell-Cafe mailing list
>> Haskell-Cafe@haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>
>
>
>
> --
> I try to take things like a crow; war and chaos don't always ruin a picnic,
> they just mean you have to be careful what you swallow.
>
> -- Jessica Edwards




-- 
I try to take things like a crow; war and chaos don't always ruin a picnic,
they just mean you have to be careful what you swallow.

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


Re: [Haskell-cafe] Re: Wrapping FTGL in FFI calls

2008-06-20 Thread Jefferson Heard
Exactly.  thanks!

On Fri, Jun 20, 2008 at 4:26 PM, Jules Bean <[EMAIL PROTECTED]> wrote:

> Jefferson Heard wrote:
>
>> Oh, and I should say the function I want to implement is
>>
>> getFontBBox :: Font -> String -> IO [Float]
>>
>> I do know how to marhsal/unmarshal the String.  Just not the CFloat array
>> to Haskell [Float]
>>
>
> import Foreign.C
> import Foreign.Ptr
> import Foreign.Marshal.Array
>
> import Control.Applicative((<$>))
>
> oneway :: Ptr CFloat -> IO [Float]
> oneway p = map real2Frac <$> peekArray 4 p
>
> the other way you would probably want withArray, but I think this is the
> way you need?
>
>
>


-- 
I try to take things like a crow; war and chaos don't always ruin a picnic,
they just mean you have to be careful what you swallow.

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


[Haskell-cafe] Error in configure script for GHC

2008-06-27 Thread Jefferson Heard
I've tried all the 6.6 and 6.8 versions, trying to compile them on a
RHEL-based supercomputer, and I always see this error when I run
./configure:

-bash-3.00$ ./configure
checking build system type... x86_64-unknown-linux-gnu
checking host system type... x86_64-unknown-linux-gnu
checking target system type... x86_64-unknown-linux-gnu
Which we'll further canonicalise into: x86_64-unknown-linux
checking for path to top of build tree... pwd: timer_create: Invalid
argument
configure: error: cannot determine current directory

Is this a known bug with GHC, or is it my supercomputer?  We have several
supercomputers here running in production, so I can't really ask them to
change the configuration just for me, but nonetheless I'd like to run on
them.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Error in configure script for GHC

2008-06-27 Thread Jefferson Heard
Linux version 2.6.9-34.0.2.ELsmp ([EMAIL PROTECTED]) (gcc
version 3.4.5 20051201 (Red Hat 3.4.5-2)) #1 SMP Fri Jul 7 18:22:55 CDT 2006

This is my version string if that helps...  I'd do the bootstrap build right
now, but hackage is down (I understand it's moving), and I can't get to the
instructions for bootstrapping.

On Fri, Jun 27, 2008 at 2:00 PM, Brandon S. Allbery KF8NH <
[EMAIL PROTECTED]> wrote:

>
> On Jun 27, 2008, at 10:15 , Jefferson Heard wrote:
>
>  checking for path to top of build tree... pwd: timer_create: Invalid
>> argument
>>
>
> Translated into plain English, this means "your glibc is too old for this
> binary distribution".
> You will probably have to build from source with an older gcc as the
> bootstrap compiler.
>
> --
> brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
> system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
> electrical and computer engineering, carnegie mellon universityKF8NH
>
>
>


-- 
I try to take things like a crow; war and chaos don't always ruin a picnic,
they just mean you have to be careful what you swallow.

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


Re: [Haskell-cafe] Newbie: Appending arrays?

2008-07-10 Thread Jefferson Heard
Two questions.  How often does the array change, and how big does it
get?  It may well be that you just copy it and take the hit, as
that'll be cheaper (even in C, incidentally) than any other solution,
if it's a short array or if the updates happen rarely.

If not, try using Data.Array.Diff and replaceDiffArray.  This is
usually fairly efficient for most applications.

By the way, depending on the type of the data you're putting into
these arrays, Data.ByteString might be a good choice as well.

On Thu, Jul 10, 2008 at 12:12 PM, Felipe Lessa <[EMAIL PROTECTED]> wrote:
> 2008/7/10 Dmitri O.Kondratiev <[EMAIL PROTECTED]>:
>> allows construct an array of a fixed size. How to add more elements to the
>> array later?
>
> I can't really answer your question, however I bet that it would
> require allocating another, bigger array and copying the old elements
> over, at least from time to time. So you may want to take a look at
> Data.Sequence[1], supporting O(1) append on both sides and (sort of)
> O(log i) for accessing the i-th element.
>
> [1] 
> http://www.haskell.org/ghc/docs/latest/html/libraries/containers/Data-Sequence.html
>
> HTH,
>
> --
> Felipe.
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>



-- 
I try to take things like a crow; war and chaos don't always ruin a
picnic, they just mean you have to be careful what you swallow.

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


[Haskell-cafe] Remote control of firefox through Haskell?

2008-07-15 Thread Jefferson Heard
Is there a library out there that will allow me to remote-control the
firefox or mozilla browsers, e.g. change the current page, open a new
tab?

-- 
I try to take things like a crow; war and chaos don't always ruin a
picnic, they just mean you have to be careful what you swallow.

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


Re: [Haskell-cafe] Remote control of firefox through Haskell?

2008-07-15 Thread Jefferson Heard
Thanks, Rahul, Don.  These work...
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Space leaks

2008-07-17 Thread Jefferson Heard
Peter, from 500 feet, we can't see much, but your strictness might
actually be your problem depending on what "largish" looks like and
whether you're reading your data from disc.  It's entirely possible
that your data structure updates or disc reads are head-strict and
you're evaluating or loading the entirety of data in memory at a
single update.

-- Jeff

On Thu, Jul 17, 2008 at 2:58 PM, Luke Palmer <[EMAIL PROTECTED]> wrote:
> On Thu, Jul 17, 2008 at 12:14 PM, Peter Gavin <[EMAIL PROTECTED]> wrote:
>> Hello everyone,
>>
>> I have this piece of code I've been working on, and I've been stuck on
>> tracking down a space leak in it for some time now.  The code is essentially
>> a tight loop that updates a rather largish data structure with embedded
>> functions that are called by the driver loop.  The code doesn't accumulate
>> any data as the loop runs (at least deliberately), so I would expect the
>> memory profile to be flat.  Unfortunately, the profile is a wedge :)   I've
>> added bangs and `seq` literally everywhere, and it looks (to me at least)
>> like there's nothing left to be lazily evaluated anywhere.  I've used
>> retainer profiling, and the functions that are leaking space according to
>> the profiler output are strict throughout.
>
> I don't know what I can suggest as for general tactics.  Without
> seeing the code it's hard to say what could be happening.  Just
> remember that strictness is not always the answer!
>
> >From the very limited amount of information I got from this
> description, my first guess would be the data structure itself, or the
> functions inside it.  If it's lazily generated, then you might not be
> seeing the full amount of space it's taking up at once.  But that's
> just a guess.
>
> Luke
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>



-- 
I try to take things like a crow; war and chaos don't always ruin a
picnic, they just mean you have to be careful what you swallow.

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


Re: [Haskell-cafe] [Off-topic] Loss of humour

2008-07-23 Thread Jefferson Heard
http://bash.org ?

On Wed, Jul 23, 2008 at 2:45 PM, Andrew Coppin
<[EMAIL PROTECTED]> wrote:
> A while back I found a page somewhere containing some rather amusing IRC
> quotes. Unfortunately it seems to have vanished. I can't remember where on
> earth I found it, but I've scoured the Internet trying to track it down. (In
> particular, it contained a quote of somebody impersonating a typical Haskell
> newbie - lots of enthusiasm and no attention span! Well it amused *me*
> anyway...) Anybody have any ideas where this has gone?
>
> Also... the current Humour page on the Haskell wiki contains a link to
> Lambdabot's quotes database, but on my system, clicking this link just
> displays a few hundred pages of gibberish. Is this normal?
>
> As I final note...
> http://www.haskell.org/haskellwiki/Humor/Goldilocks
> Damn, I wish *I* thought of that! ;-)
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>



-- 
I try to take things like a crow; war and chaos don't always ruin a
picnic, they just mean you have to be careful what you swallow.

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


Re: [Haskell-cafe] FPers in Northwest Arkansas?

2008-07-25 Thread Jefferson Heard
Dunno about that, but I'm a NW arkansas expat.

2008/7/25 Nathan Bloomfield <[EMAIL PROTECTED]>:
> Greetings, Haskell-cafe. I am interested in joining or starting a functional
> programming interest group in my area. Are there any haskellers in the
> Northwest Arkansas region?
>
> Nathan Bloomfield
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>



-- 
I try to take things like a crow; war and chaos don't always ruin a
picnic, they just mean you have to be careful what you swallow.

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


[Haskell-cafe] Re: [HOpenGL] Fw: patch applied (ghc): Remove the OpenGL family of libraries fromextralibs

2008-07-25 Thread Jefferson Heard
I don't know how much I can do to keep them in sync, as I don't know
anything about the HLP, however, I'm actively using OpenGL 2.1 in
Haskell for research and prototyping and the inclusion of OpenGL in
Haskell has been central to my case for using it in my workplace.  I
don't know what I can do to help, but if anyone will point me in the
right direction, I'll try to throw some inertia at it...

-- Jeff

On Fri, Jul 25, 2008 at 12:57 PM, Claus Reinke <[EMAIL PROTECTED]> wrote:
> FYI: Haskell's OpenGL binding has just been dropped from GHC's
> extralibs, which means that it will no longer be kept in sync with GHC
> development, at least not by GHC HQ.
>
> GHC HQ has its hands full and -generally speaking - extralibs are to
> be replaced by H(L)P, the Haskell (Library) Platform:
>
> http://haskell.org/haskellwiki/Haskell_Platform
>
> so this part is understandable. But OpenGL has been dropped before
> H(L)P is ready to take over from extralibs, and at the recent GHC Irc
> meeting on the topic
>
> http://hackage.haskell.org/trac/ghc/attachment/wiki/IRC_Meetings/ghc-2008-07-16.log
>
> the mood seemed to favour not including OpenGL&co in the initial
> versions of H(L)P. Sven put a lot of good work into these libraries,
> but he is often not around for a long time, and it would be a shame
> if these gems were orphaned and went out of sync in the meantime.
>
> While I haven't used OpenGL in a while, I've always hoped to come
> back to that, not to mention Sven's spatial audio binding additions.
> And if I'm not mistaken, there are other community members who
> are using these libs right now for research, possibly even prototyping
> in connection with a startup?
>
> So, if one of you wanted to step forward and offer to keep these
> Haskell bindings for OpenGL&co maintained, perhaps steward them
> into the H(L)P, now would probably be a good time.
>
> Just thought I'd forward this, for those not following cvs-ghc,
> Claus
>
> - Original Message - From: "Ian Lynagh" <[EMAIL PROTECTED]>
> To: <[EMAIL PROTECTED]>
> Sent: Friday, July 25, 2008 12:11 AM
> Subject: patch applied (ghc): Remove the OpenGL family of libraries
> fromextralibs
>
>
>> Thu Jul 24 03:27:36 PDT 2008  Ian Lynagh <[EMAIL PROTECTED]>
>>  * Remove the OpenGL family of libraries from extralibs
>>
>>   M ./libraries/Makefile -4
>>   M ./libraries/extra-packages -4
>>
>> View patch online:
>>
>> http://darcs.haskell.org/ghc/_darcs/patches/20080724102736-3fd76-f5601cb7a290661124c44e9ec6c113812c12d08d.gz
>>
>> ___
>> Cvs-ghc mailing list
>> [EMAIL PROTECTED]
>> http://www.haskell.org/mailman/listinfo/cvs-ghc
>
> ___
> HOpenGL mailing list
> [EMAIL PROTECTED]
> http://www.haskell.org/mailman/listinfo/hopengl
>



-- 
I try to take things like a crow; war and chaos don't always ruin a
picnic, they just mean you have to be careful what you swallow.

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


Re: [Haskell-cafe] Fw: patch applied (ghc): Remove the OpenGL family of libraries fromextralibs

2008-07-25 Thread Jefferson Heard
Well, since HOpenGL seems to support practically all of OpenGL 2.1, I
don't see that there's much to maintain, except compatibility with
upcoming releases of GHC and possibly some optimization.  Maybe I'm
missing something, though.  Is there a list of outstanding bugs
somewhere?  I personally know of one bug that I found some time ago,
which I simply worked around, but a comprehensive list, I'm not aware
of.

-- Jeff

On Fri, Jul 25, 2008 at 1:27 PM, Don Stewart <[EMAIL PROTECTED]> wrote:
> claus.reinke:
>> FYI: Haskell's OpenGL binding has just been dropped from GHC's
>> extralibs, which means that it will no longer be kept in sync with GHC
>> development, at least not by GHC HQ.
>>
>> GHC HQ has its hands full and -generally speaking - extralibs are to
>> be replaced by H(L)P, the Haskell (Library) Platform:
>>
>> http://haskell.org/haskellwiki/Haskell_Platform
>>
>> so this part is understandable. But OpenGL has been dropped before
>> H(L)P is ready to take over from extralibs, and at the recent GHC Irc
>> meeting on the topic
>>
>> http://hackage.haskell.org/trac/ghc/attachment/wiki/IRC_Meetings/ghc-2008-07-16.log
>>
>> the mood seemed to favour not including OpenGL&co in the initial
>> versions of H(L)P. Sven put a lot of good work into these libraries,
>> but he is often not around for a long time, and it would be a shame
>> if these gems were orphaned and went out of sync in the meantime.
>>
>> While I haven't used OpenGL in a while, I've always hoped to come
>> back to that, not to mention Sven's spatial audio binding additions.
>> And if I'm not mistaken, there are other community members who
>> are using these libs right now for research, possibly even prototyping
>> in connection with a startup?
>>
>> So, if one of you wanted to step forward and offer to keep these
>> Haskell bindings for OpenGL&co maintained, perhaps steward them
>> into the H(L)P, now would probably be a good time.
>>
>> Just thought I'd forward this, for those not following cvs-ghc,
>> Claus
>
> Note the OpenGL are still just as maintained as they used to be -- that
> is, it hasn't had a maintainer for several years.
>
> The only change is that the GHC developers don't put them in a tarball
> on haskell.org/ghc prior to releasing GHC itself.
>
> -- Don
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>



-- 
I try to take things like a crow; war and chaos don't always ruin a
picnic, they just mean you have to be careful what you swallow.

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


Re: [Haskell-cafe] Fw: patch applied (ghc): Remove the OpenGL familyof libraries fromextralibs

2008-07-26 Thread Jefferson Heard
Yes, same here; don't worry, it's not going away.   It would be nice
to know, though, how many people are using it and what they're using
it for.  I'm using it for information visualization, and slowly
evolving/cribbing together something like the Processing
(http://www.processing.org) framework for Haskell as I do more things.

On Sat, Jul 26, 2008 at 5:46 AM, Alberto Ruiz <[EMAIL PROTECTED]> wrote:
> Don Stewart wrote:
>>
>> claus.reinke:
>>>
>>> But neither do I believe the rumour that OpenGL isn't much
>>> used, and forwarding the removal notice gives those users the
>>> opportunity to speak up now if they prefer no gaps in OpenGL presence, or
>>> forever to hold their peace, as they say.
>>
>> I for one have noticed this library *is* actively used. Many of the fun
>> new games that have appeared are using it, in particular.
>>
>> Such as:
>>
>>http://hackage.haskell.org/cgi-bin/hackage-scripts/package/frag
>>http://hackage.haskell.org/cgi-bin/hackage-scripts/package/Monadius
>>http://hackage.haskell.org/cgi-bin/hackage-scripts/package/roguestar-gl
>>http://hackage.haskell.org/cgi-bin/hackage-scripts/package/rsagl
>>http://hackage.haskell.org/cgi-bin/hackage-scripts/package/Shu-thing
>>http://hackage.haskell.org/cgi-bin/hackage-scripts/package/topkata
>>
>> The tutorial was also translated to the wiki last week,
>>
>>http://haskell.org/haskellwiki/Opengl
>>
>> It's a good, reliable package, in active use, widely ported.
>
> I'd just like to say that HOpenGL is essential for me. It is one of the
> reasons why I finally decided to use Haskell for all my work...
>
> Alberto
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>



-- 
I try to take things like a crow; war and chaos don't always ruin a
picnic, they just mean you have to be careful what you swallow.

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


Re: [Haskell-cafe] Re: [HOpenGL] Fw: patch applied (ghc): Remove the OpenGL family of libraries fromextralibs

2008-07-28 Thread Jefferson Heard
Right.  Just got back from being on travel, but the bug was that
genNames hangs and fails to return on WinXP 32 when trying to return
display list objects.  It turns out that you can pretend that display
lists are already allocated with most video cards, so it's not a big
deal, but it was a seriously confusing bug for a day or two.  when I
get back to the office, I'll forward the offending code.

On Fri, Jul 25, 2008 at 4:58 PM, Christopher Lane Hinson
<[EMAIL PROTECTED]> wrote:
>
> HOpenGL is in remarkably good shape for being unmaintained for several
> years.  I think the quiet on the HOpenGL mailing list speaks positively to
> the quality of the library.
>
> Perhaps those of us who have an interest in HOpenGL can arrange to work as
> comaintainers.
>
> I think I could be bothered to do weekly builds against GHC to make sure we
> stay up to date.  I'll set that up in the next month or so.
>
> Jeff, please point me to your bug.  I'd like to take a look.
>
> --Lane
>
> On Fri, 25 Jul 2008, Jefferson Heard wrote:
>
>> I don't know how much I can do to keep them in sync, as I don't know
>> anything about the HLP, however, I'm actively using OpenGL 2.1 in
>> Haskell for research and prototyping and the inclusion of OpenGL in
>> Haskell has been central to my case for using it in my workplace.  I
>> don't know what I can do to help, but if anyone will point me in the
>> right direction, I'll try to throw some inertia at it...
>>
>> -- Jeff
>
> ___
> HOpenGL mailing list
> [EMAIL PROTECTED]
> http://www.haskell.org/mailman/listinfo/hopengl
>



-- 
I try to take things like a crow; war and chaos don't always ruin a
picnic, they just mean you have to be careful what you swallow.

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


Re: [Haskell-cafe] Fw: patch applied (ghc): Remove the OpenGL familyof libraries fromextralibs

2008-07-29 Thread Jefferson Heard
Scott, I couldn't have said it better. My impression has always been
that HOpenGL looks like OpenGL would have looked like if they'd had a
flexible language to work with when they desgned it.  My only quibble
would be with the documentation.  Is there any way out there for
haddock to produce a linked and indexed PDF, so that I can better
guess where one function will be relative to another that feels like
it ought to be related?

On Mon, Jul 28, 2008 at 11:42 PM, scodil <[EMAIL PROTECTED]> wrote:
>
> I'll chime in with a "me too". I use Haskell and OpenGL for prototyping
> scientific visualization software, 3D models and such. Not that I think it
> couldn't be used for production software, its just that I just don't produce
> much :)
>
> The library really is fantastic. I don't think it gets enough fanfare. The
> only
> other GL API that rivals it is the C API itself. Most other languages
> provide a
> shoddy & incomplete interface to that, instead of an idiomatic
> interpretation of the OpenGL spec. I can't think of a single language, not
> even
> python, whose OpenGL bindings come close.
>
> I get the impression (from a inadequate sample of irc logs and list chatter)
> that many Haskellers see HOpenGL as 'just an OpenGL binding', like it was
> readline or curses or something. It just plugs a hole in the Haskell/OS
> interface, and its worth is merely a function of the size and importance of
> that hole. Instead I advocate, as Claus and others have done, that it's a
> shining example of how to write a Haskell interface to a well known API.
>
> If you never used C OpenGL and learned GL using Haskell, you might not
> notice
> anything special about it. But that's kind of my point, its just so damn
> good
> it blends into the background. The only people who notice this, I think, are
> experienced C OpenGL programmers, and the overlap between them and the
> Haskell
> community in general is small I bet. Their voice in that community smaller
> still.
>
> This probably has little bearing on the issue of whether to keep or drop
> HOpenGL in the near future, but I think that if 'the community' (or whoever
> has
> a say in these things) like the style of HOpenGL, and want to encourage
> bindings to be written in that style, they should place the library
> prominently
> in the pantheon of Haskell libs. Demoting it has the opposite effect.
>
> Anyway, I just wanted to take advantage of a rare opportunity to sing its
> praise.
>
> Scott
>
>
>> Yes, same here; don't worry, it's not going away.   It would be nice
>> to know, though, how many people are using it and what they're using
>> it for.  I'm using it for information visualization, and slowly
>> evolving/cribbing together something like the Processing
>> (http://www.processing.org) framework for Haskell as I do more things.
>>
>> On Sat, Jul 26, 2008 at 5:46 AM, Alberto Ruiz <[EMAIL PROTECTED]> wrote:
>>> Don Stewart wrote:

 claus.reinke:
>
> But neither do I believe the rumour that OpenGL isn't much
> used, and forwarding the removal notice gives those users the
> opportunity to speak up now if they prefer no gaps in OpenGL presence,
> or
> forever to hold their peace, as they say.

 I for one have noticed this library *is* actively used. Many of the fun
 new games that have appeared are using it, in particular.

 Such as:

http://hackage.haskell.org/cgi-bin/hackage-scripts/package/frag
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/Monadius

 http://hackage.haskell.org/cgi-bin/hackage-scripts/package/roguestar-gl
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/rsagl
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/Shu-thing
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/topkata

 The tutorial was also translated to the wiki last week,

http://haskell.org/haskellwiki/Opengl

 It's a good, reliable package, in active use, widely ported.
>>>
>>> I'd just like to say that HOpenGL is essential for me. It is one of the
>>> reasons why I finally decided to use Haskell for all my work...
>>>
>>> Alberto
>>> ___
>>> Haskell-Cafe mailing list
>>> Haskell-Cafe@haskell.org
>>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>>
>>
>>
>>
>> --
>> I try to take things like a crow; war and chaos don't always ruin a
>> picnic, they just mean you have to be careful what you swallow.
>>
>> -- Jessica Edwards
>> ___
>> Haskell-Cafe mailing list
>> Haskell-Cafe@haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
>
> --
> View this message in context: 
> http://www.nabble.com/Fw%3A-patch-applied-%28ghc%29%3A-Remove-the-OpenGL-family-of-libraries-fromextralibs-tp18655695p18704556.html
> Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.
>
> __

[Haskell-cafe] Problem compiling a CGI script that needs to write to file during its execution

2008-07-29 Thread Jefferson Heard
Please ignore the obvious security holes, as this is not a script
meant for public consumption, but some internal testing and
prototyping.  I would like to write the result of my computation out
to a file inside of cgiMain, but the type of the monad inside cgiMain
is this odd CGIT IO CGIResult.  I tried using liftM on writeFile, but
it then complained that "newanns" was a string instead of a list of
strings, which I don't understand at all.  Here's the code:

DeleteAnnotation.hs:


import Network.CGI
import Annotations
import Graphics.Rendering.OpenGL.GL (GLfloat)
import Control.Monad (liftM)
import Data.List (filter)

getInput' v = do
  x <- getInput v
  case x of
Nothing -> fail "essential variable not found"
Just y -> return y

cgiMain :: String -> CGI CGIResult
cgiMain anns_dot_txt = do
  ordnl <- (liftM read) $ getInput' "ordinal"
  let anns = (filter (notequal ordnl) . read $ anns_dot_txt) :: [Annotation]
  newanns = show anns
  output $ newanns
  writeFile "Annotations.txt" $ newanns

notequal :: String -> Annotation -> Bool
notequal ordnl ann = ordnl == ordinal ann

main :: IO ()
main = do
  f <- readFile "Annotations.txt"
  runCGI (handleErrors (cgiMain f))



$ ghc --make DeleteAnnotation

DeleteAnnotation.hs:19:2:
Couldn't match expected type `CGIT IO CGIResult'
   against inferred type `IO ()'
In the expression: writeFile "Annotations.txt" $ newanns
In the expression:
do ordnl <- (liftM read) $ getInput' "ordinal"
   let anns = ...
   newanns = show anns
 output $ newanns
 writeFile "Annotations.txt" $ newanns
In the definition of `cgiMain':
cgiMain anns_dot_txt
  = do ordnl <- (liftM read) $ getInput' "ordinal"
   let anns = ...
   
 output $ newanns
   

If I change writeFile "Annotations.txt" to (liftM (writeFile
"Annotations.txt")):

$ ghc --make DeleteAnnotation

DeleteAnnotation.hs:19:42:
Couldn't match expected type `String' against inferred type `Char'
  Expected type: [String]
  Inferred type: String
In the second argument of `($)', namely `newanns'
In the expression: (liftM (writeFile "Annotations.txt")) $ newanns
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Problem compiling a CGI script that needs to write to file during its execution

2008-07-29 Thread Jefferson Heard
Beautiful, thank you.  That worked.

On Tue, Jul 29, 2008 at 12:07 PM, allan <[EMAIL PROTECTED]> wrote:
> Hi
>
> I had this same problem and I'm not sure my way is correct but I used 
> 'Control.Monad.Trans.liftIO'
> Here is some code that I am using
>
> {-
>  The main program is pretty simple we just run the CGI action.
> -}
> main :: IO ()
> main =  Cgi.runCGI $ Cgi.handleErrors cgiMain
>
> {-
>  To be able to produce graphs which we can then display in the output
>  webpage we require that our main function, that is the one which creates
>  the page be in the IO monad.
> -}
> cgiMain :: CGI CGIResult
> cgiMain =
>  do visitInfo <- getAnalysisData
> page  <- Monad.Trans.liftIO $ createPage visitInfo
> Cgi.output $ Xhtml.renderHtml page
>
> createPage :: Visit -> IO Html
> createPage . blah stuff you don't care about
>
> getAnalysisData :: CGI Visit
>
> Visit is a data type I've made to hold the information obtained from the page.
>
> Hope this helps
> allan
>
>
> Jefferson Heard wrote:
>> Please ignore the obvious security holes, as this is not a script
>> meant for public consumption, but some internal testing and
>> prototyping.  I would like to write the result of my computation out
>> to a file inside of cgiMain, but the type of the monad inside cgiMain
>> is this odd CGIT IO CGIResult.  I tried using liftM on writeFile, but
>> it then complained that "newanns" was a string instead of a list of
>> strings, which I don't understand at all.  Here's the code:
>>
>> DeleteAnnotation.hs:
>>
> [snip code]
>
> --
> The University of Edinburgh is a charitable body, registered in
> Scotland, with registration number SC005336.
>
>



-- 
I try to take things like a crow; war and chaos don't always ruin a
picnic, they just mean you have to be careful what you swallow.

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


[Haskell-cafe] Looking for a more functional way to do this

2008-08-04 Thread Jefferson Heard
Working with HOpenGL and GLUT, I find myself approaching a common
problem with a common solution that I don't really like all that much,
as it reeks of procedural programming.  Basically the problem is that
of complex program state, such that when the user provides input to
the program in the form of a mouse click or a typed string or
character, the program updates its internal state to reflect this,
whether that's changing the rotation, scale, or position of a screen
element, or deciding what data to have loaded from disc.

What I often do is something that looks like this:

data ProgramState  = ProgramState {
some_associative_data :: Map String String
  , position :: GL.Vector3 Float
  , look_at :: GL Vector3 Float
  , selectables :: Map GLuint NamedObject
  }

render :: IORef ProgramState -> IO ()
render state = do
  st <- readIORef state
  ...

handleMouseClicks :: IORef ProgramState -> GLUT.KeyboardMouseHandler
handleMouseClicks state ... = do
  st <- readIORef state
  ...

main = do
  ...
  let st = ProgramState { Map.empty ... }
  render' = render st
  mouse' = handleMouseClicks st

  GLUT.renderCallback $= render
  GLUT.keyboardMouseCallback $= Just mouse'

and so on and so forth.   Generally there are not fewer than 5 and not
more than about 32 variables that I have to track between mouse
clicks, and there's all this boilerplate code as well.  I'm searching
for a better way to do this, and I feel sure there is one.  I'm
considering using Template Haskell or possibly SYB to generate this
code, but it also seems like I also ought to be able to declare some
kind of state monad or continuation monad that can encapsulate
ProgramState without having to declare an explicit structure for it
everytime.

For one thing, I'd like to genericize this code and write something
akin to Processing for Haskell (http://www.processing.org).
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Looking for a more functional way to do this

2008-08-06 Thread Jefferson Heard
Adrian, my understanding is that it's not that simple, because I need
to preserve the state between calls to GLUT's callbacks, which all
return IO ().

2008/8/6 Adrian Neumann <[EMAIL PROTECTED]>:
> There is the State Monad which is build just for that kind of purpose, I
> believe:
>
> http://www.haskell.org/all_about_monads/html/statemonad.html
>
> That would safe you from passing around the State
>
> Jefferson Heard schrieb:
>>
>> Working with HOpenGL and GLUT, I find myself approaching a common
>> problem with a common solution that I don't really like all that much,
>> as it reeks of procedural programming.  Basically the problem is that
>> of complex program state, such that when the user provides input to
>> the program in the form of a mouse click or a typed string or
>> character, the program updates its internal state to reflect this,
>> whether that's changing the rotation, scale, or position of a screen
>> element, or deciding what data to have loaded from disc.
>>
>> What I often do is something that looks like this:
>>
>> data ProgramState  = ProgramState {
>>some_associative_data :: Map String String
>>  , position :: GL.Vector3 Float
>>  , look_at :: GL Vector3 Float
>>  , selectables :: Map GLuint NamedObject
>>  }
>>
>> render :: IORef ProgramState -> IO ()
>> render state = do
>>  st <- readIORef state
>>  ...
>>
>> handleMouseClicks :: IORef ProgramState -> GLUT.KeyboardMouseHandler
>> handleMouseClicks state ... = do
>>  st <- readIORef state
>>  ...
>>
>> main = do
>>  ...
>>  let st = ProgramState { Map.empty ... }
>>  render' = render st
>>  mouse' = handleMouseClicks st
>>
>>  GLUT.renderCallback $= render
>>  GLUT.keyboardMouseCallback $= Just mouse'
>>
>> and so on and so forth.   Generally there are not fewer than 5 and not
>> more than about 32 variables that I have to track between mouse
>> clicks, and there's all this boilerplate code as well.  I'm searching
>> for a better way to do this, and I feel sure there is one.  I'm
>> considering using Template Haskell or possibly SYB to generate this
>> code, but it also seems like I also ought to be able to declare some
>> kind of state monad or continuation monad that can encapsulate
>> ProgramState without having to declare an explicit structure for it
>> everytime.
>>
>> For one thing, I'd like to genericize this code and write something
>> akin to Processing for Haskell (http://www.processing.org).
>> ___
>> 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
>
>



-- 
I try to take things like a crow; war and chaos don't always ruin a
picnic, they just mean you have to be careful what you swallow.

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


[Haskell-cafe] ANN: FTGL 1.0. Portable truetype font rendering in OpenGL

2008-08-07 Thread Jefferson Heard
Hi folks.  I've just released some Haskell bindings to FTGL at
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/FTGL .
FTGL is an easy to use library for portable rendering of TrueType
fonts in OpenGL, with functions for creating bitmapped fonts,
texture-mapped fonts, buffered fonts, polygonal 2D fonts, and extruded
polygonal 3D fonts.  The code works on Windows and Linux.  I've not
tested it yet on the Mac.

To use FTGL in your programs, just import Graphics.Rendering.FTGL and use

do
  font <- createTextureFont "font.ttf"
  setFontFaceSize font 24 72
  renderFont font "some string"

More documentation can be found at the FTGL homepage at
http://ftgl.sourceforge.net

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


Re: [Haskell-cafe] Re: [HOpenGL] ANN: FTGL 1.0. Portable truetype font rendering in OpenGL

2008-08-07 Thread Jefferson Heard
Is DeviL currently working?  I don't see any Haddock documentation,
and it says "build-failure ghc-6.8"...

On Thu, Aug 7, 2008 at 3:49 PM, Felipe Lessa <[EMAIL PROTECTED]> wrote:
> On Thu, Aug 7, 2008 at 4:43 PM, Jefferson Heard
> <[EMAIL PROTECTED]> wrote:
>> Hi folks.  I've just released some Haskell bindings to FTGL at
>> http://hackage.haskell.org/cgi-bin/hackage-scripts/package/FTGL .
>
> That's a great contribution, thanks! Now we have OpenGL, GLFW, FTGL,
> DevIL, OpenAL, and it's getting better and better.
>
> --
> Felipe.
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>



-- 
I try to take things like a crow; war and chaos don't always ruin a
picnic, they just mean you have to be careful what you swallow.

-- Jessica Edwards

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


[Haskell-cafe] ANN: Tutorial on information visualization and visual analytics in Haskell

2008-08-09 Thread Jefferson Heard
This is the tutorial I'll be presenting at DEFUN 2008.  I'll be
building a site around it until then, complete with compilable code
examples, but I thought I would let everyone get a sneak peek at the
long version of the tutorial before I'm done with it.  The code is as
yet untested, and keep in mind, advanced Haskellers, that I'm
purposefully simplifying some things to be understood by the beginner
to the intermediate Haskeller.  Comments and questions are welcome and
encouraged.  Please do ignore typos in the inline code for now,
though, as I'll be spending this week testing it out and making sure
everything works.

The link is:

http://bluheron.europa.renci.org/docs/BeautifulCode.pdf

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


[Haskell-cafe] Re: ANN: Tutorial on information visualization and visual analytics in Haskell

2008-08-10 Thread Jefferson Heard
As is always the case with anything you release to the public, I've
discovered inconsistencies and typos in the text since I released it.
I've tried to clean up all the typos I could find.  Still working on
the code, but there's a new edition out there on the website.

On Sat, Aug 9, 2008 at 2:30 PM, Jefferson Heard
<[EMAIL PROTECTED]> wrote:
> This is the tutorial I'll be presenting at DEFUN 2008.  I'll be
> building a site around it until then, complete with compilable code
> examples, but I thought I would let everyone get a sneak peek at the
> long version of the tutorial before I'm done with it.  The code is as
> yet untested, and keep in mind, advanced Haskellers, that I'm
> purposefully simplifying some things to be understood by the beginner
> to the intermediate Haskeller.  Comments and questions are welcome and
> encouraged.  Please do ignore typos in the inline code for now,
> though, as I'll be spending this week testing it out and making sure
> everything works.
>
> The link is:
>
> http://bluheron.europa.renci.org/docs/BeautifulCode.pdf
>
> -- Jeff
>



-- 
I try to take things like a crow; war and chaos don't always ruin a
picnic, they just mean you have to be careful what you swallow.

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


Re: [Haskell-cafe] ANN: Tutorial on information visualization and visual analytics in Haskell

2008-08-10 Thread Jefferson Heard
The final version will have graphics from the code that I present,
yes, as well as from other projects I've done in Haskell in
information visualization.  As for the comments next to the Haskell
Code, no -- there was no special tool involved. Sadly, I wrote the
entire document in Word 2007, as it was the best tool I had at hand.
After coming up with a template, I had basically everything I needed,
and it was going to be less work than tweaking LaTeX to do exactly
what I wanted to do with the code.

On Sun, Aug 10, 2008 at 2:34 PM, Justin Bailey <[EMAIL PROTECTED]> wrote:
> On Sat, Aug 9, 2008 at 11:30 AM, Jefferson Heard
> <[EMAIL PROTECTED]> wrote:
>> The link is:
>>
>> http://bluheron.europa.renci.org/docs/BeautifulCode.pdf
>
> Very readable and interesting. You may want to add some pictures or
> graphs if you weren't planning on that already.
>
> I really like how you have comments next to the haskell code. Is that
> a literate file? Are you using some well-known tool to weave the
> comments into the code? It looks like presentations I've seen with
> CWEB but I don't know of a tool like that for Haskell code ...
>
> Justin
>



-- 
I try to take things like a crow; war and chaos don't always ruin a
picnic, they just mean you have to be careful what you swallow.

-- Jessica Edwards

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


Re: [Haskell-cafe] ANN: Tutorial on information visualization and visual analytics in Haskell

2008-08-19 Thread Jefferson Heard
The tutorial has now been updated to what I think will more or less be
the final version.  There are now figures where appropriate.  The code
has been checked, and I'm sure now that the examples work.  Now that
I'm done, I'll repeat the original announcement, and all can enjoy:

This is the tutorial I'll be presenting at DEFUN 2008.  I'll be
building a site around it until then, complete with compilable code
examples, but I thought I would let everyone get a sneak peek at the
long version of the tutorial before I'm done with it.  The code is as
yet untested, and keep in mind, advanced Haskellers, that I'm
purposefully simplifying some things to be understood by the beginner
to the intermediate Haskeller.  Comments and questions are welcome and
encouraged.

 The link is:

http://bluheron.europa.renci.org/docs/BeautifulCode.pdf

On Sun, Aug 10, 2008 at 12:50 AM, Don Stewart <[EMAIL PROTECTED]> wrote:
> jefferson.r.heard:
>> This is the tutorial I'll be presenting at DEFUN 2008.  I'll be
>> building a site around it until then, complete with compilable code
>> examples, but I thought I would let everyone get a sneak peek at the
>> long version of the tutorial before I'm done with it.  The code is as
>> yet untested, and keep in mind, advanced Haskellers, that I'm
>> purposefully simplifying some things to be understood by the beginner
>> to the intermediate Haskeller.  Comments and questions are welcome and
>> encouraged.  Please do ignore typos in the inline code for now,
>> though, as I'll be spending this week testing it out and making sure
>> everything works.
>>
>> The link is:
>>
>> http://bluheron.europa.renci.org/docs/BeautifulCode.pdf
>
> This is a beautiful piece of work, Jefferson!
>
>
> And maybe a nice time to mention that Jefferson will be presenting,
> along with some other leading lights in the community, at DEFUN, our
> first developer-oriented workshop at ICFP.
>
>http://www.deinprogramm.de/defun-2008/
>
> So if the ICFP theory-heavy schedule seems a bit dry to you, consider
> registering for the DEFUN tutorials, and come away having built some
> beautiful code in Haskell.
>
> -- Don
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>



-- 
I try to take things like a crow; war and chaos don't always ruin a
picnic, they just mean you have to be careful what you swallow.

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


Re: [Haskell-cafe] String to Double conversion in Haskell

2008-08-24 Thread Jefferson Heard
Because normally, Prelude.read covers this.  Don's link is the most
efficient, but you can also do

(read . ByteString.unpack $ bytestring) :: Double

to get a Double from a printed representation of most numbers.

2008/8/24 Daryoush Mehrtash <[EMAIL PROTECTED]>:
> I am curious to understand the logic, the "Haskell Think", here.  Why is it
> that the byteString only supports conversion to int.
>
> daryoush
> On Sun, Aug 24, 2008 at 2:23 PM, Don Stewart <[EMAIL PROTECTED]> wrote:
>>
>> dmehrtash:
>> >I am trying to convert a string to a float.  It seems that
>> > Data.ByteString
>> >library only supports readInt.After some googling I came accross
>> > a
>> >possibloe implementation: [1]http://sequence.svcs.cs.pdx.edu/node/373
>> >
>>
>> Use the bytstring-lexing library,
>>
>>
>>  http://hackage.haskell.org/cgi-bin/hackage-scripts/package/bytestring-lexing
>>
>> Which provides a copying and non-copying lexer for doubles,
>>
>>readDouble   :: ByteString -> Maybe (Double, ByteString)
>>unsafeReadDouble :: ByteString -> Maybe (Double, ByteString)
>>
>> -- Don
>
>
>
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>



-- 
I try to take things like a crow; war and chaos don't always ruin a
picnic, they just mean you have to be careful what you swallow.

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


Re: [Haskell-cafe] OpenGL's VBO with Haskell

2008-08-25 Thread Jefferson Heard
That code looks like it ought to work, and I assume if you're using
VBOs that you know how to make sure your frustum is setup so that
you're object's visible.  Are you running this in Windows or in Linux
or ? and what version of GHC are you using?

There is also a specific HOpenGL mailinglist, just called HOpenGL that
you can join by searching for it on the http://haskell.org site.

On Mon, Aug 25, 2008 at 1:43 PM, Twinside <[EMAIL PROTECTED]> wrote:
> Hi Haskell list,
>
> Today I'm turning to you for the use of VBO (Vertex Buffer Object) in
> Haskell. I seem
> to be able to create one without any problem using the following code :
>
> --
> vboOfList :: Int -> [Float] -> IO BufferObject
> vboOfList size elems =
>let ptrsize = toEnum $ size * 4
>arrayType = ElementArrayBuffer
>in do
>[array] <- genObjectNames 1
>bindBuffer arrayType $= Just array
>arr <- newListArray (0, size - 1) elems
>withStorableArray arr (\ptr -> bufferData arrayType $= (ptrsize, ptr,
> StaticDraw))
>bindBuffer ArrayBuffer $= Nothing
>reportErrors
>return array
> --
>
> However the problem arise when I try to draw primitives using this vbo :
>
> --
> displayVbo buff size = do
>let stride = toEnum sizeOfVertexInfo
>vxDesc = VertexArrayDescriptor 3 Float stride $ offset 0
>colors = VertexArrayDescriptor 4 Float stride $ offset 12
>texCoo = VertexArrayDescriptor 2 Float stride $ offset (12 + 16)
>filt   = VertexArrayDescriptor 4 Float stride $ offset (12 + 16 + 8)
>bindBuffer ArrayBuffer $= Just buff
>
>arrayPointer VertexArray $= vxDesc
>arrayPointer ColorArray $= colors
>arrayPointer TextureCoordArray $= texCoo
>arrayPointer SecondaryColorArray $= filt
>
>drawArrays Quads 0 size
>bindBuffer ArrayBuffer $= Nothing
> --
>
> Nothing is displayed on screen.
>
> As you can see, my VBO contain interleaved data :
> - 3 float for the vertex
> - 4 for the color
> - 2 for the texture coordinate
> - 4 for the secondary color)
>
> The 'offset' function has type Int -> Ptr Float, and is used to forge a
> pointer from an Int, to mimic
> the C way of using VBO. As far as I've checked, the values in my list for
> VBO generation are valid and well
> displayed using other techniques.
>
> So is there a workaround other method for my solution, preferably by keeping
> my data interleaved?
> Secondly,  is there any sample for advanced features like VBOs in Haskell?
>
> Regards,
> Vincent
>
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>



-- 
I try to take things like a crow; war and chaos don't always ruin a
picnic, they just mean you have to be careful what you swallow.

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


Re: [Haskell-cafe] OpenGL's VBO with Haskell

2008-08-25 Thread Jefferson Heard
Oh, and you might try this using Vertex Arrays instead of VBOs.  I'll
also assume you're checking for the appropriate ARB extensions to make
sure VBOs are available on your hardware...  If this displays
correctly using Vertex Arrays (which can still be interleaved), then I
would check your hardware if I were you.

On Mon, Aug 25, 2008 at 2:35 PM, Jefferson Heard
<[EMAIL PROTECTED]> wrote:
> That code looks like it ought to work, and I assume if you're using
> VBOs that you know how to make sure your frustum is setup so that
> you're object's visible.  Are you running this in Windows or in Linux
> or ? and what version of GHC are you using?
>
> There is also a specific HOpenGL mailinglist, just called HOpenGL that
> you can join by searching for it on the http://haskell.org site.
>
> On Mon, Aug 25, 2008 at 1:43 PM, Twinside <[EMAIL PROTECTED]> wrote:
>> Hi Haskell list,
>>
>> Today I'm turning to you for the use of VBO (Vertex Buffer Object) in
>> Haskell. I seem
>> to be able to create one without any problem using the following code :
>>
>> --
>> vboOfList :: Int -> [Float] -> IO BufferObject
>> vboOfList size elems =
>>let ptrsize = toEnum $ size * 4
>>arrayType = ElementArrayBuffer
>>in do
>>[array] <- genObjectNames 1
>>bindBuffer arrayType $= Just array
>>arr <- newListArray (0, size - 1) elems
>>withStorableArray arr (\ptr -> bufferData arrayType $= (ptrsize, ptr,
>> StaticDraw))
>>bindBuffer ArrayBuffer $= Nothing
>>reportErrors
>>return array
>> --
>>
>> However the problem arise when I try to draw primitives using this vbo :
>>
>> --
>> displayVbo buff size = do
>>let stride = toEnum sizeOfVertexInfo
>>vxDesc = VertexArrayDescriptor 3 Float stride $ offset 0
>>colors = VertexArrayDescriptor 4 Float stride $ offset 12
>>texCoo = VertexArrayDescriptor 2 Float stride $ offset (12 + 16)
>>filt   = VertexArrayDescriptor 4 Float stride $ offset (12 + 16 + 8)
>>bindBuffer ArrayBuffer $= Just buff
>>
>>arrayPointer VertexArray $= vxDesc
>>arrayPointer ColorArray $= colors
>>arrayPointer TextureCoordArray $= texCoo
>>arrayPointer SecondaryColorArray $= filt
>>
>>drawArrays Quads 0 size
>>bindBuffer ArrayBuffer $= Nothing
>> --
>>
>> Nothing is displayed on screen.
>>
>> As you can see, my VBO contain interleaved data :
>> - 3 float for the vertex
>> - 4 for the color
>> - 2 for the texture coordinate
>> - 4 for the secondary color)
>>
>> The 'offset' function has type Int -> Ptr Float, and is used to forge a
>> pointer from an Int, to mimic
>> the C way of using VBO. As far as I've checked, the values in my list for
>> VBO generation are valid and well
>> displayed using other techniques.
>>
>> So is there a workaround other method for my solution, preferably by keeping
>> my data interleaved?
>> Secondly,  is there any sample for advanced features like VBOs in Haskell?
>>
>> Regards,
>> Vincent
>>
>>
>> ___
>> Haskell-Cafe mailing list
>> Haskell-Cafe@haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>
>
>
>
> --
> I try to take things like a crow; war and chaos don't always ruin a
> picnic, they just mean you have to be careful what you swallow.
>
> -- Jessica Edwards
>



-- 
I try to take things like a crow; war and chaos don't always ruin a
picnic, they just mean you have to be careful what you swallow.

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


Re: [Haskell-cafe] monadic map on a Data.IntMap

2008-09-08 Thread Jefferson Heard
I suppose a

mapM_ monadicFunction . Data.IntMap.toList $ m

doesn't work for you?

On Mon, Sep 8, 2008 at 2:11 PM, minh thu <[EMAIL PROTECTED]> wrote:
> Hi,
>
> Is there something like a fmapM_ ?
> In particular, I'd like to mapM_ a Data.IntMap instead of a List
>
> Thank you,
> Thu
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>



-- 
I try to take things like a crow; war and chaos don't always ruin a
picnic, they just mean you have to be careful what you swallow.

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


Re: [Haskell-cafe] Python's big challenges, Haskell's big advantages?

2008-09-17 Thread Jefferson Heard
Multiprocessing is hardly a solution...  I realize the Python
interpreter's fairly lightweight on its own, but the weight of a full
unix process plus the weight of the python interpreter in terms of
memory, context switching times, and finally the clunkiness of the
fork() model (which is HOW many years old now?).  They need a model
programmers are familiar with, e.g. threads-allocate-to-cores a la
Java or C, or they need a model that is entirely new or is based on
source-code annotation (like Strategies and Control.Parallel).



On Wed, Sep 17, 2008 at 8:58 AM, Manlio Perillo
<[EMAIL PROTECTED]> wrote:
> Don Stewart ha scritto:
>>
>>
>> http://www.heise-online.co.uk/open/Shuttleworth-Python-needs-to-focus-on-future--/news/111534
>>
>> "cloud computing, transactional memory and future multicore processors"
>>
>
> Multicore support is already "supported" in Python, if you use
> multiprocessing, instead of multithreading.
>
> And scalability is not a "real" problem, if you write RESTful web
> applications.
>
>> Get writing that multicore, STM, web app code!
>>
>
>
> Manlio Perillo
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>



-- 
I try to take things like a crow; war and chaos don't always ruin a
picnic, they just mean you have to be careful what you swallow.

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


Re: [Haskell-cafe] Python's big challenges, Haskell's big advantages?

2008-09-17 Thread Jefferson Heard
Both Jython and JRuby can use multicore parallelism.  Which, of
course, you need desperately when running in Jython and JRuby, because
they're slow as christmas for most tasks.  In addition, Jython is not
a predictably complete version of Python and its internals are not
well documented in the least, and the documentation for what CPython
code will work in Jython and what won't is sadly lacking.

In my experience, it doesn't make it an unusable tool, but the tasks
it is suited for fall more along the lines of traditional scripting of
a large working Java application.  I wouldn't want to see a large app
written in Jython or JRuby.

-- Jeff

On Wed, Sep 17, 2008 at 9:18 AM, Arnar Birgisson <[EMAIL PROTECTED]> wrote:
> Hi again,
>
> On Wed, Sep 17, 2008 at 15:13, Bruce Eckel <[EMAIL PROTECTED]> wrote:
>>> Well, I'm a huge Python fan myself, but multiprocessing is not really
>>> a solution as much as it is a workaround. Python as a language has no
>>> problem with multithreading and multicore support and has all
>>> primitives to do conventional shared-state parallelism. However, the
>>> most popular /implementation/ of Python sacrifies this for
>>> performance, it has nothing to do with the language itself.
>>
>> Actually, no. Neither Python nor Ruby can utilize more than a single
>> processor using threads. The only way to use more than one processor
>> is with processes.
>
> I wanted to make a distinction between the language and its
> implementation. I think you are conflating the two.
>
> If you read the Python specification there is nothing preventing you
> from running on two cores in parallel. The standard library does
> indeed have semaphores, monitors, locks etc. In fact, I'm pretty sure
> the Jython implementation can use multiple cores. It is just CPython
> that can't, as is very well known and advertised.
>
> cheers,
> Arnar
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>



-- 
I try to take things like a crow; war and chaos don't always ruin a
picnic, they just mean you have to be careful what you swallow.

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