Is it usual to read a Maybe (IORef a) ?

Hi, I'd like to write a data structure to be used inside the IO monad. The structure has some handles of type Maybe (IORef a), i.e. IORef are pointers and the Maybe is like null pointers. So I came up with the following functions : readHandle :: Maybe (IORef a) -> IO (Maybe a) readField :: (a -> b) -> Maybe (IORef a) -> IO (Maybe b) readHandle Nothing = do return Nothing readHandle (Just r) = do v <- readIORef r return $ Just v readField f h = do m <- readHandle h return $ fmap f m Is it something usual ? Are there any related functions in the standard libraries ? Thanks, Thu

Hello minh, Wednesday, September 3, 2008, 2:09:38 PM, you wrote:
I'd like to write a data structure to be used inside the IO monad. The structure has some handles of type Maybe (IORef a), i.e. IORef are pointers and the Maybe is like null pointers.
i've not used this but overall it seems like a correct way to emulate NULL. the whole question is that you probably still think C if you need NULL pointers at all :)
readHandle :: Maybe (IORef a) -> IO (Maybe a)
Are there any related functions in the standard libraries ?
readHandle = maybe (return Nothing) (fmap Just . readIORef) or you can add your own primitive: liftNULL op = maybe (return Nothing) (fmap Just . op) readHandle = liftNULL readIORef -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

2008/9/3 Bulat Ziganshin
Hello minh,
Wednesday, September 3, 2008, 2:09:38 PM, you wrote:
I'd like to write a data structure to be used inside the IO monad. The structure has some handles of type Maybe (IORef a), i.e. IORef are pointers and the Maybe is like null pointers.
i've not used this but overall it seems like a correct way to emulate NULL. the whole question is that you probably still think C if you need NULL pointers at all :)
Maybe, I'm adapting some C++ code... Do you suggest I use data Thing = Thing | None and IORef Thing instead of data Thing = Thing and Maybe (IORef Thing) ? I'm writing a data structure that can hold Things (and that can be mutated) or nothing (there is a hole in the wrapping data). Thanks, Thu

minh thu wrote:
Do you suggest I use
data Thing = Thing | None
and IORef Thing instead of
data Thing = Thing
and Maybe (IORef Thing) ?
I'm writing a data structure that can hold Things (and that can be mutated) or nothing (there is a hole in the wrapping data).
I'd have thought you wanted "IORef (Maybe Thing)", which says that the pointer always exists, but may not point to anything. On the other hand "Maybe (IORef Thing)" says that the pointer may or may not exist. Paul.

2008/9/4 Paul Johnson
minh thu wrote:
Do you suggest I use
data Thing = Thing | None
and IORef Thing instead of
data Thing = Thing
and Maybe (IORef Thing) ?
I'm writing a data structure that can hold Things (and that can be mutated) or nothing (there is a hole in the wrapping data).
I'd have thought you wanted "IORef (Maybe Thing)", which says that the pointer always exists, but may not point to anything. On the other hand "Maybe (IORef Thing)" says that the pointer may or may not exist.
Yes, someone else said it too. But you saiy that regarding the pointer. If you look at the thing the pointer (if any) points at, what's the difference ? Either there is none : Nothing or IORef Nothing, or there is one : Just (IORef 5) or IORef (Just 5). The difference is you have to allocate a new IORef whenever you want to make the thing pointed at appear in the first case. I'm more concerned by the hole the user can create/fill than by emulating C null pointers. Anyway, as Lennart suggested, I will try with Data.Map or Data.IntMap. Thanks thu

On Sep 4, 2008, at 12:50 PM, minh thu wrote:
I'd have thought you wanted "IORef (Maybe Thing)", which says that the pointer always exists, but may not point to anything. On the other hand "Maybe (IORef Thing)" says that the pointer may or may not exist.
Yes, someone else said it too. But you saiy that regarding the pointer. If you look at the thing the pointer (if any) points at, what's the difference ? Either there is none : Nothing or IORef Nothing, or there is one : Just (IORef 5) or IORef (Just 5).
There is still a difference. With Maybe (IORef a), the nothingness is expressed only locally, but with IORef (Maybe a), the nothingness can be shared and mutated by any other IORefs that point to it as well. - Jake McArthur

minh thu wrote:
2008/9/4 Paul Johnson
: I'd have thought you wanted "IORef (Maybe Thing)", which says that the pointer always exists, but may not point to anything. On the other hand "Maybe (IORef Thing)" says that the pointer may or may not exist.
Yes, someone else said it too. But you saiy that regarding the pointer. If you look at the thing the pointer (if any) points at, what's the difference ? Either there is none : Nothing or IORef Nothing, or there is one : Just (IORef 5) or IORef (Just 5).
The difference is you have to allocate a new IORef whenever you want to make the thing pointed at appear in the first case.
The difference is that IORef(Maybe a) lets someone in IO modify the pointer in place. So if the IORef is pointing to Nothing, someone can come and fix that so it's pointing to Just thing, without needing to alter any of the data structure or context above the IORef. They can also use this same ability to change an IORef pointing to something into one pointing to Nothing, either for good or ill. With Maybe(IORef a) the pointer either exists or does not, and that fact can never be changed without rebuilding the datastructure/context above the Maybe. Provided that the pointer exists, it can be freely modified by anyone in IO to point to different things throughout its life (but it's always pointing to something). Depending on the exact semantics you're trying to model, either approach can be correct. The way C and similar languages typically deal with variables holding pointers is like IORef(Maybe a). A "const" pointer ---pointing to a fixed destination, where the memory at that destination can be altered--- is similar to Maybe(IORef a). Good luck with Data.IntMap, hopefully it'll simplify things. -- Live well, ~wren

Looks like MaybeT? http://hackage.haskell.org/cgi-bin/hackage-scripts/package/MaybeT-0.1.1
readHandle x = runMaybeT $ do ref <- MaybeT (return x) liftIO (readIORef ref) readField f h = runMaybeT $ do a <- MaybeT (readHandle h) return (f a)
(or, the short version)
readHandle x = runMaybeT (liftIO . readIORef =<< MaybeT (return x)) readField f = runMaybeT . liftM f . MaybeT . readHandle
As a bonus, readHandle and readField work in any MonadIO due to the
use of liftIO (as opposed to just lift).
-- ryan
On Wed, Sep 3, 2008 at 3:09 AM, minh thu
Hi,
I'd like to write a data structure to be used inside the IO monad. The structure has some handles of type Maybe (IORef a), i.e. IORef are pointers and the Maybe is like null pointers.
So I came up with the following functions :
readHandle :: Maybe (IORef a) -> IO (Maybe a) readField :: (a -> b) -> Maybe (IORef a) -> IO (Maybe b)
readHandle Nothing = do return Nothing readHandle (Just r) = do v <- readIORef r return $ Just v
readField f h = do m <- readHandle h return $ fmap f m
Is it something usual ? Are there any related functions in the standard libraries ?
Thanks, Thu _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Wednesday 03 September 2008 12:09:38 minh thu wrote:
Hi,
I'd like to write a data structure to be used inside the IO monad. The structure has some handles of type Maybe (IORef a), i.e. IORef are pointers and the Maybe is like null pointers.
So I came up with the following functions :
readHandle :: Maybe (IORef a) -> IO (Maybe a) readField :: (a -> b) -> Maybe (IORef a) -> IO (Maybe b)
readHandle Nothing = do return Nothing readHandle (Just r) = do v <- readIORef r return $ Just v
readField f h = do m <- readHandle h return $ fmap f m
Is it something usual ? Are there any related functions in the standard libraries ?
A value of type Maybe (IORef a) is an optional pointer that must point to an object. If you want a pointer that points to either Nothing (aka null) or to a value, you should use IORef (Maybe a). Then readHandle :: IORef (Maybe a) -> IO (Maybe a) readHandle = readIORef readfield :: (a -> b) -> IORef (Maybe a) -> IO (Maybe b) readfield f p = (fmap . fmap) f (readIORef p)

It looks like this code isn't really in fitting with normal Haskell idioms. Emulating C in Haskell will only give you a harder way of writing C. Don't think about emulating a potentially null pointer with Maybe (IORef a) and passing this to a function to read content unless you also want to implement the function "segfault :: IO ()". You really need to ask yourself whether it makes sense to read a NULL / Nothing field. In C this would cause a segfault. The idea in Haskell is that you don't allow invalid values to be passed in to a function at all. Each function should be pure and accept only sensible inputs, allowing you to analyse what each function does in isolation from the rest of the program. In Haskell, functions should use the type system to only accept arguments which make sense. The caller should handle the possibility that a function it calls returns nothing, not expect every other callee to do so. The Maybe monad helps with this for many cases: lookupEmployee :: Integer -> Maybe Employee lookupPassportNo :: Employee -> PassportNo lookupMarriageCertificate :: PassportNo -> Maybe MarriageCert getPassportNumbers :: MarriageCert -> (PassportNo, PassportNo) getNameFromPassport :: PassportNo -> Maybe String lookupSpouse :: Integer -> Maybe String lookupSpouse employee_no = do employee <- lookupEmployee employee_no let passport = lookupPassportNo employee cert <- lookupMarriageCertificate let (p1, p2) = getPassportNumbers cert let partner = if p1 == passport then p2 else p1 getNameFromPassport partner In this example, if any lookup which can fail does, the result is Nothing. Each lookup function can assume that a valid argument is present, though some types of lookup may still give no result. The caller chooses how to account for this inability to find a match, in this case by itself having no result. The thing I'm more concerned about here is the use of IORefs inside data structures at all. A data structure containing IORefs is mutable and can only be manipulated in the IO monad, which defeats the point of Haskell. There is a use case for using mutable structures for some resource-intensive operations, but even then it's often trading short-term speed for long term difficulties. If you think immutable structures imply poor performance, take a look at projects such as uvector and Data Parallel Haskell - immutable data structures which beat the hell out traditional, C-like techniques. If you must use IORefs, consider only using them to hold the whole structure, which is modified by normal, pure functions. If you don't think you can make do with this, you're probably still thinking about the program in an imperative manner. You will probably be better off either rethinking how you're doing things or, if you cannot translate the concepts to a functional form, using an imperative language. Good luck, Tim On Wed, 03 Sep 2008 22:09:38 minh thu wrote:
Hi,
I'd like to write a data structure to be used inside the IO monad. The structure has some handles of type Maybe (IORef a), i.e. IORef are pointers and the Maybe is like null pointers.
So I came up with the following functions :
readHandle :: Maybe (IORef a) -> IO (Maybe a) readField :: (a -> b) -> Maybe (IORef a) -> IO (Maybe b)
readHandle Nothing = do return Nothing readHandle (Just r) = do v <- readIORef r return $ Just v
readField f h = do m <- readHandle h return $ fmap f m
Is it something usual ? Are there any related functions in the standard libraries ?
Thanks, Thu _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Timothy Goddard wrote:
It looks like this code isn't really in fitting with normal Haskell idioms [...]
this is all very much true. Still I understand the application area (for this example) is interactive graph editing and there the "in-place update" perhaps is the right model for what the user of the program does (remove/insert node/edge). So at least the model of the GUI needs some notion of "state"? Of course from the GUI state one should compute the underlying and *immutable* data object for further processing. J.W.

2008/9/4 Timothy Goddard
It looks like this code isn't really in fitting with normal Haskell idioms.
I guess you mean by Haskell idiom : "pure". But Haskell allows you to do IO, etc.
Emulating C in Haskell will only give you a harder way of writing C. Don't think about emulating a potentially null pointer with Maybe (IORef a) and passing this to a function to read content unless you also want to implement the function "segfault :: IO ()".
You really need to ask yourself whether it makes sense to read a NULL / Nothing field. In C this would cause a segfault. The idea in Haskell is that you don't allow invalid values to be passed in to a function at all. Each function should be pure and accept only sensible inputs, allowing you to analyse what each function does in isolation from the rest of the program.
In Haskell, functions should use the type system to only accept arguments which make sense. The caller should handle the possibility that a function it calls returns nothing, not expect every other callee to do so. The Maybe monad helps with this for many cases:
lookupEmployee :: Integer -> Maybe Employee lookupPassportNo :: Employee -> PassportNo lookupMarriageCertificate :: PassportNo -> Maybe MarriageCert getPassportNumbers :: MarriageCert -> (PassportNo, PassportNo) getNameFromPassport :: PassportNo -> Maybe String
lookupSpouse :: Integer -> Maybe String lookupSpouse employee_no = do employee <- lookupEmployee employee_no let passport = lookupPassportNo employee cert <- lookupMarriageCertificate let (p1, p2) = getPassportNumbers cert let partner = if p1 == passport then p2 else p1 getNameFromPassport partner
In this example, if any lookup which can fail does, the result is Nothing. Each lookup function can assume that a valid argument is present, though some types of lookup may still give no result. The caller chooses how to account for this inability to find a match, in this case by itself having no result.
Thanks for the exemple, but I'm aware of monads (even if I can't still use them easily when many of them are mixed). Here my problem is more about interactively editable data structure (at least from the point of view of the user). I would be very happy to do it with pure functions.
The thing I'm more concerned about here is the use of IORefs inside data structures at all. A data structure containing IORefs is mutable and can only be manipulated in the IO monad, which defeats the point of Haskell. There is a use case for using mutable structures for some resource-intensive operations, but even then it's often trading short-term speed for long term difficulties. If you think immutable structures imply poor performance, take a look at projects such as uvector and Data Parallel Haskell - immutable data structures which beat the hell out traditional, C-like techniques.
I'm looking at the FGL package, it seems very intersting. I don't think immutable data structures imply poor perfromance, but I think designing the examples you give is quite complicated and done by really experienced Haskell programmers. Please, don't answer to my problem (even if I haven't really explain it) by exposing state-of-the-art Haskell goodness.
If you must use IORefs, consider only using them to hold the whole structure, which is modified by normal, pure functions. If you don't think you can make do with this, you're probably still thinking about the program in an imperative manner. You will probably be better off either rethinking how you're doing things or, if you cannot translate the concepts to a functional form, using an imperative language.
Overall, I agree I have to look for a more pure approach. Although, I think something like FGL required a lot of work. But raising, say, uvector, in face of my use of IORef seems a bit quick.
Good luck,
Thank you, Thu
Tim
On Wed, 03 Sep 2008 22:09:38 minh thu wrote:
Hi,
I'd like to write a data structure to be used inside the IO monad. The structure has some handles of type Maybe (IORef a), i.e. IORef are pointers and the Maybe is like null pointers.
So I came up with the following functions :
readHandle :: Maybe (IORef a) -> IO (Maybe a) readField :: (a -> b) -> Maybe (IORef a) -> IO (Maybe b)
readHandle Nothing = do return Nothing readHandle (Just r) = do v <- readIORef r return $ Just v
readField f h = do m <- readHandle h return $ fmap f m
Is it something usual ? Are there any related functions in the standard libraries ?
Thanks, Thu _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

I would represent the data structure in a pure way, and restrict the
IO monad to the operations that actually do IO.
If you need some kind of mutable graph, I suggest representing that
graph as a map (Data.Map) from node names to neighbors.
The "mutation" is then just updating the map. An extra benefit from
this is that you get really simple undo in your editor.
-- Lennart
On Thu, Sep 4, 2008 at 8:53 AM, minh thu
2008/9/4 Timothy Goddard
: It looks like this code isn't really in fitting with normal Haskell idioms.
I guess you mean by Haskell idiom : "pure". But Haskell allows you to do IO, etc.
Emulating C in Haskell will only give you a harder way of writing C. Don't think about emulating a potentially null pointer with Maybe (IORef a) and passing this to a function to read content unless you also want to implement the function "segfault :: IO ()".
You really need to ask yourself whether it makes sense to read a NULL / Nothing field. In C this would cause a segfault. The idea in Haskell is that you don't allow invalid values to be passed in to a function at all. Each function should be pure and accept only sensible inputs, allowing you to analyse what each function does in isolation from the rest of the program.
In Haskell, functions should use the type system to only accept arguments which make sense. The caller should handle the possibility that a function it calls returns nothing, not expect every other callee to do so. The Maybe monad helps with this for many cases:
lookupEmployee :: Integer -> Maybe Employee lookupPassportNo :: Employee -> PassportNo lookupMarriageCertificate :: PassportNo -> Maybe MarriageCert getPassportNumbers :: MarriageCert -> (PassportNo, PassportNo) getNameFromPassport :: PassportNo -> Maybe String
lookupSpouse :: Integer -> Maybe String lookupSpouse employee_no = do employee <- lookupEmployee employee_no let passport = lookupPassportNo employee cert <- lookupMarriageCertificate let (p1, p2) = getPassportNumbers cert let partner = if p1 == passport then p2 else p1 getNameFromPassport partner
In this example, if any lookup which can fail does, the result is Nothing. Each lookup function can assume that a valid argument is present, though some types of lookup may still give no result. The caller chooses how to account for this inability to find a match, in this case by itself having no result.
Thanks for the exemple, but I'm aware of monads (even if I can't still use them easily when many of them are mixed). Here my problem is more about interactively editable data structure (at least from the point of view of the user). I would be very happy to do it with pure functions.
The thing I'm more concerned about here is the use of IORefs inside data structures at all. A data structure containing IORefs is mutable and can only be manipulated in the IO monad, which defeats the point of Haskell. There is a use case for using mutable structures for some resource-intensive operations, but even then it's often trading short-term speed for long term difficulties. If you think immutable structures imply poor performance, take a look at projects such as uvector and Data Parallel Haskell - immutable data structures which beat the hell out traditional, C-like techniques.
I'm looking at the FGL package, it seems very intersting. I don't think immutable data structures imply poor perfromance, but I think designing the examples you give is quite complicated and done by really experienced Haskell programmers. Please, don't answer to my problem (even if I haven't really explain it) by exposing state-of-the-art Haskell goodness.
If you must use IORefs, consider only using them to hold the whole structure, which is modified by normal, pure functions. If you don't think you can make do with this, you're probably still thinking about the program in an imperative manner. You will probably be better off either rethinking how you're doing things or, if you cannot translate the concepts to a functional form, using an imperative language.
Overall, I agree I have to look for a more pure approach. Although, I think something like FGL required a lot of work. But raising, say, uvector, in face of my use of IORef seems a bit quick.
Good luck,
Thank you, Thu
Tim
On Wed, 03 Sep 2008 22:09:38 minh thu wrote:
Hi,
I'd like to write a data structure to be used inside the IO monad. The structure has some handles of type Maybe (IORef a), i.e. IORef are pointers and the Maybe is like null pointers.
So I came up with the following functions :
readHandle :: Maybe (IORef a) -> IO (Maybe a) readField :: (a -> b) -> Maybe (IORef a) -> IO (Maybe b)
readHandle Nothing = do return Nothing readHandle (Just r) = do v <- readIORef r return $ Just v
readField f h = do m <- readHandle h return $ fmap f m
Is it something usual ? Are there any related functions in the standard libraries ?
Thanks, Thu _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

2008/9/4 Lennart Augustsson
I would represent the data structure in a pure way, and restrict the IO monad to the operations that actually do IO. If you need some kind of mutable graph, I suggest representing that graph as a map (Data.Map) from node names to neighbors. The "mutation" is then just updating the map. An extra benefit from this is that you get really simple undo in your editor.
This is what I was looking yesterday and right now,probably using Data.IntMap. Data.FiniteMap on hackage says it's deprecated. Do you know in favor of what ? FGL uses its own Data.Graph.Inductive.Internal.FiniteMap, saying Data.FiniteMap is not enough. Should it use Data.Map ? Thanks for the suggestion, Thu
-- Lennart
On Thu, Sep 4, 2008 at 8:53 AM, minh thu
wrote: 2008/9/4 Timothy Goddard
: It looks like this code isn't really in fitting with normal Haskell idioms.
I guess you mean by Haskell idiom : "pure". But Haskell allows you to do IO, etc.
Emulating C in Haskell will only give you a harder way of writing C. Don't think about emulating a potentially null pointer with Maybe (IORef a) and passing this to a function to read content unless you also want to implement the function "segfault :: IO ()".
You really need to ask yourself whether it makes sense to read a NULL / Nothing field. In C this would cause a segfault. The idea in Haskell is that you don't allow invalid values to be passed in to a function at all. Each function should be pure and accept only sensible inputs, allowing you to analyse what each function does in isolation from the rest of the program.
In Haskell, functions should use the type system to only accept arguments which make sense. The caller should handle the possibility that a function it calls returns nothing, not expect every other callee to do so. The Maybe monad helps with this for many cases:
lookupEmployee :: Integer -> Maybe Employee lookupPassportNo :: Employee -> PassportNo lookupMarriageCertificate :: PassportNo -> Maybe MarriageCert getPassportNumbers :: MarriageCert -> (PassportNo, PassportNo) getNameFromPassport :: PassportNo -> Maybe String
lookupSpouse :: Integer -> Maybe String lookupSpouse employee_no = do employee <- lookupEmployee employee_no let passport = lookupPassportNo employee cert <- lookupMarriageCertificate let (p1, p2) = getPassportNumbers cert let partner = if p1 == passport then p2 else p1 getNameFromPassport partner
In this example, if any lookup which can fail does, the result is Nothing. Each lookup function can assume that a valid argument is present, though some types of lookup may still give no result. The caller chooses how to account for this inability to find a match, in this case by itself having no result.
Thanks for the exemple, but I'm aware of monads (even if I can't still use them easily when many of them are mixed). Here my problem is more about interactively editable data structure (at least from the point of view of the user). I would be very happy to do it with pure functions.
The thing I'm more concerned about here is the use of IORefs inside data structures at all. A data structure containing IORefs is mutable and can only be manipulated in the IO monad, which defeats the point of Haskell. There is a use case for using mutable structures for some resource-intensive operations, but even then it's often trading short-term speed for long term difficulties. If you think immutable structures imply poor performance, take a look at projects such as uvector and Data Parallel Haskell - immutable data structures which beat the hell out traditional, C-like techniques.
I'm looking at the FGL package, it seems very intersting. I don't think immutable data structures imply poor perfromance, but I think designing the examples you give is quite complicated and done by really experienced Haskell programmers. Please, don't answer to my problem (even if I haven't really explain it) by exposing state-of-the-art Haskell goodness.
If you must use IORefs, consider only using them to hold the whole structure, which is modified by normal, pure functions. If you don't think you can make do with this, you're probably still thinking about the program in an imperative manner. You will probably be better off either rethinking how you're doing things or, if you cannot translate the concepts to a functional form, using an imperative language.
Overall, I agree I have to look for a more pure approach. Although, I think something like FGL required a lot of work. But raising, say, uvector, in face of my use of IORef seems a bit quick.
Good luck,
Thank you, Thu
Tim
On Wed, 03 Sep 2008 22:09:38 minh thu wrote:
Hi,
I'd like to write a data structure to be used inside the IO monad. The structure has some handles of type Maybe (IORef a), i.e. IORef are pointers and the Maybe is like null pointers.
So I came up with the following functions :
readHandle :: Maybe (IORef a) -> IO (Maybe a) readField :: (a -> b) -> Maybe (IORef a) -> IO (Maybe b)
readHandle Nothing = do return Nothing readHandle (Just r) = do v <- readIORef r return $ Just v
readField f h = do m <- readHandle h return $ fmap f m
Is it something usual ? Are there any related functions in the standard libraries ?
Thanks, Thu _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (10)
-
Bulat Ziganshin
-
hs
-
Jake Mcarthur
-
Johannes Waldmann
-
Lennart Augustsson
-
minh thu
-
Paul Johnson
-
Ryan Ingram
-
Timothy Goddard
-
wren ng thornton