Re: [Haskell-cafe] Performance of functional priority queues

2009-12-24 Thread Matt Morrow
On 12/23/09, Jon Harrop j...@ffconsultancy.com wrote: And your results above indicate that the fastest imperative heap is over 3x faster than the fastest functional heap? It's saying that (1) Using an imprecise an inefficient-relative-to-a-accurate-GC-that-doesn't-

Re: [Haskell-cafe] Performance of functional priority queues

2009-12-24 Thread Matt Morrow
On 12/25/09, Matt Morrow moonpa...@gmail.com wrote: On 12/23/09, Jon Harrop j...@ffconsultancy.com wrote: And your results above indicate that the fastest imperative heap is over 3x faster than the fastest functional heap? Also, I've now added you to (1) my list of people never to hire

Re: [Haskell-cafe] FGL/Haskell and Hierarchical Clustering/dendograms

2009-12-23 Thread Matt Morrow
Hi Nikolas, Interesting problem. I'd do something like the following, where the initial spanning tree from you example (re-tree-ified) is: {- ghci :t t t :: Tree (Id, Cost) g ghci ppT t (4,0) | +- (3,1) | | | `- (1,1) | `- (2,3) | `- (5,12) -} and which results in the tree: {- ghci let

Re: [Haskell-cafe] FGL/Haskell and Hierarchical Clustering/dendograms

2009-12-23 Thread Matt Morrow
] -} --- Matt On 12/23/09, Matt Morrow moonpa...@gmail.com wrote: Hi Nikolas, Interesting problem. I'd do something like the following, where the initial spanning tree from you example (re-tree-ified) is: {- ghci :t t t :: Tree (Id, Cost) g ghci ppT t

Re: [Haskell-cafe] Boxed Mutable Arrays

2009-12-15 Thread Matt Morrow
What are peoples' thoughts on this? http://hackage.haskell.org/trac/ghc/ticket/650#comment:16 Matt On 12/14/09, Brad Larsen brad.lar...@gmail.com wrote: Is anyone working on fixing ticket #650 http://hackage.haskell.org/trac/ghc/ticket/650? In short, STArray and the garbage collector don't

Re: [Haskell-cafe] Re: can there be (hash-table using) O(n) version of this (I think currently) n log n algo?

2009-12-09 Thread Matt Morrow
Never underestimate teh power of the Int{Set,Map}: {-# LANGUAGE BangPatterns #-} import Data.Set(Set) import Data.IntSet(IntSet) import qualified Data.Set as S import qualified Data.IntSet as IS import Control.Parallel.Strategies(rnf) import Data.Monoid(Monoid(..)) import Data.List findsumsIS ::

Re: [Haskell-cafe] GHC magic optimization ?

2009-12-04 Thread Matt Morrow
Although, in Luke's example, x = sum [1..10^6] + product [1..10^6] x' = let l = [1..10^6] in sum l + product l We can do much much better, if we're sufficiently smart. -- Define: bar m n = foo (enumFromTo m n) foo xs = sum xs + prod xs -- We're given: sum = foldl (+) 0 product = foldl (*) 1

Re: [Haskell-cafe] inotify-alike for mac os x?

2009-12-04 Thread Matt Morrow
Conal, If I were looking to do this, I'd read the relevant parts of the libev code. Matt On 12/3/09, Conal Elliott co...@conal.net wrote: I'd like to make some FRPish toys that keep files updated to have functional relationships with other files. hinotify looks like just the sort of

Re: [Haskell-cafe] GHC magic optimization ?

2009-12-04 Thread Matt Morrow
] + product [1..10^6] x' = let l = [1..10^6] in sum l + product l -- We get: x' = bar 1 (10^6) Matt On 12/4/09, Matt Morrow moonpa...@gmail.com wrote: Although, in Luke's example, x = sum [1..10^6] + product [1..10^6] x' = let l = [1..10^6] in sum l + product l We can do much much better

Re: [Haskell-cafe] x - String

2009-10-18 Thread Matt Morrow
On 10/17/09, Andrew Coppin andrewcop...@btinternet.com wrote: Derek Elkins wrote: See vacuum: http://hackage.haskell.org/package/vacuum Could be useful... Thanks! As Derek mentioned, vacuum would be perfect for this:

Re: [Haskell-cafe] Lightweight type-level dependent programming in Haskell

2009-06-11 Thread Matt Morrow
I like this one: - data N a where Z :: N () N :: N a - N (N a) type family Nest n (f ::* - *)a nest :: N n - (forall a. a - f a) - a - Nest n f a type instance Nest () f a = f a nest

Re: [Haskell-cafe] Haskell and symbolic references

2009-05-31 Thread Matt Morrow
(i always forget to reply-to-all) If you'd like to reference C functions with Strings, one possible way is to use System.Posix.DynamicLinker and the wrapper over libffi that's been uploaded to hackage recently: [...@monire asdf]$ ghci GHCi, version 6.10.1: http://www.haskell.org/ghc/ :? for

Re: [Haskell-cafe] Template Haskell very wordy w/r/t Decs and Types

2009-05-27 Thread Matt Morrow
Spectacular! How difficult would it be to implement splicing in decls? I'm interested in having a go at it, and it seems like a perfect time since I can cheat off the fresh diff. In particular I'd love to be able to do stuff like this (without the current vicious hackery i'm using) (and granted,

[Haskell-cafe] O LANGUAGE DESIGNER, REMEMBER THE POOR USER

2009-04-16 Thread Matt Morrow
This is interesting (and from 1990): http://groups.google.co.uk/group/comp.lang.functional/msg/655bb7bbd0fd8586 (Not sure if this is well-known. It seems like it either is, or it should be. Either way, I just stumbled across it.) ___ Haskell-Cafe

[Haskell-cafe] Re: O LANGUAGE DESIGNER, REMEMBER THE POOR USER

2009-04-16 Thread Matt Morrow
. On purity: I want a language that is not purely functional because functional languages do not reflect the basic structure of computers. If you want to write a matrix inversion algorithm it will be hard to do it efficiently without assignment. Matt On Thu, Apr 16, 2009 at 7:04 PM, Matt Morrow moonpa

Re: [Haskell-cafe] Code Golf

2009-04-15 Thread Matt Morrow
I think this has the semantics you're looking for. (it would probably be somewhat prettier if mappend wasn't such an ugly identifier (compared to, say, (++)), but this is just me trying to sneak a shot in against the Monoid method's names ;) ghci let diag = foldr (curry (prod mappend fst snd .

Re: [Haskell-cafe] Code Golf

2009-04-15 Thread Matt Morrow
*..against Monoid's method names. On Wed, Apr 15, 2009 at 9:59 PM, Matt Morrow moonpa...@gmail.com wrote: ... against the Monoid method's names. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell

Re: [Haskell-cafe] Code Golf

2009-04-15 Thread Matt Morrow
And i forgot to include the defs of (co)prod: coprod () i1 i2 = (\a b - i1 a i2 b) prod () p1 p2 = (\a - p1 a p2 a) diag = foldr (curry (prod mappend fst snd . uncurry (coprod mappend (splitAt 2)

Re: [Haskell-cafe] Strange type error with associated type synonyms

2009-04-07 Thread Matt Morrow
On Mon, Apr 6, 2009 at 7:39 PM, Manuel M T Chakravarty c...@cse.unsw.edu.au wrote: Peter Berry: 3) we apply appl to x, so Memo d1 a = Memo d a. unify d = d1 But for some reason, step 3 fails. Step 3 is invalid - cf, http://www.haskell.org/pipermail/haskell-cafe/2009-April/059196.html.

Re: [Haskell-cafe] Re: ANNOUNCE: vacuum-cairo: a cairo frontend to vacuum for live Haskell data visualization

2009-04-02 Thread Matt Morrow
Very nice. Gleb Alexeyev gleb.alex...@gmail.com wrote: http://hackage.haskell.org/cgi-bin/hackage-scripts/package/vacuum-ubigraph ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Re: ANNOUNCE: vacuum-cairo: a cairo frontend to vacuum for live Haskell data visualization

2009-04-01 Thread Matt Morrow
Morrow's vacuum library. Awesome stuff, kudos to you and Matt Morrow! I thought it'd be fun to visualize data structures in three dimensions. Attached is quick and dirty hack based on your code and Ubigraph server ( http://ubietylab.net/ubigraph/). The demo video (apologies for poor quality

[Haskell-cafe] ANNOUNCE: vacuum: extract graph representations of ghc heap values.

2009-03-30 Thread Matt Morrow
I am pleased to announce the release of vacuum, a Haskellhttp://haskell.org/library for extracting graph representations of values from the GHC http://haskell.org/ghc/ heap, which may then be further processed and/or translated to Graphviz http://graphviz.org/ dot format to be visualized. The

[Haskell-cafe] ANNOUNCE: vacuum: extract graph representations of ghc heap values. (take 2)

2009-03-30 Thread Matt Morrow
I am pleased to announce the release of vacuum, a library for extracting graph representations of values from the GHC heap, which may then be further processed and/or translated to Graphviz dot format to be visualized. The package website is at http://moonpatio.com/vacuum/ , which contains a

[Haskell-cafe] (no subject)

2009-01-21 Thread Matt Morrow
Hi, I managed to miss not one, but two separate emails containing patches to haskell-src meta. My sincere apologies to those who've sent me patches. I'll be applying them among other improvement to src-meta and will update the package on hackage in short time (today :). Matt

Re: [Haskell-cafe] haskell-src-meta Package

2009-01-21 Thread Matt Morrow
Hi, I managed to miss not one, but two separate emails containing patches to haskell-src meta. My sincere apologies to those who've sent me patches. I'll be applying them among other improvement to src-meta and will update the package on hackage in short time (today :). Matt

Re: [Haskell-cafe] Type Family Relations

2009-01-05 Thread Matt Morrow
Generalizing the previous post, with: - {-# LANGUAGE GADTs #-} module Equ where data a:==:b where Equ :: (a ~ b) = a:==:b symm :: (a:==:a) symm = Equ refl :: (a:==:b) - (b:==:a) refl Equ = Equ trans :: (a:==:b) -

Re: [Haskell-cafe] Haskell syntax inside QuasiQuote

2008-10-28 Thread Matt Morrow
Ooh, interesting. I'm going to look into this.. On 10/28/08, Reiner Pope [EMAIL PROTECTED] wrote: Unfortunately, I've uncovered a problem in the parser. For instance, with your module, [$hs|1+1*2|] evaluates to 4 rather than 3. This seems to be a general problem with infix operators, which I

Re: [Haskell-cafe] Haskell syntax inside QuasiQuote

2008-10-26 Thread Matt Morrow
to the pkg over the next few days. Cheers, Matt On 10/21/08, Reiner Pope [EMAIL PROTECTED] wrote: It sounds like you're doing exactly what I'm looking for. I look forward to more. Reiner On Tue, Oct 21, 2008 at 4:28 PM, Matt Morrow [EMAIL PROTECTED] wrote: Is there a simple way to do this, i.e

Re: [Haskell-cafe] Haskell syntax inside QuasiQuote

2008-10-20 Thread Matt Morrow
Is there a simple way to do this, i.e. using existing libraries? Yes indeed. I'll be traveling over the next two days, and am shooting for a fully functional hackage release by mid next week. What I need is a Haskell expression parser which outputs values of type

Re: [Haskell-cafe] Multi-line string literals are both easy /and/elegant in Haskell

2008-10-14 Thread Matt Morrow
On 10/13/08, Andrew Coppin wrote: Cool. Is there any progress on getting GHC to *not* freak out when you ask it to compile a CAF containing several hundred KB of string literal? :-} Yes and no. There's dons' compiled-constants pkg which has a solution:

[Haskell-cafe] Re: Multi-line string literals are both easy /and/ elegant in Haskell

2008-10-14 Thread Matt Morrow
How exactly QuasiQuote behave, and what is available to handle them? (Or: can I find information already on the web?) A QuasiQuoter is data QuasiQuoter = QuasiQuoter {quoteExp :: String - Q Exp, quotePat :: String - Q Pat} -- Defined in Language.Haskell.TH.Quote

[Haskell-cafe] Multi-line string literals are both easy /and/ elegant in Haskell

2008-10-13 Thread Matt Morrow
The new QuasiQuotes extension arriving with ghc 6.10 is very exciting, and handling multi-line string literals is like stealing candy from a baby. ;) - -- Here.hs module Here (here) where import Language.Haskell.TH.Quote

[Haskell-cafe] Types and Trees

2008-09-03 Thread Matt Morrow
I really learned a lot from writing the below code, and thought I'd share it with the group. I'm slightly at a loss for words, having just spent the last two hours on this when I most certainly should have been doing other work, but these are two hours I won't regret. I'm very interested in