Functor fmap, pattern match function values, haskell

社会主义新天地 提交于 2019-12-11 05:29:14

问题


I have the following type, and would like to make it a Functor:

newtype SubsM a = SubsM {runSubsM :: Context -> Either Error (a, Env)}

So far i got this

instance Functor SubsM where
    fmap f (SubsM a)  =  SubsM (\s->(Right((f a),(fst s))))

I get an error because a is not the expected type, my question is how do i pattern match a on the left-hand side?


回答1:


You can pattern match on the Either Error (a, Env) with case:

instance Functor SubsM where
  fmap f (SubsM cf) = SubsM $ \c ->  case (cf c) of
    Left err -> Left err
    Right (v, env) -> Right (f v, env)

In the Left case you propagate the error, in the Right case you unpack the resulting pair and apply f to the first element.




回答2:


I prefer not to have to think, when the machine is quite capable of doing the thinking for you.

{-# LANGUAGE DeriveFunctor #-}

newtype SubsM a = SubsM {runSubsM :: Context -> Either Error (a, Env)}
    deriving Functor



回答3:


Note that you can also use the existing Functor instances for -> and Either to do much of the work for you:

instance Functor SubsM where
  fmap g (SubsM cf) = SubsM (fmap (fmap (leftfmap g)) cf)
    where
      leftfmap f (a, b) = (f a, b)

The Functor instance for (,) maps over the right-hand value, not the left-hand one, so you can't use fmap there. You can also write leftfmap as first if you import that function from Control.Arrow.




回答4:


Much of the work necessary is already done for you since both Either a b and (,) are instance of the Bifunctor class.

-- Using the tuple instance
first f (x, y) == (f x, y)

-- Using the Either instance
second g (Left err) = Left err   -- basically, id
first g (Right v) = Right (g v)

Using these functions, you can shorten this drastically (a step-by-step reduction starting with Lee's answer follows):

import Data.Bifunctor
instance Functor SubsM where
   fmap f = SubsM . second (first f) . runSubsM

Would anyone actually write code like this, let alone do so from scratch? Probably not. It's not immediately obvious how it works, but deriving it one step at a time is pretty straightforward, and you might find one of the intermediate steps useful.

I'd probably write something like

instance Functor SubsM where
  fmap f (SubsM cf) = SubsM $ \c -> (second . first) f (cf c)

which limits the more esoteric parts to the single function (second . first).


Derivation of the short form

First, use the Bifunctor instance of (,) to avoid pattern-matching on the tuple.

-- first f (v, env) == (f v, env)
instance Functor SubsM where
   fmap f (SubsM cf) = SubsM $ \c ->  case (cf c) of
      Left err -> Left err
      Right t -> Right (first f t)

Next, use the Bifunctor instance of Either a b to avoid pattern-matching on the return value of cf c:

-- second (first f) (Left err) == Left Err
-- second (first f) (Right t) == Right (first f) t
instance Functor SubsM where
   fmap f (SubsM cf) = SubsM $ \c ->  second (first f) (cf c)

You can also avoid pattern-matching on the SubsM value by unpacking it on the right-hand side with runSubsM:

instance Functor SubsM where
   fmap f cf = SubsM $ \c ->  second (first f) ((runSubsM cf) c)

Finally, we just start applying function composition to eliminate explict arguments where possible.

instance Functor SubsM where
   -- fmap f cf = SubsM $ \c ->  second (first f) ((runSubsM cf) c)
   -- fmap f cf = SubsM $ \c ->  second (first f) . (runSubsM cf) $ c
   -- fmap f cf = SubsM $ second (first f) . (runSubsM cf)
   -- One more function composition allows us to drop cf as an
   -- explicit argument
   fmap f = SubsM . second (first f) . runSubsM


来源:https://stackoverflow.com/questions/39515022/functor-fmap-pattern-match-function-values-haskell

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