How do I map a String and a IO String?

I want to replace lines with the content of a file if the line is a filename
{-# LANGUAGE LambdaCase #-} test = do putStrLn $ concatMap (\l -> l ++ "\n") $ map (\case l | (isPrefixOf "./" l) -> readFile l | otherwise -> l)
But since l is a String and readFile gives an IO String this doesn't work. How should I get around this? Kind regards, Jona

On Thu, Jun 29, 2017 at 02:33:22PM +0200, Jona Ekenberg wrote:
I want to replace lines with the content of a file if the line is a filename
Hello Jonas, you want to user `return`: λ> :t return return :: Monad m => a -> m a which lifts a simple value inside a monad (in this case, a -> IO a), like this: lineOrIO :: String -> IO String lineOrIO cs | (isPrefixOf "./" cs) = readFile cs | otherwise = return cs If this is not a school assignment, consider replacing `isPrefixOf "./"` with something from `System.Directory`. Does this help?

2017-06-29 15:16 GMT+02:00 Francesco Ariis
On Thu, Jun 29, 2017 at 02:33:22PM +0200, Jona Ekenberg wrote:
I want to replace lines with the content of a file if the line is a filename
Hello Jonas, you want to user `return`:
λ> :t return return :: Monad m => a -> m a
which lifts a simple value inside a monad (in this case, a -> IO a), like this:
lineOrIO :: String -> IO String lineOrIO cs | (isPrefixOf "./" cs) = readFile cs | otherwise = return cs
If this is not a school assignment, consider replacing `isPrefixOf "./"` with something from `System.Directory`.
Does this help?
Thank you for your help Francesco! I tried writing it like this:
lineOrIo :: String -> IO String lineOrIo cs | (isPrefixOf "./" cs) = readFile cs | otherwise = return cs
printLines path = do file <- readFile path lines <- map lineOrIo (lines file) print lines
But when evaluating I get this error: PrintComments.lhs:20:14-38: error: … • Couldn't match type ‘[]’ with ‘IO’ Expected type: IO (IO String) Actual type: [IO String] • In a stmt of a 'do' block: lines <- map lineOrIo (lines file) In the expression: do { file <- readFile path; lines <- map lineOrIo (lines file); print lines } In an equation for ‘printLines’: printLines path = do { file <- readFile path; lines <- map lineOrIo (lines file); print lines } Compilation failed. Sadly I am not yet very used to the error messages, so I don't understand what ghci is telling me. As far as I can tell (lines file) should give me an array of strings, which I turn into an array of IO String. Could that be the error? It shouldn't be [IO String] but instead IO [String]? How do I turn the former into the latter? Kind regards, Jona PS. It is not a school assignment, so I'll make sure to check out System.Directory.
_______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners

On Thu, Jun 29, 2017 at 04:15:16PM +0200, Jona Ekenberg wrote:
Thank you for your help Francesco!
I tried writing it like this:
lineOrIo :: String -> IO String lineOrIo cs | (isPrefixOf "./" cs) = readFile cs | otherwise = return cs
printLines path = do file <- readFile path lines <- map lineOrIo (lines file) print lines
You are using `map`, which has signature λ> :t map map :: (a -> b) -> [a] -> [b] But lineOrIo hasn't signature `a -> b` but `a -> m b` (where m is a monad)! mapM will fit the bill: mapM :: Monad m => (a -> m b) -> [a] -> m [b] and that should do it!
participants (2)
-
Francesco Ariis
-
Jona Ekenberg