On stream processing, and a new release of timeplot coming

Hi Cafe, 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. There's an interesting function statefulSummary that shows how closures allow you to achieve encapsulation over an unknown piece of state - curiously enough, you can't define StreamSummary a r as StreamSummary { init :: s, insert :: a->s->s, finalize :: s->r } (existentially qualified over s), as then you can't define summaryByKey - you don't know what type to store in the states map. It is used to incrementally build all plots simultaneously, shown by the main loop in makeChart at https://github.com/jkff/timeplot/blob/master/Tools/TimePlot.hs Incremental building of plots of different types is at https://github.com/jkff/timeplot/blob/master/Tools/TimePlot/Plots.hs There are also a few interesting functions in that file - e.g. edges2eventsSummary, which applies a summary over a stream of "long" events to a stream of rise/fall edges. This means that you can define a "stream transformer" (Stream a -> Stream b) as a function (StreamSummary b -> StreamSummary a), which can be much easier. I have to think more about this idea. -- Eugene Kirpichov Principal Engineer, Mirantis Inc. http://www.mirantis.com/ Editor, http://fprog.ru/

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

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 < apfelmus@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
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-cafehttp://www.haskell.org/mailman/listinfo/haskell-cafe
-- Eugene Kirpichov Principal Engineer, Mirantis Inc. http://www.mirantis.com/ Editor, http://fprog.ru/

On Mon, Dec 26, 2011 at 12:19 AM, 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.
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 < apfelmus@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
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-cafehttp://www.haskell.org/mailman/listinfo/haskell-cafe
-- Eugene Kirpichov Principal Engineer, Mirantis Inc. http://www.mirantis.com/ Editor, http://fprog.ru/
-- Eugene Kirpichov Principal Engineer, Mirantis Inc. http://www.mirantis.com/ Editor, http://fprog.ru/

On Sun, Dec 25, 2011 at 9:19 PM, 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.
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
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) <*> (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
-- Eugene Kirpichov Principal Engineer, Mirantis Inc. http://www.mirantis.com/ Editor, http://fprog.ru/
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Work is punishment for failing to procrastinate effectively.

2011/12/26 Gábor Lehel
On Sun, Dec 25, 2011 at 9:19 PM, Eugene Kirpichov
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:
Actually it's not a bifunctor - it's a functor in one argument and contrafunctor in the other. Is there a name for such a structure?
* 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
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
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,
the 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
-- Eugene Kirpichov Principal Engineer, Mirantis Inc. http://www.mirantis.com/ Editor, http://fprog.ru/
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Work is punishment for failing to procrastinate effectively.
-- Eugene Kirpichov Principal Engineer, Mirantis Inc. http://www.mirantis.com/ Editor, http://fprog.ru/

On Mon, Dec 26, 2011 at 12:32:13PM +0400, Eugene Kirpichov wrote:
2011/12/26 Gábor Lehel
On Sun, Dec 25, 2011 at 9:19 PM, Eugene Kirpichov
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:
Actually it's not a bifunctor - it's a functor in one argument and contrafunctor in the other. Is there a name for such a structure?
"Bifunctor" is usually used for such things as well. Data.Bifunctor only covers bifunctors which are covariant in both arguments. -Brent

On 12/28/11 10:14 AM, Brent Yorgey wrote:
On Mon, Dec 26, 2011 at 12:32:13PM +0400, Eugene Kirpichov wrote:
Actually it's not a bifunctor - it's a functor in one argument and contrafunctor in the other. Is there a name for such a structure?
"Bifunctor" is usually used for such things as well. Data.Bifunctor only covers bifunctors which are covariant in both arguments.
I'd just call them (contra(variant)) bifunctors. Or, more likely, I'd call them hom-(bi)functors since chances are the bifunctor supports the full structure of a category. -- Live well, ~wren

On Sun, Dec 25, 2011 at 11:25 AM, Heinrich Apfelmus < apfelmus@quantentunnel.de> wrote:
Your StreamSummary type has a really nice interpretation: it's a reification of case expressions [on lists].
nice observation!
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. [...]
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
[...]
Likewise, each function from lists can be represented in terms of our new data type [...]
length' :: ListTo a Int length' = CaseOf (0) (\x -> fmap (1+) length')
length = interpret length'
This version of `length` is tail recursive while the previous version is not. In general, all functions defined in terms of `ListTo` and `interpret` are spine strict - they return a result only after consuming all input list constructors. This is what Eugene observed when defining the identity function as idC = CaseOf [] (\x -> (x:) <$> idC) This version does not work for infinite lists. Similarly, `head` and `take` cannot be defined as lazily as in the standard libraries. We can support lazier list consumers by adding a case to the ListTo type that allows to stop consuming the list. To avoid confusion, I chose new names for my new types. data ListConsumer a b = Done !b | Continue !b (a -> ListConsumer a b) The interpretation function just ignores the remaining input in the case of `Done`: consumeList :: ListConsumer a b -> [a] -> b consumeList (Done b) _ = b consumeList (Continue b _) [] = b consumeList (Continue _ f) (x:xs) = consumeList (f x) xs We can define lazier versions of `head` and `take` as follows: headC :: ListConsumer a a headC = Continue (error "head of empty list") Done takeC :: Int -> ListConsumer a [a] takeC 0 = Done [] takeC n = Continue [] (\x -> (x:) <$> takeC (n-1)) However, we still cannot define a lazy version of the identity funtion with list consumers. The identity function and `takeC` belong to a special case of a list consumers because they also *produce* lists. We can define a specialized type for list transformers that consume and produce lists. One advantage of this specialization will be that we can define a lazy version of the identity function. The transformer type can have functor and applicative instances similar to the consumer type to compose transformers in parallel. Additionally, it can have category and arrow instances to compose transformers sequentially. Here is a type for lazy list transformers: data ListTransformer a b = Cut | Put b (ListTransformer a b) | Get (a -> ListTransformer a b) A transformer can either cut off the input list and return the empty list, output a new element before transforming the input, or consume one element from the input list and transform the remaining elements. The interpretation function should make this clearer: transformList :: ListTransformer a b -> [a] -> [b] transformList Cut _ = [] transformList (Put b t) xs = b : transformList t xs transformList (Get _) [] = [] transformList (Get f) (x:xs) = transformList (f x) xs Note that, if the transformer wants to read another element that is not there, it simply returns the empty list. Now we can define a lazy identity function and another version of `take`: idT :: ListTransformer a a idT = Get (\x -> Put x idT) takeT :: Int -> ListTransformer a a takeT 0 = Cut takeT n = Get (\x -> Put x (takeT (n-1))) Here is another translation of a common list function: filterT :: (a -> Bool) -> ListTransformer a a filterT p = Get (\x -> if p x then Put x (filterT p) else filterT p) `filterT` is an example for a function that can consume several input elements before producing an output element. Other examples for functions of this kind are chunking functions: pairsT :: ListTransformer a (a,a) pairsT = Get (\x -> Get (\y -> Put (x,y) pairsT)) chunks :: Int -> ListTransformer a [a] chunks n = collect n where collect 0 = Put [] (chunks n) collect m = Get (\x -> collect (m-1) >>> Get (\xs -> Put (x:xs) id)) Here are some example calls in GHCi that demonstrate the category and applicative instances for sequential and parallel composition (see below for a link to the complete source code): ghci> transformList pairsT [1..5] [(1,2),(3,4)] -- 5 is ignored ghci> transformList pairsT [1..6] [(1,2),(3,4),(5,6)] ghci> transformList (chunks 2) [1..5] [[1,2],[3,4]] -- similar to pairsT ghci> transformList (chunks 3) [1..6] [[1,2,3],[4,5,6]] ghci> transformList (takeT 3 . chunks 3) [1..] -- infinite input [[1,2,3],[4,5,6],[7,8,9]] ghci> transformList ((,) <$> takeT 3 . chunks 3 <*> chunks 2 . filterT even) [1..] [([1,2,3],[2,4]),([4,5,6],[6,8]),([7,8,9],[10,12])] When we compose transformers in parallel, the memory requirements depend on how far they run out of sync. If they consume elements at the same pace, memory requirements should be constant. Otherwise, some part of the input is retained to satisfy all transformers. In the final call above bigger and bigger parts are retained because the first transformer is slower than the second. As transformers are a special case of consumers, we can compose a consumer and a transformer to give a new consumer: (<.) :: ListConsumer b c -> ListTransformer a b -> ListConsumer a c Done c <. _ = Done c Continue c _ <. Cut = Done c Continue _ f <. Put x t = f x <. t Continue c f <. Get g = Continue c (\a -> Continue c f <. g a) Using the instances for parallel and sequential transformer composition as well as the instances for parallel consumer composition, we can build complex consumers that still execute in lockstep and consume their input lazily. Sebastian P.S. https://gist.github.com/1521467

Whoa. Sebastian, you're my hero — I've been struggling with defining Arrow for ListTransformer for a substantial time without success, and here you got it, dramatically simpler than I thought it could be done (I was using explicit queues).
I wonder if now this datatype of yours is isomorphic to StreamSummary b r -> StreamSummary a r.
26.12.2011, в 19:56, Sebastian Fischer
On Sun, Dec 25, 2011 at 11:25 AM, Heinrich Apfelmus
wrote: Your StreamSummary type has a really nice interpretation: it's a reification of case expressions [on lists]. nice observation!
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. [...]
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
[...]
Likewise, each function from lists can be represented in terms of our new data type [...]
length' :: ListTo a Int length' = CaseOf (0) (\x -> fmap (1+) length')
length = interpret length'
This version of `length` is tail recursive while the previous version is not. In general, all functions defined in terms of `ListTo` and `interpret` are spine strict - they return a result only after consuming all input list constructors.
This is what Eugene observed when defining the identity function as
idC = CaseOf [] (\x -> (x:) <$> idC)
This version does not work for infinite lists. Similarly, `head` and `take` cannot be defined as lazily as in the standard libraries.
We can support lazier list consumers by adding a case to the ListTo type that allows to stop consuming the list. To avoid confusion, I chose new names for my new types.
data ListConsumer a b = Done !b | Continue !b (a -> ListConsumer a b)
The interpretation function just ignores the remaining input in the case of `Done`:
consumeList :: ListConsumer a b -> [a] -> b consumeList (Done b) _ = b consumeList (Continue b _) [] = b consumeList (Continue _ f) (x:xs) = consumeList (f x) xs
We can define lazier versions of `head` and `take` as follows:
headC :: ListConsumer a a headC = Continue (error "head of empty list") Done
takeC :: Int -> ListConsumer a [a] takeC 0 = Done [] takeC n = Continue [] (\x -> (x:) <$> takeC (n-1))
However, we still cannot define a lazy version of the identity funtion with list consumers.
The identity function and `takeC` belong to a special case of a list consumers because they also *produce* lists. We can define a specialized type for list transformers that consume and produce lists. One advantage of this specialization will be that we can define a lazy version of the identity function. The transformer type can have functor and applicative instances similar to the consumer type to compose transformers in parallel. Additionally, it can have category and arrow instances to compose transformers sequentially.
Here is a type for lazy list transformers:
data ListTransformer a b = Cut | Put b (ListTransformer a b) | Get (a -> ListTransformer a b)
A transformer can either cut off the input list and return the empty list, output a new element before transforming the input, or consume one element from the input list and transform the remaining elements. The interpretation function should make this clearer:
transformList :: ListTransformer a b -> [a] -> [b] transformList Cut _ = [] transformList (Put b t) xs = b : transformList t xs transformList (Get _) [] = [] transformList (Get f) (x:xs) = transformList (f x) xs
Note that, if the transformer wants to read another element that is not there, it simply returns the empty list.
Now we can define a lazy identity function and another version of `take`:
idT :: ListTransformer a a idT = Get (\x -> Put x idT)
takeT :: Int -> ListTransformer a a takeT 0 = Cut takeT n = Get (\x -> Put x (takeT (n-1)))
Here is another translation of a common list function:
filterT :: (a -> Bool) -> ListTransformer a a filterT p = Get (\x -> if p x then Put x (filterT p) else filterT p)
`filterT` is an example for a function that can consume several input elements before producing an output element. Other examples for functions of this kind are chunking functions:
pairsT :: ListTransformer a (a,a) pairsT = Get (\x -> Get (\y -> Put (x,y) pairsT))
chunks :: Int -> ListTransformer a [a] chunks n = collect n where collect 0 = Put [] (chunks n) collect m = Get (\x -> collect (m-1) >>> Get (\xs -> Put (x:xs) id))
Here are some example calls in GHCi that demonstrate the category and applicative instances for sequential and parallel composition (see below for a link to the complete source code):
ghci> transformList pairsT [1..5] [(1,2),(3,4)] -- 5 is ignored ghci> transformList pairsT [1..6] [(1,2),(3,4),(5,6)] ghci> transformList (chunks 2) [1..5] [[1,2],[3,4]] -- similar to pairsT ghci> transformList (chunks 3) [1..6] [[1,2,3],[4,5,6]] ghci> transformList (takeT 3 . chunks 3) [1..] -- infinite input [[1,2,3],[4,5,6],[7,8,9]] ghci> transformList ((,) <$> takeT 3 . chunks 3 <*> chunks 2 . filterT even) [1..] [([1,2,3],[2,4]),([4,5,6],[6,8]),([7,8,9],[10,12])]
When we compose transformers in parallel, the memory requirements depend on how far they run out of sync. If they consume elements at the same pace, memory requirements should be constant. Otherwise, some part of the input is retained to satisfy all transformers. In the final call above bigger and bigger parts are retained because the first transformer is slower than the second.
As transformers are a special case of consumers, we can compose a consumer and a transformer to give a new consumer:
(<.) :: ListConsumer b c -> ListTransformer a b -> ListConsumer a c Done c <. _ = Done c Continue c _ <. Cut = Done c Continue _ f <. Put x t = f x <. t Continue c f <. Get g = Continue c (\a -> Continue c f <. g a)
Using the instances for parallel and sequential transformer composition as well as the instances for parallel consumer composition, we can build complex consumers that still execute in lockstep and consume their input lazily.
Sebastian
P.S. https://gist.github.com/1521467
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

2011/12/26 Eugene Kirpichov
Whoa. Sebastian, you're my hero — I've been struggling with defining Arrow for ListTransformer for a substantial time without success, and here you got it, dramatically simpler than I thought it could be done (I was using explicit queues).
This stuff is tricky. I noticed that my Applicative instance did not satisfy all required laws. I think I could fix this by changing the implementation of pure to pure x = Put x $ pure x in analogy to the ZipList instance. At least, QuickCheck does not complain anymore (I did not write proofs). The original definition of `pure` was inspired by Chris Smith's post on the connection of Category/Applicative and Arrow: http://cdsmith.wordpress.com/2011/08/13/arrow-category-applicative-part-iia/ However, even with the fixed Applicative instance, the Arrow instance does not satisfy all laws. ListTransformer seems to be a type that has valid Category and Applicative instances which do not give rise to a valid Arrow instance as outlined by Chris. One of his additional axioms relating Category and Applicative does not hold. I have extended the (corrected) code with QuickCheck tests: https://gist.github.com/1521467 I wonder if now this datatype of yours is isomorphic to StreamSummary b r
-> StreamSummary a r.
Not sure what you mean here. StreamSummary seems to be the same as ListConsumer but I don't see how functions from consumers to consumers are list transformers, i.e., functions from lists to lists. Sebastian

On Tue, Dec 27, 2011 at 7:23 AM, Sebastian Fischer
2011/12/26 Eugene Kirpichov
Whoa. Sebastian, you're my hero — I've been struggling with defining Arrow for ListTransformer for a substantial time without success, and here you got it, dramatically simpler than I thought it could be done (I was using explicit queues).
This stuff is tricky. I noticed that my Applicative instance did not satisfy all required laws. I think I could fix this by changing the implementation of pure to
pure x = Put x $ pure x
in analogy to the ZipList instance. At least, QuickCheck does not complain anymore (I did not write proofs).
The original definition of `pure` was inspired by Chris Smith's post on the connection of Category/Applicative and Arrow:
http://cdsmith.wordpress.com/2011/08/13/arrow-category-applicative-part-iia/
However, even with the fixed Applicative instance, the Arrow instance does not satisfy all laws. ListTransformer seems to be a type that has valid Category and Applicative instances which do not give rise to a valid Arrow instance as outlined by Chris. One of his additional axioms relating Category and Applicative does not hold.
I have extended the (corrected) code with QuickCheck tests:
Thanks, I'll take a look.
I wonder if now this datatype of yours is isomorphic to StreamSummary b
r -> StreamSummary a r.
Not sure what you mean here. StreamSummary seems to be the same as ListConsumer but I don't see how functions from consumers to consumers are list transformers, i.e., functions from lists to lists.
Well. They are isomorphic, if list transformers are represented as functions from lists. I'm assuming they could be with the other representation too. type ListT a b = forall r . ([b] -> r) -> ([a] -> r) there :: ([a] -> [b]) -> ListT a b there as2bs bs2r = bs2r . as2bs back :: ListT a b -> ([a] -> [b]) back f = f id
Sebastian
-- Eugene Kirpichov Principal Engineer, Mirantis Inc. http://www.mirantis.com/ Editor, http://fprog.ru/

On Tue, Dec 27, 2011 at 5:35 AM, Eugene Kirpichov
I wonder if now this datatype of yours is isomorphic to StreamSummary b
r -> StreamSummary a r.
Not sure what you mean here. StreamSummary seems to be the same as ListConsumer but I don't see how functions from consumers to consumers are list transformers, i.e., functions from lists to lists.
Well. They are isomorphic, if list transformers are represented as functions from lists. I'm assuming they could be with the other representation too.
type ListT a b = forall r . ([b] -> r) -> ([a] -> r)
I see! I think the type type ContListTransformer a b = forall r . ListConsumer b r -> ListConsumer a r is isomorphic to `ListConsumer a [b]`. Here are the isomorphisms (I did not check whether they are indeed isomorphisms): clt2lc :: ContListTransformer a b -> ListConsumer a [b] clt2lc clt = clt idC lc2clt :: ListConsumer a [b] -> ContListTransformer a b lc2clt _ (Done r) = Done r lc2clt (Done []) (Continue r _) = Done r lc2clt (Done (b:bs)) (Continue _ f) = lc2clt (Done bs) (f b) lc2clt (Continue bs f) c = Continue (consumeList c bs) (\a -> lc2clt (f a) c) However, `ListTransformer a b` is less expressive because of it's incremental nature. Every list transformer `t` satisfies the following property for all `xs` and `ys`: transformList t xs `isPrefixOf` transformList t (xs++ys) List *consumers* don't need to follow this restriction. For example, the consumer Continue [1] (\_ -> Done []) which represents the function nonIncr [] = [1] nonIncr _ = [] is not incremental in the sense above, because not (nonIncr [] `isPrefixOf` nonIncr ([]++[0])) I think it is the incremental nature of list transformers that allows them to be composed in lock-step in the Category instance. `lc2clt` above is sequential composition for list *consumers* but it applies the second consumer only after executing the first completely. Sebastian

Sebastian Fischer wrote:
Heinrich Apfelmus wrote:
Likewise, each function from lists can be represented in terms of our new data type [...]
length' :: ListTo a Int length' = CaseOf (0) (\x -> fmap (1+) length')
length = interpret length'
This version of `length` is tail recursive while the previous version is not. In general, all functions defined in terms of `ListTo` and `interpret` are spine strict - they return a result only after consuming all input list constructors.
This is what Eugene observed when defining the identity function as
idC = CaseOf [] (\x -> (x:) <$> idC)
This version does not work for infinite lists. Similarly, `head` and `take` cannot be defined as lazily as in the standard libraries.
Indeed, the trouble is that my original formulation cannot return a result before it has evaluated all the case expressions. To include laziness, we need a way to return results early. Sebastian's ListTransformer type does precisely that for the special case of lists as results, but it turns out that there is also a completely generic way of returning results early. In particular, we can leverage lazy evaluation for the result type. The idea is, of course, to reify another function. This time, it's going to be fmap data ListTo a b where Fmap :: (b -> c) -> ListTo a b -> ListTo a c CaseOf :: b -> (a -> ListTo a b) -> ListTo a b (GADT syntax due to the existential quantification implied by Fmap ). To see why this works, have a look at the interpreter interpret :: ListTo a b -> ([a] -> b) interpret (Fmap f g) = fmap f (interpret g) interpret (CaseOf nil cons) = \ys -> case ys of [] -> nil (x:xs) -> interpret (cons x) xs In the case of functions, fmap is simply function concatenation fmap f (interpret g) = f . interpret g Now, the point is that our interpretation returns part of the result early whenever the function f is lazy and returns part of the result early. For instance, we can write the identity function as idL :: ListTo a [a] idL = CaseOf [] $ \x -> Fmap (x:) idL When interpreted, this function will perform a pattern match on the input list first, but then the Fmap will ensure that we return the first element of the result. This seems incredible, so I encourage the reader to check this by looking at the reduction steps for the expression interpret idL (1:⊥) To summarize, we do indeed have id = interpret idL . Of course, the result type is not restricted to lists, any other type will do. For instance, here the definition of a short-circuiting and andL :: ListTo Bool Bool andL = CaseOf True $ \b -> Fmap (\c -> if b then c else False) andL testAnd = interpret andL (True:False:undefined) -- *ListTo> testAnd -- False With the right applicative instance, it also possible to implement take and friends, see also the example code at https://gist.github.com/1523428 Essentially, the Fmap constructor also allows us to define a properly lazy function const .
To avoid confusion, I chose new names for my new types.
data ListConsumer a b = Done !b | Continue !b (a -> ListConsumer a b)
I know that you chose these names to avoid confusion, but I would like to advertise again the idea of choosing the *same* names for the constructors as the combinators they represent data ListConsumer a b = Const b | CaseOf b (a -> ListConsumer a b) interpret :: ListConsumer a b -> ([a] -> b) interpret (Const b) = const b interpret (CaseOf nil cons) = \ys -> case ys of [] -> nil (x:xs) -> interpret (const x) xs This technique for designing data structures has the huge advantage that it's immediately clear how to interpret it and which laws are supposed to hold. Especially in the case of lists, I think that this approach clears up a lot of confusion about seemingly new concepts like Iteratees and so on: Iteratees are just ordinary functions [a] -> b, albeit with a slightly different representation in terms of familiar combinators like case of, const, or fmap. The "turn combinators into constructors" technique is the staple of designing combinator libraries and goes back to at least Hughes' famous paper John Hughes. The Design of a Pretty-printing Library. (1995) http://citeseer.ist.psu.edu/viewdoc/summary?doi=10.1.1.38.8777 Best regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com
participants (6)
-
Brent Yorgey
-
Eugene Kirpichov
-
Gábor Lehel
-
Heinrich Apfelmus
-
Sebastian Fischer
-
wren ng thornton