On 2008 Sep 24, at 22:51, Daryoush Mehrtash wrote:
I am having hard time making sense of the types in the following example from the Applicative Programming paper: http://www.cs.nott.ac.uk/~ctm/IdiomLite.pdf

ap :: Monad m ⇒ m (a → b ) → m a → m b
ap mf mx = do
    f ← mf
    x ← mx
    return (f x )
Using this function we could rewrite sequence as:

sequence :: [ IO a ] → IO [ a ]
sequence [ ] = return [ ]
sequence (c : cs ) = return (:) 'ap' c 'ap' sequence cs


I am specifically confused over the type of "m" in:

     return (:) 'ap' c

"c" is obviously an instance of IO a monad. "return (:)" on the other hand (at least as I would expect it) is an instance of " ->" monad.

Note that he first argument to ap is a function wrapped by a monad. "return (:)" wraps the function/operator (:) in an arbitrary monad (but then the type signature of sequence makes the monad IO).

    (:) :: a -> [a] -> [a]
    return (:) :: IO (a -> ([a] -> [a])) -- b is ([a] -> [a])
ap (return (:)) :: IO a -> IO ([a] -> [a]) -- (IO a) is (m a) and (IO ([a] -> [a])) is (m b) return (:) `ap` c :: IO ([a] -> [a]) -- c is (IO a) per type signature return (:) `ap` c `ap` :: IO [a] -> IO [a] -- f in ap is the preceding IO ([a] -> [a]) return (:) `ap` c `ap` sequence cs :: IO [a] -- (sequence cs) is (IO [a]) per type signature

--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon university    KF8NH


_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to