Writing a counter function

I'm trying to write a counter function that would return a tuple whose first element is the current value and whose second element is a new counter. The following line: counter n = (n,(counter (n+1))) Generates the following error on Hugs and a similar one with ghci: ERROR "counter.hs":6 - Type error in function binding *** Term : counter *** Type : a -> (a,b) *** Does not match : a -> b *** Because : unification would give infinite type Is there any way to do it? I tried using data, type and newtype and none of them worked. Regards, Shlomi Fish ---------------------------------------------------------------------- Shlomi Fish shlomif@vipe.technion.ac.il Home Page: http://t2.technion.ac.il/~shlomif/ Home E-mail: shlomif@iglu.org.il He who re-invents the wheel, understands much better how a wheel works.

On Sat, 29 Jun 2002, Shlomi Fish wrote: (snip)
counter n = (n,(counter (n+1))) (snip)
This doesn't work because you seem to be defining an infinitely deep tuple (1,(2,(3,(4,(....))))) which is naughty. I'm not really sure what alternative to suggest beyond [n .. ] without knowing more about what you are trying to do. -- Mark

On Sat, 29 Jun 2002, Mark Carroll wrote:
On Sat, 29 Jun 2002, Shlomi Fish wrote: (snip)
counter n = (n,(counter (n+1))) (snip)
This doesn't work because you seem to be defining an infinitely deep tuple (1,(2,(3,(4,(....))))) which is naughty.
I'm not really sure what alternative to suggest beyond [n .. ] without knowing more about what you are trying to do.
Actually, I'd like a more generalized counter. Something that would return both the number and a handler to add another number, which in turn would return the new sum and a new handler, etc. Regards, Shlomi Fish
-- Mark
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
---------------------------------------------------------------------- Shlomi Fish shlomif@vipe.technion.ac.il Home Page: http://t2.technion.ac.il/~shlomif/ Home E-mail: shlomif@iglu.org.il He who re-invents the wheel, understands much better how a wheel works.

Hello! On Sat, Jun 29, 2002 at 06:23:27PM +0300, Shlomi Fish wrote:
[...]
Actually, I'd like a more generalized counter. Something that would return both the number and a handler to add another number, which in turn would return the new sum and a new handler, etc.
That's just what lazy lists are for. The "handler" thing is done automatically thanks to lazy evaluation. I.e. countFrom n = n : countFrom (n + 1) or just countFrom n = [n..] Kind regards, Hannah.

On Sat, 29 Jun 2002, Hannah Schroeter wrote:
Hello!
On Sat, Jun 29, 2002 at 06:23:27PM +0300, Shlomi Fish wrote:
[...]
Actually, I'd like a more generalized counter. Something that would return both the number and a handler to add another number, which in turn would return the new sum and a new handler, etc.
That's just what lazy lists are for. The "handler" thing is done automatically thanks to lazy evaluation.
I.e. countFrom n = n : countFrom (n + 1) or just countFrom n = [n..]
No. But I want to generate an irregular series, which I determine the intervals between two consecutive numbers myself. E.g: let (num1, next1) = (counter 5) (num2, next2) = (next1 100) (num3, next3) = (next2 50) in [num1,num2,num3] Will have the numbers [5, 105, 155]. Regards, Shlomi Fish
Kind regards,
Hannah. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
---------------------------------------------------------------------- Shlomi Fish shlomif@vipe.technion.ac.il Home Page: http://t2.technion.ac.il/~shlomif/ Home E-mail: shlomif@iglu.org.il He who re-invents the wheel, understands much better how a wheel works.

Shlomi Fish wrote:
No. But I want to generate an irregular series, which I determine the intervals between two consecutive numbers myself. E.g:
let (num1, next1) = (counter 5) (num2, next2) = (next1 100) (num3, next3) = (next2 50) in [num1,num2,num3]
Will have the numbers [5, 105, 155].
What do you mean by "determine"? You can write sequence = iterate step_counter 0 if the interval between successive numbers is determined by the current number, or sequence = map f [1..] if it's determined by the index in the sequence. or sequence = map snd $ iterate step_counter (0,-7) step_counter (a,b) = (a+1, f a b) if it depends on both. Jón -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk 31 Chalmers Road jf@cl.cam.ac.uk Cambridge CB1 3SZ +44 1223 570179 (after 14:00 only, please!)

On Sat, 29 Jun 2002, Jon Fairbairn wrote:
Shlomi Fish wrote:
No. But I want to generate an irregular series, which I determine the intervals between two consecutive numbers myself. E.g:
let (num1, next1) = (counter 5) (num2, next2) = (next1 100) (num3, next3) = (next2 50) in [num1,num2,num3]
Will have the numbers [5, 105, 155].
What do you mean by "determine"?
_I_ want to determine which step to go to next. I'd like to pass a parameter the counter each time, and each time get the next number as well as a new counter. Regards, Shlomi Fish
You can write
sequence = iterate step_counter 0
if the interval between successive numbers is determined by the current number, or
sequence = map f [1..]
if it's determined by the index in the sequence.
or
sequence = map snd $ iterate step_counter (0,-7) step_counter (a,b) = (a+1, f a b)
if it depends on both.
J�n
---------------------------------------------------------------------- Shlomi Fish shlomif@vipe.technion.ac.il Home Page: http://t2.technion.ac.il/~shlomif/ Home E-mail: shlomif@iglu.org.il He who re-invents the wheel, understands much better how a wheel works.

Just for the record, here is a Perl function that does this: ############### sub counter { my $a = shift; my $next = sub { my $to_add = shift ; return counter($to_add+$a); }; return ($a, $next); } my ($result,$next) = counter(5); my ($result2, $next2) = $next->(100); my ($result3, $next3) = $next2->(50); my ($result4, $next4) = $next->(30); print "\$result=$result\n\$result2=$result2\n\$result3=$result3\n\$result4=$result4\n"; ############ Regards, Shlomi Fish ---------------------------------------------------------------------- Shlomi Fish shlomif@vipe.technion.ac.il Home Page: http://t2.technion.ac.il/~shlomif/ Home E-mail: shlomif@iglu.org.il He who re-invents the wheel, understands much better how a wheel works.

On Sat, 29 Jun 2002, Shlomi Fish wrote:
No. But I want to generate an irregular series, which I determine the intervals between two consecutive numbers myself. E.g:
let (num1, next1) = (counter 5) (num2, next2) = (next1 100) (num3, next3) = (next2 50) in [num1,num2,num3]
Will have the numbers [5, 105, 155].
The other answers you've received really question whether this is a good way to use Haskell at all --- usually, if you want to generate a sequence of values, it's a good idea just to represent them explicitly as a (lazy) list. For example, you can compute more-or-less the same result as you want just using standard list processing functions: Main> scanl (+) 0 [5,100,50] [0,5,105,155] However, you can also do almost exactly what you suggest. Not quite exactly, because the function you describe would have a recursive type type Counter = Int -> (Int, Counter) and Haskell requires that type recursion involve a data or newtype. So, here's a solution: newtype Counter = Counter (Int -> (Int, Counter)) count :: Counter -> Int -> (Int, Counter) count (Counter c) = c counter n = (n, Counter next) where next k = counter (n+k) xs = let (num1, next1) = (counter 5) (num2, next2) = (next1 `count` 100) (num3, next3) = (next2 `count` 50) in [num1,num2,num3] Main> xs [5,105,155] The only difference from your idea is that a counter is not a function; we have to use the function count to invoke it. And that's forced on us by the need to avoid type recursion. John Hughes

No. But I want to generate an irregular series, which I determine the intervals between two consecutive numbers myself. E.g:
let (num1, next1) = (counter 5) (num2, next2) = (next1 100) (num3, next3) = (next2 50) in [num1,num2,num3]
Will have the numbers [5, 105, 155].
Here's another not-exactly-what-you-wanted solution. :) If you don't mind changing your example to let (num1, next1) = out (counter 5) (num2, next2) = out (next1 100) (num3, next3) = out (next2 50) in [num1,num2,num3] then, you can do this: newtype Counter = MkCounter Int counter :: Int -> Counter counter n = MkCounter n out :: Counter -> (Int,Int -> Counter) out (MkCounter n) = (n,MkCounter . (n +)) Sam Moelius

No. But I want to generate an irregular series, which I determine the intervals between two consecutive numbers myself. E.g:
let (num1, next1) = (counter 5) (num2, next2) = (next1 100) (num3, next3) = (next2 50) in [num1,num2,num3]
Will have the numbers [5, 105, 155].
Here's another not-exactly-what-you-wanted solution. :) If you don't mind changing your example to let (num1, next1) = out (counter 5) (num2, next2) = out (next1 100) (num3, next3) = out (next2 50) in [num1,num2,num3] then, you can do this: newtype Counter = MkCounter Int counter :: Int -> Counter counter n = MkCounter n out :: Counter -> (Int,Int -> Counter) out (MkCounter n) = (n,MkCounter . (n +)) Sam Moelius

On Sat, 29 Jun 2002, Samuel E. Moelius III wrote: (snip)
Here's another not-exactly-what-you-wanted solution. :) (snip)
Do any of the experimental extensions to Haskell allow a what-he-wanted solution? I couldn't arrange one in H98 without something having an infinitely-recursive type signature. I'm sure it would have been easy in Lisp, and he already gave a Perl equivalent, so I'm wondering if it could be at all sane for Haskell to allow such stuff and if Haskell is somehow keeping us on the straight and narrow by disallowing the exact counter that was originally requested. The beauty of his request was that it was so simple and seemed to make sense; I went ahead and tried to fulfill it before realising I couldn't do it either. -- Mark

On Sat, 2002-06-29 at 15:26, Mark Carroll wrote:
On Sat, 29 Jun 2002, Samuel E. Moelius III wrote: (snip)
Here's another not-exactly-what-you-wanted solution. :) (snip)
Do any of the experimental extensions to Haskell allow a what-he-wanted solution? I couldn't arrange one in H98 without something having an infinitely-recursive type signature. I'm sure it would have been easy in Lisp, and he already gave a Perl equivalent, so I'm wondering if it could be at all sane for Haskell to allow such stuff and if Haskell is somehow keeping us on the straight and narrow by disallowing the exact counter that was originally requested.
The beauty of his request was that it was so simple and seemed to make sense; I went ahead and tried to fulfill it before realising I couldn't do it either.
I could not manage to do this with a simple always-increment-by-one function, but the problem of adding a number n each time was a quite a bit easier - though it still took me a while to escape the infinite recursive type , it seems that you need to indirect through another datatype (here FP). you can't print z or z', but the show defined will allow you to print out a FooPair ----- data FooPair = FP Integer (Integer -> FooPair) instance Show FooPair where show (FP i f) = "FooPair " ++ (show i) ++ "...fun..." incg :: Integer -> Integer -> FooPair incg n = \i -> let j = n+i in (FP j (incg j)) val (FP i _) = i fun (FP _ f) = f x = incg 7 -- the original function y = x 3 -- increment the current value by 3 and return the FP pair zf = fun y -- get the new function zv = val y -- and the value in the pair z' = z 99 -- now get the next value function pair ----- -- jeff putnam -- jefu.jefu@verizon.net -- http://home1.get.net/res0tm0p

G'day all. On Sat, Jun 29, 2002 at 05:26:46PM -0500, Mark Carroll wrote:
Do any of the experimental extensions to Haskell allow a what-he-wanted solution? I couldn't arrange one in H98 without something having an infinitely-recursive type signature. I'm sure it would have been easy in Lisp, and he already gave a Perl equivalent, so I'm wondering if it could be at all sane for Haskell to allow such stuff and if Haskell is somehow keeping us on the straight and narrow by disallowing the exact counter that was originally requested.
In principle it's perfectly possible to have a type system which works over regular trees. The main difficulty is how to actually express a type. You'd need something like letrec for types. typedef Counter = letrec x = Int -> (Int, x) in x It makes a few type-related things more inefficient, but it need not impose a huge cost in places where it's not used. It's fairly straightforward to optimise non-recursive types to the way they are handled at the moment at the cost of a more complex compiler. At least that's the story before you add all the other features of Haskell's type system. I'm not sure, for example, how it would interact with overlapping typeclass instances. This is the central problem with extensions to the type system: how well or badly it combines with all the other extensions that have been added over the years. In this case, I really don't see that you would get much in the way of extra expressiveness. Breaking recursion is as simple as introducing a newtype. Moreover, it's arguably "the Haskell way" just to introduce a new type whenever you need one, because it's so cheap to do. Cheers, Andrew Bromage

I adjunt some code that i supose is what are you locking for.
Is based in a previous message (by jefu on 13 of june) idea from the
"Haskell acumulator" thread.
the "prueba" function is the translation of your example.
By the way, what's the purpose of this coding? (this is the type of
question: "ok, I have a hammer, now, for what kind of nail it is useful?")
Cheers,
Luis Michelena
----- Original Message -----
From: Shlomi Fish
On Sat, 29 Jun 2002, Hannah Schroeter wrote:
Hello!
On Sat, Jun 29, 2002 at 06:23:27PM +0300, Shlomi Fish wrote:
[...]
Actually, I'd like a more generalized counter. Something that would return both the number and a handler to add another number, which in turn would return the new sum and a new handler, etc.
That's just what lazy lists are for. The "handler" thing is done automatically thanks to lazy evaluation.
I.e. countFrom n = n : countFrom (n + 1) or just countFrom n = [n..]
No. But I want to generate an irregular series, which I determine the intervals between two consecutive numbers myself. E.g:
let (num1, next1) = (counter 5) (num2, next2) = (next1 100) (num3, next3) = (next2 50) in [num1,num2,num3]
Will have the numbers [5, 105, 155].
Regards,
Shlomi Fish
Kind regards,
Hannah. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
---------------------------------------------------------------------- Shlomi Fish shlomif@vipe.technion.ac.il Home Page: http://t2.technion.ac.il/~shlomif/ Home E-mail: shlomif@iglu.org.il
He who re-invents the wheel, understands much better how a wheel works.

Mark Carrol wrote:
The beauty of his request was that it was so simple and seemed to make sense;
) I don't claim that this is particularly well written, in
But there's the rub. It's not beautiful and it doesn't make
much sense. I really wish we could get away from the "How do
I convert this imperative code snippet into Haskell"
questions into "How do I solve this abstract problem?"
Take the perl:
##############
sub counter
{
my $a = shift;
my $next = sub {
my $to_add = shift ;
return counter($to_add+$a);
};
return ($a, $next);
}
my ($result,$next) = counter(5);
my ($result2, $next2) = $next->(100);
my ($result3, $next3) = $next2->(50);
my ($result4, $next4) = $next->(30);
print "\$result=$result\n\$result2=$result2\n\$result3=$result3\n\$result4=$result4\n";
###########
Now, an extensionally equal Haskell programme is the following:
main = putStr "$result=5\n\
\$result2=105\n\
\$result3=155\n\
\$result4=35\n"
Like the original programme, it takes no inputs and produces
a certain output. You might well object that this programme
isn't /intentionally/ equal to the one given, but then I
can't work out what the intention was!
I guess that the last "$next" on the last line should have
been "$next3", but I'm not certain, and I certainly have no
idea what the programme is /for/.
The point of Haskell is not that it is easy to write
programmes. On that metric, assembler isn't bad. I don't
find it particularly hard to write assembler
programmes. What I do find hard is reading them, and
determining whether they are what I intended. The big
advantages of Haskell are that it prevents you from writing
certain kinds of programme, and makes it easier to write
certain other kinds.
None of the responses so far has focussed on the problem
with the kind of function defined in the Perl above, namely
that one tends to make slips in passing the correct next
state to the function. One way round this is to use a
monad:
import Single_State
main = putStrLn result where
result = runS (do result1 <- set_state 5
result2 <- step_counter 100
result3 <- step_counter 50
result4 <- step_counter 30
return $ "result1 = "++show result1
++"\nresult2 = "++show result2
++"\nresult3 = "++show result3
++"\nresult4 = "++show result4)
0
step_counter:: Int -> Single_State Int Int
step_counter n = do a <- get_state
set_state (n+a)
(Single_State is a silly example at

On Sun, 30 Jun 2002, Jon Fairbairn wrote: (snip)
But there's the rub. It's not beautiful and it doesn't make much sense. I really wish we could get away from the "How do I convert this imperative code snippet into Haskell" questions into "How do I solve this abstract problem?"
The question as originally posed didn't seem like it particularly needed something imperative though. For instance, the Perl isn't strongly imperative - it's largely just a list of declarations and functions (some anonymous) where you can think of the variables as being locally-declared constants. For instance, the first bit is very similar to, say, counter a = (a, \to_add -> counter (a + to_add)) I think that's very different from asking people to translate into Haskell things where variables have their value change and whatever. Jon Cast's observation makes more sense to me - it's not a imperative/functional issue so much as a weak or strong typing issue. (snip)
I guess that the last "$next" on the last line should have been "$next3", but I'm not certain, and I certainly have no idea what the programme is /for/.
Yes, I'm sure you're right there. Thanks very much for sharing the monadic approach - I was curious as to if monads could be used to break the recursion, and I didn't see anyone else mention that. I've certainly found Jon Cast's, John Hughes' and Andrew Bromage's articles interesting - it seems like this is a well-known issue and Haskell currently lies on an attractive point on the tradeoff between making things awkward and opening cans of worms. -- Mark

lmichele wrote (on Sun, 30 Jun 2002 at 09:26):
> By the way, what's the purpose of this coding? (this is the type of > question: "ok, I have a hammer, now, for what kind of nail it is useful?") I would guess that something like the asked-for counter could be useful if one is allocating ranges of addresses to things, for example heap nodes when compiling a function body to instructions to build a graph. Why not have a monad m a = Int -> (a,Int) which is a state monad plus the operation bump : Int -> m Int bump k n = (n,n+k) Rgds, Peter Hancock

G'day all. On Sun, Jun 30, 2002 at 01:51:56PM +0100, Peter G. Hancock wrote:
Why not have a monad m a = Int -> (a,Int) which is a state monad plus the operation bump : Int -> m Int
bump k n = (n,n+k)
Oh, ye of insufficient genericity. We can do better than that... import MonadTrans class (Monad m, Enum i) => MonadCounter i m | m -> i where bump :: Int -> m i newtype CounterT i m a = CounterT { runCounterT :: i -> m (a,i) } instance (Monad m, Enum i) => Monad (CounterT i m) where return a = CounterT $ \x -> return (a, x) m >>= k = CounterT $ \x -> do (a, x') <- runCounterT m x runCounterT (k a) x' fail str = CounterT $ \_ -> fail str instance (Monad m, Enum i) => MonadCounter i (CounterT i m) where bump k = CounterT $ \x -> let (next:_) = drop k [x..] in return (x, next) instance (Enum i) => MonadTrans (CounterT i) where lift m = CounterT $ \x -> do a <- m return (a, x) evalCounterT :: (Monad m, Enum i) => CounterT i m a -> i -> m a evalCounterT m x = do (a, _) <- runCounterT m x return a -- Example code follows main :: IO () main = evalCounterT count 0 count :: CounterT Int IO () count = do x1 <- bump 1 x2 <- bump 5 x3 <- bump 0 x4 <- bump 1 lift (putStrLn $ show [x1,x2,x3,x4]) I'd better get back to work now. Cheers, Andrew Bromage

Shlomi Fish wrote (on 29-06-02 17:30 +0300):
I'm trying to write a counter function that would return a tuple whose first element is the current value and whose second element is a new counter.
John Hughes showed how to do this. Here is a closely related, more abstract solution which employs existential types. First let me give a paradigmatic example which is slightly different from what you want: streams. data Stream a = forall x. Stm x (x -> a) (x -> x) Note that we hide the state type x. This lets us keep the implementation hidden from the client. value (Stm state val next) = val state next (Stm state val next) = Stm (next state) val next both s = (value s, next s) unfold :: x -> (x -> a) -> (x -> x) -> Stream a unfold state val next = Stm state val next -- the naturals nats1 = unfold 0 id succ -- value nats1 = 0 -- value (next nats1) = 1 -- value (next (next nats1)) = 2 ... In the example above, we use an integer for the state, project it out when we need a value, and increment it to get the next state. Here's another way to do it, using a state which is not an integer. nats2 = unfold [0..] head tail Here we just used an infinite list for the state. head :: List Int -> Int, so the state type is now different from "method" result type. And here's an example where we use a step of 100 when we create the stream. -- step 100 stm1 = unfold 5 id (+ 100) But you wanted an object where we can choose the step at each "point in time". OK: data MyStream a = forall x. MyStm x (x -> a) (a -> x -> x) myValue (MyStm state val next) = val state myNext arg (MyStm state val next) = MyStm (next arg state) val next myBoth arg s = (myValue s, myNext arg s) myUnfold :: x -> (x -> a) -> (a -> x -> x) -> MyStream a myUnfold state val next = MyStm state val next counter n = myUnfold n id (+) Now the state-transforming function accepts an extra argument along with the state. And in fact we were able to generalize the idea of "stepping", since we never had to mention integers or addition till the last line. Easy, right? You can see the pattern for defining similar sorts datatypes now. Hide the state type x with a forall, and, for each way of observing and/or transforming the state, include a function of type x -> ... OO people call this a (functional) object. Mathematicians call it a coalgebra. There is a notion of coalgebraic (or coinductive) datatype which is dual to the notion of algebraic datatypes in Haskell; sometimes they're called codatatypes. The analog of unfold is fold, of methods (sometimes called destructors or observors) are data constructors, and of the state type is the "accumulator" type which is the result of a fold. Some languages like Charity support codatatypes directly, but in Haskell we can get the same effect with a local forall. Actually, you can make this even more OO-like using type classes, but things seem to get messy if we keep the result type polymorphic so I'll fix it to Integer: class CounterState x where sValue :: x -> Integer sNext :: Integer -> x -> x data Counter = forall x. CounterState x => Counter x instance CounterState Integer where sValue = id sNext step state = step + state mkCounter :: Integer -> Counter mkCounter n = Counter n A disadvantage of this approach is that now you can only have one implementation for each state type; with unfold, where we stored the functions in the data constructor fields, we could give many implementations of the methods for each state type. In OO terms, the type class approach is "class-based" whereas the unfold approach is "object-based". The advantage, of course, is that you can use inheritance via the type class inheritance now. BTW, I hope that this note will not encourage the OO readers on this list to "objectify" _everything_ now, because that leads (IMO) to twisted programs which often emphasize the wrong sort of flexibility. Both datatypes and codatatypes have their place: * A datatype is called for when you need a collection of finite-sized values (lists, trees, etc.), and want to be able to traverse them easily. The fold for a datatype does this for you, and is guaranteed to terminate. * A codatatype is called for when you have a collection of infinite-sized or circular values (streams, automata, etc.) and you want to be able to index arbitrarily into (grab subparts of) them, without possibility of error or exposing the representation. Note that you cannot generally traverse a value of a codatatype: if you try to "fold" a stream, the computation will diverge. On the other hand, you cannot index arbitrarily deeply into a value of a datatype. Remember our stream example? We could have called the "value" function "head" and the "next" function "tail". You can always apply these to a stream, and they will never fail. But if you try that with lists, you will raise an error once you get to the end of it. -- Frank Atanassow, Information & Computing Sciences, Utrecht University Padualaan 14, PO Box 80.089, 3508 TB Utrecht, Netherlands Tel +31 (030) 253-3261 Fax +31 (030) 251-379

Mark Carroll wrote:
On Sun, 30 Jun 2002, Jon Fairbairn wrote: (snip)
But there's the rub. It's not beautiful and it doesn't make much sense. I really wish we could get away from the "How do I convert this imperative code snippet into Haskell" questions into "How do I solve this abstract problem?"
The question as originally posed didn't seem like it particularly needed something imperative though.
That largely misses the point. My objection is to the mindset behind the question.
the first bit is very similar to, say,
counter a = (a, \to_add -> counter (a + to_add))
Which looks to me like imperative programming. Indeed, the Monad answer that I posted is imperative programming, it just happens to be done in Haskell. Stepwise transformation of a state is, on some occasions, the right answer to a problem. Unfortunately in this thread we haven't been told what the problem is. The question is of the form "how do I make a hammer?" when a hammer is rarely the most appropriate tool. That's what I'd like to get away from. Jón -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk 31 Chalmers Road jf@cl.cam.ac.uk Cambridge CB1 3SZ +44 1223 570179 (after 14:00 only, please!)
participants (11)
-
A./C. Luis Pablo Michelena
-
Andrew J Bromage
-
Frank Atanassow
-
Hannah Schroeter
-
John Hughes
-
Jon Fairbairn
-
Mark Carroll
-
peter@premise.demon.co.uk
-
Samuel E. Moelius III
-
Shlomi Fish
-
that jefu guy