[Haskell-cafe] Detecting unused read handles? (was: File handles and pipes)

2008-10-19 Thread Stephen Hicks
On Sun, Oct 19, 2008 at 1:44 AM, Brandon S. Allbery KF8NH
[EMAIL PROTECTED] wrote:
 On 2008 Oct 19, at 1:37, Stephen Hicks wrote:

 I'm trying to understand how to get pipes working in Haskell, in
 particular with the revamped System.Process (though I've tried similar
 experiments with System.Posix.IO and Control.Concurrent).
 Specifically I'm trying to concatenate the output of two system calls
 into the input of a third.  The following code does not get the job
 done:

 Pipes are perhaps a bit misnamed:  if you want to combine the output of two
 pipes and funnel it into a third you can't simply plumb them together, you
 need to provide code which reads from the output pipes and writes into the
 input pipe.  If you don't care about order, forkIO a thread for each output
 pipe which reads from the output pipe it's passed and writes to the input
 pipe.  If order is significant, use mapM/forM to run the output-to-input
 code on each handle in turn.

Thanks a lot - that seems to work very well, and even scales to large
amounts of data nicely (and quickly, with Lazy ByteStrings).

I've got one more question now.  Suppose I want to do the same thing
on the other side, with two processes *receiving* the data.  Is there
a way to tell whether the first process wants input, and if not, wait
for the second process to do anything?

That is, suppose I have something like

 do (Just inh1, _, _, p1) - createProcess (shell echo 1) { std_in = 
 CreatePipe }
-- wait for p1, possibly feeding it some input?
(Just inh2, _, _, p2) - createProcess (shell cat) { std_in = CreatePipe 
 }

Is there a way to figure out that the echo 1 process never wanted
any input, and therefore not give it any?  I looked through all of
System.IO and everything seemed to indicate that inh1 was open, even
after the process ended.  The only indication otherwise was that
hflush inh1 failed with resource vanished.  I guess what I'm
asking is I want to wait until the process p1 is waiting for input
and/or terminates, and if it's the latter, move on to the next
process in line, before actually doing any hPutStr into the read
handles.  Is that possible?

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


Re: [Haskell-cafe] File handles and pipes

2008-10-19 Thread Donn Cave
Quoth Stephen Hicks [EMAIL PROTECTED]:

In general, given a handful of system calls (and/or
 read/write handles), is there a way to combine them all together?

Well, sure - if I understand what you mean.  Not Handles, in the
sense of a Haskell library construct, but UNIX pipes and processes
are reasonably simple to work with in a general purpose programming
language.

I'm sorry to say the following isn't real code, since GHC doesn't
run on the platform I'm using to write this mail, but I hope it will
serve to demonstrate the principles using bare UNIX system calls,
and that it doesn't contain any serious errors.

forkProcess $ do  -- pipe tail
(pa0, pa1) - createPipe
--  Command exec'd in this fork reads from this pipe,
--  so dup 0 (input) from pipe input fd.  Both ends of
--  pipe will be inherited by child forks.
dupTo pa0 0
forkProcess $ do  -- first pipe head
--  Command exec'd in this fork writes to parent's pipe.
dupTo pa1 1
--  Close parent's pipe so fds won't be inherited by
--  next fork.
closeFd pa0
closeFd pa1
forkProcess $ execFile /bin/df ...   -- second pipe head
execFile /bin/df ...
--  Close own pipe write end, so child process exit(s) will cause EOF
closeFd pa1
execFile /usr/bin/sort ...

Key points:

Input, output and error are file descriptors 0, 1 and 2,
  by definition (pronounced unit 0, etc.)

dupTo (UNIX system call dup2()) duplexes an I/O stream, so
  dupTo p0 0 sets up a pipe for a standard UNIX command
  that reads from unit 0.

Reads from the pipe's read fd will either return data or block,
  until exit of the *last* process with the pipe's write end open.
  Hence the importance of closing the write end of your own pipe,
  and not letting pipe fds leak into child processes.

Donn Cave, [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] is 256M RAM insufficient for a 20 millionelement Int/Int map?

2008-10-19 Thread Claus Reinke

 I have a standard Data.Map.Map as the base structure for one of my
 macid data tables (jobs), but I noticed something
 that is probably causing problems for me.
 Even a simple 20 million record with int/int key values causes an out
 of memory error for me in ghci,
Int keys, Int values eh?
Does using IntMap help?

Interesting. Map Int Int, IntMap Int and [(Int, Int)] use pretty much
the same amount of memory, assuming that no keys or values are shared:


I haven't followed the thread, but one thing that keeps tripping me
up wrt memory use is that Maps aren't strict in their values by default.

Worse, if that is not what you want for your application, working
around it can be rather awkward (Data.Map at least provides
insertWith', but there's no unionWith', and Data.IntMap doesn't
even have insertWith'). 

Ideally, I'd just like to indicate the strictness in the types (hint to ghc 
hackers: 'Data.Map.Map Int !Int' and '[!a]' would really be useful!-), 
but as that isn't supported, separate operations (with seq inserted 
manually at suitable places) seem necessary (hint to container library 
maintainers: please provide full set of strict operation variants!-).


If this is (or contributes to) the problem, it should show up in heap
profiles as an upward ramp and could be fixed by defining and using
locally augmented versions of the Map operations. 


Claus


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


Re[2]: [Haskell-cafe] is 256M RAM insufficient for a 20 million element Int/Int map?

2008-10-19 Thread Bulat Ziganshin
Hello Bertram,

Sunday, October 19, 2008, 6:19:31 AM, you wrote:

 That's 5 words per elements

... that, like everything else, should be multiplied by 2-3 to
account GC effect

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


[Haskell-cafe] Re: File handles and pipes

2008-10-19 Thread Matti Niemenmaa
Brandon S. Allbery KF8NH wrote:
 Pipes are perhaps a bit misnamed:  if you want to combine the output of
 two pipes and funnel it into a third you can't simply plumb them
 together, you need to provide code which reads from the output pipes
 and writes into the input pipe.

With the new System.Process in 6.10, that's not the case. If you're building a
pipeline a | b | c | d you only need to write into a and read from d,
System.Process handles everything in between.

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


Re[2]: [Haskell-cafe] is 256M RAM insufficient for a 20 million element Int/Int map?

2008-10-19 Thread Philippa Cowderoy
On Sun, 19 Oct 2008, Bulat Ziganshin wrote:

 Hello Bertram,
 
 Sunday, October 19, 2008, 6:19:31 AM, you wrote:
 
  That's 5 words per elements
 
 ... that, like everything else, should be multiplied by 2-3 to
 account GC effect
 

Unless I'm much mistaken, that isn't the case when you're looking at the 
minimum heap size because the GC'll run more frequently when you hit the 
max heap size supported anyway, no? The 2-3 is relevant when asking if 
it'll go at all fast, or how much memory'll get eaten if it's there, sure.

-- 
[EMAIL PROTECTED]

Society does not owe people jobs.
Society owes it to itself to find people jobs.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] haskell facebook

2008-10-19 Thread Jason Dusek
  Has anyone taken a stab at Haskell FaceBook bindings?

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


Re[3]: [Haskell-cafe] is 256M RAM insufficient for a 20 million element Int/Int map?

2008-10-19 Thread Philippa Cowderoy
On Sun, 19 Oct 2008, Bulat Ziganshin wrote:

 Hello Philippa,
 
 Sunday, October 19, 2008, 3:25:26 PM, you wrote:
 
  ... that, like everything else, should be multiplied by 2-3 to
  account GC effect
 
  Unless I'm much mistaken, that isn't the case when you're looking at the
  minimum heap size because the GC'll run more frequently when you hit the
  max heap size supported anyway, no?
 
 what you mean? max heap size is 2gb probably. it may be configured on
 cmdline and if you will enable say 200 mb heap and your program use
 only 180 mb - it will run successfully, using only 200 mb of memory.
 drawback, of course, is that it may become 10x slower
 

Ah, so you can't trust GHC to pick a max heap size within what the OS 
actually has available? That does make the RTS option rather necessary. 
But well worth knowing if you're trying to make something run in a known 
footprint.

-- 
[EMAIL PROTECTED]

The task of the academic is not to scale great
intellectual mountains, but to flatten them.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] is 256M RAM insufficient for a 20 millionelement Int/Int map?

2008-10-19 Thread Luke Palmer
On Sun, Oct 19, 2008 at 4:26 AM, Claus Reinke [EMAIL PROTECTED] wrote:
 (hint to ghc hackers: 'Data.Map.Map Int !Int' and '[!a]' would really be 
 useful!-),

I can't figure out what that means though.  Strictness is not a
property of types or of values, it is a property of functions.   [!]
is not a subtype of [] ; IOW, there is no a such that [a] = [!Int]
(where [!Int] is a list with strict values).  For example, if we
allowed this, the following property breaks:

  length xs == length (map f xs)

Since it is not true on strict lists.

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


Re[3]: [Haskell-cafe] is 256M RAM insufficient for a 20 million element Int/Int map?

2008-10-19 Thread Bulat Ziganshin
Hello Philippa,

Sunday, October 19, 2008, 3:25:26 PM, you wrote:

 ... that, like everything else, should be multiplied by 2-3 to
 account GC effect

 Unless I'm much mistaken, that isn't the case when you're looking at the
 minimum heap size because the GC'll run more frequently when you hit the
 max heap size supported anyway, no?

what you mean? max heap size is 2gb probably. it may be configured on
cmdline and if you will enable say 200 mb heap and your program use
only 180 mb - it will run successfully, using only 200 mb of memory.
drawback, of course, is that it may become 10x slower



-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re[4]: [Haskell-cafe] is 256M RAM insufficient for a 20 million element Int/Int map?

2008-10-19 Thread Bulat Ziganshin
Hello Philippa,

Sunday, October 19, 2008, 3:58:35 PM, you wrote:

 what you mean? max heap size is 2gb probably. it may be configured on

 Ah, so you can't trust GHC to pick a max heap size within what the OS 
 actually has available?

hm, this includes virtual memory too. there are code snippets that
limits heap to, say, 80% of RAM:

/* after a tip from David Roundy */
#include Rts.h
#include RtsFlags.h
#include unistd.h

void defaultsHook (void) {
  RtsFlags.GcFlags.maxStkSize  =  8*1002 / sizeof(W_); /* 80M */

#ifdef _SC_PHYS_PAGES
  unsigned long long pagesize = sysconf(_SC_PAGESIZE);
  unsigned long long numpages = sysconf(_SC_PHYS_PAGES);
  unsigned long long mhs = numpages*pagesize*8/10;
  RtsFlags.GcFlags.maxHeapSize = 1ULL+mhs/BLOCK_SIZE_W;
#endif
}


but my point was about original program thta doesn't include any such
tricks, of course



-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] is 256M RAM insufficient for a 20 million element Int/Int map?

2008-10-19 Thread Bertram Felgenhauer
Bulat Ziganshin wrote:
 Hello Bertram,
 
 Sunday, October 19, 2008, 6:19:31 AM, you wrote:
 
  That's 5 words per elements
 
 ... that, like everything else, should be multiplied by 2-3 to
 account GC effect

True. You can control this factor though. Two RTS options help:

  -c  (Enable compaction for all major collections) - mostly
  avoids fragmentation in the old generation.
  -Ffactor
  (Control the amount of memory reserved in terms of the size
  of the oldest generation. The default is 2, meaning that if
  the oldest generation is 200MB in size, 400 MB of heap will
  be used)

Consider this program,

 module Main (main) where
 
 import qualified Data.IntMap as M
 import Data.List (foldl')
 
 main = do
 loop (M.fromList [(i,0) | i - [1..500]]) 1
 
 loop dict j = do
 i - readLn
 print $ dict M.! (i :: Int)
 let dict' = foldl' (\m (k, v) - M.insert k v m) dict [(,) i $! j*i | i 
 - [j`mod`10 * 50 + 1..j`mod`10 * 50 + 50]]
 loop dict' (j+1)

This program maintains an IntMap with 5 million entries, which means
200 MB of live data on a 32 bit computer. It updates the map a lot, too,
so I think this is a fairly realistic example.

Running it on a 51 line input with various RTS options [*], we get:

Options  Memory used   Time used
+RTS -c -F1.1220 MB3m22s
+RTS -c -F1.2243 MB2m12s
+RTS -c -F1.5306 MB1m58s
+RTS -c  398 MB1m57s
+RTS -F 1.1  406 MB1m43s
+RTS -F 1.2  425 MB1m15s
+RTS -F 1.5  483 MB1m6s
none 580 MB1m11s

Heap residency was around 200.5 million bytes in all runs.

As expected, saving memory this way doesn't come cheap - it can
dramatically increase the program's runtime. But if a program builds
and slowly updates a large dictionary, playing with these options can
help a lot.

Bertram

[*] time (seq 50; echo 0) | ./Main +RTS -sstderr -c -F1.2
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: HDBC or HSQL

2008-10-19 Thread Thomas Hartman
I am asking because I am trying to make HAppS a reasonable replacement
for all contexts in which you would otherwise use an external
 relational
database except those in which an external SQL database is a specific
requirement.

My experience with HAppS so far suggests that if one's data set is in
the millions, an external database -- or some sort of off-ram storage
mechanism is indeed a requirement, because even a 16GB server will
eventually run out of memory.

For example, I have a demo app (happstutorial.com) that stores jobs or
users as records. On average, each record takes about 100B of memory,
when checkpointed on hard disk. Not sure how much this amounts to in
ram, but but on a 256M workstation with 256M of virtual memory, the
checkpointing mechanism had an out of memory error with under 500,000
records.

This doesn't seem totally unreasonable to me: 500,000 * 100 =
50,000,000B, which is 20% of my physical memory and 10% of my total
(including virtual) memory.

Also, as my recent post to haskell cafe says, I can't even fit a 20M
element Data.Map.Map Int Int object into memory on my 256M laptop.

On a 16GB server, you might get 32X the limit I ran into, but you will
still have out of memory errors with  15 million records.

Perhaps a recordset in the millions isn't a reasonable requirement,
but most web 2.0 type projects are of this scope, I think.

Thomas.

2007/8/4 Alex Jacobson [EMAIL PROTECTED]:
 Have you looked at the HAppS.DBMS.IxSet?  It gives you a type safe way to
 query indexed collections.

 -Alex-

 Isto Aho wrote:

 Hi,

 I'd like to store small matrices into a db. Number of rows and columns may
 vary in a way not
 known in advance. One might use a relation (matrixId, col, row, value) or
 something like that
 but if it is possible to put a matrix in one command into db, some queries
 will be easier.
 E.g., one relation can store several matrices and it would be easy to
 query, how many
 matrices are stored currently. With that above four tuple you can find out
 the number of unique
 matrixId's, too, but it is not as easy as with matrices.

 Anyhow, now I'm not sure if I should stick with HSQL any more... Earlier
 comments on this
 thread made me think that maybe it would be a better idea to try to learn
 enough HDBC.

 This would be used in a server application. Is HAppS applicable here?

 e.g. after some tweaking the following works with HSQL:

 addRows = do
dbh - connect server database user_id passwd
intoDB dbh ([555,111, 50, 1000]::[Int])
 ([21.0,22.0,23.0,24.0]::[Double])
intoDB dbh ([556,111, 50, 1000]::[Int])
 ([21.0,22.0,23.0,24.0]::[Double])
intoDB dbh ([]::[Int]) ([]::[Double])
   where
intoDB dbh i_lst d_lst =
catchSql (do
let cmd = INSERT INTO trial (intList, dList)
 VALUES ( ++
toSqlValue i_lst ++ , ++ toSqlValue d_lst
 ++ )
execute dbh cmd
)
(\e - putStrLn $ Problem:  ++ show e)


 Similarly, queries can handle matrices and I like that it is now
 possible to select those columns or rows from the stored matrix that
 are needed.  E.g.

 retrieveRecords2 :: Connection - IO [[Double]]
 retrieveRecords2 c = do
-- query c select dList[1:2] from trial = collectRows getRow
query c select dList from trial = collectRows getRow
where
getRow :: Statement - IO [Double]
getRow stmt = do
lst   - getFieldValue stmt dList
return lst
 readTable2 = do
dbh - connect server database user_id passwd
values - retrieveRecords2 dbh
putStrLn $ dLists are :  ++ (show values)


 br,
 Isto


 2007/8/1, Alex Jacobson [EMAIL PROTECTED]
 mailto:[EMAIL PROTECTED]:

Out of curiosity, can I ask what you are actually trying to do?

I am asking because I am trying to make HAppS a reasonable replacement
for all contexts in which you would otherwise use an external
 relational
database except those in which an external SQL database is a specific
requirement.

-Alex-


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

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


Re: [Haskell-cafe] Re: HDBC or HSQL

2008-10-19 Thread Thomas Hartman
For the reasons described in my previous message, I plan on looking
into using takusen with HAppS.

2007/8/4 Alex Jacobson [EMAIL PROTECTED]:
 Have you looked at the HAppS.DBMS.IxSet?  It gives you a type safe way to
 query indexed collections.

 -Alex-

 Isto Aho wrote:

 Hi,

 I'd like to store small matrices into a db. Number of rows and columns may
 vary in a way not
 known in advance. One might use a relation (matrixId, col, row, value) or
 something like that
 but if it is possible to put a matrix in one command into db, some queries
 will be easier.
 E.g., one relation can store several matrices and it would be easy to
 query, how many
 matrices are stored currently. With that above four tuple you can find out
 the number of unique
 matrixId's, too, but it is not as easy as with matrices.

 Anyhow, now I'm not sure if I should stick with HSQL any more... Earlier
 comments on this
 thread made me think that maybe it would be a better idea to try to learn
 enough HDBC.

 This would be used in a server application. Is HAppS applicable here?

 e.g. after some tweaking the following works with HSQL:

 addRows = do
dbh - connect server database user_id passwd
intoDB dbh ([555,111, 50, 1000]::[Int])
 ([21.0,22.0,23.0,24.0]::[Double])
intoDB dbh ([556,111, 50, 1000]::[Int])
 ([21.0,22.0,23.0,24.0]::[Double])
intoDB dbh ([]::[Int]) ([]::[Double])
   where
intoDB dbh i_lst d_lst =
catchSql (do
let cmd = INSERT INTO trial (intList, dList)
 VALUES ( ++
toSqlValue i_lst ++ , ++ toSqlValue d_lst
 ++ )
execute dbh cmd
)
(\e - putStrLn $ Problem:  ++ show e)


 Similarly, queries can handle matrices and I like that it is now
 possible to select those columns or rows from the stored matrix that
 are needed.  E.g.

 retrieveRecords2 :: Connection - IO [[Double]]
 retrieveRecords2 c = do
-- query c select dList[1:2] from trial = collectRows getRow
query c select dList from trial = collectRows getRow
where
getRow :: Statement - IO [Double]
getRow stmt = do
lst   - getFieldValue stmt dList
return lst
 readTable2 = do
dbh - connect server database user_id passwd
values - retrieveRecords2 dbh
putStrLn $ dLists are :  ++ (show values)


 br,
 Isto


 2007/8/1, Alex Jacobson [EMAIL PROTECTED]
 mailto:[EMAIL PROTECTED]:

Out of curiosity, can I ask what you are actually trying to do?

I am asking because I am trying to make HAppS a reasonable replacement
for all contexts in which you would otherwise use an external
 relational
database except those in which an external SQL database is a specific
requirement.

-Alex-


 ___
 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] package question/problem

2008-10-19 Thread Henning Thielemann


On Sat, 18 Oct 2008, Duncan Coutts wrote:


On Fri, 2008-10-17 at 18:23 -0500, Galchin, Vasili wrote:

Hello,

I am trying to cabal install HSQL. I am using ghc 6.8.2.


The simple answer is that the package is unmaintained and has not been
updated to work with ghc 6.8.x.


As far as I know, the current maintainer is Frederik Eaton 
[EMAIL PROTECTED].

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


Re: [Haskell-cafe] haskell facebook

2008-10-19 Thread Robert Wills

I don't know much about this, but...

http://hackage.haskell.org/packages/archive/HAppS-Server/0.9.2.1/doc/html/HAppS-Server-Facebook.html

As I recall, Alex Jacobson's talk contained an example of building a 
facebook app.


http://www.bayfp.org/blog/2007/10/16/alex-jacobson-on-happs-videos-slides/

-Rob

Jason Dusek wrote:

  Has anyone taken a stab at Haskell FaceBook bindings?

--
_jsn
___
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] is 256M RAM insufficient for a 20 millionelementInt/Int map?

2008-10-19 Thread Claus Reinke

(hint to ghc hackers: 'Data.Map.Map Int !Int' and '[!a]' would really be 
useful!-),


I can't figure out what that means though.  Strictness is not a
property of types or of values, it is a property of functions.   [!]
is not a subtype of [] ; IOW, there is no a such that [a] = [!Int]
(where [!Int] is a list with strict values).  For example, if we
allowed this, the following property breaks:

 length xs == length (map f xs)

Since it is not true on strict lists.


I'm not entirely sure this couldn't be worked out. Let's say that
every type breaks into terminating and non-terminating computations:

   a = !a | ^a

For your equation to break, you're assuming implicit conversions
between some 'a' and '!a', ie, something like

   (undefined :: a) :: !a
   (const undefined :: a - b) :: !a - !a

But those shouldn't typecheck! We can't decide termination, so not
all objects of type 'a' can be classified into the subtypes '!a' or '^a'.
Membership in '!a' can be constructive only, and map for strict lists 
would have a type somewhat like this


   mapS :: !(!a - !a) - [!a] - [!a]

Without a function, 'mapS' can't construct an element-strict result list,
hence the first '!' (and 'mapS undefined' won't typecheck). Nor can it
do so without a function that can construct (or pass on) strict elements,
hence the '!' on the result type of the parameter function (so 'mapS 
(const undefined)' won't typecheck, either). Since there are no ways 
of producing an arbitrary '!a' out of thin air, polymorphic parameter 
functions will have type '!a-!a' (if 'a' gets specialised, eg to 'Int',

then trivial 'Int-!Int' functions are possible).

Being conjured out of thin air, none of this might not hold up under 
closer scrutiny, but papers like [1] suggest that it isn't entirely out of

reach  - further references or counterexamples appreciated!-)

Claus

[1] http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.55.8984
   Unboxing using specialisation, Simon L. Peyton Jones and Patrick M. Sansom
   
___

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


Re: [Haskell-cafe] haskell facebook

2008-10-19 Thread Thomas Hartman
I think the facebook stuff is abandonware.

2008/10/19 Robert Wills [EMAIL PROTECTED]:
 I don't know much about this, but...

 http://hackage.haskell.org/packages/archive/HAppS-Server/0.9.2.1/doc/html/HAppS-Server-Facebook.html

 As I recall, Alex Jacobson's talk contained an example of building a
 facebook app.

 http://www.bayfp.org/blog/2007/10/16/alex-jacobson-on-happs-videos-slides/

 -Rob

 Jason Dusek wrote:

  Has anyone taken a stab at Haskell FaceBook bindings?

 --
 _jsn
 ___
 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


external sort on hackage Re: [Haskell-cafe] External Sort and unsafeInterleaveIO

2008-10-19 Thread Thomas Hartman
External sort is on hackage at

http://hackage.haskell.org/cgi-bin/hackage-scripts/package/external-sort

Ben, I forgot to correct your name, but I will fix it soon.

Thomas.

2008/10/11 Ben [EMAIL PROTECTED]:
 Fine with me, except my last name is Lee not Midfield.  Thanks for
 doing this.

 Ben Midfield Lee

 On Sat, Oct 11, 2008 at 7:52 AM, Thomas Hartman [EMAIL PROTECTED] wrote:
 I kinda-sorta half-cabalized it at

 darcs get http://darcsdump.dreamhosters.com/external-sort (untested
 via cabal install but mostly done)

 As soon as my project gets approved I'll put it up on hackage.

 If Ben wants it under his account at hackage of course I'll defer to him.

 Thomas.

 2007/7/18 Donald Bruce Stewart [EMAIL PROTECTED]:
 midfield:
 hi --

 thanks for the useful comments!  i will definitely go through them
 carefully.  unfortunately for this code (but fortunately for me) i
 defend my dissertation on monday so i'm a little distracted right
 now.

 i'm more than happy to donate this code or whatever improvements
 happen to it.  actually, hGetContentsWithCursor seems like a candidate
 for inclusion with Data.ByteStrings or Data.Binary or something -- it
 seems like it might find other uses.  (i think you liked that bit of
 code because i ripped it off of you guys!  it's very short hamming

 Can't fault that style ;)

 distance from the original.)  anyhow, all that will have to wait a
 couple weeks or so.  also i've never cabalized anything so i may come
 begging for help.

 We have a tutorial for that, luckily:

http://haskell.org/haskellwiki/How_to_write_a_Haskell_program

 And a tool to automate it, mkcabal, so should be fairly straightforward.


 at some point i thought i saw how to do recursive external sort, to
 keep memory usage truly constant, but with my current lack of sleep i
 have lost that illusion.  i'm also curious about the performance
 characteristics of this vs Prelude sort vs the version using the
 tournament mergesort apfelmus suggested.  i need to find a computer
 with a lot more RAM than my weakling laptop.  finally, it would be
 good to be able to have the blocksize controlled by Kb of RAM rather
 than # of elements, not sure how to get that information.

 ultimately this was part of my project to write lucene for haskell.  i
 think with this out of the way, plus all the Data.Binary / ByteString
 goodness, it shouldn't take too long.  keep writing good libraries for
 me!


 Great. Good to see things working.

 -- Don
 ___
 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] Detecting unused read handles? (was: File handles and pipes)

2008-10-19 Thread Brandon S. Allbery KF8NH

On 2008 Oct 19, at 2:39, Stephen Hicks wrote:

I've got one more question now.  Suppose I want to do the same thing

on the other side, with two processes *receiving* the data.  Is there
a way to tell whether the first process wants input, and if not, wait
for the second process to do anything?



Not readily, because if the process ends up outputting more than a  
certain amount (_PIPE_BUF kernel parameter) of data your program will  
deadlock.  I think you need to forkIO and use MVars to synchronize.


--
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


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


Re: [Haskell-cafe] Error building GHC 6.8.3: version of ../../compiler/stage1/ghc-inplace could not be determined

2008-10-19 Thread Ian Lynagh

Hi Devin,

On Sun, Oct 12, 2008 at 06:03:30PM -0700, Devin Mullins wrote:
 
 I'm trying to build 6.8.3 on Linux PowerPC, based on an old binary of
 6.4 (latest build for this arch that I found). stage1 seems to have
 built, but from there, building libraries almost immediately fails:

You could unpack the Debian package of 6.8.2:
http://packages.debian.org/lenny/powerpc/ghc6/download

ar -x foo.deb and then tar -zxf data.tar.gz if I remember correctly.
You'll have to manually tweak the paths in package.conf and the shell
script wrappers, though.

Also, when building yourself, an unregisterised build is more likely to
work correctly on PPC/Linux:
http://hackage.haskell.org/trac/ghc/wiki/Building/Unregisterised

 What's going wrong? How do I fix it? Is there a better mailing list to
 ask?

glasgow-haskell-users is a better list for this sort of question.


Thanks
Ian

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


Re: [Haskell-cafe] package question/problem

2008-10-19 Thread Mads Lindstrøm
Hi,

Galchin, Vasili wrote:

 Hi Duncan,
 
 I was under the impression that HDBC doesn't support myqsl??

You can connect HDBC to MySQL using the HDBC-ODBC backend, see
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/HDBC-odbc.


Greetings,

Mads Lindstrøm


 
 Regards, Vasili
 
 On Sat, Oct 18, 2008 at 6:36 PM, Duncan Coutts
 [EMAIL PROTECTED] wrote:
 On Fri, 2008-10-17 at 18:23 -0500, Galchin, Vasili wrote:
  Hello,
 
  I am trying to cabal install HSQL. I am using ghc
 6.8.2.
 
 
 The simple answer is that the package is unmaintained and has
 not been
 updated to work with ghc 6.8.x.
 
 You can either use HDBC instead or fix HSQL by applying one of
 the
 patches floating around or fix it by following Bertram or
 Marc's advice.
 
 (Note that ghc-pkg hide/expose is a red herring)
 
 
 Duncan
 
 
 
 ___
 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] is 256M RAM insufficient for a 20 millionelementInt/Int map?

2008-10-19 Thread Dan Doel
On Sunday 19 October 2008 10:32:08 am Claus Reinke wrote:
  (hint to ghc hackers: 'Data.Map.Map Int !Int' and '[!a]' would really be
  useful!-),
 
  I can't figure out what that means though.  Strictness is not a
  property of types or of values, it is a property of functions.   [!]
  is not a subtype of [] ; IOW, there is no a such that [a] = [!Int]
  (where [!Int] is a list with strict values).  For example, if we
  allowed this, the following property breaks:
 
   length xs == length (map f xs)
 
  Since it is not true on strict lists.

 I'm not entirely sure this couldn't be worked out. Let's say that
 every type breaks into terminating and non-terminating computations:

 a = !a | ^a

 For your equation to break, you're assuming implicit conversions
 between some 'a' and '!a', ie, something like

 (undefined :: a) :: !a
 (const undefined :: a - b) :: !a - !a

 But those shouldn't typecheck! We can't decide termination, so not
 all objects of type 'a' can be classified into the subtypes '!a' or '^a'.
 Membership in '!a' can be constructive only, and map for strict lists
 would have a type somewhat like this

 mapS :: !(!a - !a) - [!a] - [!a]

 Without a function, 'mapS' can't construct an element-strict result list,
 hence the first '!' (and 'mapS undefined' won't typecheck). Nor can it
 do so without a function that can construct (or pass on) strict elements,
 hence the '!' on the result type of the parameter function (so 'mapS
 (const undefined)' won't typecheck, either). Since there are no ways
 of producing an arbitrary '!a' out of thin air, polymorphic parameter
 functions will have type '!a-!a' (if 'a' gets specialised, eg to 'Int',
 then trivial 'Int-!Int' functions are possible).

 Being conjured out of thin air, none of this might not hold up under
 closer scrutiny, but papers like [1] suggest that it isn't entirely out of
 reach  - further references or counterexamples appreciated!-)

I don't think there's any realistic way to keep his equation from breaking. 
For instance, you might be able to prevent someone from writing:

f :: !a - !a
f _ = undefined

However, that still doesn't guarantee that you can't write non-terminating 
functions, which are semantically bottom:

f :: !a - !a
f a = f a

Note, that you can even write non-termination for unboxed types:

n :: Int#
n = n

Even though such values may be supposedly unlifted. So, given that second f, 
clearly length (map f xs) = _|_ when length xs  1.

Total languages go through a great deal of effort to prevent this sort of 
thing. For instance, many use syntactic checks on the functions your write to 
ensure that they are structurally recursive. So, perhaps you could add these 
checks to a Haskell compiler, but you'd also have to ensure that you don't 
produce total values from non-total values, because doing structural recursion 
over coinductive values (like infinite lists) introduces bottom.

And finally, you'd have to do similar checks on Haskell's data types, because 
the unrestricted recursive types that Haskell has allow you to introduce 
bottom without explicit recursion:

newtype Wrap a = Roll { unRoll :: Wrap a - a }

-- (\x - x x) (\x - x x)
omega :: a
omega = w (Roll w) where w x = unRoll x x

The solution most total languages take is to make sure that all such recursive 
types are strictly positive (recursive uses of the type may not be to the left 
of an arrow; Wrap clearly fails this check).

Anyhow, it seems to me that to adequately separate all this stuff, and prevent 
things like 'length xs = length (mapS f xs)' from breaking, you'd end up with 
an entirely separate total sublanguage that doesn't interact much with the 
existing part (which kind of ruins the appeal of introducing such annotations 
in the first place). Perhaps I'm missing something, though.

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


[Haskell-cafe] Re: [Haskell] Probably a trivial thing for people knowing Haskell

2008-10-19 Thread Paul Johnson

Friedrich wrote:

Paul Johnson [EMAIL PROTECTED] writes:
  

[...] Because file reading is lazy,
each line is only read when it is to be processed, and then gets
reaped by the garbage collector.  So it all runs in constant memory.


Would you mind to elaborate a bit about it. What's so terrible to open
one file after the other, reading it line by line and close the file
thereafter. 
  
Its not wrong, its just more work.  Also from a structural point of view 
its better to separate the code that reads the files from the code that 
processes the text.  The conventional way forces you to mix them.



(By the way, putting in the top level type declarations helps a lot
when you make a mistake.)


Well I have my problems with that. Probably it comes from using
Languages like Ruby and my special dislike of typing things comes
especially from Java, C++ (well C is not innocent in that regard
also. 

  
OK, its a matter of personal preference (although it really does help 
anyone else reading your code).  However I find that if I leave out the 
top level definitions then type error messages at compile time are much 
harder to figure out, especially in a big program.  So I find that the 
extra typing pays in the long run.  :-/


Paul.

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


[Haskell-cafe] A heretic question

2008-10-19 Thread Achim Schneider
What kind of things, barring coding on Haskell-less platforms and
library interfaces would you choose to do in C++?

I'm asking 'cos I'm learning C++ and can't get the proper motivation to
do any program I can think of in it: If I need abstraction, I'm
thinking Haskell or Scheme, and if I'm thinking performance, C itself
more than suffices.

Plus template programming makes me shudder because of its atrocities
against clear and straightforward FP, but that's a different matter.

Coming to think of it, a compiler from a clean syntax to C++ templates
sounds like a fun project... which I'd do in Haskell.

-- 
(c) this sig last receiving data processing entity. Inspect headers
for copyright history. All rights reserved. Copying, hiring, renting,
performance and/or quoting of this signature prohibited.

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


Re: [Haskell-cafe] A heretic question

2008-10-19 Thread John Van Enk
C++ is nicer to work with, when you have the option, on embedded
microprocessors. Dealing with C all the time can be a little cumbersome.
Actually, I've parroted this over and over, if I *could* use Haskell on an
embedded micro, I would. There needs to be more work in that area.

/jve


On Sun, Oct 19, 2008 at 5:08 PM, Achim Schneider [EMAIL PROTECTED] wrote:

 What kind of things, barring coding on Haskell-less platforms and
 library interfaces would you choose to do in C++?

 I'm asking 'cos I'm learning C++ and can't get the proper motivation to
 do any program I can think of in it: If I need abstraction, I'm
 thinking Haskell or Scheme, and if I'm thinking performance, C itself
 more than suffices.

 Plus template programming makes me shudder because of its atrocities
 against clear and straightforward FP, but that's a different matter.

 Coming to think of it, a compiler from a clean syntax to C++ templates
 sounds like a fun project... which I'd do in Haskell.

 --
 (c) this sig last receiving data processing entity. Inspect headers
 for copyright history. All rights reserved. Copying, hiring, renting,
 performance and/or quoting of this signature prohibited.

 ___
 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] A heretic question

2008-10-19 Thread Miguel Mitrofanov


On 20 Oct 2008, at 01:08, Achim Schneider wrote:

I'm asking 'cos I'm learning C++ and can't get the proper motivation  
to

do any program I can think of in it: If I need abstraction, I'm
thinking Haskell or Scheme, and if I'm thinking performance, C itself
more than suffices.


Seems like you've just explained why C++ isn't good for anything.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] A heretic question

2008-10-19 Thread Derek Elkins
On Sun, 2008-10-19 at 23:08 +0200, Achim Schneider wrote:
 What kind of things, barring coding on Haskell-less platforms and
 library interfaces would you choose to do in C++?
 
 I'm asking 'cos I'm learning C++ and can't get the proper motivation to
 do any program I can think of in it: If I need abstraction, I'm
 thinking Haskell or Scheme, and if I'm thinking performance, C itself
 more than suffices.
 
 Plus template programming makes me shudder because of its atrocities
 against clear and straightforward FP, but that's a different matter.
 

I tend to use C++ whenever I strongly care about data representation
(which is admittedly rarely.)  You can use C for that; I just prefer C
to C++ for almost everything.

The only other thing that would almost certainly lead me to using C++ is
if I needed to use to a C++ library.  C++ is extremely difficult to
interface to.

 Coming to think of it, a compiler from a clean syntax to C++ templates
 sounds like a fun project... which I'd do in Haskell.

This is actually one of the first things I wrote in Haskell.  It's not
even much of a compiler but mostly just filling in the blanks of some
templates.

So I could write:
fac 0 = 1
fac n = n * fac (n - 1)

and get output akin to the example on wikipedia.

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


Re: [Haskell-cafe] A heretic question

2008-10-19 Thread Erik de Castro Lopo
Achim Schneider wrote:

 What kind of things, barring coding on Haskell-less platforms and
 library interfaces would you choose to do in C++?

I'm realatively new to Haskell but I've been coding pretty intensively
in Ocaml for a number of years.

For new code, there is stuff I would do in C over Haskell/Ocaml; low
level libraries, realtime audio DSP (digital signal processing) and
device drivers. For all of these I would choose C over C++ because C
is a cleaner less cluttered language. As soon as I want to do something
more high level, then I choose a real high level languague like Ocaml
and maybe some day even Haskell.

Erik
-- 
-
Erik de Castro Lopo
-
A task always takes longer than you expect, even when you take into
account Hofstadter's Law. -- Douglas Hofstadter
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] A heretic question

2008-10-19 Thread Jason Dagit
On Sun, Oct 19, 2008 at 2:08 PM, Achim Schneider [EMAIL PROTECTED] wrote:

 What kind of things, barring coding on Haskell-less platforms and
 library interfaces would you choose to do in C++?


You're asking a crowd that is heavily biased towards Haskell, what they
would use C++ for?  You should expect many answers to be of the form, Well,
if Haskell doesn't work, I'll try generating C or C++ from Haskell.  :)

Which means, people here often see other languages as target languages for
code generators.  Which is something I think is pretty cool.  But, getting
back to your question...

If I were considering writing something in C++ here are some of my
considerations:
1) Is the thing I'm writing known to be easy to solve in C++?
2) Will writing it in C++ instead of, say, Haskell give me access to a
developer pool that is superior for the task?
3) Will dealing with the very few drawbacks of laziness, in particular lazy
IO or space leaks from laziness, end up dominating the development effort?
4) Is it a work related project?
5) Am I just making a prototype or executable specification?

I put (2) and (4) up there because I think it's important to consider who
you'll be working with.  I can't really get way with using Haskell much at
my day job because I'm the only one there that wants to use it.  The company
has to deal with the code I create even if I move on.  Also, programming is
hard regardless of how cool your language is.  So it always seems wise to
work with the sharpest set of programmers that you can.  Sometimes that
means picking a particular language.

It's also important to think about the merits of the languages themselves,
such as (1), (3) and (5) point out.  If you're prototyping, Haskell is light
years ahead of C++.  Then again, optimizing C++ programs, while tedious and
error prone, is understood by far more people than optimizing Haskell
programs.  Laziness can be unpredictable.

I like Haskell a lot and I'd bias all my answers to the above 5 towards it,
but C++ is also a very cool language.  It's just cool for very different
reasons than Haskell is cool.

I'm asking 'cos I'm learning C++ and can't get the proper motivation to
 do any program I can think of in it: If I need abstraction, I'm
 thinking Haskell or Scheme, and if I'm thinking performance, C itself
 more than suffices.



 Plus template programming makes me shudder because of its atrocities
 against clear and straightforward FP, but that's a different matter.


Heh.  Yeah, it can be ugly, but it's also very powerful.  The template
system is Turing complete as you may know.  Boost and Loki are two good
examples of some of the cool things you can do with C++ if you really work
the template system.

Coming to think of it, a compiler from a clean syntax to C++ templates
 sounds like a fun project... which I'd do in Haskell.


Ah yes, even you're thinking about code generators.  It's a very common way
to think in this community it would seem.

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


Re: [Haskell-cafe] Glut using freeglut and non starndard header / lib location?

2008-10-19 Thread Henk-Jan van Tuyl

On Sat, 18 Oct 2008 01:19:42 +0200, Marc Weber [EMAIL PROTECTED] wrote:


Which is the way to install the glut library with non standard header /
lib location?

I've tried setting CFLAGS before running
./configure
./setup configure

and adding the include directory this way
  include-dirs: include,  
/nix/store/rz4nfm5qcrjrk0jsr1lxnjwamgxmgip8-freeglut-2.4.0/include


All results in
checking for GL/glut.h... (cached) no
checking GLUT/glut.h usability... no
checking GLUT/glut.h presence... no
checking for GLUT/glut.h... no
configure: error: no GLUT header found, so this package cannot be built

The configure script is meant to be run by cabal only?

Marc


Have you tried setting the environment variable C_INCLUDE_PATH? If you set  
it to /include/path, the file glut.h should be in directory  
/include/path/GL


--
Regards,
Henk-Jan van Tuyl


--
http://functor.bamikanarie.com
http://Van.Tuyl.eu/
--


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


Re: [Haskell-cafe] is 256M RAM insufficient for a 20 millionelement Int/Int map?

2008-10-19 Thread Don Stewart
claus.reinke:
  I have a standard Data.Map.Map as the base structure for one of my
  macid data tables (jobs), but I noticed something
  that is probably causing problems for me.
  Even a simple 20 million record with int/int key values causes an out
  of memory error for me in ghci,
 Int keys, Int values eh?
 Does using IntMap help?
 Interesting. Map Int Int, IntMap Int and [(Int, Int)] use pretty much
 the same amount of memory, assuming that no keys or values are shared:
 
 I haven't followed the thread, but one thing that keeps tripping me
 up wrt memory use is that Maps aren't strict in their values by default.
 
 Worse, if that is not what you want for your application, working
 around it can be rather awkward (Data.Map at least provides
 insertWith', but there's no unionWith', and Data.IntMap doesn't
 even have insertWith'). 
 
 Ideally, I'd just like to indicate the strictness in the types (hint to ghc 
 hackers: 'Data.Map.Map Int !Int' and '[!a]' would really be useful!-), 
 but as that isn't supported, separate operations (with seq inserted 
 manually at suitable places) seem necessary (hint to container library 
 maintainers: please provide full set of strict operation variants!-).
 
 If this is (or contributes to) the problem, it should show up in heap
 profiles as an upward ramp and could be fixed by defining and using
 locally augmented versions of the Map operations. 

I'd like them strict and specialised,

So that:

data IntMap a = Nil
  | Tip {-# UNPACK #-} !Key a
  | Bin {-# UNPACK #-} !Prefix {-# UNPACK #-} !Mask !(IntMap a) 
!(IntMap a) 

applied as so,

type T = IntMap {-# UNPACK #-} !Int

would be equivalent to

data IntMapT = Nil
 | Tip {-# UNPACK #-} !Key {-# UNPACK #-} !Int 
 | Bin {-# UNPACK #-} !Prefix {-# UNPACK #-} !Mask !(IntMap a) 
!(IntMap a) 

where we've avoided an indirection in the Tip nodes. Less space, faster access.

In general, being able to specialise polymorphic structures so they look like 
unpacked
monomorphic ones would be awesome.

(!Int, !Bool) -   (,) {-# UNPACK #-}!Int {-# UNPACK #-}!Bool

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


Re: [Haskell-cafe] A heretic question

2008-10-19 Thread Luke Palmer
On Sun, Oct 19, 2008 at 3:08 PM, Achim Schneider [EMAIL PROTECTED] wrote:
 What kind of things, barring coding on Haskell-less platforms and
 library interfaces would you choose to do in C++?

I would recommend programming a simple game using SDL.  That is
currently not that much easier in Haskell than it is in C++  (only a
couple orders of magnitude ;-).

As for what would actually be strictly *easier* or *better* to use C++
for... well let me just say that I used to be a C++ guru, and now I
haven't used it for two years.

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


Re: [Haskell-cafe] is 256M RAM insufficient for a 20 millionelement Int/Int map?

2008-10-19 Thread Luke Palmer
On Sun, Oct 19, 2008 at 5:05 PM, Don Stewart [EMAIL PROTECTED] wrote:
 In general, being able to specialise polymorphic structures so they look like 
 unpacked
 monomorphic ones would be awesome.

(!Int, !Bool) -   (,) {-# UNPACK #-}!Int {-# UNPACK #-}!Bool

I repeat my concern about this notation and the implications thereof.
(!Int, !Bool) cannot be passed to a function accepting (a,b).

However, I feel there's something very useful here that should be
fleshed out rather than hacked.  For example, a theory of composable
strict structures in a lazy language.

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


Re: [Haskell-cafe] A heretic question

2008-10-19 Thread Bulat Ziganshin
Hello Achim,

Monday, October 20, 2008, 1:08:06 AM, you wrote:

 thinking Haskell or Scheme, and if I'm thinking performance, C itself
 more than suffices.

... and machine code too :D  C++ is the highest level language that
provide asm-like speed, so it's hard to find reasons to use C instead.
and templates may be used to generates lots of efficient code
automatically


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] Error building GHC 6.8.3: version of ../../compiler/stage1/ghc-inplace could not be determined

2008-10-19 Thread Devin Mullins
On Sun, Oct 19, 2008 at 05:13:55PM +0100, Ian Lynagh wrote:
 You could unpack the Debian package of 6.8.2:
 http://packages.debian.org/lenny/powerpc/ghc6/download

Thanks! Indeed, I was able to use this to build 6.8.3.

 Also, when building yourself, an unregisterised build is more likely to
 work correctly on PPC/Linux:
 http://hackage.haskell.org/trac/ghc/wiki/Building/Unregisterised

Yeah, I tried that, too, but ran into an error (and had neither the
time, the energy, nor the knowledge to investigate). Don't matter now.

 glasgow-haskell-users is a better list for this sort of question.

Yeah, I discovered that after I sent.

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


[Haskell-cafe] Questions for Free!

2008-10-19 Thread Creighton Hogg
Hello Haskellers,
So I have a bit of a follow up question after reading Theorems For
Free! this weekend.
There's a throw away comment near the beginning about how you can
recast the results into category theoretic form, but using lax natural
transformations.
Now I'm assuming this means a natural transformation but where the
naturality square holds only up to isomorphism instead of equality,
but is that correct?  Also, why would you need such a condition?

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


Re: [Haskell-cafe] is 256M RAM insufficient for a 20 millionelement Int/Int map?

2008-10-19 Thread Max Bolingbroke
2008/10/20 Don Stewart [EMAIL PROTECTED]:
 claus.reinke:
 Ideally, I'd just like to indicate the strictness in the types (hint to ghc
 hackers: 'Data.Map.Map Int !Int' and '[!a]' would really be useful!-),
 In general, being able to specialise polymorphic structures so they look like 
 unpacked
 monomorphic ones would be awesome.

(!Int, !Bool) -   (,) {-# UNPACK #-}!Int {-# UNPACK #-}!Bool

I spent some time thinking about how one might actually go about
implementing this in GHC today, and came to the conclusion that it
interacts far too badly with separate compilation.

In an ideal world, you know which specialisations to generate for the
data structure when compiling it in the first place. You would then of
course generate the appropriate specialisations for all subsequent
polymorphic function definitions that use the speciliased type ((,),
IntMap or whatever), so you don't lose the ability to apply your
unpacked version to a function of type like (a, b) - a - see
http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.55.8984 that
Claus pointed to. But we don't have that information yet at the point
where we compile a data definition...

The CLR has a similar problem but gets away with it because it has a
JIT compiler that can see the original definitions of classes /
methods and instantiate them at the necessary types at runtime (see
http://research.microsoft.com/~akenn/generics/space2004generics.pdf).

One possible approach for GHC would be to generate all possible
specializations for a datatype + functions when compiling a module.
This sounds bad, but actually you only need to cater for at most three
unboxed field sizes:

1) 32 bit (Int#, Word#, Float#, Addr#)
2) 64 bit (Int64#, Word64#)
3) Usually 64 bit (Double#)

Of course, if you have a type like (,,,) with 4 type arguments you
still have to potentially generate 3^4 specialisations (and
corresponding functions!) so this /can/ get bad quickly :-).

This is also sort of a hack, in that it crucially relies on the fact
that unboxed tuples don't really make sense as type arguments yet.
This is because types like (# Int, Bool #) - Int are rejected by the
compiler - unboxed tuples can only occur on the right of function
arrows. However, this is just a technical limitation, and were it to
be lifted it might make sense to be able to instantiate data types at
unboxed tuple types, blowing this scheme out of the water.

You could also export the entire definition of functions+data
structures you might need to specialise across module boundaries, and
generate specialisations where they are needed, but this can lead to
redundant code generation with diamond dependencies (see the
Syme/Kennedy paper - though I don't think their problem with redundant
type descriptors applies to Haskell, making it easier to apply) and
would bloat .hi files. This might still be the best way to go about
it, should someone choose to implement it,.

A further alternative would be to just compile every function once,
but pass something like a dictionary to every function to tell it how
to handle its own arguments (how much stuff to pop off the stack etc).
Clean ,but the huge runtime overhead of this approach kind of defeats
the point of using unboxed types in the first place.

A final alternative would be to somehow recompile a module with the
desired instantiation if it turned out not to contain it. But this
could potentially lead to greatly increased compile times...

So, I can't really see a clean way to go about this without going the
whole hog and turning GHC into a whole-program compiler :-)

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


Re: [Haskell-cafe] is 256M RAM insufficient for a 20 millionelement Int/Int map?

2008-10-19 Thread Max Bolingbroke
2008/10/20 Luke Palmer [EMAIL PROTECTED]:
 On Sun, Oct 19, 2008 at 5:05 PM, Don Stewart [EMAIL PROTECTED] wrote:
 In general, being able to specialise polymorphic structures so they look 
 like unpacked
 monomorphic ones would be awesome.

(!Int, !Bool) -   (,) {-# UNPACK #-}!Int {-# UNPACK #-}!Bool

 I repeat my concern about this notation and the implications thereof.
 (!Int, !Bool) cannot be passed to a function accepting (a,b).

 However, I feel there's something very useful here that should be
 fleshed out rather than hacked.  For example, a theory of composable
 strict structures in a lazy language.

This paper might be of interest to you, assuming you haven't seen it:
http://research.microsoft.com/~simonpj/papers/not-not-ml/index.htm. It
doesn't really deal with the issue of UNPACKed data structures, but
does show the first steps towards making sense of types like [!Int] vs
[Int] (if we consider !Int as an ML-style Int (albeit a boxed one)
and Int as the vanilla Haskell flavour).

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


Re: [Haskell-cafe] A heretic question

2008-10-19 Thread ajb

G'day all.

On Sun, 2008-10-19 at 23:08 +0200, Achim Schneider wrote:


I'm asking 'cos I'm learning C++ and can't get the proper motivation to
do any program I can think of in it: If I need abstraction, I'm
thinking Haskell or Scheme, and if I'm thinking performance, C itself
more than suffices.


Unless I'm working on a platform where memory is so tight that I
can't afford the cost of vtables, EH, RTTI and extra stack usage,
I always prefer C++ to C.  Always.  On the sorts of CPUs you find
on desktops and servers, and even most embedded platforms these
days, there is no advantage in using C over C++, and significant
advantages in using C++ over C.

The trouble is that C++ is a tool that's hard to use well.  But that's
why they pay us the big bucks, right?

Quoting Derek Elkins [EMAIL PROTECTED]:


I tend to use C++ whenever I strongly care about data representation
(which is admittedly rarely.)


Indeed.  Having said that, type families mean that Haskell now gives
you much finer control over data representation, though still not fine
enough for many applications.

The more general thing is that C++ gives you fine control over
resources.  Resources appear and disappear at predictable times, which
in some applications is important.

My last point is that C++ has a lot more tool support: compilers,
libraries, frameworks, refactoring browsers and so on.

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


Re[2]: [Haskell-cafe] A heretic question

2008-10-19 Thread Bulat Ziganshin
Hello ajb,

Monday, October 20, 2008, 4:50:45 AM, you wrote:

 The trouble is that C++ is a tool that's hard to use well.  But that's
 why they pay us the big bucks, right?

i think that one day we will hear that ML was too easy language and
they invented Haskell in order to keep future salaries high LOL

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: Re[2]: [Haskell-cafe] A heretic question

2008-10-19 Thread Brandon S. Allbery KF8NH

On 2008 Oct 19, at 21:07, Bulat Ziganshin wrote:

Monday, October 20, 2008, 4:50:45 AM, you wrote:
The trouble is that C++ is a tool that's hard to use well.  But  
that's

why they pay us the big bucks, right?


i think that one day we will hear that ML was too easy language and
they invented Haskell in order to keep future salaries high LOL



I thought that was what Agda was for.  :)

--
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


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


Re: [Haskell-cafe] package question/problem

2008-10-19 Thread Duncan Coutts
On Sat, 2008-10-18 at 23:38 -0500, Galchin, Vasili wrote:
 Hi Duncan,
 
 I was under the impression that HDBC doesn't support myqsl??

I believe it works via ODBC.

But perhaps you can persuade Frederik Eaton to make new working releases
of HSQL.

Duncan

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


Re: [Haskell-cafe] is 256M RAM insufficient for a 20 millionelement Int/Int map?

2008-10-19 Thread Duncan Coutts
On Sun, 2008-10-19 at 16:05 -0700, Don Stewart wrote:

 I'd like them strict and specialised,
 
 So that:
 
 data IntMap a = Nil
   | Tip {-# UNPACK #-} !Key a
   | Bin {-# UNPACK #-} !Prefix {-# UNPACK #-} !Mask !(IntMap 
 a) !(IntMap a) 
 
 applied as so,
 
 type T = IntMap {-# UNPACK #-} !Int

Yes, except that it should be newtype. That gives a proper boundary to
apply injection / projection functions for the different internal
representation.

Duncan

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