user3292534
user3292534

Reputation:

Properly defining a monad class

How do I make following declaration of a list monad compilable?

module Main where

instance Monad m where
  -- "return" constructs a one-item list.
  return x = [x]
  -- "bind" concatenates the lists obtained by applying f to each item in list xs.
  xs >>= f = concat (map f xs)
  -- The zero object is an empty list.
  mzero = []

Currently I get the following error:

monad_ex1.hs:9:3: ‘mzero’ is not a (visible) method of class ‘Monad’

My code is from https://en.wikipedia.org/wiki/Monad_(functional_programming)#Collections , goal is to run create compilable code from that, import it in ghci and play around with it.

Removing mzero from the code leads to another cryptic message:

Illegal instance declaration for ‘Monad m’
      (All instance types must be of the form (T a1 ... an)
       where a1 ... an are *distinct type variables*,
       and each type variable appears at most once in the instance head.
       Use FlexibleInstances if you want to disable this.)
    In the instance declaration for ‘Monad m’

Upvotes: 0

Views: 370

Answers (1)

K. A. Buhr
K. A. Buhr

Reputation: 51129

There are a few potential pitfalls here, most of which are covered in the comments:

  • There is no mzero defined for Monad instances, and you'll get an error if you try to specify one. mzero would be defined in the MonadPlus instance, if any.
  • Trying to redefine the monad instance for built-in lists won't work. You need to define your own List type if you want to play with this.
  • In "modern" Haskell (since GHC 7.10), the implementation of the Applicative => Monad Proposal has obsoleted a lot of old Monad tutorials and made user-defined Monads a little more difficult to write because you also need to define Functor and Applicative instances (detailed migration instructions).

So, here is a translation of your list example to use a user-defined List type with GHC 7.10-compatible boilerplate. Note that the definition for return gets moved into the Applicative instance's pure instead.

module MyListMonad where

import Control.Monad

data List a = Empty | Cons a (List a) deriving (Show, Eq)

instance Functor List where
  fmap = liftM                      -- boilerplate
instance Applicative List where
  pure x = Cons x Empty             -- put definition of `return` here
  (<*>) = ap 
instance Monad List where
  return = pure                     -- boilerplate
  (>>) = (*>)                       -- boilerplate
  xs >>= f = myConcat (myMap f xs)  -- bind definition here

myConcat :: List (List a) -> List a
myConcat (Cons lst rest) = myAppend lst (myConcat rest)
myConcat Empty = Empty

myAppend :: List a -> List a -> List a
myAppend (Cons x rest) ys = Cons x (myAppend rest ys)
myAppend Empty ys = ys

myMap :: (a -> b) -> List a -> List b
myMap f (Cons x rest) = Cons (f x) (myMap f rest)
myMap _ Empty = Empty

test = do x <- Cons 1 $ Cons 2 $ Cons 3 Empty
          y <- Cons 4 $ Cons 5 $ Empty
          return (x * y)

Upvotes: 2

Related Questions