0

Why is it that I can do the following:

import Data.Word
import Data.Binary.Get
import Control.Applicative
import Control.Monad.Error

getW1 :: ErrorT String Get Word8
getW1 = lift getWord8

f1 = (+1) <$> getW1

but I cannot do:

f2 = (+) <$> getW1 <*> getW1

and how I do I modify f2 so that it will work as I intend?

me2
  • 3,069
  • 2
  • 26
  • 33

2 Answers2

3

<$> only requires that ErrorT String Get to be an instance of Functor. <*> requires that it be an instance of Applicative. I think this instance declaration should work:

{-# LANGUAGE FlexibleInstances #-}

instance (Error e, Monad m) => Applicative (ErrorT e m) where
    pure = return
    (<*>) = ap
MtnViewMark
  • 5,120
  • 2
  • 20
  • 29
0

To do error handling, you don't necessary need the Either(T) monad. You can be perfectly fine by staying in Applicative via composition. Example (for fun using AccValidation which accumulates all errors):

import Control.Applicative
import Control.Monad.Error

import Data.Validation
import Data.Bifoldable
import Data.Functor.Compose

-- Replicating OP example with a Dummy monad (Get is made Applicative in newer libs)

data Dummy a = D a
  deriving Show

instance Monad Dummy where
  return = D
  (D x) >>= f = f x

instance Functor Dummy where
  fmap f (D x) = D (f x)

getM1 :: ErrorT String Dummy Int
getM1 = lift (D 1)

-- Can do with Applicatives + (Acc)Validation too

instance Applicative Dummy where
  pure = return
  (<*>) = ap

getA :: Compose Dummy (AccValidation String) Int
getA = Compose $ D (success 1)

getE :: Compose Dummy (AccValidation String) Int
getE = Compose $ D (failure "bad")

-- Applicative composition can work either way

getA2 :: Compose (AccValidation String) Dummy Int
getA2 = Compose $ success (D 1)

getE2 :: Compose (AccValidation String) Dummy Int
getE2 = Compose $ failure "bad"

main = do
    runMonadic $ (+) <$> getM1 <*> getM1    -- D "2"
    --
    runApplicative $ (+) <$> getA  <*> getA   -- D "2"
    runApplicative $ (+) <$> getE  <*> getA   -- D "bad"
    runApplicative $ (+) <$> getE  <*> getE   -- D "badbad"
    --
    runOtherApp    $ (+) <$> getA2 <*> getA2  -- "D 2"
    runOtherApp    $ (+) <$> getE2 <*> getE2  -- "badbad"
    where
      runMonadic      = print . fmap (either id show) . runErrorT
      runApplicative  = print . fmap (validate id show) . getCompose
      runOtherApp     = print . validate id show . getCompose

-- some helper mimicking @either@ of @Either@
validate :: (e -> c) -> (a -> c) -> AccValidation e a -> c
validate f g = bifoldl (const f) (const g) undefined
ron
  • 9,262
  • 4
  • 40
  • 73