How to structure an application?

Hi, I hope to get some advice on how to structure an application. So I acquire a handle early on that I use all over the app, but I don't want to pass the handle itself around, but wrap the handle with "commands" that a) make a nicer api and/or b) only allow specific usecases of the handle. I tried and failed to use MonadReader in a straightforward way and now I'm wondering what options there are. Looking forward to your feedback, Best, Tilmann module Main where import Control.Monad import Control.Monad.Reader import Graphics.UI.WX import System.IO -- imagine many more commands like this one ping :: (MonadReader Handle m, MonadIO m) => m () ping = do h <- ask liftIO $ hPutStrLn h "ping" main :: IO () main = do let h = stdout -- in the real app, this handle isn't stdout of course but opened separately start $ runReaderT wxApp h wxApp :: (MonadReader Handle m, MonadIO m) => m () wxApp = do ping -- this works, but I don't need it here.. liftIO $ do f <- frame [ ] timer f [ interval := 1000 -- , on command := hputStrLn h "ping" -- this is what I try to avoid -- , on command := ping -- of course, this doesn't work, but it would be so nice.. , enabled := True] return () -- Alternatively main2 :: IO () main2 = do let h = stdout start $ runReaderT wxApp2 (mkCommands h) wxApp2 :: (MonadReader Commands m, MonadIO m) => m () wxApp2 = do commands <- ask liftIO $ do f <- frame [ ] timer f [ interval := 1000 , on command := ping2 commands , enabled := True] return () data Commands = Commands { ping2 :: IO () -- .. many more } mkCommands :: Handle -> Commands mkCommands h = Commands (hPutStrLn h "ping")

Tilmann
Hi,
I hope to get some advice on how to structure an application. So I acquire a handle early on that I use all over the app, but I don't want to pass the handle itself around, but wrap the handle with "commands" that a) make a nicer api and/or b) only allow specific usecases of the handle. I tried and failed to use MonadReader in a straightforward way and now I'm wondering what options there are. Looking forward to your feedback,
Below a certain size I'd actually consider just passing the handle around, possibly in a type holding other info that's needed "all over." At some point that becomes unwieldy and then I'd look at things like - monad transformers (like you have below) - tagless final: https://serokell.io/blog/2018/12/07/tagless-final - readerT design pattern: https://www.fpcomplete.com/blog/2017/06/readert-design-pattern I'm not too experienced with them, but I'm guessing free monads/effects would be an alternative too... /M -- Magnus Therning OpenPGP: 0x927912051716CE39 email: magnus@therning.org twitter: magthe http://magnus.therning.org/ I am always doing that which I cannot do, in order that I may learn how to do it. — Pablo Picasso

Hi Tilmann,
wxApp :: (MonadReader Handle m, MonadIO m) => m () wxApp = do ping -- this works, but I don't need it here.. liftIO $ do f <- frame [ ] timer f [ interval := 1000 -- , on command := hputStrLn h "ping" -- this is what I try to avoid -- , on command := ping -- of course, this doesn't work, but it would be so nice.. , enabled := True] return ()
I assume that WX expects an 'IO' action for the 'command', but 'ping' is an action of the 'ReaderT' monad. WX won't be able to execute this action, because it doesn't know anything about the 'ReaderT' monad, so there's no 'Handle' that it could give to the 'ping' function. I think the most straight forward solution is to have a function 'ping': ping :: Handle -> IO () ping h = hputStrLn h "ping" And then a 'wxApp' like: wxApp :: (MonadReader Handle m, MonadIO m) => m () wxApp = do handle <- ask liftIO $ do f <- frame [ ] timer f [ interval := 1000, on command := ping handle, enabled := True] return () So instead of having 'ping' in the 'ReaderT' monad you just give it explicitly the data of the monad. You could have a helper function that does this transformation: handlize :: (MonadReader Handle m, MonadIO m) => (Handle -> IO()) -> m (IO ()) handlize func = do handle <- ask return $ func handle wxApp :: (MonadReader Handle m, MonadIO m) => m () wxApp = do cmd <- handlize ping liftIO $ do f <- frame [ ] timer f [ interval := 1000, on command := cmd, enabled := True] return () Greetings, Daniel
participants (3)
-
Daniel Trstenjak
-
Magnus Therning
-
Tilmann