
I have the following functions: makePair :: (String, String) -> IO PairBox parseFile :: String -> [(String, String)] importFile :: Editor -> String -> IO () importFile ed path = do s <- readFile path ps <- mapM (\x -> makePair (x, "")) (lines s) es <- return $ V.fromList ps writeIORef ed es loadFile :: Editor -> String -> IO () loadFile ed path = do s <- readFile path ps <- mapM makePair (parseFile s) es <- return $ V.fromList ps writeIORef ed es The problem is that loadFile and importFile are so similar it seems a shame not to combine them somehow, but anything I can think of doing leaves the code looking more rather than less messy. Any nice ideas? martin

Martin,
importFile :: Editor -> String -> IO () importFile ed path = do s <- readFile path ps <- mapM (\x -> makePair (x, "")) (lines s) es <- return $ V.fromList ps writeIORef ed es
loadFile :: Editor -> String -> IO () loadFile ed path = do s <- readFile path ps <- mapM makePair (parseFile s) es <- return $ V.fromList ps writeIORef ed es
The problem is that loadFile and importFile are so similar it seems a shame not to combine them somehow, but anything I can think of doing leaves the code looking more rather than less messy. Any nice ideas?
Have you considered abstracting over the bits in which importFile and loadFile differ? For example: processFile :: (String -> IO [PairBox]) -> Editor -> String -> IO () processFile f ed path = do s <- readFile path ps <- f s es <- return $ V.fromList ps writeIORef ed es importFile = processFile (mapM (\x -> makePair (x, "")) . lines) loadFile = processFile (mapM makePair . parseFile) Or, alternatively: processFile :: (String -> [a]) -> (a -> IO PairBox) -> Editor -> String -> IO () processFile f g ed path = do s <- readFile path ps -> mapM g (f s) es -> return $ V.fromList ps writeIORef ed es importFile = processFile lines (\x -> makePair (x, "")) loadFile = processFile parseFile makePair Or: processFile :: (String -> [a]) -> (a -> (String, String)) -> Editor -> String -> IO () processFile f g ed path = do s <- readFile path ps -> mapM (makePair . g) (f s) es -> return $ V.fromList ps writeIORef ed es importFile = processFile lines (flip (,) "") loadFile = processFile parseFile id HTH, Stefan

On Tue, Nov 29, 2011 at 12:35 AM, Stefan Holdermans
Have you considered abstracting over the bits in which importFile and loadFile differ? For example:
processFile :: (String -> IO [PairBox]) -> Editor -> String -> IO () processFile f ed path = do s <- readFile path ps <- f s es <- return $ V.fromList ps writeIORef ed es
importFile = processFile (mapM (\x -> makePair (x, "")) . lines) loadFile = processFile (mapM makePair . parseFile)
This was what I had tried; my issue was that the resulting code looked harder rather than easier to read, so it felt more like golfing than refactoring.
Or, alternatively:
processFile :: (String -> [a]) -> (a -> IO PairBox) -> Editor -> String -> IO () processFile f g ed path = do s <- readFile path ps -> mapM g (f s) es -> return $ V.fromList ps writeIORef ed es
importFile = processFile lines (\x -> makePair (x, "")) loadFile = processFile parseFile makePair
This does look significantly nicer - I hadn't thought of splitting it into two functions rather than one, but it makes the code look much less cluttered. (The trick with `flip` is tempting, but again at the cost of having to peer rather too closely at the implementation of processFile when reading the code). Thanks! martin

Martin,
(The trick with `flip` is tempting, but again at the cost of having to peer rather too closely at the implementation of processFile when reading the code).
That "trick" is of course completely orthogonal. One could just as well write: processFile :: (String -> [a]) -> (a -> (String, String)) -> Editor -> String -> IO () processFile f g ed path = do s <- readFile path ps -> mapM (makePair . g) (f s) es -> return $ V.fromList ps writeIORef ed es importFile = processFile lines (\x -> (x, "")) loadFile = processFile parseFile id Cheers, Stefan

On Tue, Nov 29, 2011 at 12:55 AM, Stefan Holdermans
Martin,
(The trick with `flip` is tempting, but again at the cost of having to peer rather too closely at the implementation of processFile when reading the code).
That "trick" is of course completely orthogonal. One could just as well write:
processFile :: (String -> [a]) -> (a -> (String, String)) -> Editor -> String -> IO () processFile f g ed path = do s <- readFile path ps -> mapM (makePair . g) (f s) es -> return $ V.fromList ps writeIORef ed es
importFile = processFile lines (\x -> (x, "")) loadFile = processFile parseFile id
good point :) though i ended up writing a new function parseImport = (map $ \x -> (x, "")) . lines, so that i could drop the second argument and have everything look nice and neat. martin

2011/11/29 Stefan Holdermans
Martin,
(The trick with `flip` is tempting, but again at the cost of having to peer rather too closely at the implementation of processFile when reading the code).
That "trick" is of course completely orthogonal. One could just as well write:
processFile :: (String -> [a]) -> (a -> (String, String)) -> Editor -> String -> IO () processFile f g ed path = do s <- readFile path ps -> mapM (makePair . g) (f s) es -> return $ V.fromList ps writeIORef ed es
importFile = processFile lines (\x -> (x, "")) loadFile = processFile parseFile id
With the TupleSections extension, you can write (,"") Cheers, Thu

Am 29.11.2011 um 09:16 schrieb Martin DeMello:
I have the following functions:
makePair :: (String, String) -> IO PairBox
parseFile :: String -> [(String, String)]
importFile :: Editor -> String -> IO () importFile ed path = do s <- readFile path ps <- mapM (\x -> makePair (x, "")) (lines s) es <- return $ V.fromList ps writeIORef ed es
loadFile :: Editor -> String -> IO () loadFile ed path = do s <- readFile path ps <- mapM makePair (parseFile s) es <- return $ V.fromList ps writeIORef ed es
The problem is that loadFile and importFile are so similar it seems a shame not to combine them somehow, but anything I can think of doing leaves the code looking more rather than less messy. Any nice ideas?
fromRawFile, fromSavedFile :: String -> IO [PairBox] fromRawFile = mapM (\x -> makePair (x, "")) . lines fromSavedFile = mapM makePair . parseFile setEditor :: Editor -> [PairBox] -> IO () setEditor ed = writeIORef ed . V.fromList importFile, loadFile :: Editor -> String -> IO () importFile ed = readfile >=> fromRawFile >=> setEditor loadFile ed = readfile >=> fromSavedFile >=> setEditor
participants (4)
-
Holger Siegel
-
Martin DeMello
-
Stefan Holdermans
-
Vo Minh Thu