Search code examples
haskellarrow-abstraction

Couldn't match expected type ‘a -> Int’ with actual type ‘IOArrow String Int’


I am trying to understand the Arrow and create the following example:

{-# LANGUAGE Arrows #-}


module Main where

import Control.Arrow
import Control.Monad
import qualified Control.Category as Cat
import Data.List
import Data.Maybe

data IOArrow a b = IOArrow { runIOArrow :: a -> IO b }

instance Cat.Category IOArrow where
  id = IOArrow return
  IOArrow f . IOArrow g = IOArrow $ f <=< g

instance Arrow IOArrow where
  arr f = IOArrow $ return . f
  first (IOArrow f) = IOArrow $ \(a, c) -> do
    x <- f a
    return (x, c)

foo :: Int -> String
foo = show

bar :: String -> IO Int
bar = return . read

main :: IO ()
main = do
  let f = arr (++"!!") . arr foo . IOArrow bar . arr id
  result <- runIOArrow f "123"
  putStrLn result 

The compiler complains:

    • Couldn't match expected type ‘a -> Int’
                  with actual type ‘IOArrow String Int’
    • Possible cause: ‘IOArrow’ is applied to too many arguments
      In the first argument of ‘(.)’, namely ‘IOArrow bar’
      In the second argument of ‘(.)’, namely ‘IOArrow bar . arr id’
      In the second argument of ‘(.)’, namely
        ‘arr foo . IOArrow bar . arr id’
    • Relevant bindings include
        f :: a -> [Char] (bound at app/Main.hs:32:7)
   |
32 |   let f = arr (++"!!") . arr foo . IOArrow bar . arr id
   |                                    ^^^^^^^^^^^


    • Couldn't match expected type ‘IOArrow [Char] String’
                  with actual type ‘a0 -> [Char]’
    • Probable cause: ‘f’ is applied to too few arguments
      In the first argument of ‘runIOArrow’, namely ‘f’
      In a stmt of a 'do' block: result <- runIOArrow f "123"
      In the expression:
        do let f = arr (++ "!!") . arr foo . IOArrow bar . arr id
           result <- runIOArrow f "123"
           putStrLn result
   |
33 |   result <- runIOArrow f "123"
   |                        ^  

What am I doing wrong?


Solution

  • You want (.) :: Category cat => cat b c -> cat a b -> cat a c from Control.Category, but you end up using (.) :: (b -> c) -> (a -> b) -> (a -> c) from the Prelude.

    • Enable NoImplicitPrelude then import the Prelude explicitly hiding id and (.)
    • Import Control.Category unqualified (or suffer Cat.. everywhere)

    Bonus: arr id is just id from Control.Catgory.

    {-# LANGUAGE Arrows, NoImplicitPrelude #-}
    
    module Main where
    
    import Prelude hiding ((.), id)
    import Control.Arrow
    import Control.Monad
    import Control.Category
    import Data.List
    import Data.Maybe
    
    data IOArrow a b = IOArrow { runIOArrow :: a -> IO b }
    
    instance Category IOArrow where
      id = IOArrow return
      IOArrow f . IOArrow g = IOArrow $ f <=< g
    
    instance Arrow IOArrow where
      arr f = IOArrow $ return . f
      first (IOArrow f) = IOArrow $ \(a, c) -> do
        x <- f a
        return (x, c)
    
    foo :: Int -> String
    foo = show
    
    bar :: String -> IO Int
    bar = return . read
    
    main :: IO ()
    main = do
      let f = arr (++"!!") . arr foo . IOArrow bar . id
      result <- runIOArrow f "123"
      putStrLn result