[Haskell-cafe] Re: Type question in instance of a class

2008-11-18 Thread Maurí­cio

  (...) One way to code this would be to use functional dependencies:
 
  class MyClass r s | r - s where function :: r - s


One additional  problem is that I  (believe I) need that  my class takes
just  one type


FDs with just one type parameter are called ATs :)

(FDs = functional dependencies, ATs is a new feature of ghc 6.8/6.10)



Sorry for asking, but I tried to read 6.10 extension documentation
in user's guide, as well as release notes for 6.10 and 6.8, and
could not figure out what exactly are ATs. Can you give me a direction?

Thanks,
Maurício

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


[Haskell-cafe] Re: Statically dimension-checked hmatrix

2008-11-18 Thread Patrick Perry



What is the situation regarding statically dimension-checked linear
algebra libraries? It seems that Frederik Eaton was working on one in
2006 (see the paper Statically typed linear algebra in Haskell), and
he produced the Vectro library from this, based on GSLHaskell.

Are there any more recent efforts into this, particularly using the
new TFs? If not, I might have a go at it, as a thin wrapper for
hmatrix.


The BLAS bindings I wrote use phantom types to make sure the  
dimensions are consistent.  See, for example the functions to get row  
and column views of a matrix:


http://hackage.haskell.org/packages/archive/blas/0.6/doc/html/Data-Matrix-Dense-Class.html#v%3ArowViews

Also, the multiplication routines:

http://hackage.haskell.org/packages/archive/blas/0.6/doc/html/BLAS-Matrix-Immutable.html

I've found that phantom types are a good trade off: they provide  
enough type safety to catch common mistakes without being too much of  
a hassle to use.  Another benefit (which I didn't anticipate) is that  
they help a *lot* with documentation.


I'm skeptical of value that comes from stronger typing.  At some point  
the types become too much of a hassle to be worth using.  Even phantom  
types get in the way sometimes and require use of either GADTs,  
unsafeCoerce, or both, which is annoying.


I'd be interested to hear about any developments you make in this area.


Patrick

p.s. If you're interested in trying it out, the version of blas on  
hackage doesn't compile with ghc-6.10.1, but the version in the darcs  
repository at http://stat.stanford.edu/~patperry/code/blas does.


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


Re: [Haskell-cafe] Proof of a multi-threaded application

2008-11-18 Thread Neil Davies

Ketil

You may not be asking the right question here. Your final system's  
performance is going to be influenced far more by your algorithm for  
updating than by STM (or any other concurrency primitive's) performance.


Others have already mentioned the granularity of locking - but that  
one of the performance design decisions that you need to quantify.


The relative merits of various approaches are going to come down to  
issues such as


  * given that you have a lock what is the cost of locking (in term  
of the lack of forward progress)
  * how often will you have to pay this cost (that will be  
application / data dependent)
  * given you use STM, what is the (differential) cost of the  
underlying housekeeping (depends what processing is with the  
'atomically')
  * what is the likelihood that you will have to undo stuff  
(represents the same cost as the lack of forward progress).


So the answer which is better, as it always is, will be - it depends

Welcome to the wonderful world of performance engineering.

The answer you seek is tractable - but will require more analysis.

Neil


On 18 Nov 2008, at 06:35, Ketil Malde wrote:


Tim Docker [EMAIL PROTECTED] writes:


My apologies for side-tracking, but does anybody have performance
numbers for STM? I have an application waiting to be written using
STM, boldly parallelizing where no man has parallelized before, but
if it doesn't make it faster,



Faster than what?


Faster than an equivalent non-concurrent program.  It'd also be nice
if performance was comparable lock-based implementation.


Are you considering using STM just to make otherwise pure code run in
parallel on multiple cores?


No, I have a complex structure that must be updated in non-predictable
ways.  That's what STM is for, no?

-k
--
If I haven't seen further, it is by standing in the footprints of  
giants

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


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


Re: [Haskell-cafe] Re: Type question in instance of a class

2008-11-18 Thread Reiner Pope
ATs are Associated Types, aka Type Families. They can be found in
the GHC 6.10 manual here:
http://haskell.org/ghc/docs/6.10.1/html/users_guide/type-families.html

As a starting point, you might want to try something like:

class Complex c where
   type RealType c
   realPart :: c - RealType c
   imagPart :: c - RealType c


Cheers,
Reiner

On Tue, Nov 18, 2008 at 7:01 PM, Maurí­cio [EMAIL PROTECTED] wrote:
   (...) One way to code this would be to use functional dependencies:
  
   class MyClass r s | r - s where function :: r - s

 One additional  problem is that I  (believe I) need that  my class takes
 just  one type

 FDs with just one type parameter are called ATs :)

 (FDs = functional dependencies, ATs is a new feature of ghc 6.8/6.10)


 Sorry for asking, but I tried to read 6.10 extension documentation
 in user's guide, as well as release notes for 6.10 and 6.8, and
 could not figure out what exactly are ATs. Can you give me a direction?

 Thanks,
 Maurício

 ___
 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] Cabal and more than one version

2008-11-18 Thread Jason Dusek
  I'd like to be able to do something like:

if (template-haskell  2.3)
  cpp-options: -D TH_THE_YOUNGER
else
  cpp-options: -D TH_THE_ELDER

  I guess this kind of thing is not possible at present?

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


[Haskell-cafe] GHC 6.10.1 and cabal[-install]

2008-11-18 Thread Wolfgang Jeltsch
Hello,

I installed GHC 6.10.1 today and expected it to contain the cabal command line 
utility.  Unfortunately, this was not the case.  Where can I download it?  
How do I install and configure it so that it is integrated best with 
GHC 6.10.1?  For example, should cabal use some directory in the GHC tree to 
place compiled packages in?

http://hackage.haskell.org/ still links to cabal-install for a convenient 
way for installing packages.  I thought that cabal-install is outdated.  
Isn’t it?  Generally, Cabal info and documentation ist too hard to find on 
the web, in my opinion.

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


[Haskell-cafe] implementing python-style dictionary in Haskell

2008-11-18 Thread kenny lu
Dear all,

I am trying to implement the python-style dictionary in Haskell.

Python dictionary is a data structure that maps one key to one value.
For instance, a python dictionary
d = {'a':1, 'b':2 }
maps key 'a' to 1, 'b' to 2.
Python dictionary allows for update. e.g. the statement
d['a'] = 3
changes the value pointed by 'a' from 1 to 3.

Internally, python dictionary is implemented using hash table.

My first attempt is to use Data.HashTable. However it was immediately
abandoned, as I realize the memory usage is unreasonably huge.


== SECOND ATTEMPT ==
My second attempt is to use Data.Map


{-# OPTIONS_GHC -fglasgow-exts #-}
module Main where

import qualified Data.HashTable as HT
import qualified Data.IntMap as IM
import qualified Data.Map as DM
import qualified Data.ByteString.Char8 as S
import Data.Char


-- the Dict type class
class Dict d k v | d - k v where
empty :: d
insert :: k - v - d - d
lookup :: k - d - Maybe v
update :: k - v - d - d

-- Let's use string as key
type Key = String

-- insert key-value pairs into a dictionary
fromList :: Dict d k a = [(k,a)] - d
fromList l =
foldl (\d (key,val) - insert key val d) empty l


instance Dict (DM.Map S.ByteString a) Key a where
empty = DM.empty
insert key val dm =
let packed_key = S.pack key
in DM.insert packed_key val dm
lookup key dm =
let packed_key = S.pack key
in DM.lookup packed_key dm
update key val dm =
let packed_key = S.pack key
in DM.update (\x - Just val) packed_key dm


Which kinda works, however since Map is implemented using a balanced tree,
therefore,
when as the dictionary grows, it takes a long time to insert new key-value
pair.


== THIRD ATTEMPT ==
My third attempt is to use Data.IntMap

-- an implementation of Dict using IntMap
instance Dict (IM.IntMap a) Key a where
empty = IM.empty
insert key val im =
let int_key = fromIntegral (HT.hashString key)
in IM.insert int_key val im
lookup key im =
let int_key = fromIntegral (HT.hashString key)
in IM.lookup int_key im
update key val im =
let int_key = fromIntegral (HT.hashString key)
in IM.update (\x - Just val) int_key im


This implementation is faster than the Map approach, however this
implementation
can't handle collision well, two keys which are hashed into the same integer
will overwrite each other.


== FOURTH ATTEMPT ==

My fourth implementation is to use Trie. The idea is to split a string (a
key) into
a list of 4-character chunks. Each chunk can be mapped into a 32-bit integer
without collision.
We then insert the value with this list of chunks into the Trie.


-- an implementation of Dict using Trie
instance Dict (Trie a) Key a where
empty = emptyTrie
insert key val trie =
let key_chain = chain key
in insertTrie key_chain val trie
lookup key trie =
let key_chain = chain key
in lookupTrie key_chain trie
update key val trie =
let key_chain = chain key
in updateTrie key_chain val trie


-- an auxillary function that splits string into small pieces,
-- 4 characters per piece, 4 chars = 32 bit
chain :: Key - [Key]
chain k | length k  4 = let (k',ks) = splitAt 4 k
 in (k':chain ks)
| otherwise= [k]

-- a collision-free hash function which turns four chars into Int32
safehash :: [Char] - Int
safehash cs | length cs  4 = error safehash failed.
| otherwise =
sum [ (ord c)*(256^i)   | (c,i) - zip cs [0..3] ]


-- a trie datatype
data Trie a = Trie [a] (IM.IntMap (Trie a))

-- the empty trie
emptyTrie = Trie [] (IM.empty)

-- insert value into the trie
insertTrie :: [String] - a - Trie a - Trie a
insertTrie [] i (Trie is maps) = Trie (i:is) maps
insertTrie (word:words) i (Trie is maps) =
let key = safehash word
in case IM.lookup key maps of
 { Just trie - let trie' = insertTrie words i trie
maps' = IM.update (\x - Just trie') key maps
in Trie is maps'
 ; Nothing - let trie = emptyTrie
  trie' = insertTrie words i trie
  maps' = IM.insert key trie' maps
  in Trie is maps'
 }

-- lookup value from the trie
lookupTrie :: [String] - Trie a - Maybe a
lookupTrie [] (Trie vs _) =
case vs of
  [] - Nothing
  (x:_) - Just x
lookupTrie (word:words) (Trie is maps) =
let key = safehash word
in case IM.lookup key maps of
   Just trie - lookupTrie words trie
   Nothing   - Nothing

-- update the trie with the given value.
updateTrie :: [String] - a - Trie a - Trie a
-- we only update the first value and leave the rest unchanged.
updateTrie [] y (Trie (x:xs) maps) = Trie (y:xs) maps
updateTrie (word:words) v  (Trie is maps) =
let key = safehash word
in case IM.lookup key maps of
   Just trie - let trie' = updateTrie words v trie
maps'  = IM.update (\x - Just trie') key maps
in Trie is maps'
   Nothing   - Trie is maps



== BENCH MARK ==

I have a 

Re: [Haskell-cafe] implementing python-style dictionary in Haskell

2008-11-18 Thread Jason Dusek
  Did you use Unicode in Python?

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


Re: [Haskell-cafe] implementing python-style dictionary in Haskell

2008-11-18 Thread Bulat Ziganshin
Hello kenny,

Tuesday, November 18, 2008, 1:37:36 PM, you wrote:

 The above number shows that my implementations of python style
 dictionary  are space/time in-efficient as compared to python. 

thanks, interesting code

1. why you think that your code should be faster? pythob
implementation is probably written in C ince it's one of its core data
structures

2. you can solve IntMap problem by storing list of values with the
same hash in tree's nodes


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


RE: [Haskell-cafe] GHC 6.10.1 and cabal[-install]

2008-11-18 Thread Tobias Bexelius
Hi,

I used the cabal-install on hackage:
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/cabal-install

In order to install it you will need these two packages first:
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/HTTP-3001.1.4
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/zlib-0.5.0.0


For each package (starting with the last two of course), run:

 runghc Setup configure
 runghc Setup build
 runghc Setup install

Once its all done, you can instead use

cabal install x

to install package x, and don't need to care about dependencies anymore. And 
theres nothing else you need to do in order to integrate it with ghc either...
 
/Tobias

-Original Message-
From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED] On Behalf Of Wolfgang Jeltsch
Sent: den 18 november 2008 11:01
To: haskell-cafe@haskell.org
Subject: [Haskell-cafe] GHC 6.10.1 and cabal[-install]

Hello,

I installed GHC 6.10.1 today and expected it to contain the cabal command line 
utility.  Unfortunately, this was not the case.  Where can I download it?  
How do I install and configure it so that it is integrated best with 
GHC 6.10.1?  For example, should cabal use some directory in the GHC tree to 
place compiled packages in?

http://hackage.haskell.org/ still links to cabal-install for a convenient way 
for installing packages.  I thought that cabal-install is outdated.  
Isn't it?  Generally, Cabal info and documentation ist too hard to find on the 
web, in my opinion.

Best wishes,
Wolfgang
___
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] implementing python-style dictionary in Haskell

2008-11-18 Thread Claus Reinke

main :: IO ()
main = do { content - readFile in.txt
 ; let -- change this following type annotation
   -- to change different type of the dictionary
   -- dict :: DM.Map S.ByteString Int
   -- dict :: IM.IntMap Int
   dict :: Trie Int
   dict = fromList (map parse_a_line  (lines content))
..
   where  parse_a_line :: String - (Key,Int)
  parse_a_line line = case words line of
 [key,val] - (key,read val)
 _ - error  parse error.  


Maps tend to be strict in their keys, but not in their values.
You might be storing a lot of thunks with unparsed Strings 
instead of plain Int values.


Something like this might make a difference wrt memory usage:

  [key,val] - ((,) key) $! (read val)

Hth,
Claus


Here is a comparison of memory usage

Map : 345 MB
IntMap : 146 MB
Trie : 282 MB
Python : 94 MB


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


Re: [Haskell-cafe] implementing python-style dictionary in Haskell

2008-11-18 Thread kenny lu
Hi Bulat,



 1. why you think that your code should be faster? pythob
 implementation is probably written in C ince it's one of its core data
 structures


I am not hoping that my code should be faster, but at least not as slow as
what it gets.
Basically I am looking for an implementation which is close to the one in
python.



 2. you can solve IntMap problem by storing list of values with the
 same hash in tree's nodes


Yeah, that would probably speed up the building time of the dictionary.
However, storing the list of values in the tree nodes requires storing their
original keys,
so that it maintains the one-key-to-one-value semantics. This would takes up
more space
compared to the Trie approach.

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


Re: [Haskell-cafe] implementing python-style dictionary in Haskell

2008-11-18 Thread Tillmann Rendel

kenny lu wrote:

Internally, python dictionary is implemented using hash table.

My first attempt is to use Data.HashTable. However it was immediately
abandoned, as I realize the memory usage is unreasonably huge.


Why should a Haskell hash table need more memory then a Python hash 
table? I've heard that Data.HashTable is bad, so maybe writing a good 
one could be an option.



Python dictionary allows for update. e.g. the statement
d['a'] = 3
changes the value pointed by 'a' from 1 to 3.


I understand changes in the sense of an destructive update: The hash 
table stays the same (in terms of object identity), but the content of 
the memory cell storing the value of d['a'] is changed in place. That 
means that the old hash table, with d['a'] == 1, doesn't exist anymore.



-- the Dict type class
class Dict d k v | d - k v where
empty :: d
insert :: k - v - d - d
lookup :: k - d - Maybe v
update :: k - v - d - d


But here you want to create a new d, e.g. a whole new hash table, which 
contains mostly the same content, but one memory cell different. The old 
hash table still exists in memory. That is a totally different operation 
which is quite likely to need more memory.


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


Re[2]: [Haskell-cafe] implementing python-style dictionary in Haskell

2008-11-18 Thread Bulat Ziganshin
Hello kenny,

Tuesday, November 18, 2008, 2:34:25 PM, you wrote:

 I am not hoping that my code should be faster, but at least not as slow as 
 what it gets.
 Basically I am looking for an implementation which is close to the one in 
 python.

well, if haskell will allow to produce code not slower than C, it will
be world's best language :) unfortunately, you should pay a lot for
it's elegance

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] implementing python-style dictionary in Haskell

2008-11-18 Thread Krzysztof Skrzętnicki
2008/11/18 kenny lu [EMAIL PROTECTED]:
 Dear all,

 I am trying to implement the python-style dictionary in Haskell.

 Python dictionary is a data structure that maps one key to one value.
 For instance, a python dictionary
 d = {'a':1, 'b':2 }
 maps key 'a' to 1, 'b' to 2.
 Python dictionary allows for update. e.g. the statement
 d['a'] = 3
 changes the value pointed by 'a' from 1 to 3.

 Internally, python dictionary is implemented using hash table.

 My first attempt is to use Data.HashTable. However it was immediately
 abandoned, as I realize the memory usage is unreasonably huge.

 ...

 I tested all three implementations by building a dictionary of size 100.
 The result shows that the Map and the Trie approaches handle collision well,
 but
 the IntMap approach does not.


 Here is a comparison of memory usage

 Map : 345 MB
 IntMap : 146 MB
 Trie : 282 MB
 Python : 94 MB

 Here is a comparison of execution time (on an intel dual core 2.0G)

 Map: 26 sec
 IntMap: 9 sec
 Trie: 12 sec
 Python: 2.24 sec


 The above number shows that my implementations of python style dictionary
 are space/time in-efficient as compared to python.

 Can some one point out what's wrong with my implementations?


First of all, you use Strings. That's a very bad thing when you care
about memory restrictions. Fire up ghci type something like this:
 let aas = replicate (1024*1024*10) 'a'
 -- 22 Mb memory usage
 length aas
 10485760
 -- 270 Mb memory usage
10 Mb string caused as much as 250 Mb increase in ghci's memory consumption.

My guess? Use hashtables with ByteStrings.
I rewrote part of your code. Results are quite promising.

Haskell:
121 Mb total memory in use

 INIT  time0.02s  (  0.00s elapsed)
 MUT   time0.84s  (  1.00s elapsed)
 GCtime1.97s  (  2.02s elapsed)
 EXIT  time0.00s  (  0.00s elapsed)
 Total time2.83s  (  3.02s elapsed)

 %GC time  69.6%  (66.8% elapsed)
Python:
$ time python dict.py
256

real0m2.278s
user0m2.233s
sys 0m0.078s

memory: 101 Mb (as reported by Windows' Task Manager).

The code:

--- cut ---

import qualified Data.ByteString.Lazy.Char8 as BS
import Data.Int
import Data.Bits

(...)

parse_a_line_BS :: BS.ByteString - (BS.ByteString,Int)
parse_a_line_BS line = case BS.words line of
  [key,val] - (key,(read . BS.unpack) val)
  _ - error  parse error.  


main :: IO ()
main = do
  dict - HT.new (==) hashByteString
  indata - (map parse_a_line_BS `fmap` BS.lines `fmap` BS.readFile in.txt)
  mapM_ (\ (k,v) - HT.insert dict k v) indata
  HT.lookup dict (BS.pack key256) = \v - case v of
Just vv - putStrLn (show vv)
Nothing - putStrLn
(Not found)

-- derived from Data.HashTable.hashString
hashByteString :: BS.ByteString - Int32
hashByteString = BS.foldl' f golden
   where f m c = fromIntegral (ord c) * magic + hashInt32 m
 magic = 0xdeadbeef

hashInt32 :: Int32 - Int32
hashInt32 x = mulHi x golden + x

mulHi :: Int32 - Int32 - Int32
mulHi a b = fromIntegral (r `shiftR` 32)
   where r :: Int64
 r = fromIntegral a * fromIntegral b

golden :: Int32
golden = 1013904242 -- = round ((sqrt 5 - 1) * 2^32) :: Int32

--- cut ---

I had to rewrite hashString to work for ByteStrings - basically it's
just using different foldl'.

All best

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


Re[2]: [Haskell-cafe] implementing python-style dictionary in Haskell

2008-11-18 Thread Bulat Ziganshin
Hello Tillmann,

Tuesday, November 18, 2008, 2:46:47 PM, you wrote:

 Why should a Haskell hash table need more memory then a Python hash
 table? I've heard that Data.HashTable is bad, so maybe writing a good 
 one could be an option.

about Data.HashTable: it uses one huge array to store all the entries.
the catch is that GC need to scan entire array on every (major) GC.
using array of hashtables may improve situation a lot

plus check GC times for every version: +RTS -Soutfile


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] Proof of a multi-threaded application

2008-11-18 Thread Neil Davies


On 18 Nov 2008, at 10:04, Ketil Malde wrote:


Neil Davies [EMAIL PROTECTED] writes:


You may not be asking the right question here. Your final system's
performance is going to be influenced far more by your algorithm for
updating than by STM (or any other concurrency primitive's)
performance.


I may not be asking the right question, but I am happy about the
answer, including yours :-)

I think STM is semantically the right tool for the (my) job, but for
it to be useful, the implementation must not be the limiting factor.
I.e running on n+1 CPUs should be measurably faster than running on n,
at least up to n=8, and preferably more.


More detailed questions: how complex is the mutual exclusion block? If  
it is well known now and not likely to change you can implement  
several ways and work out any extra overhead (run it lot) against the  
other approaches. Nothing like a quick benchmark. Otherwise stick with  
STM (its composable after all).



With the assuming I can get enough parallelism and avoiding too many
rollbacks, of course.


Its not the parallelism that is the issue here, it is the locality of  
reference. If you have data that is likely to be widely spread amongst  
all the possible mutual exclusion blocks then you are on to a winner.  
If your data is clustered and likely to hit the same 'block' then,  
whatever you do, your scalability is scuppered.


Also, consider how much concurrency you've got, not just the  
parallelism. You need enough concurrency to exploit the parallelism  
but not too much more - too much more can start creating contention  
for the mutual exclusion blocks that would not have existed at less  
concurrency.




Others have already mentioned the granularity of locking - but that
one of the performance design decisions that you need to quantify.


Yes.  Fine grained - I'm thinking a large Array of TVars.  (If you
only have a single TVar, it might as well be an MVar, no?)


What do those TVars contain? how many of them are being updated  
atomically?



-k
--
If I haven't seen further, it is by standing in the footprints of  
giants


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


Re: [Haskell-cafe] implementing python-style dictionary in Haskell

2008-11-18 Thread Tillmann Rendel

Hello Alberto,

I cc this to haskell-cafe again.

Alberto G. Corona wrote:

Not so much memory, because data is referentially transparent, the new Map
can point to whole subtrees of the old map that stay the same. is similar
than  when a new list is created by prefixing a new element from a old list
ys= x:xs.  ys is not at all a fresh copy, but  x plus a pointer to the head
of xs. this is the only new data that is needed to create ys.


You could just as well compare with appending a new element to the end 
of the list, which needs a complete copy of the list structure to be 
made. One has to look more closely to see which case it is here.


More specifically, I do not see how this sharing of substructures could 
be employed in the implementation of hash tables, which rely on O(1) 
random access into arrays.


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


Re: [Haskell-cafe] Proof of a multi-threaded application

2008-11-18 Thread Ryan Ingram
On Tue, Nov 18, 2008 at 2:04 AM, Ketil Malde [EMAIL PROTECTED] wrote:
 Yes.  Fine grained - I'm thinking a large Array of TVars.  (If you
 only have a single TVar, it might as well be an MVar, no?)

With only one I think that IORef + atomicModifyIORef might even be better! :)

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


Re: [Haskell-cafe] implementing python-style dictionary in Haskell

2008-11-18 Thread Alberto G. Corona
The most balanced case may be the insertion of a element in the middle of  a
list, but this is far worst than to insert an element in a particular branch
of a tree ( it needs an average of list-lenght/2 element creations while in
a tree  needs only  (average-branch-length)/2)

I refer to Maps, because Hashtables, in the IO monad, are mutable.  by the
way  let map2= map1 takes 0 bytes of memory And both do not share side
effects, while creating two copies of a hastable to avoid side effects
between them needs 2 * size.

2008/11/18 Tillmann Rendel [EMAIL PROTECTED]

 Hello Alberto,

 I cc this to haskell-cafe again.

 Alberto G. Corona wrote:

 Not so much memory, because data is referentially transparent, the new Map
 can point to whole subtrees of the old map that stay the same. is similar
 than  when a new list is created by prefixing a new element from a old
 list
 ys= x:xs.  ys is not at all a fresh copy, but  x plus a pointer to the
 head
 of xs. this is the only new data that is needed to create ys.


 You could just as well compare with appending a new element to the end of
 the list, which needs a complete copy of the list structure to be made. One
 has to look more closely to see which case it is here.

 More specifically, I do not see how this sharing of substructures could be
 employed in the implementation of hash tables, which rely on O(1) random
 access into arrays.

  Tillmann

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


Re: [Haskell-cafe] GHC 6.10.1 and cabal[-install]

2008-11-18 Thread Wolfgang Jeltsch
Am Dienstag, 18. November 2008 11:01 schrieb Wolfgang Jeltsch:
 Hello,

 I installed GHC 6.10.1 today and expected it to contain the cabal command
 line utility.  Unfortunately, this was not the case.  Where can I download
 it?

Meanwhile, I found out that the package cabal-install includes the cabal 
command.  On the other hand I thought that there was a now deprecated command 
line tool named cabal-install.  I find this a bit confusing.

 How do I install and configure it so that it is integrated best with
 GHC 6.10.1?  For example, should cabal use some directory in the GHC tree 
 to place compiled packages in?

Cabal wants to place package info in $HOME/.cabal.  However, I want to install 
packages globally with sudo.  So I want to have a global package cache.  Is 
there a common directory to be used for that or is cabal[-install] only for 
per-user installations?

Well, there is the --global option but it is apparently only for registering 
packages globally.  Does it change the destination directory for the 
installed packages too?  If yes, to what directory?  Is the default --global 
or --user?  Sorry, but I cannot find the answers to this in the docs and I 
don’t want to mess up my file system.

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


Re: Re[2]: [Haskell-cafe] implementing python-style dictionary in Haskell

2008-11-18 Thread Jan-Willem Maessen


On Nov 18, 2008, at 7:03 AM, Bulat Ziganshin wrote:


Hello Tillmann,

Tuesday, November 18, 2008, 2:46:47 PM, you wrote:


Why should a Haskell hash table need more memory then a Python hash
table? I've heard that Data.HashTable is bad, so maybe writing a good
one could be an option.


about Data.HashTable: it uses one huge array to store all the entries.
the catch is that GC need to scan entire array on every (major) GC.


Actually, the scan on every major (full) GC is unavoidable.  What  
*can* be avoided is a scan on every *minor* GC that occurs after an  
update.  I forget what the exact strategy is here, but I know that one  
write used to cause the entire array to be re-scanned; what I don't  
remember is when/if the array transitions back to a state where it  
isn't being scanned by minor GC anymore.



using array of hashtables may improve situation a lot


Yes, this would be worth trying.  Understanding the current GC  
strategy would make it easier to make the right tradeoffs here; we  
expect n insertions will touch O(n) subtables, so repeated insertion  
will make life worse if we're not careful.


-Jan-Willem Maessen


plus check GC times for every version: +RTS -Soutfile


--
Best regards,
Bulatmailto:[EMAIL PROTECTED]

___
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] portable arrow instances

2008-11-18 Thread Wolfgang Jeltsch
Hello,

how do I make a library work with both GHC 6.8 and GHC 6.10?  According to 
http://www.haskell.org/haskellwiki/Upgrading_packages#Arrow_instances, I 
should change all my Arrow instances but then they don’t work with GHC 6.8 
anymore, do they?  Or is the solution to force GHC 6.8 users to use 
base-4.0.0.0?

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


Re: [Haskell-cafe] portable arrow instances

2008-11-18 Thread Ross Paterson
On Tue, Nov 18, 2008 at 03:01:00PM +0100, Wolfgang Jeltsch wrote:
 how do I make a library work with both GHC 6.8 and GHC 6.10?  According to 
 http://www.haskell.org/haskellwiki/Upgrading_packages#Arrow_instances, I 
 should change all my Arrow instances but then they don't work with GHC 6.8 
 anymore, do they?  Or is the solution to force GHC 6.8 users to use 
 base-4.0.0.0?

GHC 6.8 users can't use base-4.  I think it's either two versions or cpp.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Deploying a Binary Haskell Package

2008-11-18 Thread John Van Enk
This question isn't directly related to Haskell, but I figure some one might
know here.

I want to deploy an application. I could either:
1) Tell people how to download GHC, have them check out the repository, have
them install all the needed hackage packages, ...
or
2) Give them a setup.msi/exe

I'm curious if any one has done this with a Haskell package. It seems that
it's something that might make sense being integrated into Cabal (runhaskell
Setup msi).

Either way, has some one deployed a Haskell binary as a MSI package?

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


Re: [Haskell-cafe] implementing python-style dictionary in Haskell

2008-11-18 Thread Don Stewart
Which version of GHC and which version of the Data.ByteString library?
There was an inlining bug related to Data.Map /Data.IntMap performance
fixed between the 6.8.x release and the current bytestring release.

In testing, Data.Map with strict bytestring keys matched the python (C
implemented) dictionary, after I fixed the inlining for word lookups.

You'll need to be using bytestring 0.9.1.x though.

-- Don

haskellmail:
Dear all,
 
I am trying to implement the python-style dictionary in Haskell.
 
Python dictionary is a data structure that maps one key to one value.
For instance, a python dictionary
d = {'a':1, 'b':2 }
maps key 'a' to 1, 'b' to 2.
Python dictionary allows for update. e.g. the statement
d['a'] = 3
changes the value pointed by 'a' from 1 to 3.
 
Internally, python dictionary is implemented using hash table.
 
My first attempt is to use Data.HashTable. However it was immediately
abandoned, as I realize the memory usage is unreasonably huge.
 
== SECOND ATTEMPT ==
My second attempt is to use Data.Map
 
{-# OPTIONS_GHC -fglasgow-exts #-}
module Main where
 
import qualified Data.HashTable as HT
import qualified Data.IntMap as IM
import qualified Data.Map as DM
import qualified Data.ByteString.Char8 as S
import Data.Char
 
-- the Dict type class
class Dict d k v | d - k v where
empty :: d
insert :: k - v - d - d
lookup :: k - d - Maybe v
update :: k - v - d - d
 
-- Let's use string as key
type Key = String
 
-- insert key-value pairs into a dictionary
fromList :: Dict d k a = [(k,a)] - d
fromList l =
foldl (\d (key,val) - insert key val d) empty l
 
instance Dict (DM.Map S.ByteString a) Key a where
empty = DM.empty
insert key val dm =
let packed_key = S.pack key
in DM.insert packed_key val dm
lookup key dm =
let packed_key = S.pack key
in DM.lookup packed_key dm
update key val dm =
let packed_key = S.pack key
in DM.update (\x - Just val) packed_key dm
 
Which kinda works, however since Map is implemented using a balanced tree,
therefore,
when as the dictionary grows, it takes a long time to insert new key-value
pair.
 
== THIRD ATTEMPT ==
My third attempt is to use Data.IntMap
 
-- an implementation of Dict using IntMap
instance Dict (IM.IntMap a) Key a where
empty = IM.empty
insert key val im =
let int_key = fromIntegral (HT.hashString key)
in IM.insert int_key val im
lookup key im =
let int_key = fromIntegral (HT.hashString key)
in IM.lookup int_key im
update key val im =
let int_key = fromIntegral (HT.hashString key)
in IM.update (\x - Just val) int_key im
 
This implementation is faster than the Map approach, however this
implementation
can't handle collision well, two keys which are hashed into the same
integer will overwrite each other.
 
== FOURTH ATTEMPT ==
 
My fourth implementation is to use Trie. The idea is to split a string (a
key) into
a list of 4-character chunks. Each chunk can be mapped into a 32-bit
integer without collision.
We then insert the value with this list of chunks into the Trie.
 
-- an implementation of Dict using Trie
instance Dict (Trie a) Key a where
empty = emptyTrie
insert key val trie =
let key_chain = chain key
in insertTrie key_chain val trie
lookup key trie =
let key_chain = chain key
in lookupTrie key_chain trie
update key val trie =
let key_chain = chain key
in updateTrie key_chain val trie
 
-- an auxillary function that splits string into small pieces,
-- 4 characters per piece, 4 chars = 32 bit
chain :: Key - [Key]
chain k | length k  4 = let (k',ks) = splitAt 4 k
 in (k':chain ks)
| otherwise= [k]
 
-- a collision-free hash function which turns four chars into Int32
safehash :: [Char] - Int
safehash cs | length cs  4 = error safehash failed.
| otherwise =
sum [ (ord c)*(256^i)   | (c,i) - zip cs [0..3] ]
 
-- a trie datatype
data Trie a = Trie [a] (IM.IntMap (Trie a))
 
-- the empty trie
emptyTrie = Trie [] (IM.empty)
 
-- insert value into the trie
insertTrie :: [String] - a - Trie a - Trie a
insertTrie [] i (Trie is maps) = Trie (i:is) maps
insertTrie (word:words) i (Trie is maps) =
let key = safehash word
in case IM.lookup key maps of
 { Just trie - let trie' = insertTrie words i trie
maps' = IM.update (\x - Just trie') key maps
in Trie is maps'
 ; Nothing - let trie = emptyTrie
  trie' = insertTrie words i trie
  maps' = IM.insert key trie' maps

Re: [Haskell-cafe] implementing python-style dictionary in Haskell

2008-11-18 Thread kenny lu
Dear Don,
I am using GHC 6.8.1

Regards,
Kenny

On Tue, Nov 18, 2008 at 11:33 PM, Don Stewart [EMAIL PROTECTED] wrote:

 Which version of GHC and which version of the Data.ByteString library?
 There was an inlining bug related to Data.Map /Data.IntMap performance
 fixed between the 6.8.x release and the current bytestring release.

 In testing, Data.Map with strict bytestring keys matched the python (C
 implemented) dictionary, after I fixed the inlining for word lookups.

 You'll need to be using bytestring 0.9.1.x though.

 -- Don

 haskellmail:
 Dear all,
 
 I am trying to implement the python-style dictionary in Haskell.
 
 Python dictionary is a data structure that maps one key to one value.
 For instance, a python dictionary
 d = {'a':1, 'b':2 }
 maps key 'a' to 1, 'b' to 2.
 Python dictionary allows for update. e.g. the statement
 d['a'] = 3
 changes the value pointed by 'a' from 1 to 3.
 
 Internally, python dictionary is implemented using hash table.
 
 My first attempt is to use Data.HashTable. However it was immediately
 abandoned, as I realize the memory usage is unreasonably huge.
 
 == SECOND ATTEMPT ==
 My second attempt is to use Data.Map
 
 {-# OPTIONS_GHC -fglasgow-exts #-}
 module Main where
 
 import qualified Data.HashTable as HT
 import qualified Data.IntMap as IM
 import qualified Data.Map as DM
 import qualified Data.ByteString.Char8 as S
 import Data.Char
 
 -- the Dict type class
 class Dict d k v | d - k v where
 empty :: d
 insert :: k - v - d - d
 lookup :: k - d - Maybe v
 update :: k - v - d - d
 
 -- Let's use string as key
 type Key = String
 
 -- insert key-value pairs into a dictionary
 fromList :: Dict d k a = [(k,a)] - d
 fromList l =
 foldl (\d (key,val) - insert key val d) empty l
 
 instance Dict (DM.Map S.ByteString a) Key a where
 empty = DM.empty
 insert key val dm =
 let packed_key = S.pack key
 in DM.insert packed_key val dm
 lookup key dm =
 let packed_key = S.pack key
 in DM.lookup packed_key dm
 update key val dm =
 let packed_key = S.pack key
 in DM.update (\x - Just val) packed_key dm
 
 Which kinda works, however since Map is implemented using a balanced
 tree,
 therefore,
 when as the dictionary grows, it takes a long time to insert new
 key-value
 pair.
 
 == THIRD ATTEMPT ==
 My third attempt is to use Data.IntMap
 
 -- an implementation of Dict using IntMap
 instance Dict (IM.IntMap a) Key a where
 empty = IM.empty
 insert key val im =
 let int_key = fromIntegral (HT.hashString key)
 in IM.insert int_key val im
 lookup key im =
 let int_key = fromIntegral (HT.hashString key)
 in IM.lookup int_key im
 update key val im =
 let int_key = fromIntegral (HT.hashString key)
 in IM.update (\x - Just val) int_key im
 
 This implementation is faster than the Map approach, however this
 implementation
 can't handle collision well, two keys which are hashed into the same
 integer will overwrite each other.
 
 == FOURTH ATTEMPT ==
 
 My fourth implementation is to use Trie. The idea is to split a string
 (a
 key) into
 a list of 4-character chunks. Each chunk can be mapped into a 32-bit
 integer without collision.
 We then insert the value with this list of chunks into the Trie.
 
 -- an implementation of Dict using Trie
 instance Dict (Trie a) Key a where
 empty = emptyTrie
 insert key val trie =
 let key_chain = chain key
 in insertTrie key_chain val trie
 lookup key trie =
 let key_chain = chain key
 in lookupTrie key_chain trie
 update key val trie =
 let key_chain = chain key
 in updateTrie key_chain val trie
 
 -- an auxillary function that splits string into small pieces,
 -- 4 characters per piece, 4 chars = 32 bit
 chain :: Key - [Key]
 chain k | length k  4 = let (k',ks) = splitAt 4 k
  in (k':chain ks)
 | otherwise= [k]
 
 -- a collision-free hash function which turns four chars into Int32
 safehash :: [Char] - Int
 safehash cs | length cs  4 = error safehash failed.
 | otherwise =
 sum [ (ord c)*(256^i)   | (c,i) - zip cs [0..3] ]
 
 -- a trie datatype
 data Trie a = Trie [a] (IM.IntMap (Trie a))
 
 -- the empty trie
 emptyTrie = Trie [] (IM.empty)
 
 -- insert value into the trie
 insertTrie :: [String] - a - Trie a - Trie a
 insertTrie [] i (Trie is maps) = Trie (i:is) maps
 insertTrie (word:words) i (Trie is maps) =
 let key = safehash word
 in case IM.lookup key maps of
  { Just trie - let trie' = insertTrie words i trie

Re: [Haskell-cafe] Deploying a Binary Haskell Package

2008-11-18 Thread Don Stewart
vanenkj:
This question isn't directly related to Haskell, but I figure some one
might know here.
 
I want to deploy an application. I could either:
1) Tell people how to download GHC, have them check out the repository,
have them install all the needed hackage packages, ...
or
2) Give them a setup.msi/exe
 
I'm curious if any one has done this with a Haskell package. It seems that
it's something that might make sense being integrated into Cabal
(runhaskell Setup msi).
 
Either way, has some one deployed a Haskell binary as a MSI package?
 

Yes, Galois has , using the windows installer builder (for binary
Haskell blobs).

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


Re: [Haskell-cafe] Proof of a multi-threaded application

2008-11-18 Thread Hans van Thiel

On Mon, 2008-11-17 at 05:52 -0700, Luke Palmer wrote:
 On Mon, Nov 17, 2008 at 4:04 AM, Silviu ANDRICA [EMAIL PROTECTED] wrote:
  Hello,
I am very new to Haskell, this is my first day, and I wanted to know if it
  is possible to prove correctness of a multi-threaded application written in
  Haskell.
  Basically, I want to check that a multi-threaded implementation of an
  algorithm that detects cycles in a dynamically changing graph, actually
  detects the cycles. Also, the algorithm prevents previously detected cycles
  from happening by not allowing certain edges to be added. And I want to
  check that this property also holds.
 
 This is going to be difficult -- no matter what language you try to
 prove it in.  In Haskell you have a decent shot, I suppose, since you
 could at least prove the pure bits correct without much fuss.
 
 The way I might try to approach this is to model your algorithm and
 the dynamically changing graph together as a nondeterministic state
 machine: a function of type State - [State]  (returning all the
 possible next steps of the system).  Then I would look for some
 invariant that is preserved at each step, and prove its preservation.
 
 That is how you could prove your *algorithm* correct.  But I suspect
 there will be many difficulties proving that your implementation
 corresponds to your algorithm.  This is mostly because in the IO
 monad, anything goes; i.e. the semantics are complex and mostly
 unknown.  You might make some progress by isolating a small portion of
 the IO monad and assuming that it obeys some particular reasonable
 nondeterministic semantics.  But that will be a large, intuitive
 assumption which will decrease the degree of certainty of your proof.
 
 If you implement your algorithm in terms of STM (one of Haskell's
 flaunting points :-) rather than more traditional primitives (eg.
 locks) you will have a better shot, since you can more easily show
 that an invariant is kept before and after a transaction, without
 having to fuss with the concurrency details inside where the invariant
 is briefly broken.
 
 Concurrency is quite hard to reason about formally (no matter what
 language it is in).  Good luck!
 
 Luke
 
Yes, but if it's worth the effort you could do a formal verification,
not of the code, but of a model with the Spin model checker.

http://spinroot.com/spin/whatispin.html

First you write a model in Promela (Process meta language) which looks a
lot like C, but abstracts from (most of) the computations and instead
concentrates on communication and coordination of non-deterministic
processes. With Spin and the graphical interface XSpin (or the
alternative JSpin) you can both simulate and verify your model.
It finds deadlocks, you can write asserts, test liveness and you can
even check claims in LTL (linear temporal logic) about execution paths.
It's all open source and free. 'The Spin Model Checker', by Gerard
Holzmann, is the reference, but there are several other books about Spin
and its principles. 

Best Regards,

Hans van Thiel


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


Re: [Haskell-cafe] implementing python-style dictionary in Haskell

2008-11-18 Thread Don Stewart
Great. Assuming you're following the advice to use bytestrings, please
install the newest bytestring library version, here,

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

Data.Map or Data.IntMap with bytestrings should be quite efficient.
(or use a trie if more precision is needed)

-- Don

haskellmail:
Dear Don,
I am using GHC 6.8.1
 
Regards,
Kenny
 
On Tue, Nov 18, 2008 at 11:33 PM, Don Stewart [EMAIL PROTECTED] wrote:
 
  Which version of GHC and which version of the Data.ByteString library?
  There was an inlining bug related to Data.Map /Data.IntMap performance
  fixed between the 6.8.x release and the current bytestring release.
 
  In testing, Data.Map with strict bytestring keys matched the python (C
  implemented) dictionary, after I fixed the inlining for word lookups.
 
  You'll need to be using bytestring 0.9.1.x though.
 
  -- Don
 
  haskellmail:
  Dear all,
  
  I am trying to implement the python-style dictionary in Haskell.
  
  Python dictionary is a data structure that maps one key to one
  value.
  For instance, a python dictionary
  d = {'a':1, 'b':2 }
  maps key 'a' to 1, 'b' to 2.
  Python dictionary allows for update. e.g. the statement
  d['a'] = 3
  changes the value pointed by 'a' from 1 to 3.
  
  Internally, python dictionary is implemented using hash table.
  
  My first attempt is to use Data.HashTable. However it was
  immediately
  abandoned, as I realize the memory usage is unreasonably huge.
  
  == SECOND ATTEMPT ==
  My second attempt is to use Data.Map
  
  {-# OPTIONS_GHC -fglasgow-exts #-}
  module Main where
  
  import qualified Data.HashTable as HT
  import qualified Data.IntMap as IM
  import qualified Data.Map as DM
  import qualified Data.ByteString.Char8 as S
  import Data.Char
  
  -- the Dict type class
  class Dict d k v | d - k v where
  empty :: d
  insert :: k - v - d - d
  lookup :: k - d - Maybe v
  update :: k - v - d - d
  
  -- Let's use string as key
  type Key = String
  
  -- insert key-value pairs into a dictionary
  fromList :: Dict d k a = [(k,a)] - d
  fromList l =
  foldl (\d (key,val) - insert key val d) empty l
  
  instance Dict (DM.Map S.ByteString a) Key a where
  empty = DM.empty
  insert key val dm =
  let packed_key = S.pack key
  in DM.insert packed_key val dm
  lookup key dm =
  let packed_key = S.pack key
  in DM.lookup packed_key dm
  update key val dm =
  let packed_key = S.pack key
  in DM.update (\x - Just val) packed_key dm
  
  Which kinda works, however since Map is implemented using a
  balanced tree,
  therefore,
  when as the dictionary grows, it takes a long time to insert new
  key-value
  pair.
  
  == THIRD ATTEMPT ==
  My third attempt is to use Data.IntMap
  
  -- an implementation of Dict using IntMap
  instance Dict (IM.IntMap a) Key a where
  empty = IM.empty
  insert key val im =
  let int_key = fromIntegral (HT.hashString key)
  in IM.insert int_key val im
  lookup key im =
  let int_key = fromIntegral (HT.hashString key)
  in IM.lookup int_key im
  update key val im =
  let int_key = fromIntegral (HT.hashString key)
  in IM.update (\x - Just val) int_key im
  
  This implementation is faster than the Map approach, however this
  implementation
  can't handle collision well, two keys which are hashed into the
  same
  integer will overwrite each other.
  
  == FOURTH ATTEMPT ==
  
  My fourth implementation is to use Trie. The idea is to split a
  string (a
  key) into
  a list of 4-character chunks. Each chunk can be mapped into a
  32-bit
  integer without collision.
  We then insert the value with this list of chunks into the Trie.
  
  -- an implementation of Dict using Trie
  instance Dict (Trie a) Key a where
  empty = emptyTrie
  insert key val trie =
  let key_chain = chain key
  in insertTrie key_chain val trie
  lookup key trie =
  let key_chain = chain key
  in lookupTrie key_chain trie
  update key val trie =
  let key_chain = chain key
  in updateTrie key_chain val trie
  
  -- an auxillary 

[Haskell-cafe] Re: [off-topic] OOPer?

2008-11-18 Thread Larry Evans

On 11/17/08 18:24, Daniel Yokomizo wrote:
 On Mon, Nov 17, 2008 at 9:49 PM, Maurí­cio [EMAIL PROTECTED]
 mailto:[EMAIL PROTECTED] wrote:

(...)  I don't recall where I found the following example, but
 copied

   it locally as compelling evidence  that the functional solution
 can be
   much clearer and  shorter than the same solution  modeled with
 objects
   and inheritance.

[snip]


   -- Arithmetic expression forms data Expr = Num Int | Add Expr Expr
  
   -- Evaluate expressions
   eval :: Expr - Int
   (...)


   public abstract class Expr {
  public abstract int eval ();
  public abstract void modn(int v);

[snip]

 when the first standard was set, and  I can tell you for sure 
that, even
 at that  time, no one who  knows at least  the basics of C++ 
would ever

 write that problem like this.

Mauri, I'm not sure what you mean. Do you mean:

  1) No C++er would ever structure the problem like:

   -- Arithmetic expression forms
   data Expr = Num Int | Add Expr Expr

   -- Evaluate expressions
   eval :: Expr - Int
   eval (Num i) = i
   eval (Add l r ) = eval l + eval r

 If so, then I'm unsure what you could mean since
 the closest counterpart to:

   date Expr = Num Int | Add Expr Expr

 in c++ is an abstract Expr class with derived
 classes, Int and Add, just as shown in Greg's Java counterpart to
 the haskell Expr.

  2) No C++er would every solve the problem with a heirarchy of Expr
 classes with virtual functions.

 If so, then I'm really confused because that's exactly the way I
 would do it *except* if I wanted to avoid the overhead of
 virtual function dispatch.  In this case, I would use template
 metaprogramming (WARNING: not for c++ template metaprogramming
 novices):


http://www.boost.org/doc/libs/1_37_0/doc/html/proto/users_guide.html#boost_proto.users_guide.intermediate_form.expression_introspection.defining_dsel_grammars

 In the proto metaprogramming, AFAICT, the 1st element of the
 proto::expr template, the tag, corresponds to Expr constructor's,
 Num and Add, of Greg's haskell example code.  The | separating
 the Expr constructor variants corresponds to the proto::or_
 template.

 So, if template metaprogramming were used, then there are some
 very good c++ programmer which would structure their c++ code
 like the haskell code (although, as seen by the

#boost_proto.users_guide.intermediate_form.expression_introspection.defining_dsel_grammars
 reference, it's a bit obscured by all the scaffolding needed
 to make it work).

 Another reference which *may* reflect the haskell structure is:

   http://research.microsoft.com/~akenn/generics/gadtoop.pdf

 I must admit I don't really understand it, but it seems to have
 some similarities to haskell's structure.  The author even uses
 haskell code to compare with his corresponding extension to
 c#. In particular, page 9 contains an example use of his proposed
 switch statement extension which looks very similar to the way
 haskell would pattern match on an expression to dispatch to the
 appropriate case.


[snip]


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


Re: [Haskell-cafe] implementing python-style dictionary in Haskell

2008-11-18 Thread David Menendez
2008/11/18 kenny lu [EMAIL PROTECTED]:
 Here is a comparison of memory usage

 Map : 345 MB
 IntMap : 146 MB
 Trie : 282 MB
 Python : 94 MB

 Here is a comparison of execution time (on an intel dual core 2.0G)

 Map: 26 sec
 IntMap: 9 sec
 Trie: 12 sec
 Python: 2.24 sec


 The above number shows that my implementations of python style dictionary
 are space/time in-efficient as compared to python.

 Can some one point out what's wrong with my implementations?

This isn't really a fair comparison. Map, IntMap, and Trie are
persistent data structures, and Python dictionaries are ephemeral.
(That is, when you add a key to a Map, you actually create a new one
that shares structure with the old one, and both can be used in
subsequent code. In Python, you would have to copy the dictionary.)

-- 
Dave Menendez [EMAIL PROTECTED]
http://www.eyrie.org/~zednenem/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Type question in instance of a class

2008-11-18 Thread Peter Hercek

David Menendez wrote:

On Sun, Nov 16, 2008 at 7:09 PM, Luke Palmer [EMAIL PROTECTED] wrote:

On Sun, Nov 16, 2008 at 5:06 PM, Peter Hercek [EMAIL PROTECTED] wrote:

... and the only value the function can return is bottom.
Is there any type system which would have more than
 one value which inhabits all types?

Well something like lazy C# might; i.e. every value has a _|_
(nontermination) and null (termination but undefined).


For that matter, Control.Exception allows you to distinguish
exceptional values from each other.



OK, thanks for responses. I'm not sure I understand it well
 so I try to summarize:

Control.Exception is an extension, also it probably cannot
 catch error :: String - a since the report says so:
 http://www.haskell.org/onlinereport/exps.html#sect3.1
 So Haskell'98 has only one value of all types (the bottom).

But Haskell with Control.Exception extension has more values
 of all types since they can be thrown and later caught and
 investigated at that place.

Maybe the last sentence of section 2.1 (_|_ Bottom) of
 Haskell/Denotational semantics should be clarified better.

http://en.wikibooks.org/wiki/Haskell/Denotational_semantics#.E2.8A.A5_Bottom

So when trying to use Curry-Howard isomorphism for something
 in Haskell, one sould be pretty carefull what features of are
 being used.

Peter.

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


Re: [Haskell-cafe] Re: Type question in instance of a class

2008-11-18 Thread J. Garrett Morris
On Tue, Nov 18, 2008 at 1:38 AM, Reiner Pope [EMAIL PROTECTED] wrote:
 ATs are Associated Types, aka Type Families. They can be found in
 the GHC 6.10 manual here:
 http://haskell.org/ghc/docs/6.10.1/html/users_guide/type-families.html

 As a starting point, you might want to try something like:

 class Complex c where
   type RealType c
   realPart :: c - RealType c
   imagPart :: c - RealType c

I imagine that the generalized newtype deriving might be trickier to
get working for this formulation.

 /g

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


Re: [Haskell-cafe] Re: Type question in instance of a class

2008-11-18 Thread Jonathan Cast
On Tue, 2008-11-18 at 19:05 +0100, Peter Hercek wrote:
 David Menendez wrote:
  On Sun, Nov 16, 2008 at 7:09 PM, Luke Palmer [EMAIL PROTECTED] wrote:
  On Sun, Nov 16, 2008 at 5:06 PM, Peter Hercek [EMAIL PROTECTED] wrote:
  ... and the only value the function can return is bottom.
  Is there any type system which would have more than
   one value which inhabits all types?
  Well something like lazy C# might; i.e. every value has a _|_
  (nontermination) and null (termination but undefined).
  
  For that matter, Control.Exception allows you to distinguish
  exceptional values from each other.
  
 
 OK, thanks for responses. I'm not sure I understand it well
   so I try to summarize:
 
 Control.Exception is an extension, also it probably cannot
   catch error :: String - a since the report says so:
   http://www.haskell.org/onlinereport/exps.html#sect3.1

I think `cannot be caught by the user' is intended to be descriptive
here; or, alternately, this is one place where GHC deviates from the
spec.  catch (error foo) h will certainly sometimes behave as h
(UserError foo).  Non-deterministically.

jcc


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


Re: [Haskell-cafe] implementing python-style dictionary in Haskell

2008-11-18 Thread Luke Palmer
On Tue, Nov 18, 2008 at 10:37 AM, David Menendez [EMAIL PROTECTED] wrote:
 This isn't really a fair comparison. Map, IntMap, and Trie are
 persistent data structures, and Python dictionaries are ephemeral.
 (That is, when you add a key to a Map, you actually create a new one
 that shares structure with the old one, and both can be used in
 subsequent code. In Python, you would have to copy the dictionary.)

But when these persistent data structures are used in a
single-threaded way, why should we not hope for the performance to be
comparable?

It may not be easy, but just saying they are persistent is not
really an excuse.

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


Re: [Haskell-cafe] implementing python-style dictionary in Haskell

2008-11-18 Thread Don Stewart
dave:
 2008/11/18 kenny lu [EMAIL PROTECTED]:
  Here is a comparison of memory usage
 
  Map : 345 MB
  IntMap : 146 MB
  Trie : 282 MB
  Python : 94 MB
 
  Here is a comparison of execution time (on an intel dual core 2.0G)
 
  Map: 26 sec
  IntMap: 9 sec
  Trie: 12 sec
  Python: 2.24 sec
 
 
  The above number shows that my implementations of python style dictionary
  are space/time in-efficient as compared to python.
 
  Can some one point out what's wrong with my implementations?
 
 This isn't really a fair comparison. Map, IntMap, and Trie are
 persistent data structures, and Python dictionaries are ephemeral.
 (That is, when you add a key to a Map, you actually create a new one
 that shares structure with the old one, and both can be used in
 subsequent code. In Python, you would have to copy the dictionary.)
 

Strings, not ByteStrings. that's the difference.

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


Re: [Haskell-cafe] Deploying a Binary Haskell Package

2008-11-18 Thread Duncan Coutts
On Tue, 2008-11-18 at 10:20 -0500, John Van Enk wrote:
 This question isn't directly related to Haskell, but I figure some one
 might know here.
 
 I want to deploy an application. I could either:
 1) Tell people how to download GHC, have them check out the
 repository, have them install all the needed hackage packages, ...
 or
 2) Give them a setup.msi/exe
 
 I'm curious if any one has done this with a Haskell package. It seems
 that it's something that might make sense being integrated into Cabal
 (runhaskell Setup msi).

I think the right approach here is as a separate tool, like we have
tools for generating native packages for rpm, deb and other
distributions.

Of course it only makes sense for applications, not libraries.

 Either way, has some one deployed a Haskell binary as a MSI package?

Not MSI[1] but .exe yes. Here's an example:

http://haskell.org/~duncan/gtk2hs/LSystemSetup.exe

It is an installer (made with the free InnoSetup builder) for a simple
graphical application that uses HOpenGL, Gtk2Hs and therefore Gtk+. It
installs the application .exe the Gtk+ dll files and a data file for the
GUI.

Duncan

[1] On a job many years ago I had to make an MSI installer and now hate
them with a passion :-)

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


Re: [Haskell-cafe] GHC 6.10.1 and cabal[-install]

2008-11-18 Thread Duncan Coutts
On Tue, 2008-11-18 at 14:23 +0100, Wolfgang Jeltsch wrote:
 Am Dienstag, 18. November 2008 11:01 schrieb Wolfgang Jeltsch:
  Hello,
 
  I installed GHC 6.10.1 today and expected it to contain the cabal command
  line utility.  Unfortunately, this was not the case.  Where can I download
  it?
 
 Meanwhile, I found out that the package cabal-install includes the cabal 
 command.  On the other hand I thought that there was a now deprecated command 
 line tool named cabal-install.  I find this a bit confusing.

The Cabal package provides the library. The cabal-install package
provides the 'cabal' command line tool.

The deprecated package you're thinking of is cabal-get or cabal-setup.

  How do I install and configure it so that it is integrated best with
  GHC 6.10.1?  For example, should cabal use some directory in the GHC tree 
  to place compiled packages in?

The defaults for user or global should be fine. There is no need to put
additional packages into the ghc install tree, indeed I would recommend
against doing that.

 Cabal wants to place package info in $HOME/.cabal.  However, I want to 
 install 
 packages globally with sudo.  So I want to have a global package cache.  Is 
 there a common directory to be used for that or is cabal[-install] only for 
 per-user installations?

It can do per-user or global. Per-user is the default.

If you want to do the build as user and just the install as root then
you can use the --global --root-cmd=sudo options. If you want to use
this every time then you can set that in the ~/.cabal/config file.

 Well, there is the --global option but it is apparently only for registering 
 packages globally.  Does it change the destination directory for the 
 installed packages too? 

Yes.

 If yes, to what directory?

/usr/local

 Is the default --global or --user?

--user

 Sorry, but I cannot find the answers to this in the docs and I 
 don’t want to mess up my file system.

The cabal user guide lists the default install directories for global
and user installs.

The default ~/.cabal/config file is slightly self-documenting in that it
lists the available options and their defaults:

[..snip..]
-- user-install: True
[..snip..]

install-dirs user
  -- prefix: /home/duncan/.cabal
  [..snip..]

install-dirs global
  -- prefix: /usr/local
  [..snip..]

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


Re: [Haskell-cafe] Cabal and more than one version

2008-11-18 Thread Duncan Coutts
On Tue, 2008-11-18 at 01:48 -0800, Jason Dusek wrote:
 I'd like to be able to do something like:
 
 if (template-haskell  2.3)
   cpp-options: -D TH_THE_YOUNGER
 else
   cpp-options: -D TH_THE_ELDER
 
   I guess this kind of thing is not possible at present?

It is possible, in two different ways.

The easiest way is that if you're using Cabal-1.6 then it provides cpp
macros to test the version number of packages you're using. 

#if MIN_VERSION_template_haskell(2,3,0)
...
#elseif
...
#endif

The alternative that works back to Cabal-1.2 is to use:

flag newer-th

...
  if flag(newer-th)
build-depends: template-haskell = 2.3
cpp-options: -D TH_THE_ELDER
  else
build-depends: template-haskell  2.3
cpp-options: -D TH_THE_YOUNGER

See also ticket http://hackage.haskell.org/trac/hackage/ticket/209 for a
proposal to add syntactic sugar similar to the syntax you first
suggested.

Duncan

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


clojure's data structures (was: Re: [Haskell-cafe] implementing python-style dictionary in Haskell)

2008-11-18 Thread Evan Laforge
This actually brings up something I was wondering about lately.  I
recently stumbled across a language called clojure, which is a
lisp-like that runs on the JVM.  The interesting thing is that
mutations go through a transactional mutable reference system, and the
other datastructures are all immutable.  The author implements an
immutable hash map with a trie on each 5 bits of the hash, so each
node potentially has 32 children.  This means that lookups are
effectively O(1) and alterations have to copy a maximum of 7 chunks of
32 pointers.  Extendable vectors are implemented similarly.

The hash tables sound basically like an IntMap on the hash code,
except as far as I know, IntMap's patricia tree splits up the bit
space adaptively instead of being hardcoded on 5 bit segments.  I'm
not sure what the performance difference would be.  I haven't run any
tests, but the clojure author claims his vector and hash map are quite
fast.  I suppose the extendable vector corresponds to the current crop
of ByteString-like variants, so we sort of already have that, though
in a kind of chaotic and inchoate way.

I'm also curious about how far the generalized trie SoC project got...
 it should be more accessible now that we have a mainline release with
ATs, right?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Fwd: [Haskell-cafe] implementing python-style dictionary in Haskell

2008-11-18 Thread Alberto G. Corona
sorry, Dons,

-- Forwarded message --
From: Alberto G. Corona [EMAIL PROTECTED]
Date: 2008/11/18
Subject: Re: [Haskell-cafe] implementing python-style dictionary in Haskell
To: Don Stewart [EMAIL PROTECTED]


By the way byteStrings are wonderful, but, it  isn´t true that byteStrings
are not so fast for managing short strings, for example keys ?

2008/11/18 Don Stewart [EMAIL PROTECTED]

dave:
  2008/11/18 kenny lu [EMAIL PROTECTED]:
   Here is a comparison of memory usage
  
   Map : 345 MB
   IntMap : 146 MB
   Trie : 282 MB
   Python : 94 MB
  
   Here is a comparison of execution time (on an intel dual core 2.0G)
  
   Map: 26 sec
   IntMap: 9 sec
   Trie: 12 sec
   Python: 2.24 sec
  
  
   The above number shows that my implementations of python style
 dictionary
   are space/time in-efficient as compared to python.
  
   Can some one point out what's wrong with my implementations?
 
  This isn't really a fair comparison. Map, IntMap, and Trie are
  persistent data structures, and Python dictionaries are ephemeral.
  (That is, when you add a key to a Map, you actually create a new one
  that shares structure with the old one, and both can be used in
  subsequent code. In Python, you would have to copy the dictionary.)
 

 Strings, not ByteStrings. that's the difference.

 -- 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] GHC 6.10.1 and cabal[-install]

2008-11-18 Thread Andrew Coppin

Duncan Coutts wrote:

The Cabal package provides the library. The cabal-install package
provides the 'cabal' command line tool.

The deprecated package you're thinking of is cabal-get or cabal-setup.
  


Will Hackage one day provide a way to discover that one package has been 
superceeded by another?


Currently you can see when a newer version of the exact same package 
exists, but (for example) take a took at how many gazillion database 
packages there are up there. Which ones are active? Which ones are 
obsolete? How can I tell??


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


Re: [Haskell-cafe] implementing python-style dictionary in Haskell

2008-11-18 Thread David Menendez
On Tue, Nov 18, 2008 at 3:52 PM, Don Stewart [EMAIL PROTECTED] wrote:
 dave:
 2008/11/18 kenny lu [EMAIL PROTECTED]:
  The above number shows that my implementations of python style dictionary
  are space/time in-efficient as compared to python.
 
  Can some one point out what's wrong with my implementations?

 This isn't really a fair comparison. Map, IntMap, and Trie are
 persistent data structures, and Python dictionaries are ephemeral.
 (That is, when you add a key to a Map, you actually create a new one
 that shares structure with the old one, and both can be used in
 subsequent code. In Python, you would have to copy the dictionary.)


 Strings, not ByteStrings. that's the difference.

Is that in response to what I wrote, or to the original question?

Speaking of ByteStrings and tries, has anyone implemented a Patricia
Trie for ByteStrings? I started putting one together a while back, but
I got distracted and never finished it.

-- 
Dave Menendez [EMAIL PROTECTED]
http://www.eyrie.org/~zednenem/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] GHC 6.10.1 and cabal[-install]

2008-11-18 Thread Jason Dagit
On Tue, Nov 18, 2008 at 1:51 PM, Andrew Coppin
[EMAIL PROTECTED]wrote:

 Duncan Coutts wrote:

 The Cabal package provides the library. The cabal-install package
 provides the 'cabal' command line tool.

 The deprecated package you're thinking of is cabal-get or cabal-setup.



 Will Hackage one day provide a way to discover that one package has been
 superceeded by another?

 Currently you can see when a newer version of the exact same package
 exists, but (for example) take a took at how many gazillion database
 packages there are up there. Which ones are active? Which ones are obsolete?
 How can I tell??


This has come up before.  As you can see here:
http://thread.gmane.org/gmane.comp.lang.haskell.cafe/46764

I think we just need someone (how about you!?) to start working on it.

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


Re: [Haskell-cafe] GHC 6.10.1 and cabal[-install]

2008-11-18 Thread Andrew Coppin

Jason Dagit wrote:



On Tue, Nov 18, 2008 at 1:51 PM, Andrew Coppin 
[EMAIL PROTECTED] mailto:[EMAIL PROTECTED] wrote:


Duncan Coutts wrote:

The Cabal package provides the library. The cabal-install package
provides the 'cabal' command line tool.

The deprecated package you're thinking of is cabal-get or
cabal-setup.
 



Will Hackage one day provide a way to discover that one package
has been superceeded by another?

Currently you can see when a newer version of the exact same
package exists, but (for example) take a took at how many
gazillion database packages there are up there. Which ones are
active? Which ones are obsolete? How can I tell??


This has come up before.  As you can see here:
http://thread.gmane.org/gmane.comp.lang.haskell.cafe/46764

I think we just need someone (how about you!?) to start working on it.


What do I need to do? Just obtain the Hackage source code and submit a 
Darcs patch or something? Or is it harder than that?


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


Re: [Haskell-cafe] GHC 6.10.1 and cabal[-install]

2008-11-18 Thread Jason Dagit
On Tue, Nov 18, 2008 at 2:00 PM, Andrew Coppin
[EMAIL PROTECTED]wrote:

 Jason Dagit wrote:



 On Tue, Nov 18, 2008 at 1:51 PM, Andrew Coppin 
 [EMAIL PROTECTED] mailto:[EMAIL PROTECTED] wrote:

Duncan Coutts wrote:

The Cabal package provides the library. The cabal-install package
provides the 'cabal' command line tool.

The deprecated package you're thinking of is cabal-get or
cabal-setup.


Will Hackage one day provide a way to discover that one package
has been superceeded by another?

Currently you can see when a newer version of the exact same
package exists, but (for example) take a took at how many
gazillion database packages there are up there. Which ones are
active? Which ones are obsolete? How can I tell??


 This has come up before.  As you can see here:
 http://thread.gmane.org/gmane.comp.lang.haskell.cafe/46764

 I think we just need someone (how about you!?) to start working on it.


 What do I need to do? Just obtain the Hackage source code and submit a
 Darcs patch or something? Or is it harder than that?


A darcs patch should work.  If you look in the thread I linked to you'll see
this message by Thomas M. DuBuisson:
http://thread.gmane.org/gmane.comp.lang.haskell.cafe/46764

Where he gives the location of secret hideout for the hackage happs server
and how to contribute.

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


Re: [Haskell-cafe] GHC 6.10.1 and cabal[-install]

2008-11-18 Thread Jason Dagit
On Tue, Nov 18, 2008 at 2:03 PM, Jason Dagit [EMAIL PROTECTED] wrote:



 On Tue, Nov 18, 2008 at 2:00 PM, Andrew Coppin 
 [EMAIL PROTECTED] wrote:

 Jason Dagit wrote:



 On Tue, Nov 18, 2008 at 1:51 PM, Andrew Coppin 
 [EMAIL PROTECTED] mailto:[EMAIL PROTECTED] wrote:

Duncan Coutts wrote:

The Cabal package provides the library. The cabal-install package
provides the 'cabal' command line tool.

The deprecated package you're thinking of is cabal-get or
cabal-setup.


Will Hackage one day provide a way to discover that one package
has been superceeded by another?

Currently you can see when a newer version of the exact same
package exists, but (for example) take a took at how many
gazillion database packages there are up there. Which ones are
active? Which ones are obsolete? How can I tell??


 This has come up before.  As you can see here:
 http://thread.gmane.org/gmane.comp.lang.haskell.cafe/46764

 I think we just need someone (how about you!?) to start working on it.


 What do I need to do? Just obtain the Hackage source code and submit a
 Darcs patch or something? Or is it harder than that?


 A darcs patch should work.  If you look in the thread I linked to you'll
 see this message by Thomas M. DuBuisson:


By copy and paste, my apologies:
http://article.gmane.org/gmane.comp.lang.haskell.cafe/46773
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] How to make interface IO() to IO a in a command-driven tool

2008-11-18 Thread Kyongho Min

Dear Haskell users,

I am working on a command-driven tool (::IO ()).
If the system invokes itself again, and the system's returned
data type would be 'IO a', say (IO Exp) (Expression).

tool:: a - IO()

The nested tool invocation returns (IO Exp) to the previous tool.
I am using dynamic error exception handling like (throwDyn exp).

If I use 'forkIO', then it works for this situation (e.g. IO Exp) but it 
is not working for 'quit' command (quit the tool:: thread blocked 
indefinitely) - quit the subtool and return to the previous tool.


Any suggestion would be helpful?

tool = {tool1, tool2, tool3, ...}

tool1:: (IO ())
  invoked  tool2:: (IO a)
 may invoked tool3:: (IO a)

tool2 is working basically on IO() and if I got the Exp (proved), then 
return it to the previous tool (say tool1).


Thanks in advance,

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


Re: [Haskell-cafe] Haskell library support

2008-11-18 Thread Galchin, Vasili
Hi Jeff,

   Is http://haskell.org/haskellwiki/Wanted_libraries kept up to date? I
wouldn't want to reinvent a wheel ;^)

Vasili

On Mon, Nov 17, 2008 at 7:04 PM, Jeff Zaroyko [EMAIL PROTECTED] wrote:

 2008/11/15 Galchin, Vasili [EMAIL PROTECTED]:
   Hello,
 
   I am looking for something to work on. Where are there perceived
 holes
  in the Haskell library support?
 
  Regards, Vasili

 Hello Vasili

 Maybe the haskell.org wiki would be a good place for people to record
 their suggestions?  http://haskell.org/haskellwiki/Wanted_libraries
 looks like a suitable place.

 Regards, Jeff

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


[Haskell-cafe] Pattern matching on numbers?

2008-11-18 Thread Ryan Ingram
How does this work?

 fac n = case n of
0 - 1
_ - n * fac (n-1)

ghci :t fac
fac :: (Num t) = t - t

The first line of fac pattern matches on 0.  So how does this work
over any value of the Num typeclass?  I know that the 1 on the rhs
of fac are replaced with (fromInteger 1), but what about numeric
literals in patterns?  Does it turn into a call to (==)?

Should whatever technique is used be extended to other typeclasses too?

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


Re: [Haskell-cafe] Pattern matching on numbers?

2008-11-18 Thread Henning Thielemann


On Tue, 18 Nov 2008, Ryan Ingram wrote:


How does this work?


fac n = case n of
   0 - 1
   _ - n * fac (n-1)


ghci :t fac
fac :: (Num t) = t - t

The first line of fac pattern matches on 0.  So how does this work
over any value of the Num typeclass?  I know that the 1 on the rhs
of fac are replaced with (fromInteger 1), but what about numeric
literals in patterns?  Does it turn into a call to (==)?


As far as I know, yes. It is even possible to trap into an error on 
pattern matching this way if fromInteger generates an 'undefined'.



Should whatever technique is used be extended to other typeclasses too?


 It is unusual to do pattern matching on fractions, you mostly need it for 
recursion on natural numbers. Thus I think the cleanest solution would be 
to treat natural numbers like strict Peano numbers

  data PeanoStrict = Zero | Succ !PeanoStrict
 but with an efficient implementation using GMP integers, maybe using 
'views', if they were part of Haskell language. Then you can implement:


fac :: Integer - Integer
fac Zero = 1
fac n1@(Succ n) = n1 * fac n

 I would then give up pattern matching on any numeric type.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] implementing python-style dictionary in Haskell

2008-11-18 Thread David Menendez
On Tue, Nov 18, 2008 at 3:46 PM, Luke Palmer [EMAIL PROTECTED] wrote:
 On Tue, Nov 18, 2008 at 10:37 AM, David Menendez [EMAIL PROTECTED] wrote:
 This isn't really a fair comparison. Map, IntMap, and Trie are
 persistent data structures, and Python dictionaries are ephemeral.
 (That is, when you add a key to a Map, you actually create a new one
 that shares structure with the old one, and both can be used in
 subsequent code. In Python, you would have to copy the dictionary.)

 But when these persistent data structures are used in a
 single-threaded way, why should we not hope for the performance to be
 comparable?

 It may not be easy, but just saying they are persistent is not
 really an excuse.

I guess that depends on what you mean by comparable. Chris Okasaki
demonstrated that, for some data structures, a persistent
implementation could be made with the same asymptotic bounds as an
ephemeral implementation, but I would still expect the persistent
version to be worse by a constant factor when used ephemerally.
Ephemeral data structures are naturally optimized for ephemeral use
cases. (I would also expect the reverse to be true.)

-- 
Dave Menendez [EMAIL PROTECTED]
http://www.eyrie.org/~zednenem/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to make interface IO() to IO a in a command-driven tool

2008-11-18 Thread Brandon S. Allbery KF8NH

On 2008 Nov 18, at 17:55, Kyongho Min wrote:

I am working on a command-driven tool (::IO ()).
If the system invokes itself again, and the system's returned
data type would be 'IO a', say (IO Exp) (Expression).

tool:: a - IO()

The nested tool invocation returns (IO Exp) to the previous tool.
I am using dynamic error exception handling like (throwDyn exp).

If I use 'forkIO', then it works for this situation (e.g. IO Exp)  
but it is not working for 'quit' command (quit the tool:: thread  
blocked indefinitely) - quit the subtool and return to the previous  
tool.



Consider using a special type of dynamic exception to mean quit.

--
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] Pattern matching on numbers?

2008-11-18 Thread David Menendez
On Tue, Nov 18, 2008 at 6:56 PM, Henning Thielemann
[EMAIL PROTECTED] wrote:

 On Tue, 18 Nov 2008, Ryan Ingram wrote:

 How does this work?

 fac n = case n of
   0 - 1
   _ - n * fac (n-1)

 ghci :t fac
 fac :: (Num t) = t - t

 The first line of fac pattern matches on 0.  So how does this work
 over any value of the Num typeclass?  I know that the 1 on the rhs
 of fac are replaced with (fromInteger 1), but what about numeric
 literals in patterns?  Does it turn into a call to (==)?

 As far as I know, yes. It is even possible to trap into an error on pattern
 matching this way if fromInteger generates an 'undefined'.

As I understand it, the use of (==) in numeric pattern matching is why
Num requires Eq.

-- 
Dave Menendez [EMAIL PROTECTED]
http://www.eyrie.org/~zednenem/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] FFI and returning structs

2008-11-18 Thread Maurí­cio

Hi,

I have not found examples of this in documentation
or hackage packages: how can I deal with funcions
returning not pointers to structs but structs
thenselves?

struct example {...

example function_name (...

My intuition said I could try a data declaration
that is a properly done instance of Storable, and
then use that.

data Example = ...

instance Storable Example where ...

But it seems I was wrong.

Do you have any tips on how to proceed?

Thanks,
Maurício

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


Re: [Haskell-cafe] Haskell library support

2008-11-18 Thread Jeff Zaroyko
On Wed, Nov 19, 2008 at 9:45 AM, Galchin, Vasili [EMAIL PROTECTED] wrote:
 Hi Jeff,

Is http://haskell.org/haskellwiki/Wanted_libraries kept up to date? I
 wouldn't want to reinvent a wheel ;^)

 Vasili


Hi Vasili,

I was hoping that this thread could spur some interest from people to
update it with their most recent wishes.

I'm not sure about a lot of the things on there already,  but I
removed the request for .NET interop since Salsa is on hackage now and
I added a wish for x86-64 support for Harpy.  Beyond that, I don't
really have a feel for what's missing since I can think of many
programs that I'd like to write with what's available already.

I've also just submitted the link [1] to the Haskell reddit, which
will hopefully reach some people who aren't subscribed to this list.

1. 
http://www.reddit.com/r/haskell/comments/7e8wt/wanted_libraries_a_wishlist_for_haskell_libraries/

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


[Haskell-cafe] streaming translation using monads

2008-11-18 Thread Warren Harris
I am working on a query language translator, and although I feel that  
a monadic formulation would work well for this application, I've  
stumbled on a number of questions and difficulties that I thought the  
knowledgeable people here might be able to help me with.


As a translator, there's a source language and a target language, and  
both of these are specified as a grammar of nested expressions. My  
first thought was to formulate the target language as an embedded  
language where each clause expression is represented as a monad  
operation, so that the bind operator can join the pieces together, e.g.:


 (clause1, clause2 ...)

could be specified as an embedded language as:

 clause1  = \ v1 -
 clause2  = \ v2 - ...

However, each of the clauses is actually an output routine to send the  
expression that it denotes to a remote server, and a parser for  
receiving the results. Since a clause is really a pair of operations,  
it doesn't seem possible to formulate a monad that will compose all  
the output routines together and compose all the input routines  
together in one shot. (Note that the variables in the above code (v1,  
v2) represent inputs to be received from the remote server -- all  
outputs are packaged into the clause expressions themselves and are  
effectively literals.)


A naive formulation of a monad to implement the above as output -  
input v might appear to work, but has the ill-effect of interleaving  
the output and input statements for each clause rather than composing  
something that can send the entire request, and then receive the  
entire result.


This forces me to use output * input v as the type of each clause  
expression, but now it is not possible to write a monad with a bind  
operation that will compose pieces in terms of input variables.  
Instead I have had to resort to using a set of combinators that thread  
a continuation function through each clause and accumulate inputs as  
they are received:


 clause1 == (\ k v1 - k (trans1 v1)) ++
 clause2 == (\ k v2 - k (trans2 v2)) ++ ...

This threading is necessary in that I want to stream the translation  
back to the client requesting the translation rather than building up  
the (possibly large) results in memory.


This formulation has proven to be quite cumbersome in practice, as the  
resulting continuation types reflect the depth-first traversal of the  
nested query expressions, and type errors can be quite unintuitive.  
(It is quite interesting though that each continuation/transformation  
function can receive not only receive the input from the immediately  
preceding clause, but from any of the preceding clauses, and also  
return more or fewer results. However getting anything wrong can be  
very problematic in that it can lead to either downstream *or*  
upstream errors depending on how the clauses are composed into an  
overall query expression.)


An alternative to all this would be to use an algebraic datatype to  
specify the target language (with separate routines for the output and  
input operations), but that would appear to require another sum type  
to express the values to be received. I'd like to avoid that if  
possible since the projection of those values back into my program  
could lead to dynamic type errors, and also causes seemingly needless  
memory allocations.


There must be another technique for this sort of streaming translation  
out there... I welcome any suggestions you might have!


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


Re: [Haskell-cafe] streaming translation using monads

2008-11-18 Thread Brandon S. Allbery KF8NH

On 2008 Nov 18, at 21:23, Warren Harris wrote:
However, each of the clauses is actually an output routine to send  
the expression that it denotes to a remote server, and a parser for  
receiving the results. Since a clause is really a pair of  
operations, it doesn't seem possible to formulate a monad that will  
compose all the output routines together and compose all the input  
routines together in one shot. (Note that the variables in the above  
code (v1, v2) represent inputs to be received from the remote server  
-- all outputs are packaged into the clause expressions themselves  
and are effectively literals.)



Have you considered using arrows instead?

--
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] implementing python-style dictionary in Haskell

2008-11-18 Thread Ryan Ingram
On Tue, Nov 18, 2008 at 12:46 PM, Luke Palmer [EMAIL PROTECTED] wrote:
 But when these persistent data structures are used in a
 single-threaded way, why should we not hope for the performance to be
 comparable?

If you can guarantee single-threaded use, then you can just use ST and
implement the ephemeral structure, right?

 It may not be easy, but just saying they are persistent is not
 really an excuse.

You can generally make a persistent data structure with the same
asymptotic bounds as the ephemeral structure, but the constant hidden
inside the O() will generally be worse.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Monadic bind with associated types + PHOAS?

2008-11-18 Thread Ryan Ingram
This is an idea that has been bouncing around in my head for a while,
having to do with embedded languages.

A few of the talks at CUFP this year mentioned using Haskell to embed
a DSL that gets compiled into the output of the program; the hydraulic
engine talk embedded the code for the real-time safety computation in
the trucks, and one of the finance talks embedded a language for
designing Excel spreadsheets.

One thing that often comes up is a desire to do a pass on the
resultant code to optimize it, but it's pretty difficult with the
standard monadic formulation because of embedded functions.  You can't
do introspection on functions in Haskell; they aren't elements of Eq
or Show.  This has caused, for example, some implementations of FRP to
switch to using arrows instead.  However, I find the arrow syntax
cumbersome and I feel it tends to obfuscate what is actually going on
in the code.

An earlier talk at ICFP mentioned using PHOAS instead of HOAS to
encode expressions.  In HOAS, a lambda expression in the target
language is represented by a function in the source language:

 data ExpE t where
ApE :: ExpE (a - b) - ExpE a - ExpE b
LamE :: (ExpE a - ExpE b) - ExpE (a - b)

But without a way to inspect the function inside LamE, you can't get
back to the source code.  You end up adding special constructors for
Primitive or Variable to let you do something with the resultant
structure, which leads to the expression language containing unsafe
constructors which need to be hidden.

PHOAS makes a small change to make many of these things possible
without compromising safety:

 data ExpP v t where
VarP :: v t - ExpP v t
ApP :: ExpP v (a - b) - ExpP v a - ExpP v b
LamP :: (v a - ExpP v b) - ExpP v (a - b)

 newtype Exp t = Exp (forall v. ExpP v t)

Now, by parametricity, if you are constructing an Exp t, the only
useful thing you can do with the variable passed to LamP is give it to
VarP.  This means the code using it is basically the same as the HOAS
code, except a couple of extra VarP constructors inserted, but you
gain the ability to inspect inside the lambda and extract the code it
generates!

An couple of examples, from a PHOAS test I wrote up:

1) An evaluator
 eval :: Exp t - t
 eval (Exp e) = evalP e

 newtype Prim a = Prim a
 evalP :: ExpP Prim t - t
 evalP (VarP (Prim a)) = a
 evalP (ApP e1 e2) = evalPrim e1 $ evalPrim e2
 evalP (LamP f) = evalPrim . f . VarP . Prim

2) using show to peek inside functions!

] -- implementation is an exercise for the reader
] -- you'll learn a lot! :)
]
] newtype Var a = Var String
] showExp :: ExpP Var a - ShowS

ghci let test = Exp $ Lam $ \a - Lam $ \b - Var a
ghci :t test
test :: Exp (t - t1 - t)
ghci print test
\x y - x

It seems to me this exact transformation could be useful to express
variable binding in embedded languages!

 type family Primitive m a
 type family BoundVar m a
 class PMonad m where
 preturn :: Primitive m a - m a
 pbind :: m a - (BoundVar m a - m b) - m b

Now, this strictly generalizes regular monads:

 newtype Wrap m a = Wrap (m a)
 unwrap (Wrap m) = m
 type instance Primitive (Wrap m) a = a
 type instance BoundVar (Wrap m) a = a
 instance Monad m = PMonad (Wrap m) where
 preturn x = WM (return x)
 pbind m f = WM (unwrap m = unwrap . f)

So, it seems like the do-notation should work on this type, although
you lose pattern matching ([x] - getArgs).  And you can use PHOAS
techniques to build up a structure that you can introspect and
optimize.

Does anyone think this is a direction worth pursuing?  It seems to me
like a point where the current syntax of Haskell could mesh well with
the new type-system technology that we keep getting from GHC HQ.

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


Re: [Haskell-cafe] implementing python-style dictionary in Haskell

2008-11-18 Thread Luke Palmer
On Tue, Nov 18, 2008 at 8:51 PM, Ryan Ingram [EMAIL PROTECTED] wrote:
 On Tue, Nov 18, 2008 at 12:46 PM, Luke Palmer [EMAIL PROTECTED] wrote:
 But when these persistent data structures are used in a
 single-threaded way, why should we not hope for the performance to be
 comparable?

 If you can guarantee single-threaded use, then you can just use ST and
 implement the ephemeral structure, right?

But that requires a special reimplementation.

 It may not be easy, but just saying they are persistent is not
 really an excuse.

 You can generally make a persistent data structure with the same
 asymptotic bounds as the ephemeral structure, but the constant hidden
 inside the O() will generally be worse.

I say this as a goal.  If we're in a performance competition, we can't
say well, it's okay that Haskell is slower because its data
structures can be used persistently.  Python's dictionaries can also,
by inserting explicit copies.  In this use case Python performs
better, and we should strive to perform as well as it does.
Persistence has no bearing on this, because the persistence is not
used.

I'm not saying it's always possible to perform just as well.  But
persistence *by itself* is not a valid argument for poor performance.

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


[Haskell-cafe] Monadic bind with associated types + PHOAS?

2008-11-18 Thread oleg

Ryan Ingram wrote:
 One thing that often comes up is a desire to do a pass on the
 resultant code to optimize it, but it's pretty difficult with the
 standard monadic formulation because of embedded functions.  You can't
 do introspection on functions in Haskell; they aren't elements of Eq
 or Show.  This has caused, for example, some implementations of FRP to
 switch to using arrows instead.  However, I find the arrow syntax
 cumbersome and I feel it tends to obfuscate what is actually going on
 in the code.

 An earlier talk at ICFP mentioned using PHOAS instead of HOAS to
 encode expressions.  In HOAS, a lambda expression in the target
 language is represented by a function in the source language:

If one uses a tagless final representation, one benefits from the
conveniences of the higher-order abstract syntax and yet gains the
ability to show terms, count the number of constructors and even
partially evaluate them (i.e., optimize). For the example, please see

http://okmij.org/ftp/tagless-final/Incope.hs
(in particular, see Semantics2 for the partial evaluator that does not
use GADT). We can easily add an interpreter that does a CPS transform,
thus letting us embed a CBV object language in a Haskell without
any use of monad or the change of syntax of the object language. We
can easily extend the language to add state (as we have done in the
OCaml part of the project).
http://okmij.org/ftp/tagless-final/README.txt
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe