Are there standard idioms for lazy, pure error handling?

I'm working on a library which needs to operate on large data sets, so I'd like to use lazy values. The library consists of pure functions from Text to [Event] and back. Normally, I use Maybe or Either for error handling in pure code, but using these precludes lazy evaluation. Using exceptions requires any errors to be handled in IO, which is annoying. The "idealized" signatures of the functions are: ---------------------------------------- import qualified Data.Text.Lazy as TL data Event = EventA | EventB | EventC parse :: TL.Text -> Either ParseError [Event] serialize :: [Event] -> Either SerializeError TL.Text ---------------------------------------- I've considered two possible error handling modes, both adapted from procedural language style. The first is simply including errors in the event list. ---------------------------------------- import qualified Data.Text as T parse :: TL.Text -> [Either ParseError Event] serialize :: [Event] -> [Either SerializeError T.Text] -- use TL.fromChunks ---------------------------------------- The second uses monadic callbacks, based on side effects: ---------------------------------------- parse :: Monad m => (Event -> m ()) -> (ParseError -> m ()) -> TL.Text -> m () serialize :: Monad m => (T.Text -> m ()) -> (SerializeError -> m ()) -> [Event] -> m () ---------------------------------------- The main problem I see with these is that they don't indicate or enforce that an error terminates the event/text streams. The first allows multiple errors in a row, or events to follow an error. The second just "feels" ugly, because using it in pure code requires clients to build a Writer (possibly wrapped with ErrorT) and deal with the associated plumbing. Is there any sort of standard idiom for handling this problem? It seems that somebody must have run across it before, but the resources I can find on lazy error handling all assume the code is impure (returning IO, etc).

I'm working on a library which needs to operate on large data sets, so I'd like to use lazy values. ... ---------------------------------------- import qualified Data.Text as T parse :: TL.Text -> [Either ParseError Event] ----------------------------------------
I would say that this is the most desirable approach, if you are generating a sequence, and want lazy processing of the elements. Indeed, in my own experience, this is the only reasonable way to deal with very large datasets, without running out of memory.
The main problem I see with these is that they don't indicate or enforce that an error terminates the event/text streams. The first allows multiple errors in a row, or events to follow an error.
Are you sure that there can be no error recovery, to continue with events after a mal-formed event has been discarded? In many cases, it is possible. However, if you really want to terminate the stream at the first error, and to reflect this in the type, then I guess you can define your own list type: data ListThenError e a = Cons a (ListThenError e a) | Error e Of course this has the disadvantage that then your consumer must change to use this type too. Regards, Malcolm

On Sun, Nov 29, 2009 at 11:08 PM, Malcolm Wallace
Are you sure that there can be no error recovery, to continue with events after a mal-formed event has been discarded? In many cases, it is possible. However, if you really want to terminate the stream at the first error, and to reflect this in the type, then I guess you can define your own list type:
data ListThenError e a = Cons a (ListThenError e a) | Error e
Of course this has the disadvantage that then your consumer must change to use this type too.
If it is correct, there is no disadvantage. Using a list when it is not the appropriate structure will make both the producer and the consumer code uglier. You might gain a little notational convenience, but you bubble implicit assumptions, such as an error terminates a stream, through the code where they can not be checked. Of course, when you have a stream from which errors can be recovered, do not use a type that terminates with errors. Everything cleans up so nicely when your model perfectly captures your problem. Luke

On Mon, 2009-11-30 at 06:08 +0000, Malcolm Wallace wrote:
However, if you really want to terminate the stream at the first error, and to reflect this in the type, then I guess you can define your own list type:
data ListThenError e a = Cons a (ListThenError e a) | Error e
Of course this has the disadvantage that then your consumer must change to use this type too.
I've been using this list type quite a lot recently. It's in the 'tar' package for example. It comes with variants of the standard functions foldl, foldr, unfoldr that take into account the error possibility. At some point we should probably make a package to standardise and document this lazy error handling idiom. Another approach that some people have advocated as a general purpose solution is to use: data Exceptional e a = Exceptional { exception :: Maybe e result :: a } However it's pretty clear from the structure of this type that it cannot cope with lazy error handling in sequences. If you try it you'll find you cannot do it without space leaks. Adding the errors directly into the structure seems the best approach to me. It means the data structure directly reflects the unfolding of the various possibilities, including errors. It also makes the strictness of operations much easier to understand. Then we just have to be comfortable manipulating these data structures using the appropriate folds and unfolds. Classic pure lazy FP. Duncan

On Mon, Nov 30, 2009 at 03:02, Duncan Coutts
On Mon, 2009-11-30 at 06:08 +0000, Malcolm Wallace wrote:
However, if you really want to terminate the stream at the first error, and to reflect this in the type, then I guess you can define your own list type:
data ListThenError e a = Cons a (ListThenError e a) | Error e
Of course this has the disadvantage that then your consumer must change to use this type too.
I've been using this list type quite a lot recently. It's in the 'tar' package for example. It comes with variants of the standard functions foldl, foldr, unfoldr that take into account the error possibility.
At some point we should probably make a package to standardise and document this lazy error handling idiom.
Wow, this is perfect! I've extracted that type out into the "failable-list" library[1], with a few added instances for common classes (Monad, Applicative, Traversable, etc). [1] http://hackage.haskell.org/package/failable-list

On Mon, 2009-11-30 at 20:10 -0800, John Millikin wrote:
On Mon, Nov 30, 2009 at 03:02, Duncan Coutts
wrote:
data ListThenError e a = Cons a (ListThenError e a) | Error e
Of course this has the disadvantage that then your consumer must change to use this type too.
I've been using this list type quite a lot recently. It's in the 'tar' package for example. It comes with variants of the standard functions foldl, foldr, unfoldr that take into account the error possibility.
At some point we should probably make a package to standardise and document this lazy error handling idiom.
Wow, this is perfect! I've extracted that type out into the "failable-list" library[1], with a few added instances for common classes (Monad, Applicative, Traversable, etc).
Nice. The one I've felt is missing in the tar package was a foldl. This is used to fully consume a failable list. It wants to return either the normal foldl result or an error encountered. When consuming with a foldr, the main use case is that you're translating into another lazy data structure which has it's own place to annotate errors. When consuming with a foldl, the main use case is that you're strictly consuming the list and purging out the errors because you want to construct a type that does not have room in it for errors. There seem to be a number of possibilities though: for reference, standard list foldl: foldl :: (b -> a -> b) -> b -> [a] -> b foldl :: (b -> a -> b) -> b -> -> FailableList e a -> Either e b or the final result as Either (e, b) b foldl :: (b -> a -> b) -> b -> (b -> e -> b) -> FailableList e a -> b foldl :: (b -> a -> b) -> b -> (b -> c) -> (b -> e -> c) -> FailableList e a -> b This last one is basically the church encoding of Either (e, b) b. Do we want the partial result at the point the list ended in error? If not then it's a little simpler. Duncan

Duncan Coutts
Nice.
I agree this is needed (or rather, would be nice to standardise). Although I don't care for the cutesy naming suggested in the 'Train' datatype, failable-list could be made more general. Why is there a specific constructor 'Done', instead of just allowing the user to select a value of type 'e' (using 'Maybe b' if nothing else works)? Perhaps we could also consider an infix notation, like: data TerminatedList a e = Then a (TerminatedList a e) | Finally e (So you could do e.g: 4 `Then` 5 `Then` 1 `Finally` "success!". Of course, you might prefer symbols instead.) -k -- If I haven't seen further, it is by standing in the footprints of giants

data TerminatedList a e = Then a (TerminatedList a e) | Finally e
Nice.
(So you could do e.g: 4 `Then` 5 `Then` 1 `Finally` "success!".
Errm, you mean: 4 `Then` 5 `Then` 1 `Then` Finally "success!" Regards, Malcolm

Malcolm Wallace
Errm, you mean: 4 `Then` 5 `Then` 1 `Then` Finally "success!"
Yes, sorry, and thanks. I guess I should learn to check with ghci before posting... How about this for a nicer syntax? infixr 8 :+ infixr 8 +: data TList a e = a :+ (TList a e) | Return e deriving Show x +: y = x :+ (Return y) *Main> 2 :+ 4 +: "success" 2 :+ (4 :+ Return "success") I like the generic terminal value, it allows things like: *Main> let count = go 0 where go i (x:xs) = x :+ go (i+1) xs; go i [] = Return i *Main> :t count count :: [t] -> TList t Integer *Main> count [1..5] 1 :+ (2 :+ (3 :+ (4 :+ (5 :+ Return 5)))) (But perhaps these things can be done more elegantly using State or similar?) -k -- If I haven't seen further, it is by standing in the footprints of giants

On Thu, 2009-12-03 at 12:34 +0100, Ketil Malde wrote:
Duncan Coutts
writes: Nice.
I agree this is needed (or rather, would be nice to standardise).
Although I don't care for the cutesy naming suggested in the 'Train' datatype, failable-list could be made more general. Why is there a specific constructor 'Done', instead of just allowing the user to select a value of type 'e' (using 'Maybe b' if nothing else works)?
Perhaps we could also consider an infix notation, like:
data TerminatedList a e = Then a (TerminatedList a e) | Finally e
(So you could do e.g: 4 `Then` 5 `Then` 1 `Finally` "success!". Of course, you might prefer symbols instead.)
I agree the naming could do with some work and it's worth trying a few variants to see what seems nicest. I've got an open mind on the suggestion to amalgamate the two ways the list could end. I'm not especially in favour of generalising for the sake of generalising, especially if it looses the connection to the notion of annotating your "ordinary" data structure with extra errors. If I effectively always have to use an Either for the final value then perhaps it does not buy anything and just makes the folds uglier (since it might loose the connection with the ordinary fold). But it could make even that use case simpler so it's worth looking at in a few examples (eg the tar package). Note that another similar use case is lazy progress reporting. In cabal-install's dependency solver I've used: -- | A type to represent the unfolding of an expensive long running -- calculation that may fail. We may get intermediate steps before the -- final result which may be used to indicate progress and/or logging -- messages. -- data Progress step fail done = Step step (Progress step fail done) | Fail fail | Done done It's a difference in emphasis but I think it may also have a different Monad instance since we consider Progress to be a single value, not a list. It's like the Either error monad but with extra writer style logging. Duncan

Duncan Coutts wrote:
I've got an open mind on the suggestion to amalgamate the two ways the list could end. I'm not especially in favour of generalising for the sake of generalising, especially if it looses the connection to the notion of annotating your "ordinary" data structure with extra errors. If I effectively always have to use an Either for the final value then perhaps it does not buy anything and just makes the folds uglier (since it might loose the connection with the ordinary fold). But it could make even that use case simpler so it's worth looking at in a few examples (eg the tar package).
These days I view folds as automatically defined by the data type, so I don't see any reason (on those grounds) to want to compare it to lists' foldr as opposed to any other arbitrary catamorphism. One reason to prefer a single basis is that it simplifies the ability to do concatenation and the associated fusion. It still only has one termination point (unlike trees) so it's still possible to do augment fusion. But because there are two bases, concatenation needs to look like this: concat2 :: T a b -> (b -> T a b) -> T a b -> T a b Whereas for the version with no Nil, it's just: concat1 :: T a b -> (b -> T a b) -> T a b As for the usage, we'd be comparing these two: concat2 foo handler bar concat1 foo (maybe bar handler) One of the nice things about not having a Nil is that it lets you easily be polymorphic over things ending in () ---a normal list---, (Maybe a) ---a fallible list---, (Either a b) ---your progress type---, etc. Whereas the version that has both Nil and End forces us into the (Maybe a) scenario. A side effect of this is that the (Either a b) option isn't available because we can only construct t=Mx.(x*t)+(1+a+b) not t=Mx.(x*t)+(a+b). -- Live well, ~wren

wren ng thornton wrote:
One of the nice things about not having a Nil is that it lets you easily be polymorphic over things ending in () ---a normal list---, (Maybe a) ---a fallible list---, (Either a b) ---your progress type---, etc. Whereas the version that has both Nil and End forces us into the (Maybe a) scenario. A side effect of this is that the (Either a b) option isn't available because we can only construct t=Mx.(x*t)+(1+a+b) not t=Mx.(x*t)+(a+b).
Er, I meant t=Mx.(c*x)+(1+a+b) vs t=Mx.(c*x)+(a+b). This is what I get for posting without coffee. -- Live well, ~wren

On Thu, 2009-12-03 at 19:49 -0500, wren ng thornton wrote:
Duncan Coutts wrote:
I've got an open mind on the suggestion to amalgamate the two ways the list could end. I'm not especially in favour of generalising for the sake of generalising, especially if it looses the connection to the notion of annotating your "ordinary" data structure with extra errors. If I effectively always have to use an Either for the final value then perhaps it does not buy anything and just makes the folds uglier (since it might loose the connection with the ordinary fold). But it could make even that use case simpler so it's worth looking at in a few examples (eg the tar package).
These days I view folds as automatically defined by the data type, so I don't see any reason (on those grounds) to want to compare it to lists' foldr as opposed to any other arbitrary catamorphism.
Sure the fold is defined by the data type, except when we are pretending that one data type is another. This type is intended as a list that is annotated with errors. So I want to be able to switch between list versions and this version just by adding an extra error-handling parameter to the ordinary list fold. As another example of this, consider the VersionRange type in Cabal. It provides two different folds depending on what view you want. Neither matches the underlying constructors exactly. Duncan

wren ng thornton wrote:
concat1 :: T a b -> (b -> T a b) -> T a b
This could just as easily be
concat :: T a b -> (b -> T a c) -> T a c
right? It's a little weird to call this concatenation, but I bet it
could come in handy.
--
Jason McCarty

On Fri, Dec 4, 2009 at 1:14 PM, Jason McCarty
wren ng thornton wrote:
concat1 :: T a b -> (b -> T a b) -> T a b
This could just as easily be
concat :: T a b -> (b -> T a c) -> T a c
right? It's a little weird to call this concatenation, but I bet it could come in handy.
T a is, among other things, the free monad for the functor (,) a. The
concat you describe is the monadic bind.
data T a b = D b | W a (T a b)
instance Monad (T a) where
return = D
D b >>= f = f b
W a t >>= f = W a (t >>= f)
--
Dave Menendez

Jason McCarty wrote:
wren ng thornton wrote:
concat1 :: T a b -> (b -> T a b) -> T a b
This could just as easily be
concat :: T a b -> (b -> T a c) -> T a c
right? It's a little weird to call this concatenation, but I bet it could come in handy.
Er right, that's what I meant. (Again the posting without enough coffee to pave over the cognitive potholes </chagrin>) -- Live well, ~wren

Ketil Malde wrote:
Although I don't care for the cutesy naming suggested in the 'Train' datatype [...]
data TerminatedList a e = Then a (TerminatedList a e) | Finally e
(So you could do e.g: 4 `Then` 5 `Then` 1 `Finally` "success!". Of course, you might prefer symbols instead.)
I don't mind Then and Finally as constructors. The thing about the Train is not so much the suggestive constructor names Wagon/Loco or Cabin/Caboose but that the concept itself has an evocative and short name, Train . In contrast, TerminatedList feels too much like an agglomeration of technical terms to me ("weak head normal form") where the names are fairly unrelated to the actual definition. (This particularly applies to "weak", one could as well have dubbed the whole thing "blue head normal form" without any loss of meaning.) Unfortunately, TerminatedList is also too long for extended use in type signatures. Something more evocative and short, similar to the good old "queue" or "stack" would be great. How about "trail" or "track", like in data Trail a b = Then a (Trail a b) | End b the idea being that the trail of say a dog eventually leads to the dog itself. Another, not entirely serious, suggestion: ;) data Life a b = Work a (Life a b) | TheEnd b Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

Duncan Coutts wrote:
On Mon, 2009-11-30 at 06:08 +0000, Malcolm Wallace wrote:
However, if you really want to terminate the stream at the first error, and to reflect this in the type, then I guess you can define your own list type:
data ListThenError e a = Cons a (ListThenError e a) | Error e
Of course this has the disadvantage that then your consumer must change to use this type too.
I've been using this list type quite a lot recently. It's in the 'tar' package for example. It comes with variants of the standard functions foldl, foldr, unfoldr that take into account the error possibility.
At some point we should probably make a package to standardise and document this lazy error handling idiom.
I propose to (trivially) generalize this type to "list with an end" data ListEnd a b = Cons a (ListEnd a b) | End b because it may have other uses than just lazy error handling. For mnemonic value, we could call it a "train": data Train a b = Wagon a (Train a b) | Loco b as it is in analogy with a sequence of wagons of the same type followed by the locomotive which has a different type. This data type naturally turns up as the differential of the lists d [x] = Train x [x] and the usual zipper ([x],[x]) is actually an optimization: Train a b == ([a] , b) Incidentally, this isomorphism corresponds to the alternative approach you mentioned:
Another approach that some people have advocated as a general purpose solution is to use:
data Exceptional e a = Exceptional { exception :: Maybe e result :: a }
As for other uses of Train , I remember seeing the following fold operation fold1 :: (a -> b -> b) -> (a -> b) -> [a] -> b fold1 f g [a] = g a foldl f g (a:x) = f a (fold1 f g x) (from Oege de Moor, Jeremy Gibbons. "Bridging the Algorithm Gap: A Linear-Time Functional Program for Paragraph Formatting" http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.47.3229 ) which is of course the natural fold for the Train data type: fold :: (a -> c -> c) -> (b -> c) -> Train a b -> c fold f g (Loco b) = g b fold f g (Wagon a t) = f a (fold f g t) Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

Excerpts from Heinrich Apfelmus's message of Tue Dec 01 11:29:24 +0100 2009:
Duncan Coutts wrote:
On Mon, 2009-11-30 at 06:08 +0000, Malcolm Wallace wrote:
However, if you really want to terminate the stream at the first error, and to reflect this in the type, then I guess you can define your own list type:
data ListThenError e a = Cons a (ListThenError e a) | Error e
Of course this has the disadvantage that then your consumer must change to use this type too.
I've been using this list type quite a lot recently. It's in the 'tar' package for example. It comes with variants of the standard functions foldl, foldr, unfoldr that take into account the error possibility.
At some point we should probably make a package to standardise and document this lazy error handling idiom.
I propose to (trivially) generalize this type to "list with an end"
data ListEnd a b = Cons a (ListEnd a b) | End b
because it may have other uses than just lazy error handling. For mnemonic value, we could call it a "train":
data Train a b = Wagon a (Train a b) | Loco b
as it is in analogy with a sequence of wagons of the same type followed by the locomotive which has a different type.
This data type naturally turns up as the differential of the lists
d [x] = Train x [x]
and the usual zipper ([x],[x]) is actually an optimization:
Train a b == ([a] , b)
Incidentally, this isomorphism corresponds to the alternative approach you mentioned:
Another approach that some people have advocated as a general purpose solution is to use:
data Exceptional e a = Exceptional { exception :: Maybe e result :: a }
As for other uses of Train , I remember seeing the following fold operation
fold1 :: (a -> b -> b) -> (a -> b) -> [a] -> b fold1 f g [a] = g a foldl f g (a:x) = f a (fold1 f g x)
This proposition looks quite nice and gently subsume the ListThenError type. type ListThenError e a = Train a (Maybe e) Anyone to put this on Hackage? -- Nicolas Pouillard http://nicolaspouillard.fr

Nicolas Pouillard wrote:
Excerpts from Heinrich Apfelmus's message of Tue Dec 01 11:29:24 +0100 2009:
I propose to (trivially) generalize this type to "list with an end"
data ListEnd a b = Cons a (ListEnd a b) | End b
because it may have other uses than just lazy error handling. For mnemonic value, we could call it a "train":
data Train a b = Wagon a (Train a b) | Loco b
[...]
This proposition looks quite nice and gently subsume the ListThenError type.
type ListThenError e a = Train a (Maybe e)
Anyone to put this on Hackage?
I rather like it too. The mnemonic version sounds a lot nicer than "ListEnd", though I'd probably call the constructors Cabin and Caboose. The nice thing about the generalization is that even though (Train a b) is very similar to ([a],b) it's not exactly isomorphic. There are differences in the strictness of generating them and I've often wanted something like Train. Wherever this ends up, it'd be pretty easy to do train-fusion in order to reduce the cost over using lists. If noone else wants to take it, I could probably find a few tuits to get it done. Though it looks like John Millikin already has failable-list up on Hackage, which differs only in also having a Nil to end with (which interferes with certain fusions, but not the major ones). -- Live well, ~wren

wren ng thornton wrote:
Nicolas Pouillard wrote:
Excerpts from Heinrich Apfelmus's message of Tue Dec 01 11:29:24 +0100 2009:
For mnemonic value, we could call it a "train":
data Train a b = Wagon a (Train a b) | Loco b
I rather like it too. The mnemonic version sounds a lot nicer than "ListEnd", though I'd probably call the constructors Cabin and Caboose. I suspect the Train name runs into cultural differences. Cabin and Caboose are not names I know in relation to trains, and even Wagon and Loco don't immediately convey to me which one is which. I think a more obvious Cons/Terminator naming scheme is best.
Neil.

On Dec 1, 2009, at 2:29 AM, Heinrich Apfelmus wrote:
data Train a b = Wagon a (Train a b) | Loco b
Surely that should be: data Train a b = Wagon a (Train a b) | Caboose b ? - MtnViewMark Mark Lentczner http://www.ozonehouse.com/mark/ mark@glyphic.com

On Tue, Dec 1, 2009 at 5:29 AM, Heinrich Apfelmus
Duncan Coutts wrote:
On Mon, 2009-11-30 at 06:08 +0000, Malcolm Wallace wrote:
However, if you really want to terminate the stream at the first error, and to reflect this in the type, then I guess you can define your own list type:
data ListThenError e a = Cons a (ListThenError e a) | Error e
Of course this has the disadvantage that then your consumer must change to use this type too.
I've been using this list type quite a lot recently. It's in the 'tar' package for example. It comes with variants of the standard functions foldl, foldr, unfoldr that take into account the error possibility.
At some point we should probably make a package to standardise and document this lazy error handling idiom.
I propose to (trivially) generalize this type to "list with an end"
data ListEnd a b = Cons a (ListEnd a b) | End b
because it may have other uses than just lazy error handling.
This is almost a composition of a non-determism monad transformer with
an exception monad.
Specifically, "LogicT (Either e) a" is (almost) isomorphic with
data NX e a = Cons a (NX e a) | Nil | Error e
reflect :: NX e a -> LogicT (Either e) a
reflect (Cons a r) = return a `mplus` reflect r
reflect Nil = mzero
reflect (Error e) = lift (Left e)
reify :: LogicT (Either e) a -> NX e a
reify m = j $ runLogicT m (\a -> Right . Cons a . j) (Right Nil)
where j = either Error id
--
Dave Menendez

Duncan Coutts wrote:
Another approach that some people have advocated as a general purpose solution is to use:
data Exceptional e a = Exceptional { exception :: Maybe e result :: a }
However it's pretty clear from the structure of this type that it cannot cope with lazy error handling in sequences. If you try it you'll find you cannot do it without space leaks.
It's not all that clear. Consider this toy example (from a private discussion with Henning Thielemann a while ago), which runs in constant space: import System.IO.Unsafe import System.Environment import Control.Monad import Data.List data Exceptional e a = Exceptional { exception :: Maybe e, result :: a } ok a = Exceptional Nothing a fault e a = Exceptional (Just e) a faulty :: Int -> IO (Exceptional Int [Int]) faulty 0 = return (fault 0 []) faulty 1 = return (ok []) faulty n = unsafeInterleaveIO $ do -- getChar r <- faulty (n-2) return $ Exceptional (exception r) (n : result r) main = do n <- readIO . head =<< getArgs Exceptional exc res <- faulty n print $ last res when (n `mod` 3 == 0) $ print exc This works because ghc's garbage collector evaluates record selectors. (There are a simpler cases where this matters, for example last $ fst $ unzip [(a,a) | a <- [1..100000000]] which also runs in constant space.) The approach is very fragile, though. For example, if we change main to main = do n <- readIO . head =<< getArgs f <- faulty n print $ last (result f) when (n `mod` 3 == 0) $ print (exception f) then the space leak reoccurs - doing the pattern match on the Excpeptional constructor before using the result is essential. Bad things also happen if ghc's optimiser turns the record selectors into explicit pattern matches in the worker ('faulty' in the example). Kind regards, Bertram

On Mon, Nov 30, 2009 at 6:22 AM, John Millikin
...I've considered two possible error handling modes...
Regarding parsing, there's a third option: iteratees[1]. See [2] for a motivation and description of iteratees. regards, Bas [1] http://hackage.haskell.org/package/iteratee [2] http://okmij.org/ftp/Streams.html#iteratee
participants (14)
-
Bas van Dijk
-
Bertram Felgenhauer
-
David Menendez
-
Duncan Coutts
-
Heinrich Apfelmus
-
Jason McCarty
-
John Millikin
-
Ketil Malde
-
Luke Palmer
-
Malcolm Wallace
-
Mark Lentczner
-
Neil Brown
-
Nicolas Pouillard
-
wren ng thornton