IO action nested in other monads not executing

强颜欢笑 提交于 2019-12-12 01:46:39

问题


I have a

foobar :: IO (ParseResult [(String,String)])

ParseResult is a monad defined here: https://hackage.haskell.org/package/haskell-src-exts-1.13.5/docs/Language-Haskell-Exts-Parser.html#t:ParseResult

I want to take those strings and write them to a LaTeXT m () defined in https://hackage.haskell.org/package/HaTeX-3.17.1.0/docs/Text-LaTeX-Base-Writer.html

Running this function results in no file being created.

writeReport2 :: [Char] -> IO (ParseResult (IO ()))
writeReport2 name = do x <- foobar
                       return $ do y <- x
                                   return $ do z <- (execLaTeXT.docAndGraph) y
                                               renderFile fileName z
  where
    fileName = name ++ ".tex"

However the code:

writeReport :: t -> LaTeXT IO a -> IO ()
writeReport name report = createLatex >>= renderFile fileName
  where
    createLatex = execLaTeXT report
    fileName = "AAAAA" ++ ".tex"


testFoo = [(" | HaskellExample Example File\n | Two examples are given below:\n\n >>> fib 10\n 55\n\n >>> putStrLn \"foo\\nbar\"\n foo\n bar ","fib :: Int -> Int"),("\n | This is a thing: ","fib = undefined"),("\n | This is a thing:\n","fibar :: String -> Float")]

itWorks = writeReport "AAAA.txt" $ docAndGraph testFoo

Will create a new file.

Both sets of code type check.


回答1:


I could get writeReport2 working without modification.

I think what might have been your problem is the nested IO action in the return value of writeResport2!

In order to flatten the nested IO actions, I had to use the function join :: Monad m => m (m a) -> m a from Control.Monad:

main :: IO ()
main = join $ fromParseResult <$> writeReport2 "test"

Here is my complete code:

{-# LANGUAGE OverloadedStrings #-}

module Main where

import           Language.Haskell.Exts.Parser
import           Text.LaTeX.Base.Writer
import           Text.LaTeX
import           Data.String
import           Control.Monad

foobar :: IO (ParseResult [(String, String)])
foobar = return (ParseOk testFoo)

testFoo = [ ( " | HaskellExample Example File\n | Two examples are given below:\n\n >>> fib 10\n 55\n\n >>> putStrLn \"foo\\nbar\"\n foo\n bar "
            , "fib :: Int -> Int"
            )
          , ("\n | This is a thing: ", "fib = undefined")
          , ("\n | This is a thing:\n", "fibar :: String -> Float")
          ]

docAndGraph :: Monad m => [(String, String)] -> LaTeXT m ()
docAndGraph x = do
    documentclass [] article
    document $
        raw (fromString (show x))

writeReport2 :: [Char] -> IO (ParseResult (IO ()))
writeReport2 name = do
    x <- foobar
    return $ do
        y <- x
        return $ do
            z <- (execLaTeXT . docAndGraph) y
            renderFile fileName z
  where
    fileName = name ++ ".tex"

main :: IO ()
main = join $ fromParseResult <$> writeReport2 "test"

Loading into GHCi:

$ stack ghci
io-action-nested-in-other-monads-not-executing-0.1.0.0: initial-build-steps (exe)
Configuring GHCi with the following packages: io-action-nested-in-other-monads-not-executing
Using main module: 1. Package `io-action-nested-in-other-monads-not-executing' component exe:io-action-nested-in-other-monads-not-executing with main-is file: /home/sven/dev/stackoverflow-questions/io-action-nested-in-other-monads-not-executing/src/Main.hs
GHCi, version 8.0.2: http://www.haskell.org/ghc/  :? for help
Loaded GHCi configuration from /home/sven/.ghc/ghci.conf
[1 of 1] Compiling Main             ( /home/sven/dev/stackoverflow-questions/io-action-nested-in-other-monads-not-executing/src/Main.hs, interpreted )
Ok, modules loaded: Main.
Loaded GHCi configuration from /tmp/ghci22616/ghci-script

And running it:

λ main

Creates this file:

$ cat test.tex 
\documentclass{article}\begin{document}[(" | HaskellExample Example File\n | Two examples are given below:\n\n >>> fib 10\n 55\n\n >>> putStrLn \"foo\\nbar\"\n foo\n bar ","fib :: Int -> Int"),("\n | This is a thing: ","fib = undefined"),("\n | This is a thing:\n","fibar :: String -> Float")]\end{document}%                                                                        

I know it is not the scope of the question, but you could circumvent the nested IO if you want, by doinf this, for example:

writeReport3 :: [Char] -> IO ()
writeReport3 name = do
    let fileName = name ++ ".tex"
    x <- foobar
    case x of
      ParseOk y -> do
        z <- execLaTeXT (docAndGraph y)
        renderFile fileName z
      ParseFailed _ _ ->
        return ()

main :: IO ()
main = writeReport3 "test"


来源:https://stackoverflow.com/questions/42382396/io-action-nested-in-other-monads-not-executing

标签
易学教程内所有资源均来自网络或用户发布的内容,如有违反法律规定的内容欢迎反馈
该文章没有解决你所遇到的问题?点击提问,说说你的问题,让更多的人一起探讨吧!