Re: [Haskell-cafe] Re: [ANN] bloomfilter 1.0 - Fast immutable and mutable Bloom filters

2008-05-31 Thread ajb

G'day all.

Quoting Achim Schneider [EMAIL PROTECTED]:


Please tell me that this isn't reversible.


It isn't reversible.

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


Re: [Haskell-cafe] Data.Tree.Zipper in the standard libraries

2008-05-31 Thread Krasimir Angelov
Hi again,

I was silent for some time but in this time I created QuickCheck tests
for Data.Tree.Zipper which achieve 100% coverage with HPC. I also
created a ticket for it: Ticket #2324

http://hackage.haskell.org/trac/ghc/ticket/2324

The attached file is the current implementation and it contains the
version updated from Iavor Diatchki. It has the advantage that it also
works with forests, not just with trees.

Initially I thought that complete testsuite for such a simple module
might be overkill but actually I found a bug :-) in the splitChildren
function which is now fixed.

The dead line for further considerations is one week.

Regards,
  Krasimir



On Sun, May 25, 2008 at 1:09 AM, Iavor Diatchki
[EMAIL PROTECTED] wrote:
 Hello,
 I think that the modified API (no state monad, and using Maybe) is
 quite nice!  I implemented a version of the the suggested API using a
 slightly different data structure, which makes the code a bit simpler,
 I think.   I put the code in the Haskell wiki:
 http://www.haskell.org/sitewiki/images/2/2d/RoseZipper.hs
 I also added a couple of extra functions that seemed useful, and
 renamed a few of the functions to be more consistent.

 As for how to distribute the code, it seems that Zipper should live in
 the same place as Data.Tree.  I think that Data.Tree is part of the
 containers package, so it would make sense to add the Zipper there
 as well.

 -Iavor



 On Sat, May 24, 2008 at 1:24 AM, Neil Mitchell [EMAIL PROTECTED] wrote:
 Hi,

 It doesn't use State monad anymore and it returns Maybe. This seems to
 be the common preference, is it? Feel free to vote against. Should we
 change Data.Map also? There is another proposal for changes in
 findMin/findMax so it is better to make this two breaking changes
 together rather than in a later release.

 The standard libraries proposal thingy is to go via the libraries
 list, create tickets etc. What reason is there to make this part of
 the base libraries, rather than a separate package on hackage? I can't
 see much reason to make Data.Tree part of the base libraries, other
 than the fact it already is, and it could easily get moved out at a
 future date.

 We've seen there is some advantage in leaving the implementation
 outside the base library, as its already changed several times in the
 past few days.

 Thnanks

 Neil
 ___
 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] [ANN] bloomfilter 1.0 - Fast immutable and mutable Bloom filters

2008-05-31 Thread David MacIver
On Fri, May 30, 2008 at 11:30 PM, Bryan O'Sullivan [EMAIL PROTECTED] wrote:
 I'm pleased to announce the availability of a fast Bloom filter library
 for Haskell.  A Bloom filter is a probabilistic data structure that
 provides a fast set membership querying capability.  It does not give
 false negatives, but has a tunable false positive rate.  (A false
 positive arises when the filter claims that an element is present, but
 in fact it is not.)

 The library is easy to use.  As an example, here's a reimplementation of
 the Unix spell command.

 import Data.BloomFilter.Easy (easyList, elemB)

 main = do
  filt - (easyList 0.01 . words) `fmap` readFile dictionary.txt
  let check word | word `elemB` filt = 
 | otherwise = word ++ \n
  interact (concat . map check . lines)

 It is also carefully tuned for performance.  On my laptop, I can sustain
 a construction or query rate well in excess of a million ByteStrings per
 second.

 Source code:

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

 Latest bits:

 darcs get http://darcs.serpentine.com/bloomfilter

The Hashable stuff in there looks like it might be independently
useful. Any interest in splitting it out into an independent package
or is it really intended to be something fairly specific to the Bloom
filter implementation?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: [Haskell] Programme terminates silently

2008-05-31 Thread Bertram Felgenhauer
(redirecting to haskell-cafe. the haskell mailing list is primarily for
announcements)

(sorry, Thomas, if you get this message twice)

Thomas Bevan wrote:
 I've written the programme below.
 
 The lircLoop should never terminate. Unfortunately it does. Worse, no error
 messages are generated.
 Not even the final line Closing down is printed.
 
 How is this possible?

I couldn't find the Hmpf.Fork module you're using, so I couldn't test this.

However, one possibility is that program receives a signal that is neither
handled or ignored. This is the case for SIGPIPE [1]. You can strace your
program to find out whether that's the case.

System.Posix.Process provides facilities for installing your own signal
handlers.

HTH,

Bertram

[1] http://hackage.haskell.org/trac/ghc/ticket/1619
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: appending an element to a list

2008-05-31 Thread Tillmann Rendel

Abhay Parvate wrote:

I think I would like to make another note: when we talk about the complexity
of a function, we are talking about the time taken to completely evaluate
the result. Otherwise any expression in haskell will be O(1), since it just
creates a thunk.


I don't like this notion of complexity, since it seems not very suited 
for the analysis of composite expression in Haskell. For example,


  repeat 42

has infinite complexity according to your definition (it doesn't even 
terminate if completely evaluated), but


  take 5 $ repeat 42

has only constant complexity even if fully evaluated. It is not clear 
how to reuse the finding about the complexity of (repeat 42) to 
determine the complexity of (take 5).


Instead, my view of complexity in lazy languages includes the 
interesting behaviour of the rest of the program as variables. For 
example, (repeat 42) needs O(n) steps to produce the first n elements of 
its output. Now, (take 5 x) restricts x to the first 5 elements, so 
(take 5 $ repeat 42) needs O(min(n, 5)) = O(1) steps to produce the 
first n elements of its output.


Is this intuitive view generalizable to arbitrary datatypes (instead of 
lists) and formalized somewhere?


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


[Haskell-cafe] Parsec, updateState, and failure

2008-05-31 Thread Dimitry Golubovsky
Hi,

If a parser which updated user state fails, will such update be reverted?

Suppose we have two parsers combined with |

p = p1 | p2

p1 has the following:

p1 = try $ do
 ... -- getting something from the input stream
 updateState (\st - ...) -- updated state based on what gotten from the input
 x - p3 -- p3 should see updated state and return something
 updateState (\st - ...) -- updated state again (if p3 succeeded)
 return x

If p3 fails, p1 fails too (second updateState will not be reached).
But what will p2 (tried next) see in the user state? Will it be state
after the first updateState, or will failure of p1 roll the update
back?

Is there any bracket- or try-catch-finally-like mechanism for Parsec?

Thanks.

-- 
Dimitry Golubovsky

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


Re: [Haskell-cafe] is there some book about haskell and data struct and alg?

2008-05-31 Thread Robert Dockins

[snip]
  Without the equivalent Haskell source code, the code must be manually
  translated from Standard ML into Haskell.  Does anybody know why the link
  is broken, when it may be fixed, and from where the Haskell source code
  can be currently obtained?
 
  Benjamin L. Russell

 If you are interested in the topic, you will probably want to check out
 Edison: http://www.cs.princeton.edu/~rdockins/edison/home/.

 I believe some of the older code in there was even written by Okasaki.

Indeed, the vast majority of the code was written by Okasaki. Most of the data 
structures from his book are in Edison.

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


[Haskell-cafe] Upd: Parsec, updateState, and failure

2008-05-31 Thread Dimitry Golubovsky
Hi,

So far, I figured it out like this:

updateState ...
mbx - (p3 = return . Just) | (return Nothing)
updateState ...
case mbx of
  Just x - return x
  Nothing - pzero

but this seems a bit clumsy - is there a more elegant solution?

-- Forwarded message --
From: Dimitry Golubovsky [EMAIL PROTECTED]
Date: Sat, May 31, 2008 at 10:12 AM
Subject: Parsec, updateState, and failure
To: haskell haskell-cafe@haskell.org


Hi,

If a parser which updated user state fails, will such update be reverted?

Suppose we have two parsers combined with |

p = p1 | p2

p1 has the following:

p1 = try $ do
 ... -- getting something from the input stream
 updateState (\st - ...) -- updated state based on what gotten from the input
 x - p3 -- p3 should see updated state and return something
 updateState (\st - ...) -- updated state again (if p3 succeeded)
 return x

If p3 fails, p1 fails too (second updateState will not be reached).
But what will p2 (tried next) see in the user state? Will it be state
after the first updateState, or will failure of p1 roll the update
back?

Is there any bracket- or try-catch-finally-like mechanism for Parsec?

Thanks.

--
Dimitry Golubovsky

Anywhere on the Web



-- 
Dimitry Golubovsky

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


Re: [Haskell-cafe] [ANN] bloomfilter 1.0 - Fast immutable and mutable Bloom filters

2008-05-31 Thread Bryan O'Sullivan
David MacIver wrote:

 The Hashable stuff in there looks like it might be independently
 useful.

Probably, yes.

 Any interest in splitting it out into an independent package
 or is it really intended to be something fairly specific to the Bloom
 filter implementation?

I'll split them if there's a request, but time constraints must alas
prevail in the face of mere polite interest :-)

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


Re: [Haskell-cafe] Parsec, updateState, and failure

2008-05-31 Thread Jonathan Cast


On 31 May 2008, at 7:12 AM, Dimitry Golubovsky wrote:


Hi,

If a parser which updated user state fails, will such update be  
reverted?


Suppose we have two parsers combined with |

p = p1 | p2

p1 has the following:

p1 = try $ do
 ... -- getting something from the input stream
 updateState (\st - ...) -- updated state based on what gotten  
from the input

 x - p3 -- p3 should see updated state and return something
 updateState (\st - ...) -- updated state again (if p3 succeeded)
 return x

If p3 fails, p1 fails too (second updateState will not be reached).
But what will p2 (tried next) see in the user state?


The same thing p1 saw.  You can see the implementation in http:// 
darcs.haskell.org/ghc-6.8/libraries/parsec/Text/ParserCombinators/ 
Parsec/Prim.hs; you want the parsecPlus function.  Furthermore, you  
might note that the GenParser type is defined as


newtype GenParser tok st a = Parser (State tok st - Consumed (Reply  
tok st a))

runP (Parser p)= p

data Consumed a = Consumed a--input is consumed
| Empty !a  --no input is  
consumed


data Reply tok st a = Ok !a !(State tok st) ParseError-- 
parsing succeeded with a
| Error ParseError-- 
parsing failed


data State tok st   = State { stateInput :: [tok]
, statePos   :: !SourcePos
, stateUser  :: !st
}


A parser that fails doesn't deliver a new state for parsecPlus to  
consider using going forward.


jcc

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


Re: [Haskell-cafe] [ANN] bloomfilter 1.0 - Fast immutable and mutable Bloom filters

2008-05-31 Thread David MacIver
On Sat, May 31, 2008 at 4:09 PM, Bryan O'Sullivan [EMAIL PROTECTED] wrote:
 David MacIver wrote:

 The Hashable stuff in there looks like it might be independently
 useful.

 Probably, yes.

 Any interest in splitting it out into an independent package
 or is it really intended to be something fairly specific to the Bloom
 filter implementation?

 I'll split them if there's a request, but time constraints must alas
 prevail in the face of mere polite interest :-)

Seems fair enough to me. I was indeed just curious. :-) I'll shout if
I have an actual use case (or possibly just include the whole thing.
It's not exactly a major size burden)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: type-level integers using type families

2008-05-31 Thread Peter Gavin

Benedikt Huber wrote:

data True
data False

type family Cond x y z
type instance Cond True y z = y
type instance Cond False y z = z 


I'm not sure if this is what you had in mind, but I also found that e.g.

  type instance Mod x y = Cond (y :: x) x  (Mod (Sub x y) y)

won't terminate, as

  Mod D0 D1 == Cond True D0 (Mod (Sub D0 D1) D0) == loop


Right, because it always tries to infer the (Mod (Sub x y) y) part no 
matter what the result of (y :: x) is.




rather than

  Mod D0 D1 == Cond True D0 ? == D0

For Mod, I used the following (usual) encoding:

  type family Mod' x y x_gt_y
  type instance Mod' x y False = x
  type instance Mod' x y True  = Mod' (Sub x y) y ((Sub x y) :=: y)
  type family Mod x y
  type instance Mod x y = Mod' x y (x :=: y)



Yes, it's possible to terminate a loop by matching the type argument 
directly.



1) One cannot define type equality (unless total type families become
available), i.e. use the overlapping instances trick:

instance Eq e e  True
instance Eq e e' False


I didn't want to mix type classes and families in my implementation. All 
the predicates are implemented like so:


 type family Eq x y
 type instance Eq D0 D0 = True
 type instance Eq D1 D1 = True
...
 type instance Eq (xh :* xl) (yh :* yl) = And (Eq xl yl) (Eq xh yh)

then I've added a single type-class

 class Require b
 instance Require True

so you can do stuff like

 f :: (Require (Eq (x :+: y) z)) = x - y - z

or whatever.  I haven't yet tested it (but I think it should work) :)

Pete



Consequently, all type-level functions which depend on type equality
(see HList) need to be encoded using type classes.

2) One cannot use superclass contexts to derive instances e.g. to define

instance Succ (s,s') =  Pred (s',s)


In constrast, when using MPTC + FD, one can establish more than one TL 
function in one definition


  class Succ x x' | x - x', x' - x

3) Not sure if this is a problem in general, but I think you cannot 
restrict the set of type family instances easily.


E.g., if you have an instance

  type instance Mod10 (x :* D0) = D0

then you also have

  Mod10 (FooBar :* D0) ~ D0

What would be nice is something like

  type instance (IsPos x) = Mod10 (x :* D0) = D0

though

  type family AssertThen b x
  type instance AssertThen True x = x
  type instance Mod10 (x :* D0) = AssertThen (IsPos x) D0

seems to work as well.

4) Not really a limitation, but if you want to use instance methods of
Nat or Bool (e.g. toBool) on the callee site, you have to provide
context that the type level functions are closed w.r.t. to the type class:


test_1a :: forall a b b1 b2 b3.
  (b1 ~ And a b,
   b2 ~ Not (Or a b),
   b3 ~ Or b1 b2,
   Bool b3) = a - b - Prelude.Bool
test_1a a b = toBool (undefined :: b3)


Actually, I think the 'a ~ b' syntax is very nice.

I'm really looking forward to type families.

best regards,

benedikt


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


Re: [Haskell-cafe] [ANN] bloomfilter 1.0 - Fast immutable and mutable Bloom filters

2008-05-31 Thread Thomas Hartman
What kind of speed do you get on your laptop for Data.Set? How much
faster is the bloom filter?

thomas.

2008/5/30 Bryan O'Sullivan [EMAIL PROTECTED]:
 I'm pleased to announce the availability of a fast Bloom filter library
 for Haskell.  A Bloom filter is a probabilistic data structure that
 provides a fast set membership querying capability.  It does not give
 false negatives, but has a tunable false positive rate.  (A false
 positive arises when the filter claims that an element is present, but
 in fact it is not.)

 The library is easy to use.  As an example, here's a reimplementation of
 the Unix spell command.

 import Data.BloomFilter.Easy (easyList, elemB)

 main = do
  filt - (easyList 0.01 . words) `fmap` readFile dictionary.txt
  let check word | word `elemB` filt = 
 | otherwise = word ++ \n
  interact (concat . map check . lines)

 It is also carefully tuned for performance.  On my laptop, I can sustain
 a construction or query rate well in excess of a million ByteStrings per
 second.

 Source code:

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

 Latest bits:

 darcs get http://darcs.serpentine.com/bloomfilter

b
 ___
 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] Parsec, updateState, and failure

2008-05-31 Thread Andrew Coppin

Dimitry Golubovsky wrote:

Hi,

If a parser which updated user state fails, will such update be reverted?
  


Without actually checking, I would strongly suspect that yes, if a 
parser fails, all its state modifications are thrown away. (This is 
usually what you would want...)



Is there any bracket- or try-catch-finally-like mechanism for Parsec?
  


I don't think so. If you find yourself wanting to parse data differently 
depending on stuff you've already seen, you might find it easier to run 
a 2-pass parser of some kind.


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


[Haskell-cafe] Re: Parsec, updateState, and failure

2008-05-31 Thread Achim Schneider
Dimitry Golubovsky [EMAIL PROTECTED] wrote:

 If a parser which updated user state fails, will such update be
 reverted?
 
I have no idea, I gave up before investigating that far.

You want to avoid state at any cost, even more so if the state would
influence parsing: spaghetti and headaches lay ahead. In the end I did
three passes: two times parsec and one time something similar to
accumMap.

Now that I'm thinking of it, it would be nice if parsec supported
spans in source positions, so that you can report errors like

XYZ at foo.bar line 3 column 2 in ZYX spanning line 2-4 column
34-20.

-- 
(c) this sig last receiving data processing entity. Inspect headers for
past copyright information. All rights reserved. Unauthorised copying,
hiring, renting, public performance and/or broadcasting of this
signature prohibited. 

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


Re: [Haskell-cafe] Re: Parsec, updateState, and failure

2008-05-31 Thread Antoine Latter
On Sat, May 31, 2008 at 12:12 PM, Achim Schneider [EMAIL PROTECTED] wrote:
 Dimitry Golubovsky [EMAIL PROTECTED] wrote:

 If a parser which updated user state fails, will such update be
 reverted?

 I have no idea, I gave up before investigating that far.

 You want to avoid state at any cost, even more so if the state would
 influence parsing: spaghetti and headaches lay ahead. In the end I did
 three passes: two times parsec and one time something similar to
 accumMap.


If you really really wanted state that doesn't un-roll when parsing
fails, this should work (but is untested):

 type MyParser = ParsecT String () (State MyState)

 runMyParser :: MyParser a - String - SourceName - MyState - (Either 
 ParseError a, MyState)

 runMyParser m in name state = flip runState state $ runPT m in name

You can then use 'get' and 'set'.

But as you suggest, that way may be madness.

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


[Haskell-cafe] Re: [ANN] bloomfilter 1.0 - Fast immutable and mutable Bloom filters

2008-05-31 Thread Aaron Denney
On 2008-05-30, Achim Schneider [EMAIL PROTECTED] wrote:
 Bryan O'Sullivan [EMAIL PROTECTED] wrote:

 A Bloom filter is a probabilistic data
 structure that provides a fast set membership querying capability.
 It does not give false negatives, but has a tunable false positive
 rate.  (A false positive arises when the filter claims that an
 element is present, but in fact it is not.)
 
 /me squints.

 Please tell me that this isn't reversible.

Tell me what you mean by reversible.  You can't, for instance,
extract the items in the set.

-- 
Aaron Denney
--

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


[Haskell-cafe] hint / ghc api and reloading modules

2008-05-31 Thread Evan Laforge
I'm using hint, but since it's basically a thin wrapper around the
GHC API, this is probably a GHC api question too.  Maybe this should
go to cvs-ghc?  Let me know and I'll go subscribe over there.

It's my impression from the documentation that I should be able to
load a module interpreted, make changes to it, and then reload it.
This is, after all what ghci does.  It's also my impression that the
other imported modules should be loaded as object files, if the .hi
and .o exist, since this is also what ghci does.

However, if I load a module and run code like so (using hint):

GHC.loadModules [Cmd.LanguageEnviron]
GHC.setTopLevelModules [Cmd.LanguageEnviron]
GHC.setImports [Prelude]
cmd_func - GHC.interpret (mangle_code text) (GHC.as :: LangType)

It works fine until I change LanguageEnviron.  If I make a change to a
function, I don't see my changes in the output, as if the session is
only getting partially reset.  If I insert a syntax error, then I do
see it, so it is recompiling the file in some way.  However, if I
*rename* the function and call it with the new name, I get a
GhcException:

During interactive linking, GHCi couldn't find the following symbol:
  ... etc.

So I examined the code in hint for loadModules and the code in
ghci/InteractiveUI.hs:/loadModule, and they do look like they're doing
basically the same things, except a call to rts_revertCAFs, which I
called too just for good measure but it didn't help (I can't find its
source anywhere, but the ghci docs imply it's optional, so I suspect
it's a red herring).

Here's a condensed summary of what hint is doing:
-- reset
GHC.setContext session [] []
GHC.setTargets session []
GHC.load session GHC.LoadAllTargets
-- rts_revertCAFs

-- load
targets - mapM (\f - GHC.guessTarget f Nothing) fs
GHC.setTargets session targets
GHC.load session GHC.LoadAllTargets

-- interpret
let expr_typesig = ($expr) :: xyz
expr_val - GHC.compileExpr session expr_typesig
return (GHC.Exts.unsafeCorce# expr_val :: a)

-- GHC.compileExpr
maybe_stuff - hscStmt hsc_env (let __cmCompileExpr = ++expr)
([n],[hv]) - (unsafeCoerce# hval) :: IO [HValue]
return (Just hv)


and then ghci does:
-- load
GHC.setTargets session []
GHC.load session LoadAllTargets

targets - io (mapM (uncurry GHC.guessTarget) files')
GHC.setTargets session targets
GHC.load session LoadAllTargets

rts_revertCAFs
putStrLn Ok, modules loaded: $modules

-- interpret
GHC.runStmt session stmt step

-- GHC.runStmt
Just (ids, hval) - hscStmt hsc_env' expr
coerce hval to (IO [HValue]) and run it carefully


So it *looks* like I'm doing basically the same thing as ghci...
except obviously I'm not because ghci reloads modules without any
trouble.  Before I go start trying to make hint even more identical to
ghci, is there anything obviously wrong here that I'm doing?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: [ANN] bloomfilter 1.0 - Fast immutable and mutable Bloom filters

2008-05-31 Thread Achim Schneider
Aaron Denney [EMAIL PROTECTED] wrote:

 On 2008-05-30, Achim Schneider [EMAIL PROTECTED] wrote:
  Bryan O'Sullivan [EMAIL PROTECTED] wrote:
 
  A Bloom filter is a probabilistic data
  structure that provides a fast set membership querying capability.
  It does not give false negatives, but has a tunable false positive
  rate.  (A false positive arises when the filter claims that an
  element is present, but in fact it is not.)
  
  /me squints.
 
  Please tell me that this isn't reversible.
 
 Tell me what you mean by reversible.  You can't, for instance,
 extract the items in the set.
 
I guess invertible would have been the right word, though it's still
ambiguous.

Turning it into something that does not give false positives, but has a
tunable false negative rate.

Without looking at the algorithm, I imagine it working somewhat like a
hashtable, and this inversion would utterly destroy my intuition.

-- 
(c) this sig last receiving data processing entity. Inspect headers for
past copyright information. All rights reserved. Unauthorised copying,
hiring, renting, public performance and/or broadcasting of this
signature prohibited. 

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


[Haskell-cafe] hmatrix

2008-05-31 Thread Anatoly Yakovenko
What is the most efficient way to update a position in a matrix or a
vector?  I came up with this:

updateVector :: Vector Double - Int - Double - Vector Double
updateVector vec pos val = vec `add` v2
   where
  v2 = fromList $ (replicate (pos) 0.0) ++ ((val - (vec @
pos)):(replicate ((dim vec)- pos - 1) 0.0))

but this seems pretty inefficient to me.

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


Re: [Haskell-cafe] hmatrix

2008-05-31 Thread Thomas Hartman
what package do you install/import to get at Vector?

2008/5/31 Thomas Hartman [EMAIL PROTECTED]:
 what package do you install/import to get at Vector?

 2008/5/31 Anatoly Yakovenko [EMAIL PROTECTED]:
 What is the most efficient way to update a position in a matrix or a
 vector?  I came up with this:

 updateVector :: Vector Double - Int - Double - Vector Double
 updateVector vec pos val = vec `add` v2
   where
  v2 = fromList $ (replicate (pos) 0.0) ++ ((val - (vec @
 pos)):(replicate ((dim vec)- pos - 1) 0.0))

 but this seems pretty inefficient to me.

 thanks,
 Anatoly
 ___
 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: [ANN] bloomfilter 1.0 - Fast immutable and mutable Bloom filters

2008-05-31 Thread Jim Snow

Achim Schneider wrote:

Aaron Denney [EMAIL PROTECTED] wrote:

  

On 2008-05-30, Achim Schneider [EMAIL PROTECTED] wrote:


Bryan O'Sullivan [EMAIL PROTECTED] wrote:

  

A Bloom filter is a probabilistic data
structure that provides a fast set membership querying capability.
It does not give false negatives, but has a tunable false positive
rate.  (A false positive arises when the filter claims that an
element is present, but in fact it is not.)



/me squints.

Please tell me that this isn't reversible.
  

Tell me what you mean by reversible.  You can't, for instance,
extract the items in the set.



I guess invertible would have been the right word, though it's still
ambiguous.

Turning it into something that does not give false positives, but has a
tunable false negative rate.

Without looking at the algorithm, I imagine it working somewhat like a
hashtable, and this inversion would utterly destroy my intuition.
  
Without looking at the code to verify that this is how it has really 
been implemented, a bloom filter is like a series of hash tables, where 
the hash table entries are one bit.  The bit is set if there is an item 
that hashes to that value in the bloom filter.  So, assuming a single 
hash table where half the bits are set, there's a 50% false positive 
rate and no false negatives when you do a membership test.


To reduce the false positives, we can add another hash table with a 
different hash function.  Assuming it also is half full, we can check if 
an item is in both tables, and our false positive rate drops to 25%.


In practice, one might use something like 32 hash tables.  This yields a 
false positive rate of 1/(2^32).  Their most obvious application is to 
store the dictionary for a spell checker in a space-efficient way, 
though I have a friend who wrote a paper on using them for router caches.


There was a google tech talk on bloom filters awhile ago: 
http://www.youtube.com/watch?v=947gWqwkhu0


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


[Haskell-cafe] Images and GUIs in Haskell

2008-05-31 Thread Ronald Guida
Two questions:

1. In a Haskell program, if all I want to do is output an image, like
a graph or chart, what is the simplest library to use?

N.B. Simpler := easier to get minimal functionality. I really don't
want to wade through a bunch of boilerplate or climb a steep learning
curve just to be able to plot a few lines or circles.

2. Suppose I want interactivity.  For example, I want to plot a line
graph, and then let the user click and drag the data points.  From
what I understand about GUIs, I would need to track mouse buttons (up
and down), mouse movements, and possibly keystrokes.  (I know this is
the complete opposite extreme from my first question)

In this case, what would be the best (not necessarily simplest)
library to use?  What would you recommend?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: type-level integers using type families

2008-05-31 Thread Peter Gavin

Replying to myself...

I put a copy of the darcs repo at http://code.haskell.org/~pgavin/tfp, 
if anyone is interested.


Pete

Peter Gavin wrote:

Has anyone else tried implementing type-level integers using type families?

I tried using a couple of other type level arithmetic libraries 
(including type-level on Hackage) and they felt a bit clumsy to use.  I 
started looking at type families and realized I could pretty much build 
an entire Scheme-like language based on them.


In short, I've got addition, subtraction,  multiplication working after 
just a days worth of hacking. I'm going to post the darcs archive 
sometime, sooner if anyone's interested.


I really like the type-families based approach to this, it's a lot 
easier to understand, and you can think about things functionally 
instead of relationally.  (Switching back and forth between Prolog-ish 
thinking and Haskell gets old quick.) Plus you can do type arithmetic 
directly in place, instead of using type classes everywhere.


One thing that I'd like to be able to do is lazy unification on type 
instances, so that things like


data True
data False

type family Cond x y z
type instance Cond True y z = y
type instance Cond False y z = z

will work if the non-taken branch can't be unified with anything.  Is 
this planned? Is it even feasible?


I'm pretty sure it would be possible to implement a Lambda like this, 
but I'm not seeing it yet. Any ideas?


Pete


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


[Haskell-cafe] Re: Images and GUIs in Haskell

2008-05-31 Thread Achim Schneider
Ronald Guida [EMAIL PROTECTED] wrote:

 Two questions:
 
 1. In a Haskell program, if all I want to do is output an image, like
 a graph or chart, what is the simplest library to use?
 
 N.B. Simpler := easier to get minimal functionality. I really don't
 want to wade through a bunch of boilerplate or climb a steep learning
 curve just to be able to plot a few lines or circles.
 
 2. Suppose I want interactivity.  For example, I want to plot a line
 graph, and then let the user click and drag the data points.  From
 what I understand about GUIs, I would need to track mouse buttons (up
 and down), mouse movements, and possibly keystrokes.  (I know this is
 the complete opposite extreme from my first question)
 
 In this case, what would be the best (not necessarily simplest)
 library to use?  What would you recommend?

http://hackage.haskell.org/packages/archive/pkg-list.html#cat:Graphics
or
Gnuplot

YMMV.

-- 
(c) this sig last receiving data processing entity. Inspect headers for
past copyright information. All rights reserved. Unauthorised copying,
hiring, renting, public performance and/or broadcasting of this
signature prohibited. 

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


Re: [Haskell-cafe] Re: Images and GUIs in Haskell

2008-05-31 Thread Ronald Guida
I wrote:
 1. In a Haskell program, if all I want to do is output an image, like
 a graph or chart, what is the simplest library to use?

Achim Schneider wrote:
 http://hackage.haskell.org/packages/archive/pkg-list.html#cat:Graphics

OK, Chart (the first package under Graphics) is obviously the answer to (1).

I wrote:
 2. Suppose I want interactivity.  For example, I want to plot a line
 graph, and then let the user click and drag the data points.  ...
 the complete opposite extreme from my first question

So I have a choice: OpenGL, HGL, SDL, ObjectIO(?), or even straight X11/Win32 :/
Let me ask both ways:

2a. Which of these (or perhaps something else) is the simplest/easiest
to get started with?

2b. Could someone please point me to some advice to help me decide
which of these would be the best for me to use.  I'm just trying to
avoid the need to invest gobs of time into investigating libraries.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Images and GUIs in Haskell

2008-05-31 Thread Achim Schneider
Ronald Guida [EMAIL PROTECTED] wrote:

 So I have a choice: OpenGL, HGL, SDL, ObjectIO(?), or even straight
 X11/Win32 :/ Let me ask both ways:
 
 2a. Which of these (or perhaps something else) is the simplest/easiest
 to get started with?
 
 2b. Could someone please point me to some advice to help me decide
 which of these would be the best for me to use.  I'm just trying to
 avoid the need to invest gobs of time into investigating libraries.

I would go for GL(U(T)), as it's as good for 2d primitives as SDL will
ever be, has excellent cross-platform support and allows you to go 3d
if you want to. There's also some very decent event handling.

-- 
(c) this sig last receiving data processing entity. Inspect headers for
past copyright information. All rights reserved. Unauthorised copying,
hiring, renting, public performance and/or broadcasting of this
signature prohibited. 

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


Re: [Haskell-cafe] hint / ghc api and reloading modules

2008-05-31 Thread Daniel GorĂ­n
(Since this can be of interest to those using the ghc-api I'm cc-ing  
the ghc users' list.)


Hi, Evan

The odd behavior you spotted happens only with hint under ghc-6.8. It  
turns out the problem was in the session initialization.


Since ghc-6.8 the newSession function no longer receives a GhcMode.  
The thing is that, apparently, if one was passing the Interactive  
mode to newSession under ghc-6.6, now you ought to set the ghcLink  
dynflag to LinkInMemory instead.


I couldn't find this documented anywhere (except for this patch  
http://www.haskell.org/pipermail/cvs-ghc/2007-April/034974.html) but  
it is what ghci is doing and after patching hint to do this the  
reloading of modules works fine.


I'll be uploading a fixed version of hint to hackage in the next days.

Thanks,
Daniel

On May 31, 2008, at 2:46 PM, Evan Laforge wrote:


I'm using hint, but since it's basically a thin wrapper around the
GHC API, this is probably a GHC api question too.  Maybe this should
go to cvs-ghc?  Let me know and I'll go subscribe over there.

It's my impression from the documentation that I should be able to
load a module interpreted, make changes to it, and then reload it.
This is, after all what ghci does.  It's also my impression that the
other imported modules should be loaded as object files, if the .hi
and .o exist, since this is also what ghci does.

However, if I load a module and run code like so (using hint):

GHC.loadModules [Cmd.LanguageEnviron]
GHC.setTopLevelModules [Cmd.LanguageEnviron]
GHC.setImports [Prelude]
cmd_func - GHC.interpret (mangle_code text) (GHC.as :: LangType)

It works fine until I change LanguageEnviron.  If I make a change to a
function, I don't see my changes in the output, as if the session is
only getting partially reset.  If I insert a syntax error, then I do
see it, so it is recompiling the file in some way.  However, if I
*rename* the function and call it with the new name, I get a
GhcException:

During interactive linking, GHCi couldn't find the following symbol:
  ... etc.

So I examined the code in hint for loadModules and the code in
ghci/InteractiveUI.hs:/loadModule, and they do look like they're doing
basically the same things, except a call to rts_revertCAFs, which I
called too just for good measure but it didn't help (I can't find its
source anywhere, but the ghci docs imply it's optional, so I suspect
it's a red herring).

Here's a condensed summary of what hint is doing:
-- reset
GHC.setContext session [] []
GHC.setTargets session []
GHC.load session GHC.LoadAllTargets
-- rts_revertCAFs

-- load
targets - mapM (\f - GHC.guessTarget f Nothing) fs
GHC.setTargets session targets
GHC.load session GHC.LoadAllTargets

-- interpret
let expr_typesig = ($expr) :: xyz
expr_val - GHC.compileExpr session expr_typesig
return (GHC.Exts.unsafeCorce# expr_val :: a)

-- GHC.compileExpr
maybe_stuff - hscStmt hsc_env (let __cmCompileExpr = ++expr)
([n],[hv]) - (unsafeCoerce# hval) :: IO [HValue]
return (Just hv)


and then ghci does:
-- load
GHC.setTargets session []
GHC.load session LoadAllTargets

targets - io (mapM (uncurry GHC.guessTarget) files')
GHC.setTargets session targets
GHC.load session LoadAllTargets

rts_revertCAFs
putStrLn Ok, modules loaded: $modules

-- interpret
GHC.runStmt session stmt step

-- GHC.runStmt
Just (ids, hval) - hscStmt hsc_env' expr
coerce hval to (IO [HValue]) and run it carefully


So it *looks* like I'm doing basically the same thing as ghci...
except obviously I'm not because ghci reloads modules without any
trouble.  Before I go start trying to make hint even more identical to
ghci, is there anything obviously wrong here that I'm doing?
___
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] hmatrix

2008-05-31 Thread Anatoly Yakovenko
http://perception.inf.um.es/~aruiz/darcs/hmatrix/doc/html/Data-Packed-Vector.html
provided by hmatrix

On Sat, May 31, 2008 at 3:20 PM, Thomas Hartman [EMAIL PROTECTED] wrote:
 what package do you install/import to get at Vector?

 2008/5/31 Thomas Hartman [EMAIL PROTECTED]:
 what package do you install/import to get at Vector?

 2008/5/31 Anatoly Yakovenko [EMAIL PROTECTED]:
 What is the most efficient way to update a position in a matrix or a
 vector?  I came up with this:

 updateVector :: Vector Double - Int - Double - Vector Double
 updateVector vec pos val = vec `add` v2
   where
  v2 = fromList $ (replicate (pos) 0.0) ++ ((val - (vec @
 pos)):(replicate ((dim vec)- pos - 1) 0.0))

 but this seems pretty inefficient to me.

 thanks,
 Anatoly
 ___
 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] type-level integers using type families

2008-05-31 Thread Bertram Felgenhauer
Peter Gavin wrote:
 Roberto Zunino wrote:
 Maybe he wants, given
   cond :: Cond x y z = x - y - z
   tt :: True
   true_exp  :: a
   false_exp :: untypable
 that
   cond tt true_exp false_exp :: a
 That is the type of false_exp is lazily inferred, so that type errors
 do not make inference fail if they show up in an unneeded place.

 Yes, that's exactly what I want, but for type families (not MPTC). I think 
 it could be done if the type arguments were matched one at a time, across 
 all visible instances.

What do you think of the following idea?

Using naive type level natural numbers,

 data Zero
 newtype Succ a = Succ a

Booleans,

 data True
 data False

comparison,

 type family (::) x y
 type instance (Zero   :: Succ a) = True
 type instance (Zero   :: Zero  ) = False
 type instance (Succ a :: Zero  ) = False
 type instance (Succ a :: Succ b) = a :: b

difference,

 type family Minus x y
 type instance Minus aZero = a
 type instance Minus (Succ a) (Succ b) = Minus a b

and a higher order type level conditional,

 type family Cond2 x :: (* - * - *) - (* - * - *) - * - * - *
 type First2  (x :: * - * - *) (y :: * - * - *) = x
 type Second2 (x :: * - * - *) (y :: * - * - *) = y
 type instance Cond2 True  = First2
 type instance Cond2 False = Second2

we can define division as follows:

 type family Div x y
 type DivZero x y = Zero
 type DivStep x y = Succ (Div (Minus0 x y) y)
 type instance Div x y = Cond2 (x :: y) DivZero DivStep x y

It's not exactly what you asked for, but I believe it gets the effect
that you wanted.

Enjoy,

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