Proposal: Add a strict version of <$> for monads

Hi all, I propose we add a strict version of <$> to base: -- | A strict version of 'Data.Functor.<$>' for monads. (<$!>) :: Monad m => (a -> b) -> m a -> m b f <$!> m = do a <- m return $! f a {-# INLINE (<$!>) #-} infixl 4 <$!> It works on Monads instead of Functors as required by us inspecting the argument. This version is highly convenient if you want to work with functors/applicatives in e.g. parser and avoid spurious thunks at the same time. I realized that it was needed while fixing large space usage (but not space-leak) issues in cassava. I believe Edward Kmett discovered the need for it independently as well. Deadline: 3 weeks Cheers, Johan

Obvious +1.
On Fri, Nov 29, 2013 at 1:07 PM, Johan Tibell
Hi all,
I propose we add a strict version of <$> to base:
-- | A strict version of 'Data.Functor.<$>' for monads. (<$!>) :: Monad m => (a -> b) -> m a -> m b f <$!> m = do a <- m return $! f a {-# INLINE (<$!>) #-}
infixl 4 <$!>
It works on Monads instead of Functors as required by us inspecting the argument.
This version is highly convenient if you want to work with functors/applicatives in e.g. parser and avoid spurious thunks at the same time. I realized that it was needed while fixing large space usage (but not space-leak) issues in cassava.
I believe Edward Kmett discovered the need for it independently as well.
Deadline: 3 weeks
Cheers, Johan
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
--
Gregory Collins

I don't like that this function is implemented for Monads, I think that it makes sense for some other functors as well. Though to do this 'properly' we would probably end up with another typeclass "StrictFunctor" or something, and that is perhaps too much unnecessary complexity. In the same vein as strict fmap, does a strict (<*>) make sense as well? -- | A strict version of `Control.Applicative.<*>` for monads (<*!>) :: Monad m => m (a -> b) -> m a -> m b mf <*!> mx = do f <- mf x <- mx return $! f x We might also call these fmap' and ap', but I prefer the operator. Twan On 29/11/13 12:07, Johan Tibell wrote:
Hi all,
I propose we add a strict version of <$> to base:
-- | A strict version of 'Data.Functor.<$>' for monads. (<$!>) :: Monad m => (a -> b) -> m a -> m b f <$!> m = do a <- m return $! f a {-# INLINE (<$!>) #-}
infixl 4 <$!>
It works on Monads instead of Functors as required by us inspecting the argument.
This version is highly convenient if you want to work with functors/applicatives in e.g. parser and avoid spurious thunks at the same time. I realized that it was needed while fixing large space usage (but not space-leak) issues in cassava.
I believe Edward Kmett discovered the need for it independently as well.
Deadline: 3 weeks
Cheers, Johan
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On Fri, Nov 29, 2013 at 1:19 PM, Twan van Laarhoven
I don't like that this function is implemented for Monads, I think that it makes sense for some other functors as well. Though to do this 'properly' we would probably end up with another typeclass "StrictFunctor" or something, and that is perhaps too much unnecessary complexity.
Do you have an example of such a functor? -- Johan

On 29.11.2013 13:23, Johan Tibell wrote:
On Fri, Nov 29, 2013 at 1:19 PM, Twan van Laarhoven
I don't like that this function is implemented for Monads, I think that it makes sense for some other functors as well. Though to do this 'properly' we would probably end up with another typeclass "StrictFunctor" or something, and that is perhaps too much unnecessary complexity.
Do you have an example of such a functor?
Async is a Functor (but not Applicative). When asyncs finish and you poll their result with `wait`, you potentially get back an IO <thunk>. (Just the first example that came to mind.) David

On 29 November 2013 23:35, David Luposchainsky
On 29.11.2013 13:23, Johan Tibell wrote:
On Fri, Nov 29, 2013 at 1:19 PM, Twan van Laarhoven
I don't like that this function is implemented for Monads, I think that it makes sense for some other functors as well. Though to do this 'properly' we would probably end up with another typeclass "StrictFunctor" or something, and that is perhaps too much unnecessary complexity.
Do you have an example of such a functor?
Async is a Functor (but not Applicative). When asyncs finish and you poll their result with `wait`, you potentially get back an IO <thunk>. (Just the first example that came to mind.)
Except wait :: Async a -> IO a, so it's actually in the IO monad (which _is_ a monad :p). I'm +1 -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com http://IvanMiljenovic.wordpress.com

On 29.11.2013 13:42, Ivan Lazar Miljenovic wrote:
On 29 November 2013 23:35, David Luposchainsky
wrote: Async is a Functor (but not Applicative). When asyncs finish and you poll their result with `wait`, you potentially get back an IO <thunk>. (Just the first example that came to mind.)
Except wait :: Async a -> IO a, so it's actually in the IO monad (which _is_ a monad :p).
Sure, but now you're in IO (and can $! in IO of course). But sometimes you may not want to `wait` just yet, and evaluate the Async's eventual result directly to WHNF, so that if you then `wait`, you get an already evaluated thing in IO.

On 29/11/13 12:23, Johan Tibell wrote:
On Fri, Nov 29, 2013 at 1:19 PM, Twan van Laarhoven
mailto:twanvl@gmail.com> wrote: I don't like that this function is implemented for Monads, I think that it makes sense for some other functors as well. Though to do this 'properly' we would probably end up with another typeclass "StrictFunctor" or something, and that is perhaps too much unnecessary complexity.
Do you have an example of such a functor?
-- Johan
The first thing that came to mind was ZipList. Perhaps a more realistic example would be parsing combinator or FRP libraries that are applicative but not monadic. Twan

I'm trying to figure out whether this is a property of the functor itself.
I guess it is, but at the same time it seems somewhat orthogonal whether to
`seq` some value`.
On Fri, Nov 29, 2013 at 3:50 PM, Twan van Laarhoven
On 29/11/13 12:23, Johan Tibell wrote:
On Fri, Nov 29, 2013 at 1:19 PM, Twan van Laarhoven
mailto:twanvl@gmail.com> wrote: I don't like that this function is implemented for Monads, I think that it makes sense for some other functors as well. Though to do this 'properly' we would probably end up with another typeclass "StrictFunctor" or something, and that is perhaps too much unnecessary complexity.
Do you have an example of such a functor?
-- Johan
The first thing that came to mind was ZipList. Perhaps a more realistic example would be parsing combinator or FRP libraries that are applicative but not monadic.
Twan

could someone explain to me why this <$!> would be for monads rather being
more generally also for functors or applicatives?
On Fri, Nov 29, 2013 at 10:35 AM, Johan Tibell
I'm trying to figure out whether this is a property of the functor itself. I guess it is, but at the same time it seems somewhat orthogonal whether to `seq` some value`.
On Fri, Nov 29, 2013 at 3:50 PM, Twan van Laarhoven
wrote: On 29/11/13 12:23, Johan Tibell wrote:
On Fri, Nov 29, 2013 at 1:19 PM, Twan van Laarhoven
mailto:twanvl@gmail.com> wrote: I don't like that this function is implemented for Monads, I think that it makes sense for some other functors as well. Though to do this 'properly' we would probably end up with another typeclass "StrictFunctor" or something, and that is perhaps too much unnecessary complexity.
Do you have an example of such a functor?
-- Johan
The first thing that came to mind was ZipList. Perhaps a more realistic example would be parsing combinator or FRP libraries that are applicative but not monadic.
Twan
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On Fri, Nov 29, 2013 at 12:03:43PM -0500, Carter Schonwald wrote:
could someone explain to me why this <$!> would be for monads rather being more generally also for functors or applicatives?
It's not clear whether such a thing can be implemented for a functor or applicative. It seemingly needs to exploit the fact that the next action in a bind can depend on the "value returned by" the previous action. Still, the semantics depend very much on the laziness properties of the monad in question. f <$!> m = do a <- m return $! f a data R x = R x data S x = S x data T x = T x instance Monad T where return = T m >>= f = T (case m of T m' -> case f m' of T y -> y) instance Monad S where return = S m >>= f = case m of S m' -> S (case f m' of S y -> y) -- Equivalent implementation -- S m' >>= f = S (case f m' of S y -> y) instance Monad R where return = R m >>= f = case m of R m' -> case f m' of R y -> R y -- Equivalent implementations: -- m >>= f = case m of R m' -> f m' -- R m' >>= f = f m' try :: Monad m => m Int -> () try l = (+1) <$!> l `seq` () *Main> try (undefined :: T Int) () *Main> try (T undefined :: T Int) () *Main> try (undefined :: S Int) *** Exception: Prelude.undefined *Main> try (S undefined :: S Int) () *Main> try (undefined :: R Int) *** Exception: Prelude.undefined *Main> try (R undefined :: R Int) *** Exception: Prelude.undefined Tom

Figure out how to write one using either of those APIs, and I'll be quite impressed. =) I personally use this quite often when working in a monad, in lieu of `return $!` games. The argument for implementing a version of it in terms of Monad and not some new class off to the side of the class hierarchy that Monad doesn't subclass is that, frankly, if such a thing existed, I'd still have to use this combinator anyways when working with a transformer stack, etc. and would derive little benefit. -Edward On Fri, Nov 29, 2013 at 12:03 PM, Carter Schonwald < carter.schonwald@gmail.com> wrote:
could someone explain to me why this <$!> would be for monads rather being more generally also for functors or applicatives?
On Fri, Nov 29, 2013 at 10:35 AM, Johan Tibell
wrote: I'm trying to figure out whether this is a property of the functor itself. I guess it is, but at the same time it seems somewhat orthogonal whether to `seq` some value`.
On Fri, Nov 29, 2013 at 3:50 PM, Twan van Laarhoven
wrote: On 29/11/13 12:23, Johan Tibell wrote:
On Fri, Nov 29, 2013 at 1:19 PM, Twan van Laarhoven
mailto:twanvl@gmail.com> wrote: I don't like that this function is implemented for Monads, I think that it makes sense for some other functors as well. Though to do this 'properly' we would probably end up with another typeclass "StrictFunctor" or something, and that is perhaps too much unnecessary complexity.
Do you have an example of such a functor?
-- Johan
The first thing that came to mind was ZipList. Perhaps a more realistic example would be parsing combinator or FRP libraries that are applicative but not monadic.
Twan
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

I'm without a doubt overlooking something, but couldn't this be (otoh)
fmap' :: Functor f => (a -> b) -> f a -> f b
fmap' f = fmap (strictify f)
where
strictify s = (($!) id) . s
Nicolas
On Nov 30, 2013 12:11 AM, "Edward Kmett"
Figure out how to write one using either of those APIs, and I'll be quite impressed. =)
I personally use this quite often when working in a monad, in lieu of `return $!` games.
The argument for implementing a version of it in terms of Monad and not some new class off to the side of the class hierarchy that Monad doesn't subclass is that, frankly, if such a thing existed, I'd still have to use this combinator anyways when working with a transformer stack, etc. and would derive little benefit.
-Edward
On Fri, Nov 29, 2013 at 12:03 PM, Carter Schonwald < carter.schonwald@gmail.com> wrote:
could someone explain to me why this <$!> would be for monads rather being more generally also for functors or applicatives?
On Fri, Nov 29, 2013 at 10:35 AM, Johan Tibell
wrote: I'm trying to figure out whether this is a property of the functor itself. I guess it is, but at the same time it seems somewhat orthogonal whether to `seq` some value`.
On Fri, Nov 29, 2013 at 3:50 PM, Twan van Laarhoven
wrote: On 29/11/13 12:23, Johan Tibell wrote:
On Fri, Nov 29, 2013 at 1:19 PM, Twan van Laarhoven
mailto:twanvl@gmail.com> wrote: I don't like that this function is implemented for Monads, I think that it makes sense for some other functors as well. Though to do this 'properly' we would probably end up with another typeclass "StrictFunctor" or something, and that is perhaps too much unnecessary complexity.
Do you have an example of such a functor?
-- Johan
The first thing that came to mind was ZipList. Perhaps a more realistic example would be parsing combinator or FRP libraries that are applicative but not monadic.
Twan
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

No. Evaluation of your 'strictify' function will be delayed for the very
same reason that evaluation of 'f' is delayed in the first place.
It doesn't matter what 'strictify' *does* if it's not even evaluated.
* Nicolas Trangez
I'm without a doubt overlooking something, but couldn't this be (otoh)
fmap' :: Functor f => (a -> b) -> f a -> f b fmap' f = fmap (strictify f) where strictify s = (($!) id) . s
Nicolas On Nov 30, 2013 12:11 AM, "Edward Kmett"
wrote: Figure out how to write one using either of those APIs, and I'll be quite impressed. =)
I personally use this quite often when working in a monad, in lieu of `return $!` games.
The argument for implementing a version of it in terms of Monad and not some new class off to the side of the class hierarchy that Monad doesn't subclass is that, frankly, if such a thing existed, I'd still have to use this combinator anyways when working with a transformer stack, etc. and would derive little benefit.
-Edward
On Fri, Nov 29, 2013 at 12:03 PM, Carter Schonwald < carter.schonwald@gmail.com> wrote:
could someone explain to me why this <$!> would be for monads rather being more generally also for functors or applicatives?
On Fri, Nov 29, 2013 at 10:35 AM, Johan Tibell
wrote: I'm trying to figure out whether this is a property of the functor itself. I guess it is, but at the same time it seems somewhat orthogonal whether to `seq` some value`.
On Fri, Nov 29, 2013 at 3:50 PM, Twan van Laarhoven
wrote: On 29/11/13 12:23, Johan Tibell wrote:
On Fri, Nov 29, 2013 at 1:19 PM, Twan van Laarhoven
mailto:twanvl@gmail.com> wrote: I don't like that this function is implemented for Monads, I think that it makes sense for some other functors as well. Though to do this 'properly' we would probably end up with another typeclass "StrictFunctor" or something, and that is perhaps too much unnecessary complexity.
Do you have an example of such a functor?
-- Johan
The first thing that came to mind was ZipList. Perhaps a more realistic example would be parsing combinator or FRP libraries that are applicative but not monadic.
Twan
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On Nov 30, 2013 12:05 PM, "Roman Cheplyaka"
No. Evaluation of your 'strictify' function will be delayed for the very same reason that evaluation of 'f' is delayed in the first place.
It doesn't matter what 'strictify' *does* if it's not even evaluated.
Right, I see. Monad is required for the proper sequencing. Thanks! Nicolas
* Nicolas Trangez
[2013-11-30 02:11:02+0100] I'm without a doubt overlooking something, but couldn't this be (otoh)
fmap' :: Functor f => (a -> b) -> f a -> f b fmap' f = fmap (strictify f) where strictify s = (($!) id) . s
Nicolas On Nov 30, 2013 12:11 AM, "Edward Kmett"
wrote: Figure out how to write one using either of those APIs, and I'll be
impressed. =)
I personally use this quite often when working in a monad, in lieu of `return $!` games.
The argument for implementing a version of it in terms of Monad and not some new class off to the side of the class hierarchy that Monad doesn't subclass is that, frankly, if such a thing existed, I'd still have to use this combinator anyways when working with a transformer stack, etc. and would derive little benefit.
-Edward
On Fri, Nov 29, 2013 at 12:03 PM, Carter Schonwald < carter.schonwald@gmail.com> wrote:
could someone explain to me why this <$!> would be for monads rather being more generally also for functors or applicatives?
On Fri, Nov 29, 2013 at 10:35 AM, Johan Tibell < johan.tibell@gmail.com>wrote:
I'm trying to figure out whether this is a property of the functor itself. I guess it is, but at the same time it seems somewhat orthogonal whether to `seq` some value`.
On Fri, Nov 29, 2013 at 3:50 PM, Twan van Laarhoven < twanvl@gmail.com>wrote:
On 29/11/13 12:23, Johan Tibell wrote:
> On Fri, Nov 29, 2013 at 1:19 PM, Twan van Laarhoven < twanvl@gmail.com > mailto:twanvl@gmail.com> wrote: > > I don't like that this function is implemented for Monads, I
quite think
> that it > makes sense for some other functors as well. Though to do this > 'properly' we > would probably end up with another typeclass "StrictFunctor" or > something, > and that is perhaps too much unnecessary complexity. > > > Do you have an example of such a functor? > > -- Johan >
The first thing that came to mind was ZipList. Perhaps a more realistic example would be parsing combinator or FRP libraries that are applicative but not monadic.
Twan
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On 2013-11-30 at 12:05:06 +0100, Roman Cheplyaka wrote:
* Nicolas Trangez
[2013-11-30 02:11:02+0100] I'm without a doubt overlooking something, but couldn't this be (otoh)
fmap' :: Functor f => (a -> b) -> f a -> f b fmap' f = fmap (strictify f) where strictify s = (($!) id) . s
No. Evaluation of your 'strictify' function will be delayed for the very same reason that evaluation of 'f' is delayed in the first place.
It doesn't matter what 'strictify' *does* if it's not even evaluated.
jfyi, if compiled with ghc -O2 -dsuppress-all -dsuppress-uniques -ddump-simpl it can be seen that fmap' is really almost the same as a plain fmap, except for an left-over eta-expansion which ghc doesn't optimize away: fmap' = \ @ a @ b @ f $dFunctor f1 -> fmap $dFunctor (\ x -> f1 x)

We've reached the end of the discussion period. Most seemed in favor. Those
who suggested adding a new type class for these kind of functors, do you
feel OK not doing that (and use Monad =>) with the argument that this
distinction is probably too fine grained and having a separate class (which
people need to implement) would probably be more of a pain than it's worth?
-- Johan
On Sat, Nov 30, 2013 at 7:41 PM, Herbert Valerio Riedel
On 2013-11-30 at 12:05:06 +0100, Roman Cheplyaka wrote:
* Nicolas Trangez
[2013-11-30 02:11:02+0100] I'm without a doubt overlooking something, but couldn't this be (otoh)
fmap' :: Functor f => (a -> b) -> f a -> f b fmap' f = fmap (strictify f) where strictify s = (($!) id) . s
No. Evaluation of your 'strictify' function will be delayed for the very same reason that evaluation of 'f' is delayed in the first place.
It doesn't matter what 'strictify' *does* if it's not even evaluated.
jfyi, if compiled with
ghc -O2 -dsuppress-all -dsuppress-uniques -ddump-simpl
it can be seen that fmap' is really almost the same as a plain fmap, except for an left-over eta-expansion which ghc doesn't optimize away:
fmap' = \ @ a @ b @ f $dFunctor f1 -> fmap $dFunctor (\ x -> f1 x)
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On Thu, Dec 19, 2013 at 08:01:01PM +0100, Johan Tibell wrote:
We've reached the end of the discussion period. Most seemed in favor. Those who suggested adding a new type class for these kind of functors, do you feel OK not doing that (and use Monad =>) with the argument that this distinction is probably too fine grained and having a separate class (which people need to implement) would probably be more of a pain than it's worth? -- Johan
There are '$' and '$!', so it's just pity that '<$>' and '<$!>' would break this naming consistency, because '<$!>' wouldn't be the strict version of '<$>'. Greetings, Daniel

On Fri, Dec 20, 2013 at 10:22 AM, John Wiegley
Daniel Trstenjak
writes: There are '$' and '$!', so it's just pity that '<$>' and '<$!>' would break this naming consistency, because '<$!>' wouldn't be the strict version of '<$>'.
I agree with Daniel.
What would be the strict version of <$>?

On Fri, Dec 20, 2013 at 11:57 AM, Daniel Trstenjak < daniel.trstenjak@gmail.com> wrote:
On Fri, Dec 20, 2013 at 10:50:24AM +0100, Johan Tibell wrote:
What would be the strict version of <$>?
In my case, it's more about the intuition of the name '<$!>' and less about the possibility of a strict version of '<$>'.
What's unintuitive about the definition of <$!> above? It's seems like the only sensible one.

On 29.11.2013 13:19, Twan van Laarhoven wrote:
In the same vein as strict fmap, does a strict (<*>) make sense as well?
I think this brings up a good point: strictness annotations may make sense in multiple other scenarios, not just for fmap. Can't we encapsulate similar functionality in a separate function first, wait for it to settle, and then introduce infix versions of it if really necessary? What about seqM :: Monad m => m a -> m a seqM m = m >>= (return $!) This would allow local definitions of f <$!> x = seqM (f <$> x) mf <*!> mx = seqM (mf <*> mx) until the dust settles. If <$!> is really used in abundance, then add <$!> as an infix. The reason why I'm hesitant to introduce a new infix for this is because I think infix is generally less readable than letter-based names. I agree that infix is good to have for functions you use a lot -- to the point where the infix is the standard application, like >>= and <$> -- but for <$!> I don't see this (yet). David

On Fri, Nov 29, 2013 at 01:32:48PM +0100, David Luposchainsky wrote:
On 29.11.2013 13:19, Twan van Laarhoven wrote:
In the same vein as strict fmap, does a strict (<*>) make sense as well?
I think this brings up a good point: strictness annotations may make sense in multiple other scenarios, not just for fmap. Can't we encapsulate similar functionality in a separate function first, wait for it to settle, and then introduce infix versions of it if really necessary?
What about
seqM :: Monad m => m a -> m a seqM m = m >>= (return $!)
I think this is an excellent idea. It makes sense to address the issue in the simplest, most generic way possible first and then later provide specialised functions when they have been shown to have widespread real-world usage. Tom (PS I note this is yet another example of the invisible Thunk type constructor causing problems!)

On Fri, Nov 29, 2013 at 1:32 PM, David Luposchainsky < dluposchainsky@googlemail.com> wrote:
On 29.11.2013 13:19, Twan van Laarhoven wrote:
In the same vein as strict fmap, does a strict (<*>) make sense as well?
I think this brings up a good point: strictness annotations may make sense in multiple other scenarios, not just for fmap. Can't we encapsulate similar functionality in a separate function first, wait for it to settle, and then introduce infix versions of it if really necessary?
What about
seqM :: Monad m => m a -> m a seqM m = m >>= (return $!)
This would allow local definitions of
f <$!> x = seqM (f <$> x) mf <*!> mx = seqM (mf <*> mx)
until the dust settles. If <$!> is really used in abundance, then add <$!> as an infix.
I think this is a good idea. We still need to think about how to make it clear to users when they need to force things when writing functorial (sp?)/applicative/monadic code. It's quite easy to introduce additional thunks there as expressions are often pushed inside a lazy data type (e.g. the state monad pushes the value inside a lazy tuple). If you look at e.g. the applicative APIs or some code that use them (e.g. attoparsec), it's not obvious that you can shoot yourself in the foot pretty easily by introducing too many thunks and thus use more space than needed. I ran into this in practice when working with attoparsec. If you use e.g. the provided sepBy combinator, you end up with a list of many thunks in it. We ended up adding strict versions of basically all the combinators to work around this. -- Johan
participants (13)
-
Carter Schonwald
-
Daniel Trstenjak
-
David Luposchainsky
-
Edward Kmett
-
Gregory Collins
-
Herbert Valerio Riedel
-
Ivan Lazar Miljenovic
-
Johan Tibell
-
John Wiegley
-
Nicolas Trangez
-
Roman Cheplyaka
-
Tom Ellis
-
Twan van Laarhoven