Search code examples
haskellio-monadalternative-functor

Alternative IO error for <|>


I am using the operator <|> for:

import qualified Data.ByteString.Lazy as B
import Network.HTTP.Conduit (simpleHttp)
import Data.Aeson
import Data.Maybe

data FooBar = FooBar {
    name :: !Text,
    surname :: !Text
    } deriving (Show,Generic)

instance FromJSON FooBar
instance ToJSON FooBar

getFeed :: String -> String -> IO (FooBar)
getFeed foo bar =  decode <$> (B.readFile foo <|> simpleHttp bar)

But when I try to compile it I get:

No instance for (Alternative IO) arising from a use of ‘<|>’
    In the second argument of ‘(<$>)’, namely
      ‘(B.readFile foo <|> simpleHttp bar)’
    In the expression:
      decode <$> (B.readFile foo <|> simpleHttp bar)
    In an equation for ‘getFeed’:
        getFeed env id
          = decode <$> (B.readFile foo <|> simpleHttp bar)

The error is a bit obscure to me. Any idea how to fix that? (BTW some insight from this reply: Confused by the meaning of the 'Alternative' type class and its relationship to other type classes)


Solution

  • Here is an example of what you can do based on the blog post Playing Catch: Handling IO Exceptions with ErrorT.

    {-# LANGUAGE GeneralizedNewtypeDeriving #-}
    
    module Lib where
    
    import qualified Data.ByteString.Lazy as B
    import Network.HTTP.Conduit (simpleHttp)
    import Control.Monad.Base
    import Control.Applicative
    import Control.Monad.Error
    import System.IO.Error
    
    newtype MyApp a = MyApp {
      getApp :: ErrorT String IO a
      } deriving (Functor, Applicative, Alternative, Monad, MonadIO, MonadError String, MonadBase IO)
    
    myReadFile path = do
      r <- liftIO $ tryIOError $ B.readFile path 
      case r of
        Left e  -> throwError (strMsg "readFile error")
        Right x -> return x
    
    mySimpleHttp bar = do
      r <- liftIO $ tryIOError $ simpleHttp bar
      case r of
        Left e -> throwError (strMsg "simpleHttp error")
        Right x -> return x
    
    getFeed foo bar =  myReadFile foo <|> mySimpleHttp bar
    
    runApp = runErrorT . getApp
    
    doit = do result <- runApp $ getFeed "some/file.txt" "http://example.com/"
              case result of
                Left e  -> putStrLn $ "error: " ++ e
                Right r -> do putStrLn $ "got a result"; print r
    

    I've been very explicit in this example - the article mentions ways you can reduce the amount of boiler-plate code.

    My cabal build-depends: setting:

    build-depends: base >= 4.7 && < 5, bytestring, mtl, http-conduit, transformers-base