Re: [Haskell-cafe] ANN: logfloat

2008-08-16 Thread wren ng thornton


-- Announcing: logfloat 0.8.5


New official release of the logfloat package for manipulating log-domain 
floating numbers. This is primarily a maintenance release updating the 
documentation and with minor tweaks on typeclass-restricted polymorphism.


Substantively, I also broke out a new type class for numbers which can 
represent transfinite values. This is primarily to deal with issues 
about Rationals and other Fractional types which cannot represent them.


I also decided to switch the code over to *.hs format so that the 
Hackage build bot can generate the documentation more reliably.



-- Description


The main reason for casting numbers into the log-domain is to prevent
underflow when multiplying many small probabilities as is done in Hidden
Markov Models and other statistical models often used for natural
language processing. The log-domain also helps prevent overflow when
multiplying many large numbers. In rare cases it can speed up numerical
computation (since addition is faster than multiplication, though
logarithms are exceptionally slow), but the primary goal is to improve
accuracy of results. A secondary goal has been to maximize efficiency
since these computations are frequently done within a /O(n^3)/ loop.

The Data.Numeric.LogFloat module provides a new data type LogFloat which
handles all the conversions and optimizations and can be treated as any
other number thanks to type classes.


-- Links


Homepage:
http://code.haskell.org/~wren/

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

Darcs:
http://code.haskell.org/~wren/logfloat

Haddock (Darcs version):
http://code.haskell.org/~wren/logfloat/dist/doc/html/logfloat/

--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] permutations and performance

2008-08-16 Thread Henning Thielemann

John D. Ramsdell schrieb:

Try deleting it and see what happens.


Erm, yes, this case is wrong:

| n <=  0 = []

There is _one_ permutation with no elements, namely [], thus it must be
| n == 0 = [[]]

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


[Haskell-cafe] X Haskell Bindings

2008-08-16 Thread Antoine Latter
Haskellers,

I'm slowly porting XCB (the X C Bindings) to Haskell, and I would like
input from any interested parties.

The following is a summary of my plan so far.  I'm interested in
hearing any suggestions or concerns about what a Haskell library for
writing X clients should look like.  This is not a release
announcement, and I can't make any promises about when this will be
delivered.

Code is available in darcs:
--  darcs get http://community.haskell.org/~aslatter/code/xhb

Some of the  advantages XCB claims over xlib are:
  + smaller API
  + latency hiding when communicating with the X server
  + direct access to the X protocol
  + improved threading support
  + easier to extend

What I plan for the X Haskell Bindings (XHB) are as follows:

 + All requests to the server are non-blocking (under most circumstances)

 + Requests which produce a reply from the server return a "token" or "receipt"

 + The caller may then, at a time of their choosing, query the receipt
for the response (or error) from the
server.  This query is blocking.

The API will look something like:

> -- | Create a window as specified
> createWindow :: Connection -> CreateWindow -> IO ()

> -- | Instruct the server that it should begin displaying the named window
> mapWindow :: Connection -> WINDOW -> IO ()

> -- | List all of the extensions supported by the server
> listExtensions :: Connection -> IO (Receipt (ListExtensionsReply))

> -- | Query a receipt for a response
> getReply :: Receipt a -> IO (Either XError a)

Note that the first two requests do not have replies, whereas the
third request expects a reply from the server.

Since the request to create a window has so many parameters, these
parameters are all wrapped up into a "CreateWindow" data type, which
is only ever used by the "createWindow" function.  The "mapWindow"
request only has one parameter, so it does not need it's own
"MapWindow" data type.


What I don't have planned out is what to do with the stream of events
and errors that come back from the server.

If an error is related to an outstanding receipt, it gets dumped there
for the caller to examine directly.  Other errors go into an error
queue.

Events go into a similar event queue.

How should this queue be exposed in the API?  Should the user of the
library register an error/event callback?

> registerErrorCallback :: Connection -> (XError -> IO ()) -> IO ()

Or is something like this enough:

> pollForError :: Connection -> IO (Maybe (XError))

> waitForError :: Connection -> IO XError

Each X extension defines its own set of errors and events
(potentially).  Should all of these be lumped together into one giant
sum-type for errors and one for events?

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


[Haskell-cafe] Re: Phantoms

2008-08-16 Thread Ben Franksen
Jason Dagit wrote:
> On Wed, Aug 6, 2008 at 11:09 AM, Andrew Coppin
> <[EMAIL PROTECTED]>wrote:
> 
>> I just (re)discovered that I can do things like
>>
>>  data Foo x = Foo Int Int
>>
>> Now "Foo Int" and "Foo Double" are, as far as the type checker cares, two
>> completely different types, even though in fact they are the same. This
>> is actually Quite Useful, in the particular case I'm working on.
> 
> Phantom types are indeed useful for many things, but a bit of cautionary
> advice.  If you start to depend on the phantoms for type safety AND you
> export your data constructors then you run a serious risk of being type
> unsafe.  Bonus points if you can demonstrate an equivalent of
> unsafeCoerce# this way.

This would be very bad, but I doubt it is possible.

> Example:
> fooCast :: Foo Int -> Foo Double
> fooCast (Foo x) = Foo x
> 
> On noes!  We just cast that Foo Int to a Foo Double without changing it! 

What's the problem?

> It works because the value on the RHS is consider freshly constructed and
> other than sharing x it is unrelated to the one on the LHS.

Right. You must call the data constructor Foo in order to exploit that it
has the type

  Foo :: Int -> Foo a

I don't see how this is not type safe, and I was not able to produce an
#unsafeCoerce with this technique. One would need some

  unFoo a -> a

but the  a  in  data Foo a  is phantom, i.e. there is no thing of type  a 
in a Foo.

Cheers
Ben

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


Re: [Haskell-cafe] permutations and performance

2008-08-16 Thread Henning Thielemann

John D. Ramsdell wrote:


Straight forward permation algorithm.


permutations :: Int -> [[Int]]
permutations n
| n <=  0 = []
| n == 1 = [[0]]


Btw. I think that case is redundant.


| otherwise =
concatMap (insertAtAllPos (n - 1)) (permutations (n - 1))
where
  insertAtAllPos x [] = [[x]]
  insertAtAllPos x (y : l) =
  (x : y : l) : map (y :) (insertAtAllPos x l)


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


[Haskell-cafe] permutations and performance

2008-08-16 Thread John D. Ramsdell
I tried to replace a permutation generator with one that generates
each permutation from the previous one, in a stream-like fashion.  I
had hoped the stream-based algorithm would be more efficient because I
use only one permutation at a time, so only the permutation and the
previous one need be in memory at one time.  I thought I'd share the
results of testing the two algorithms.

I first forced the algorithms to produce answers by printing the
length of their results.  Bad idea.  The stream-based algorithm
produces a stack overflow on an input that it can handle when the
contents of every permutation is forced.  In this run, touch = length.

$ ghc -O perms.lhs
$ echo '(True, 9)' | ./a.out
Stack space overflow: current size 8388608 bytes.
Use `+RTS -Ksize' to increase it.
$ echo '(False, 9)' | ./a.out
362880
$

I forced all parts of the computation by summing all of the numbers in
the output.  The result show the more obvious algorithm is faster.

$ ghc -O perms.lhs
$ echo '(True, 12)' | time ./a.out
31614105600
299.56user 0.97system 5:00.75elapsed 99%CPU (0avgtext+0avgdata 0maxresident)k
0inputs+0outputs (0major+479minor)pagefaults 0swaps
$ echo '(False, 12)' | time ./a.out
31614105600
213.86user 0.55system 3:34.90elapsed 99%CPU (0avgtext+0avgdata 0maxresident)k
0inputs+0outputs (0major+841minor)pagefaults 0swaps
$

> module Main(main) where

> main =
> do (new, n) <- readLn :: IO (Bool, Int)
>case new of
>  True -> print $ touch $ npermutations n
>  False -> print $ touch $ permutations n

Touch all the numbers in the output.  Originally, touch = length.

> touch :: [[Int]] -> Int
> touch xs =
> sum (map sum xs)

The permutation algorithm used by Serge Mechveliani in The Algebraic
Domain Constructor DoCon.  The idea of the algorithm was suggested to
him by S.M.Abramov.

> npermutations :: Int -> [[Int]]
> npermutations n =
> first : next (spanMonotoneous first)
> where
>   first = take n [0..]
>   next (_ , []) = []
>   next (decr, j:js) =
>   p : next (spanMonotoneous p)
>   where
> p = concat [reverse smallers, [j], reverse greaters, [i], js]
> (greaters, i:smallers) = span (> j) decr
>   spanMonotoneous (x:y:xs)
>   | x <= y = ([x], y:xs)
>   | otherwise = (x:ys, zs)
>   where
> (ys,zs) = spanMonotoneous (y:xs)
>   spanMonotoneous xs = (xs, [])
>   p : next (spanMonotoneous p)
>   where
> p = concat [reverse smallers, [j], reverse greaters, [i], js]
> (greaters, i:smallers) = span (> j) decr
>   spanMonotoneous (x:y:xs)
>   | x <= y = ([x], y:xs)
>   | otherwise = (x:ys, zs)
>   where
> (ys,zs) = spanMonotoneous (y:xs)
>   spanMonotoneous xs = (xs, [])

Straight forward permation algorithm.

> permutations :: Int -> [[Int]]
> permutations n
> | n <=  0 = []
> | n == 1 = [[0]]
> | otherwise =
> concatMap (insertAtAllPos (n - 1)) (permutations (n - 1))
> where
>   insertAtAllPos x [] = [[x]]
>   insertAtAllPos x (y : l) =
>   (x : y : l) : map (y :) (insertAtAllPos x l)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] What's in a name?

2008-08-16 Thread Brandon S. Allbery KF8NH


On 2008 Aug 16, at 13:22, Andrew Coppin wrote:
Yeah, as I said, it's not immediately obvious exactly what the best  
solution is. Maybe we just need to get everybody to come up with  
more inventive names than just "hashtable" or "binary". (E.g., We  
have several parsers already, but they all have distinctive names  
that are unlikely to clash. Maybe we just need to do that for  
everything? IDK.)


The names should really be more descriptive.  What makes hashtable A  
different/distinct from hashtable B?  What's so special about new- 
binary?


--
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] What's in a name?

2008-08-16 Thread Andrew Coppin

Robert Greayer wrote:

This seems to be a common approach, but it runs counter to the objective of 
separating 'provenance' from module naming.  'Coppin' is (part of, sans 
version) the provenance of the hashtable implementation, so I'm not sure how 
this sort of scheme is better than just shoving the unique prefix at the front 
of the module, e.g.

Coppin.Data.Hashtable

Though embedding the provenance down in the hierarchy is a common pattern,  I think it is can be 
pretty messy.  For example, the Parsec package exposes many modules, including 
"Text.Parsec.String" and "Text.ParserCombinators.Parsec.Token" -- the 
provenance appears at different levels in the hierarchy.  If you're going to shove the package name 
in there, it seems simpler to me to just shove it at the front: 
Parsec.Text.ParserCombinators.Token.  The package mounting scheme might solve this (though it seems 
to me that it requires that source for packages be kept around.  I may be wrong).
  


Yeah, as I said, it's not immediately obvious exactly what the best 
solution is. Maybe we just need to get everybody to come up with more 
inventive names than just "hashtable" or "binary". (E.g., We have 
several parsers already, but they all have distinctive names that are 
unlikely to clash. Maybe we just need to do that for everything? IDK.)



(As I already pointed out, there's at least 3 packages called "bianry", > which 
is just confusing.)



On hackage? I only see one with that the exact name "binary".
  


OK, that's interesting. Apparently something has changed. Last time I 
looked, there was "binary", "old-binary", "new-binary", "alt-binary" and 
so forth. (It seems there is now a "binary-strict", but it's pretty 
obvious how that relates to the normal "binary" package.) Obviously, 
having this profusion of nearly identical names is just confusing.


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


Re: [Haskell-cafe] why isn't the thread blocked?

2008-08-16 Thread Brandon S. Allbery KF8NH


On 2008 Aug 16, at 12:22, Changying Li wrote:

test.hs: /tmp/b: hGetChar: end of file

test.hs: /tmp/c: hGetChar: end of file


I think the thread will be blocked when /tmp/b has nothing.
but it get EOF, why ?



Because FIFOs are odd.  Open them for read/write to avoid unexpected  
EOFs and unexpected blocking.


--
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] What's in a name?

2008-08-16 Thread Brandon S. Allbery KF8NH


On 2008 Aug 16, at 5:00, Andrew Coppin wrote:
What to do at the module level is less obvious. Having several  
packages provide different implementations of the same thing is  
arguably useful. (E.g., I know Gtk2hs provies an SOE module. What  
about wxHaskell? If the interface is standard enough, a given  
application might not actually care which implementation it gets.)  
I'm open to suggestions here...



The standard way to deal with this is virtual packages.  But this  
would require significant changes to Cabal, not only to track multiple  
names for a single package but also to not complain about collisions.


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


[Haskell-cafe] why isn't the thread blocked?

2008-08-16 Thread Changying Li
I writed a little program to test forkIO. in fact, I want to know how to
implement the 'select' system call in haskell:

module Main where

import Control.Concurrent.Chan
import Control.Concurrent
import System.IO

main = do
  chan <- newChan
  handles <- mapM ((flip  openFile) ReadMode) ["/tmp/a","/tmp/b","/tmp/c"]
  let  readF h = do
  myID <- myThreadId
  chan' <- dupChan chan
  char <- hGetChar h
  writeChan chan' $ show myID
  putStrLn [char]
  threads <- mapM (\h -> forkIO $ readF h) handles
  nr <- readChan chan
  mapM killThread $ filter (\x -> show x == nr ) threads
  putStrLn  nr



I first mkfifo /tmp/{a,b,c} , then run 'echo "hello" >/tmp/a', then
'runhaskell thisProgram.hs'

but I got an error: 

test.hs: /tmp/b: hGetChar: end of file

test.hs: /tmp/c: hGetChar: end of file


I think the thread will be blocked when /tmp/b has nothing.
but it get EOF, why ?


-- 

Thanks & Regards

Changying Li

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


Re: [Haskell-cafe] What's in a name?

2008-08-16 Thread Robert Greayer



--- On Sat, 8/16/08, Andrew Coppin <[EMAIL PROTECTED]> wrote:
> > Although it is possible to hide packages by GHC options, we should not
> > do this, because several libraries might use different Hash tables and 
> > it would not be possible to write a program which uses many of these 
> > libraries. It's better to add a distinguishing part to the module 
> > name, like Data.HashTable.Coppin or so.
> 
> This is more the sort of thing I had in mind, yes.

This seems to be a common approach, but it runs counter to the objective of 
separating 'provenance' from module naming.  'Coppin' is (part of, sans 
version) the provenance of the hashtable implementation, so I'm not sure how 
this sort of scheme is better than just shoving the unique prefix at the front 
of the module, e.g.

Coppin.Data.Hashtable

Though embedding the provenance down in the hierarchy is a common pattern,  I 
think it is can be pretty messy.  For example, the Parsec package exposes many 
modules, including "Text.Parsec.String" and 
"Text.ParserCombinators.Parsec.Token" -- the provenance appears at different 
levels in the hierarchy.  If you're going to shove the package name in there, 
it seems simpler to me to just shove it at the front: 
Parsec.Text.ParserCombinators.Token.  The package mounting scheme might solve 
this (though it seems to me that it requires that source for packages be kept 
around.  I may be wrong).

> (As I already pointed out, there's at least 3 packages called "bianry", > 
> which is just confusing.)

On hackage? I only see one with that the exact name "binary".


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


Re: [Haskell-cafe] What's in a name?

2008-08-16 Thread Andrew Coppin

Henning Thielemann wrote:
Although it is possible to hide packages by GHC options, we should not 
do this, because several libraries might use different Hash tables and 
it would not be possible to write a program which uses many of these 
libraries. It's better to add a distinguishing part to the module 
name, like Data.HashTable.Coppin or so.


This is more the sort of thing I had in mind, yes.

As others have pointed out, not everybody has a domain name, so Java's 
technique of inserting a domain name perhaps isn't the best one. 
However, if we all agreed that, say, packages should be named 
"coppin-hashtable" or something, then there wouldn't be much danger of 
ambiguous package names. (As I already pointed out, there's at least 3 
packages called "bianry", which is just confusing.) It's rather less 
clear what to do with something like, say, ByteString, which is the 
product of a large number of collaborators. Then again, it's a big 
enough package that nobody is likely to come up with a similar one. 
(Unless it's a fork I suppose - in which case a prefix or suffix for the 
person who forked it might be appropriate?)


What to do at the module level is less obvious. Having several packages 
provide different implementations of the same thing is arguably useful. 
(E.g., I know Gtk2hs provies an SOE module. What about wxHaskell? If the 
interface is standard enough, a given application might not actually 
care which implementation it gets.) I'm open to suggestions here...


I don't claim to have all the answers. I'd just like to see some debate 
happening. ;-)


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