Re: [Haskell-cafe] Images in Haddock documentation: best practices?

2011-12-25 Thread Magnus Therning
On Sun, Dec 25, 2011 at 01:02:57AM -0500, Antoine Latter wrote:
 On Sun, Dec 25, 2011 at 12:04 AM, Brent Yorgey byor...@seas.upenn.edu wrote:
  Hi all,
 
  Although it doesn't seem to be documented in the user manual (!),
  Haddock supports inline images, using a url syntax.  I'd like to
  include some images in the documentation for a package I'm writing,
  but not sure of the best way.
 
 
 In case nothing else works out:
 
 http://en.wikipedia.org/wiki/Data_URI_scheme
 
 They do not work in IE 7, and in IE 9 they are limited to 32k.

Just a small correction, the page on wikipedia says that *IE 8* is
limited to 32k, and that *IE 9* doesn't have that limitation.

/M

-- 
Magnus Therning  OpenPGP: 0xAB4DFBA4 
email: mag...@therning.org   jabber: mag...@therning.org
twitter: magthe   http://therning.org/magnus


Perl is another example of filling a tiny, short-term need, and then
being a real problem in the longer term.
 -- Alan Kay


pgphC7jA5LaHl.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Siege, a DBMS written in Haskell

2011-12-25 Thread Daniel Waterworth
Hi all,

This is what I've been working on recently in my spare time,
https://github.com/DanielWaterworth/siege . It's a DBMS written in
Haskell, it's in a partially working state, you can start it up and
interact with it using the redis protocol, it implements a subset of
redis's commands.

It stores it's data in immutable trees and supports two backends, one
where it stores data to disk and another where it stores it's
immutable nodes in a redis cluster and the head reference in
zookeeper; the plan is to be CP in CAP theory. Feel free to butcher it
for your own needs and I'd be really grateful to anyone who'd like to
contribute.

Daniel

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


[Haskell-cafe] Reifying case expressions [was: Re: On stream processing, and a new release of timeplot coming]

2011-12-25 Thread Heinrich Apfelmus

Eugene Kirpichov wrote:

In the last couple of days I completed my quest of making my graphing
utility timeplot ( http://jkff.info/software/timeplotters ) not load the
whole input dataset into memory and consequently be able to deal with
datasets of any size, provided however that the amount of data to *draw* is
not so large. On the go it also got a huge speedup - previously visualizing
a cluster activity dataset with a million events took around 15 minutes and
a gig of memory, now it takes 20 seconds and 6 Mb max residence.
(I haven't yet uploaded to hackage as I have to give it a bit more testing)

The refactoring involved a number of interesting programming patterns that
I'd like to share with you and ask for feedback - perhaps something can be
simplified.

The source is at http://github.com/jkff/timeplot

The datatype of incremental computations is at
https://github.com/jkff/timeplot/blob/master/Tools/TimePlot/Incremental.hs .
Strictness is extremely important here - the last memory leak I eliminated
was lack of bang patterns in teeSummary.


Your  StreamSummary  type has a really nice interpretation: it's a 
reification of  case  expressions.


For instance, consider the following simple function from lists to integers

length :: [a] - Int
length xs = case xs of
[] - 0
(y:ys) - 1 + length ys

We want to reify the case expression as constructor of a data type. What 
type should it have? Well, a case expression maps a list  xs  to a 
result, here of type Int, via two cases: the first case gives a result 
and the other maps a value of type  a  to a function from lists to 
results again. This explanation was probably confusing, so I'll just go 
ahead and define a data type that represents functions from lists  [a] 
to some result of type  r


data ListTo a r = CaseOf r (a - ListTo a r)

interpret :: ListTo a r - ([a] - r)
interpret (CaseOf nil cons) xs =
case xs of
[] - nil
(y:ys) - interpret (cons y) ys

As you can see, we are just mapping each  CaseOf  constructor back to a 
built-in case expression.


Likewise, each function from lists can be represented in terms of our 
new data type: simply replace all built-in case expressions with the new 
constructor


length' :: ListTo a Int
length' = CaseOf
(0)
(\x - fmap (1+) length')

length = interpret length'

The CaseOf may look a bit weird, but it's really just a straightforward 
translation of the case expression you would use to define the function 
 go  instead.


Ok, this length function is really inefficient because it builds a huge 
expression of the form  (1+(1+...)). Let's implement a strict variant 
instead


lengthL :: ListTo a Int
lengthL = go 0
where
go !n = CaseOf (n) (\x - go (n+1))

While we're at it, let's translate two more list functions

foldL' :: (b - a - b) - b - ListTo a b
foldL' f b = Case b (\a - foldL' f $! f b a)

sumL:: ListTo Int Int
sumL= foldL' (\b a - a+b) 0


And now we can go for the point of this message: unlike ordinary 
functions from lists, we can compose these in lock-step! In particular, 
the following applicative instance


instance Applicative (ListTo a) where
pure b = CaseOf b (const $ pure b)
(CaseOf f fs) * (CaseOf x xs) =
CaseOf (f x) (\a - fs a * xs a)

allows us to write a function

average :: ListTo Int Double
average = divide $ sumL * lengthL
where
divide a b = fromIntegral a / fromIntegral b

that runs in constant space! Why does this work? Well, since we can now 
inspect case expressions, we can choose to evaluate them in lock-step, 
essentially computing  sum  and  length  with just one pass over the 
input list. Remember that the original definition


average xs = sum xs / length xs

has a space leak because the input list xs is being shared.


Remarks:
1. Reified case expressions are, of course, the same thing as Iteratees, 
modulo chunking and weird naming.


2. My point is topped by scathing irony: if Haskell had a form of 
*partial evaluation*, we could write applicative combinators for 
*ordinary* functions  [a] - r  and express  average  in constant space. 
 In other words, partial evaluation would make it unnecessary to reify 
case expressions for the purpose of controlling performance / space leaks.



Best regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com


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


Re: [Haskell-cafe] strict, lazy, non-strict, eager

2011-12-25 Thread Yves Parès
2011/12/25 Tom Murphy amin...@gmail.com

  On the other hand:
  I'd _strongly_ argue against making up our minds about definitions
 within the Haskell community. Most of these concepts aren't
 Haskell-specific.
  An example of something to avoid is our definitions of concurrency
 and parallellism. We as a community have specific, good definitions of
 each term. [1] So does the Erlang community. [2] Yet the definitions don't
 have anything to do with each other, which makes talking across communities
 more difficult.


 amindfv / Tom


 [0] http://www.haskell.org/haskellwiki/Eager_evaluation

 [1]
 http://learnyousomeerlang.com/the-hitchhikers-guide-to-concurrency#dont-panic,
 paragraph 4

 [2]
 http://book.realworldhaskell.org/read/concurrent-and-multicore-programming.html,
 Defining concurrency and parallelism


I kindly beg to differ. To me concurrency and parallelism have global and
cross-language definitions.
The links you gave don't only define concurrency and parallelism in
absolute as they focus their definition around Erlang's and Haskell's *models
*of concurrency/parallelism. Still the broad idea remains.

 I'd _strongly_ argue against making up our minds about definitions
within the Haskell community. Most of these concepts aren't
Haskell-specific.

My referencial was Haskell-centric. And we can go by steps: first come to a
consensus within the Haskellers and then give broad definitions that
concerne every language.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Reifying case expressions [was: Re: On stream processing, and a new release of timeplot coming]

2011-12-25 Thread Eugene Kirpichov
Hello Heinrich,

Thanks, that's sure some food for thought!

A few notes:
* This is indeed analogous to Iteratees. I tried doing the same with
Iteratees but failed, so I decided to put together something simple of my
own.
* The Applicative structure over this stuff is very nice. I was thinking,
what structure to put on - and Applicative seems the perfect fit. It's also
possible to implement Arrows - but I once tried and failed; however, I was
trying that for a more complex stream transformer datatype (a hybrid of
Iteratee and Enumerator).
* StreamSummary is trivially a bifunctor. I actually wanted to make it an
instance of Bifunctor, but it was in the category-extras package and I
hesitated to reference this giant just for this purpose :) Probably
bifunctors should be in prelude.
* Whereas StreamSummary a r abstracts deconstruction of lists, the dual
datatype (StreamSummary a r -) abstracts construction; however I just now
(after looking at your first definition of length) understood that it is
trivially isomorphic to the regular list datatype - you just need to be
non-strict in the state - listify :: ListTo a [a] = CaseOf [] (\x - fmap
(x:) listify). So you don't need functions of the form (forall r . ListTo a
r - ListTo b r) - you just need (ListTo b [a]). This is a revelation for
me.

On Sun, Dec 25, 2011 at 2:25 PM, Heinrich Apfelmus 
apfel...@quantentunnel.de wrote:

 Eugene Kirpichov wrote:

 In the last couple of days I completed my quest of making my graphing
 utility timeplot ( 
 http://jkff.info/software/**timeplottershttp://jkff.info/software/timeplotters)
  not load the
 whole input dataset into memory and consequently be able to deal with
 datasets of any size, provided however that the amount of data to *draw*
 is
 not so large. On the go it also got a huge speedup - previously
 visualizing
 a cluster activity dataset with a million events took around 15 minutes
 and
 a gig of memory, now it takes 20 seconds and 6 Mb max residence.
 (I haven't yet uploaded to hackage as I have to give it a bit more
 testing)

 The refactoring involved a number of interesting programming patterns that
 I'd like to share with you and ask for feedback - perhaps something can be
 simplified.

 The source is at 
 http://github.com/jkff/**timeplothttp://github.com/jkff/timeplot

 The datatype of incremental computations is at
 https://github.com/jkff/**timeplot/blob/master/Tools/**
 TimePlot/Incremental.hshttps://github.com/jkff/timeplot/blob/master/Tools/TimePlot/Incremental.hs.
 Strictness is extremely important here - the last memory leak I eliminated
 was lack of bang patterns in teeSummary.


 Your  StreamSummary  type has a really nice interpretation: it's a
 reification of  case  expressions.

 For instance, consider the following simple function from lists to integers

length :: [a] - Int
length xs = case xs of
[] - 0
(y:ys) - 1 + length ys

 We want to reify the case expression as constructor of a data type. What
 type should it have? Well, a case expression maps a list  xs  to a result,
 here of type Int, via two cases: the first case gives a result and the
 other maps a value of type  a  to a function from lists to results again.
 This explanation was probably confusing, so I'll just go ahead and define a
 data type that represents functions from lists  [a] to some result of type
  r

data ListTo a r = CaseOf r (a - ListTo a r)

interpret :: ListTo a r - ([a] - r)
interpret (CaseOf nil cons) xs =
case xs of
[] - nil
(y:ys) - interpret (cons y) ys

 As you can see, we are just mapping each  CaseOf  constructor back to a
 built-in case expression.

 Likewise, each function from lists can be represented in terms of our new
 data type: simply replace all built-in case expressions with the new
 constructor

length' :: ListTo a Int
length' = CaseOf
(0)
(\x - fmap (1+) length')

length = interpret length'

 The CaseOf may look a bit weird, but it's really just a straightforward
 translation of the case expression you would use to define the function  go
  instead.

 Ok, this length function is really inefficient because it builds a huge
 expression of the form  (1+(1+...)). Let's implement a strict variant
 instead

lengthL :: ListTo a Int
lengthL = go 0
where
go !n = CaseOf (n) (\x - go (n+1))

 While we're at it, let's translate two more list functions

foldL' :: (b - a - b) - b - ListTo a b
foldL' f b = Case b (\a - foldL' f $! f b a)

sumL:: ListTo Int Int
sumL= foldL' (\b a - a+b) 0


 And now we can go for the point of this message: unlike ordinary functions
 from lists, we can compose these in lock-step! In particular, the following
 applicative instance

instance Applicative (ListTo a) where
pure b = CaseOf b (const $ pure b)
(CaseOf f fs) * (CaseOf x xs) =
CaseOf (f x) (\a - fs a * xs a)

 allows us to write a function

 

Re: [Haskell-cafe] Reifying case expressions [was: Re: On stream processing, and a new release of timeplot coming]

2011-12-25 Thread Eugene Kirpichov
On Mon, Dec 26, 2011 at 12:19 AM, Eugene Kirpichov ekirpic...@gmail.comwrote:

 Hello Heinrich,

 Thanks, that's sure some food for thought!

 A few notes:
 * This is indeed analogous to Iteratees. I tried doing the same with
 Iteratees but failed, so I decided to put together something simple of my
 own.
 * The Applicative structure over this stuff is very nice. I was thinking,
 what structure to put on - and Applicative seems the perfect fit. It's also
 possible to implement Arrows - but I once tried and failed; however, I was
 trying that for a more complex stream transformer datatype (a hybrid of
 Iteratee and Enumerator).
 * StreamSummary is trivially a bifunctor. I actually wanted to make it an
 instance of Bifunctor, but it was in the category-extras package and I
 hesitated to reference this giant just for this purpose :) Probably
 bifunctors should be in prelude.
 * Whereas StreamSummary a r abstracts deconstruction of lists, the dual
 datatype (StreamSummary a r -) abstracts construction; however I just now
 (after looking at your first definition of length) understood that it is
 trivially isomorphic to the regular list datatype - you just need to be
 non-strict in the state - listify :: ListTo a [a] = CaseOf [] (\x - fmap
 (x:) listify). So you don't need functions of the form (forall r . ListTo a
 r - ListTo b r) - you just need (ListTo b [a]). This is a revelation for
 me.

Oops, this is wrong!
You cannot create a working listify that would produce the list [1..] when
applied to the list [1..].
So production of elements also needs to be explicitly abstracted by the
dual type.



 On Sun, Dec 25, 2011 at 2:25 PM, Heinrich Apfelmus 
 apfel...@quantentunnel.de wrote:

 Eugene Kirpichov wrote:

 In the last couple of days I completed my quest of making my graphing
 utility timeplot ( 
 http://jkff.info/software/**timeplottershttp://jkff.info/software/timeplotters)
  not load the
 whole input dataset into memory and consequently be able to deal with
 datasets of any size, provided however that the amount of data to *draw*
 is
 not so large. On the go it also got a huge speedup - previously
 visualizing
 a cluster activity dataset with a million events took around 15 minutes
 and
 a gig of memory, now it takes 20 seconds and 6 Mb max residence.
 (I haven't yet uploaded to hackage as I have to give it a bit more
 testing)

 The refactoring involved a number of interesting programming patterns
 that
 I'd like to share with you and ask for feedback - perhaps something can
 be
 simplified.

 The source is at 
 http://github.com/jkff/**timeplothttp://github.com/jkff/timeplot

 The datatype of incremental computations is at
 https://github.com/jkff/**timeplot/blob/master/Tools/**
 TimePlot/Incremental.hshttps://github.com/jkff/timeplot/blob/master/Tools/TimePlot/Incremental.hs.
 Strictness is extremely important here - the last memory leak I
 eliminated
 was lack of bang patterns in teeSummary.


 Your  StreamSummary  type has a really nice interpretation: it's a
 reification of  case  expressions.

 For instance, consider the following simple function from lists to
 integers

length :: [a] - Int
length xs = case xs of
[] - 0
(y:ys) - 1 + length ys

 We want to reify the case expression as constructor of a data type. What
 type should it have? Well, a case expression maps a list  xs  to a result,
 here of type Int, via two cases: the first case gives a result and the
 other maps a value of type  a  to a function from lists to results again.
 This explanation was probably confusing, so I'll just go ahead and define a
 data type that represents functions from lists  [a] to some result of type
  r

data ListTo a r = CaseOf r (a - ListTo a r)

interpret :: ListTo a r - ([a] - r)
interpret (CaseOf nil cons) xs =
case xs of
[] - nil
(y:ys) - interpret (cons y) ys

 As you can see, we are just mapping each  CaseOf  constructor back to a
 built-in case expression.

 Likewise, each function from lists can be represented in terms of our new
 data type: simply replace all built-in case expressions with the new
 constructor

length' :: ListTo a Int
length' = CaseOf
(0)
(\x - fmap (1+) length')

length = interpret length'

 The CaseOf may look a bit weird, but it's really just a straightforward
 translation of the case expression you would use to define the function  go
  instead.

 Ok, this length function is really inefficient because it builds a huge
 expression of the form  (1+(1+...)). Let's implement a strict variant
 instead

lengthL :: ListTo a Int
lengthL = go 0
where
go !n = CaseOf (n) (\x - go (n+1))

 While we're at it, let's translate two more list functions

foldL' :: (b - a - b) - b - ListTo a b
foldL' f b = Case b (\a - foldL' f $! f b a)

sumL:: ListTo Int Int
sumL= foldL' (\b a - a+b) 0


 And now we can go for the point of this message: unlike 

Re: [Haskell-cafe] Reifying case expressions [was: Re: On stream processing, and a new release of timeplot coming]

2011-12-25 Thread Gábor Lehel
On Sun, Dec 25, 2011 at 9:19 PM, Eugene Kirpichov ekirpic...@gmail.com wrote:
 Hello Heinrich,

 Thanks, that's sure some food for thought!

 A few notes:
 * This is indeed analogous to Iteratees. I tried doing the same with
 Iteratees but failed, so I decided to put together something simple of my
 own.
 * The Applicative structure over this stuff is very nice. I was thinking,
 what structure to put on - and Applicative seems the perfect fit. It's also
 possible to implement Arrows - but I once tried and failed; however, I was
 trying that for a more complex stream transformer datatype (a hybrid of
 Iteratee and Enumerator).
 * StreamSummary is trivially a bifunctor. I actually wanted to make it an
 instance of Bifunctor, but it was in the category-extras package and I
 hesitated to reference this giant just for this purpose :) Probably
 bifunctors should be in prelude.

Edward Kmett has been splitting that up into a variety of smaller
packages, for instance:

http://hackage.haskell.org/package/bifunctors

 * Whereas StreamSummary a r abstracts deconstruction of lists, the dual
 datatype (StreamSummary a r -) abstracts construction; however I just now
 (after looking at your first definition of length) understood that it is
 trivially isomorphic to the regular list datatype - you just need to be
 non-strict in the state - listify :: ListTo a [a] = CaseOf [] (\x - fmap
 (x:) listify). So you don't need functions of the form (forall r . ListTo a
 r - ListTo b r) - you just need (ListTo b [a]). This is a revelation for
 me.

 On Sun, Dec 25, 2011 at 2:25 PM, Heinrich Apfelmus
 apfel...@quantentunnel.de wrote:

 Eugene Kirpichov wrote:

 In the last couple of days I completed my quest of making my graphing
 utility timeplot ( http://jkff.info/software/timeplotters ) not load the
 whole input dataset into memory and consequently be able to deal with
 datasets of any size, provided however that the amount of data to *draw*
 is
 not so large. On the go it also got a huge speedup - previously
 visualizing
 a cluster activity dataset with a million events took around 15 minutes
 and
 a gig of memory, now it takes 20 seconds and 6 Mb max residence.
 (I haven't yet uploaded to hackage as I have to give it a bit more
 testing)

 The refactoring involved a number of interesting programming patterns
 that
 I'd like to share with you and ask for feedback - perhaps something can
 be
 simplified.

 The source is at http://github.com/jkff/timeplot

 The datatype of incremental computations is at

 https://github.com/jkff/timeplot/blob/master/Tools/TimePlot/Incremental.hs .
 Strictness is extremely important here - the last memory leak I
 eliminated
 was lack of bang patterns in teeSummary.


 Your  StreamSummary  type has a really nice interpretation: it's a
 reification of  case  expressions.

 For instance, consider the following simple function from lists to
 integers

    length :: [a] - Int
    length xs = case xs of
        []     - 0
        (y:ys) - 1 + length ys

 We want to reify the case expression as constructor of a data type. What
 type should it have? Well, a case expression maps a list  xs  to a result,
 here of type Int, via two cases: the first case gives a result and the other
 maps a value of type  a  to a function from lists to results again. This
 explanation was probably confusing, so I'll just go ahead and define a data
 type that represents functions from lists  [a] to some result of type  r

    data ListTo a r = CaseOf r (a - ListTo a r)

    interpret :: ListTo a r - ([a] - r)
    interpret (CaseOf nil cons) xs =
        case xs of
            []     - nil
            (y:ys) - interpret (cons y) ys

 As you can see, we are just mapping each  CaseOf  constructor back to a
 built-in case expression.

 Likewise, each function from lists can be represented in terms of our new
 data type: simply replace all built-in case expressions with the new
 constructor

    length' :: ListTo a Int
    length' = CaseOf
        (0)
        (\x - fmap (1+) length')

    length = interpret length'

 The CaseOf may look a bit weird, but it's really just a straightforward
 translation of the case expression you would use to define the function  go
  instead.

 Ok, this length function is really inefficient because it builds a huge
 expression of the form  (1+(1+...)). Let's implement a strict variant
 instead

    lengthL :: ListTo a Int
    lengthL = go 0
        where
        go !n = CaseOf (n) (\x - go (n+1))

 While we're at it, let's translate two more list functions

    foldL' :: (b - a - b) - b - ListTo a b
    foldL' f b = Case b (\a - foldL' f $! f b a)

    sumL    :: ListTo Int Int
    sumL    = foldL' (\b a - a+b) 0


 And now we can go for the point of this message: unlike ordinary functions
 from lists, we can compose these in lock-step! In particular, the following
 applicative instance

    instance Applicative (ListTo a) where
        pure b = CaseOf b (const $ pure b)
        (CaseOf f fs) * 

Re: [Haskell-cafe] Composing Enumeratees in enumerator

2011-12-25 Thread Conrad Parker
On 24 December 2011 05:47, Michael Craig mks...@gmail.com wrote:
 I've been looking for a way to compose enumeratees in the enumerator
 package, but I've come up with nothing so far. I want this function

 (=$=) :: Monad m = Enumeratee a0 a1 m b - Enumeratee a1 a2 m b -
 Enumeratee a0 a2 m b

 I'm building a modular library on top of enumerator that facilitates reading
 time series data from a DB, applying any number of transformations to it,
 and then writing it back / doing something else with it. I'd like to be able
 to write simple transformations (enumeratees) and compose them without
 binding them to either a db reader (enumerator) or db writer (iteratee).

 I've been looking at the iterIO package as a possible alternative, because
 it seems to allow easy composition of Inums (enumeratees). I'm a little
 skittish of it because it seems unpopular next to enumerator.

Hi Michael,

You could also look at the iteratee package. This is the signature of
the () operator:

() :: (Nullable s1, Monad m) = (forall x. Enumeratee s1 s2 m x) -
Enumeratee s2 s3 m a - Enumeratee s1 s3 m a

it's quite useful for composing enumeratees, likewise its friend ()
swims the other way.

http://hackage.haskell.org/packages/archive/iteratee/0.8.7.5/doc/html/Data-Iteratee-Iteratee.html

cheers,

Conrad.

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