Space Efficiency When Sorting a List of Many Lists

I'm a Haskell neophyte, so may be missing something obvious in the problem outlined below. I'm fairly proficient in Python + have some limited experience in OCaml and F#, so know just enough to be be dangerous, but not nearly enough to really know what I'm doing here. OK, I have text files containing 'compressed lists' Compressed lists look like this: 8+12,11,7+13,10 1+2+3,1+9,3+6,4 . . Sublists are comma-delimited, and sublist elements are separated by '+' character. I parse these to look like so: [[[8,12],[11],[7,13],[10]], [[1,2,3],[1,9],[3,6],[4]], . . ] I need to explode these and produce a lex-sorted list of exploded lists: [[1,1,3,4],[1,1,6,4],[1,9,3,4],[1,9,6,4],[2,1,3,4],[2,1,6,4],[2,9,3,4], [2,9,6,4],[3,1,3,4],[3,1,6,4],[3,9,3,4],[3,9,6,4], [8,11,7,10],[8,11,13,10],[12,11,7,10],[12,11,13,10]] I then output this data as comma-delimited lists: 1,1,3,4 1,1,6,4 . . 12,11,13,10 I can do all this in my (no doubt fairly naive) program shown below. In real life, one of my test data files contains compressed lists which all contain 7 sublists. This data (correctly) explodes to a list containing ~3,700,000 exploded lists. All good as far as correctly transforming input to output goes. However, sorting the data uses a lot of memory: Partial output from ./explode +RTS -sstderr: 540 MB total memory in use (4 MB lost due to fragmentation) If I do not do any sorting on the exploded lists, i.e. modify the main function to be main = interact (unlines . toCSV . explode . fromCSV . lines) I then see this partial output from ./explode +RTS --stderr: 2 MB total memory in use (0 MB lost due to fragmentation) I can guess that there might be be less laziness and more instantiation when sorting is introduced, but my questions are: (1) Am I doing anything terribly stupid/naive here? (2) If so, what can I do to improve space efficiency? TIA! import Data.List (sort) import Data.List.Split (splitOn) -- Cartesian Product over a List of Lists -- cp [[1,2],[3],[4,5,6]] --> [[1,3,4],[1,3,5],[1,3,6],[2,3,4],[2,3,5], [2,3,6]] cp :: [[a]] -> [[a]] cp [] = [[]] cp (xs:xss) = [y:ys | y <- xs, ys <- cp xss] -- fromCSV ["8+12,11,7+13,10", "1+2+3,1+9,3+6,4"] --> -- [[[8,12],[11],[7,13],[10]],[[1,2,3],[1,9],[3,6],[4]]] fromCSV :: [String] -> [[[Int]]] fromCSV = map parseOneLine where parseOneLine = map parseGroup . splitOn "," where parseGroup = map read . splitOn "+" -- explode [[[1,2],[3],[4,5,6]], [[1, 2], [14,15], [16]]] --> [[1,3,4], [1,3,5], -- [1,3,6],[2,3,4],[2,3,5],[2,3,6],[1,14,16],[1,15,16],[2,14,16], [2,15,16]] explode :: [[[a]]] -> [[a]] explode = concatMap cp -- toCSV [[8,11,7,10,12],[8,11,7,10,12],[8,11,7,10,12]] --> -- ["8,11,7,10,12","8,11,7,10,12","8,11,7,10,12"] toCSV :: (Show a) => [[a]] -> [String] toCSV = map $ tail . init . show --toCSV = map (intercalate "," . map show) main = interact (unlines . toCSV . sort . explode . fromCSV . lines)

On Wed, Dec 30, 2009 at 8:39 PM, Peter Green
I'm a Haskell neophyte, so may be missing something obvious in the problem outlined below. I'm fairly proficient in Python + have some limited experience in OCaml and F#, so know just enough to be be dangerous, but not nearly enough to really know what I'm doing here.
OK, I have text files containing 'compressed lists' Compressed lists look like this:
8+12,11,7+13,10 1+2+3,1+9,3+6,4 . .
Sublists are comma-delimited, and sublist elements are separated by '+' character.
I parse these to look like so:
[[[8,12],[11],[7,13],[10]], [[1,2,3],[1,9],[3,6],[4]], . . ]
I need to explode these and produce a lex-sorted list of exploded lists:
[[1,1,3,4],[1,1,6,4],[1,9,3,4],[1,9,6,4],[2,1,3,4],[2,1,6,4],[2,9,3,4],[2,9,6,4],[3,1,3,4],[3,1,6,4],[3,9,3,4],[3,9,6,4], [8,11,7,10],[8,11,13,10],[12,11,7,10],[12,11,13,10]]
I then output this data as comma-delimited lists:
1,1,3,4 1,1,6,4 . . 12,11,13,10
I can do all this in my (no doubt fairly naive) program shown below. In real life, one of my test data files contains compressed lists which all contain 7 sublists. This data (correctly) explodes to a list containing ~3,700,000 exploded lists. All good as far as correctly transforming input to output goes. However, sorting the data uses a lot of memory:
Partial output from ./explode +RTS -sstderr:
540 MB total memory in use (4 MB lost due to fragmentation)
If I do not do any sorting on the exploded lists, i.e. modify the main function to be main = interact (unlines . toCSV . explode . fromCSV . lines)
I then see this partial output from ./explode +RTS --stderr:
2 MB total memory in use (0 MB lost due to fragmentation)
I can guess that there might be be less laziness and more instantiation when sorting is introduced, but my questions are: (1) Am I doing anything terribly stupid/naive here? (2) If so, what can I do to improve space efficiency?
TIA!
import Data.List (sort) import Data.List.Split (splitOn)
-- Cartesian Product over a List of Lists -- cp [[1,2],[3],[4,5,6]] --> [[1,3,4],[1,3,5],[1,3,6],[2,3,4],[2,3,5],[2,3,6]] cp :: [[a]] -> [[a]] cp [] = [[]] cp (xs:xss) = [y:ys | y <- xs, ys <- cp xss]
-- fromCSV ["8+12,11,7+13,10", "1+2+3,1+9,3+6,4"] --> -- [[[8,12],[11],[7,13],[10]],[[1,2,3],[1,9],[3,6],[4]]] fromCSV :: [String] -> [[[Int]]] fromCSV = map parseOneLine where parseOneLine = map parseGroup . splitOn "," where parseGroup = map read . splitOn "+"
-- explode [[[1,2],[3],[4,5,6]], [[1, 2], [14,15], [16]]] --> [[1,3,4],[1,3,5], -- [1,3,6],[2,3,4],[2,3,5],[2,3,6],[1,14,16],[1,15,16],[2,14,16],[2,15,16]] explode :: [[[a]]] -> [[a]] explode = concatMap cp
-- toCSV [[8,11,7,10,12],[8,11,7,10,12],[8,11,7,10,12]] --> -- ["8,11,7,10,12","8,11,7,10,12","8,11,7,10,12"] toCSV :: (Show a) => [[a]] -> [String] toCSV = map $ tail . init . show --toCSV = map (intercalate "," . map show)
main = interact (unlines . toCSV . sort . explode . fromCSV . lines)
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
I'm not sure about your problem specifically but the external-sort package on Hackage may be of interest. Alex

On Wed, Dec 30, 2009 at 9:39 PM, Peter Green
I can guess that there might be be less laziness and more instantiation when sorting is introduced,
Yes, by a lot. Sorting requires keeping the entire list in memory. And Haskell lists, unfortunately, are not that cheap in terms of space usage (I think [Int] uses 3 words per element).
but my questions are: (1) Am I doing anything terribly stupid/naive here? (2) If so, what can I do to improve space efficiency?
TIA!
import Data.List (sort) import Data.List.Split (splitOn)
-- Cartesian Product over a List of Lists -- cp [[1,2],[3],[4,5,6]] --> [[1,3,4],[1,3,5],[1,3,6],[2,3,4],[2,3,5],[2,3,6]] cp :: [[a]] -> [[a]] cp [] = [[]] cp (xs:xss) = [y:ys | y <- xs, ys <- cp xss]
This cartesian product varies in its tail faster than its head, so every head gets its own unique tail. If you reverse the order of the bindings so that it varies in its head faster, then tails are shared. If my quick and dirty reasoning is correct, it improves the space usage by a factor of the number of sublists. cp' [] = [[]] cp' (xs:xss) = [y:ys | ys <- cp' xss, y <- xs] But if you're serious, you can probably do better than just generating them all and passing them to sort. I get the impression that there is some structure here that can be taken advantage of.
-- fromCSV ["8+12,11,7+13,10", "1+2+3,1+9,3+6,4"] --> -- [[[8,12],[11],[7,13],[10]],[[1,2,3],[1,9],[3,6],[4]]] fromCSV :: [String] -> [[[Int]]] fromCSV = map parseOneLine where parseOneLine = map parseGroup . splitOn "," where parseGroup = map read . splitOn "+"
-- explode [[[1,2],[3],[4,5,6]], [[1, 2], [14,15], [16]]] --> [[1,3,4],[1,3,5], -- [1,3,6],[2,3,4],[2,3,5],[2,3,6],[1,14,16],[1,15,16],[2,14,16],[2,15,16]] explode :: [[[a]]] -> [[a]] explode = concatMap cp
-- toCSV [[8,11,7,10,12],[8,11,7,10,12],[8,11,7,10,12]] --> -- ["8,11,7,10,12","8,11,7,10,12","8,11,7,10,12"] toCSV :: (Show a) => [[a]] -> [String] toCSV = map $ tail . init . show --toCSV = map (intercalate "," . map show)
main = interact (unlines . toCSV . sort . explode . fromCSV . lines)
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Am Donnerstag 31 Dezember 2009 11:38:51 schrieb Luke Palmer:
This cartesian product varies in its tail faster than its head, so every head gets its own unique tail. If you reverse the order of the bindings so that it varies in its head faster, then tails are shared. If my quick and dirty reasoning is correct, it improves the space usage by a factor of the number of sublists.
That reasoning is supported by http://www.haskell.org/pipermail/haskell-cafe/2009-December/070184.html However, that concerns only the generation of the lists to be sorted, as far as I can see (that will be faster and use less memory). The main problem here is the space usage of the sorting, I think. For that, probably an external sort is the best solution.

On Thu, Dec 31, 2009 at 03:38:51AM -0700, Luke Palmer wrote:
But if you're serious, you can probably do better than just generating them all and passing them to sort. I get the impression that there is some structure here that can be taken advantage of.
Isn't what he wants a trie? In particular, a Patricia trie? If he cares about repeated elements then he can use a structure like list-tries' Data.ListTrie.Patricia.Map.Ord.TrieMap[1]. The values would be the number of times that sequence was seen. Taking advantage of the list structure should give tremendous speed improvements since fewer comparisions between the list elements are made. Also the trie will automatically share common parts. All that being said, I don't think I really understood OP's problem :). HTH! [1] http://hackage.haskell.org/packages/archive/list-tries/0.1/doc/html/Data-Lis... -- Felipe.

Felipe Lessa wrote:
Luke Palmer wrote:
But if you're serious, you can probably do better than just generating them all and passing them to sort. I get the impression that there is some structure here that can be taken advantage of.
Isn't what he wants a trie? In particular, a Patricia trie?
Peter, this is a very nice problem. Is this a programming exercise or did you encounter it in the "real world"? There is indeed a structure that can be taken advantage of and it involves tries. The key point is that thanks to the lexicographic ordering, you can *interleave* exploding and sorting the rows. In other word, we can exploit the fact that for example (sort . cartesian) ([8,12]:[11]:[7,13]:[10]:[]) = [8 : (sort . cartesian) ([11]:[7,13]:[10]:[]) ] ++ [12 : (sort . cartesian) ([11]:[7,13]:[10]:[]) ] where cartesian denotes the cartesian product. The code will mainly work with functions like type Row a = [a] headsIn :: [Row a] -> [(a, [Row a])] which groups rows by their first element. The result type is best understood as a finite map from a to [Row a] headsIn :: [Row a] -> Map a [Row a] And unsurprisingly, the fixed point of the (Map a) functor is the trie for [a] . Without much explanation, here the full formulation in terms of catamorphisms and anamorphisms. {-# LANGUAGE NoMonomorphismRestriction #-} import qualified Data.Map import Control.Arrow (second) -- the underlying structure newtype Map a b = Map { unMap :: [(a,b)] } deriving (Eq, Show) -- category theory: bananas and lenses instance Functor (Map a) where fmap f = Map . (map . second) f . unMap newtype Fix f = In { out :: f (Fix f) } cata f = In . fmap (cata f) . f ana f = f . fmap (ana f) . out -- very useful type synonym to keep track of rows and colums type Row a = [a] -- grouping and "ungrouping" by the first elements of each row headsIn :: [Row a] -> Map a [Row a] headsIn xss = Map [(x,[xs]) | x:xs <- xss] headsOut :: Map a [Row a] -> [Row a] headsOut (Map []) = [[]] headsOut xxs = [x:xs | (x,xss) <- unMap xxs, xs <- xss] -- cartesian product cartesian1 :: Row [a] -> Map a (Row [a]) cartesian1 [] = Map [] cartesian1 (xs:xss) = Map [(x,xss) | x <- xs] cartesian = ana headsOut . cata cartesian1 -- sorting sort1 :: Ord a => Map a [b] -> Map a [b] sort1 = Map . Data.Map.toList . Data.Map.fromListWith (++) . unMap sortRows = ana headsOut . cata (sort1 . headsIn) -- and cold fusion! -- sortCartesian = sortRows . cartesian -- best written as hylomorphism sortCartesian = ana headsOut . cata (sort1 . cartesian1) This is readily extended to handle the explode function as well. And thanks to lazy evaluation, I expect this to run with a much better memory footprint. Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

On 31/12/2009, at 6:38 PM, Luke Palmer wrote:
On Wed, Dec 30, 2009 at 9:39 PM, Peter Green
wrote: I can guess that there might be be less laziness and more instantiation when sorting is introduced,
Yes, by a lot. Sorting requires keeping the entire list in memory. And Haskell lists, unfortunately, are not that cheap in terms of space usage (I think [Int] uses 3 words per element).
but my questions are: (1) Am I doing anything terribly stupid/naive here? (2) If so, what can I do to improve space efficiency?
TIA!
import Data.List (sort) import Data.List.Split (splitOn)
-- Cartesian Product over a List of Lists -- cp [[1,2],[3],[4,5,6]] --> [[1,3,4],[1,3,5],[1,3,6],[2,3,4],[2,3,5],[2,3,6]] cp :: [[a]] -> [[a]] cp [] = [[]] cp (xs:xss) = [y:ys | y <- xs, ys <- cp xss]
This cartesian product varies in its tail faster than its head, so every head gets its own unique tail. If you reverse the order of the bindings so that it varies in its head faster, then tails are shared. If my quick and dirty reasoning is correct, it improves the space usage by a factor of the number of sublists.
cp' [] = [[]] cp' (xs:xss) = [y:ys | ys <- cp' xss, y <- xs]
But if you're serious, you can probably do better than just generating them all and passing them to sort. I get the impression that there is some structure here that can be taken advantage of.
-- fromCSV ["8+12,11,7+13,10", "1+2+3,1+9,3+6,4"] --> -- [[[8,12],[11],[7,13],[10]],[[1,2,3],[1,9],[3,6],[4]]] fromCSV :: [String] -> [[[Int]]] fromCSV = map parseOneLine where parseOneLine = map parseGroup . splitOn "," where parseGroup = map read . splitOn "+"
-- explode [[[1,2],[3],[4,5,6]], [[1, 2], [14,15], [16]]] --> [[1,3,4],[1,3,5], -- [1,3,6],[2,3,4],[2,3,5],[2,3,6],[1,14,16],[1,15,16],[2,14,16], [2,15,16]] explode :: [[[a]]] -> [[a]] explode = concatMap cp
-- toCSV [[8,11,7,10,12],[8,11,7,10,12],[8,11,7,10,12]] --> -- ["8,11,7,10,12","8,11,7,10,12","8,11,7,10,12"] toCSV :: (Show a) => [[a]] -> [String] toCSV = map $ tail . init . show --toCSV = map (intercalate "," . map show)
main = interact (unlines . toCSV . sort . explode . fromCSV . lines)
Thank you everyone for the very helpful suggestions so far! I think I should re-state the problem and provide more background info. In answer to the poster who suggested using a Trie, there *is* a real world application for what I'm attempting to do. I'll also hint at that below: I have text files containing 'compressed lists' Compressed lists look like this: 8+12,11,7+13,10 1+2+3,1+9,3+6,4 . . Sublists are comma-delimited, and sublist elements are separated by '+' character. Sublists contain integers in the range 1..20. I parse these to look like so: [[[8,12],[11],[7,13],[10]], [[1,2,3],[1,9],[3,6],[4]], . . ] I need to explode these and produce a lex-sorted list of exploded lists: [[1,1,3,4],[1,1,6,4],[1,9,3,4],[1,9,6,4],[2,1,3,4],[2,1,6,4],[2,9,3,4], [2,9,6,4],[3,1,3,4],[3,1,6,4],[3,9,3,4],[3,9,6,4], [8,11,7,10],[8,11,13,10],[12,11,7,10],[12,11,13,10]] I then output this data as comma-delimited lists: 1,1,3,4 1,1,6,4 . . 12,11,13,10 It is a property of the underlying problem 'structure' that none of these comma-delimited lists in the exploded data is repeated. i.e. we can never see two instances of (say) 1,1,3,4. { Begin Aside on Why I Would Want to do Such a Silly Thing: 'Compressed lists' are in fact compressed wager combinations for multi- leg exotic horse racing events. 'Exploded lists' are the single wager combinations covered by the grouped combinations. Why use compressed combinations? Well, it's a lot easier to submit 5,000 compressed tickets (whether physically or electronically) than 1M single tickets for the individual combinations we have somehow managed to represent by the 5,000 compressed tickets. However, single combinations are the currency of the realm. These are the underlying wagers and compression is merely a convenience/ necessity to enable single wagers to be placed. It's not uncommon to generate large numbers of single combinations: Imagine 6 races with 15 runners in each race, and a wager requiring one to select first place getters in all 6 legs. The number of potential outcomes is 15^6 = 11,390,625. One might decide (somehow) that it makes sense in a positive expectation way to wager (say) 500K of these potential outcomes. Getting from theoretically desirable single combinations to optimally compressed wagers is actually NP-Complete and another story for another day. Suffice it to say that one might use some nasty hacks and heuristics to arrive at compressed wagers - but in the process doing violence to one's precise coverage of the theoretically desirable single combinations. That's one reason why I need to recover (by 'exploding') the *actual* wagered single combinations from the compressed/ wagers. I need to explode these compressed wagers back to single combinations because, I need to (eventually) do set comparisons on collections of single combinations. i.e. given File A and File B of compressed wagers, I need to be able to answer questions like: (1) How many single combinations are common to File A and File B (2) How many single combinations in File A are missing from File B . . etc. i.e a few of the common set comparison operations. And the dumbest, quickest and dirtiest and most idiot-proof way of doing this as a baseline approach before I start using maps, tries, etc... is to explode Files A and B into lex sorted single combinations order and then use diff -y with judicious grepping for '>' and <'' End Aside } I'm probably going to go with an external sort for starters to keep memory usage down. For most use-cases, I can get away with my current in-memory sort - just have to beware edge cases. However, later on, I'm keen to do everything with set theoretic operations and avoid writing large files of single combinations to disk. So, I guess the things I'd like to get a feel for are: (1) Is it realistic to expect to do in-memory set comparisons on sets with ~1M elements where each element is a (however-encoded) list of (say) 6 integers? I mean realistic in terms of execution time and space usage, of course. (2) What would be a good space-efficient encoding for these single combinations? I know that there will never be more than 8 integers in a combination, and none of these values will be < 1 or > 20. So perhaps I should map them to ByteString library Word8 strings? Presumably sorting a big list of ByteStrings is going to be faster than sorting a big list of lists of int?

Peter Green wrote:
Luke Palmer wrote:
Yes, by a lot. Sorting requires keeping the entire list in memory. And Haskell lists, unfortunately, are not that cheap in terms of space usage (I think [Int] uses 3 words per element).
but my questions are: (1) Am I doing anything terribly stupid/naive here? (2) If so, what can I do to improve space efficiency?
I think I should re-state the problem and provide more background info. In answer to the poster who suggested using a Trie, there *is* a real world application for what I'm attempting to do. I'll also hint at that below:
{ Begin Aside on Why I Would Want to do Such a Silly Thing:
'Compressed lists' are in fact compressed wager combinations for multi-leg exotic horse racing events. 'Exploded lists' are the single wager combinations covered by the grouped combinations.
[...]
Thanks for describing the background of this problem in detail! I was mainly asking because I'm always looking for interesting Haskell topics that can be turned into a tutorial of sorts, and this problem makes a great example. Concerning optimization, the background also reveals some additional informations, namely * The single wager combinations are short lists * and each list element is small, i.e. `elem` [1..20] * No duplicate single wagers * You are free to choose another ordering than lexicographic
I need to explode these compressed wagers back to single combinations because, I need to (eventually) do set comparisons on collections of single combinations. i.e. given File A and File B of compressed wagers, I need to be able to answer questions like:
(1) How many single combinations are common to File A and File B (2) How many single combinations in File A are missing from File B .. .. etc. i.e a few of the common set comparison operations.
And the dumbest, quickest and dirtiest and most idiot-proof way of doing this as a baseline approach before I start using maps, tries, etc... is to explode Files A and B into lex sorted single combinations order and then use diff -y with judicious grepping for '>' and <''
Looks good to me, sorted lists are a fine data structure for set operations.
I'm probably going to go with an external sort for starters to keep memory usage down. For most use-cases, I can get away with my current in-memory sort - just have to beware edge cases.
Using an out-of-the box external sort library is probably the path of least resistance, provided the library works as it should. However, your problem has a very special structure; you can interleave explode and sort and turn the algorithm into one that is partially on-line, which will save you a lot of memory. I've tried to show how to do this in my previous post; the resulting code will look something like this {-# LANGUAGE NoMonomorphismRestriction #-} import qualified Data.Map import Control.Arrow (second) newtype Map a b = Map { unMap :: [(a,b)] } deriving (Eq, Show) instance Functor (Map a) where fmap f = Map . (map . second) f . unMap hylo :: (Map a b -> b) -> (c -> Map a c) -> (c -> b) hylo f g = f . fmap (hylo f g) . g type Row a = [a] headsOut :: Map a [Row a] -> [Row a] headsOut (Map []) = [[]] headsOut m = [x:row | (x,rows) <- unMap m, row <- rows] explode1 :: [Row [a]] -> Map a [Row [a]] explode1 rows = Map [(x,[row]) | (xs:row) <- rows, x <- xs] sort1 :: Ord a => Map a [b] -> Map a [b] sort1 = Map . Data.Map.toList . Data.Map.fromListWith (++) . unMap sortExplode = hylo headsOut (sort1 . explode1) example = [[[8,12],[11],[7,13],[10]], [[1,2,3],[1,9],[3,6],[4]]] test = sortExplode example main = interact (unlines . toCSV . sortExplode . fromCSV . lines) In other words, sortExplode will "stream" the sorted single wagers on demand, unlike the monolithic sort . explode which has to produce all single wagers before sorting them.
However, later on, I'm keen to do everything with set theoretic operations and avoid writing large files of single combinations to disk.
Note that there's also the possibility of not expanding the compressed wagers at all, and perform set operations directly. For instance, it is straightforward to intersect two such sets of size n in O(n^2) time. Since n ~ 5000 , n^2 is about the same ballpark as the exploded single wager combinations.
So, I guess the things I'd like to get a feel for are:
(1) Is it realistic to expect to do in-memory set comparisons on sets with ~1M elements where each element is a (however-encoded) list of (say) 6 integers? I mean realistic in terms of execution time and space usage, of course.
(2) What would be a good space-efficient encoding for these single combinations? I know that there will never be more than 8 integers in a combination, and none of these values will be < 1 or > 20. So perhaps I should map them to ByteString library Word8 strings? Presumably sorting a big list of ByteStrings is going to be faster than sorting a big list of lists of int?
The overhead for lists and sets are quite high, it's not uncommon for 1M elements to occupy 10M-100M of memory. Not to mention that your elements are, in fact, small lists, introducing another factor of 10-100. But this can indeed be ameliorated considerably by representing your elements in a packed format like ByteStrings or a Word64. Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com
participants (6)
-
Alexander Dunlap
-
Daniel Fischer
-
Felipe Lessa
-
Heinrich Apfelmus
-
Luke Palmer
-
Peter Green