How to plug this type hole 2

百般思念 提交于 2020-01-06 03:29:07

问题


Following along from here (I've refactored the code from main into its own function) I am trying to get the following code to compile:

import qualified Data.Text as T
import Text.PDF.Info

title :: FilePath -> String
title path = do
  result <- pdfInfo path
  case result of
    Left someError -> do
      return "no title"
    Right info -> do
      case (pdfInfoTitle info) of
        Nothing -> return "no title"
        Just title -> return (T.unpack title)

I am getting

    • Couldn't match type ‘[Char]’ with ‘Char’
      Expected type: [Char]
        Actual type: [[Char]]
    • In a stmt of a 'do' block: return "no title"
      In the expression: do return "no title"
      In a case alternative: Left someError -> do return "no title"
   |
14 |       return "no title"
   |       ^^^^^^^^^^^^^^^^^

To me it looks like I am returning a String ([Char]) type, but I guess not. Guidance please, thanks in advance.

Here it is in greater context of what I hope to accomplish:

module Main where

import Control.Monad (liftM)
import Data.List (isSubsequenceOf, isSuffixOf)
import System.Directory (listDirectory)
import qualified Data.Text as T
import Text.PDF.Info

title :: FilePath -> String
title path = do
  result <- pdfInfo path
  case result of
    Left someError -> do
      return "no title"
    Right info -> do
      case (pdfInfoTitle info) of
        Nothing -> return "no title"
        Just title -> return (T.unpack title)

main :: IO ()
main = do
  print =<<
    liftM
      (filter
         (\path ->
            ((isSubsequenceOf "annotated" path) ||
             (isSubsequenceOf "annotated" (title path))) &&
            (isSuffixOf "pdf" path)))
      (listDirectory "/home/foo")

回答1:


To me it looks like I am returning a String ([Char]) type.

No. return is not, as in most imperative languages, a keyword to return content. It is a function. Indeed return :: Monad m => a -> m a is a function that "injects a value in a monadic type".

The pdfInfo function has as type pdfInfo :: MonadIO m => FilePath -> m (Either PDFInfoError PDFInfo). So we will need to use a MonadIO type:

title :: MonadIO m => FilePath -> m String
title path = do
    result <- pdfInfoTitle info
    case pdfInfo path of
        Left someError -> return "no title"
        Right info -> case (pdfInfoTitle info) of
            Nothing -> return "no title"
            Just title -> return (T.unpack title)

We here thus return an m String. You can see a MonadIO as a "recipe" to construct a value (here a String). Not a String itself.



来源:https://stackoverflow.com/questions/58035216/how-to-plug-this-type-hole-2

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