0

In the exercises of Haskell Programming from First Principle book on Semigroup, I am asked to write quickCheck for user defined typeclasses. There are many typeclasses, but I do not understand how to write even the basic ones:

Problems:

The first is for Trivial:

module Exercise where

import Test.QuickCheck

data Trivial =
  Trivial
  deriving (Eq, Show)

instance Semigroup Trivial where
  _ <> _ = undefined

instance Arbitrary Trivial where
  arbitrary = return Trivial

semigroupAssoc :: (Eq m, Semigroup m) => m -> m -> m -> Bool
semigroupAssoc a b c = (a <> (b <> c)) == ((a <> b) <> c)

type TrivialAssoc = Trivial -> Trivial -> Trivial -> Bool

The second is for

newtype Identity a = Identity a

and the third is for:

data Two a b =
  Two a b

My answers:

For the first, I changed the instance expression to

instance Semigroup Trivial where
  _ <> _ = Trivial

and it works.

I tried the following code but not work for the second:

newtype Identity a = Identity a

instance (Semigroup a) => Semigroup (Identity a) where
  (Identity a1) <> (Identity a2) = Identity (a1 <> a2)

instance Arbitrary (Identity a) where
  arbitrary = return (Identity a)

type IdentityAssoc =
  (Identity a0) -> (Identity a1) -> (Identity a2) -> Bool

main :: IO ()
main =
  quickCheck (semigroupAssoc :: IdentityAssoc)

I find I do not understand what the quickTest should check here. I even tried:

import Data.NonEmpty

newtype Identity a = Identity a

instance (Semigroup a) => Semigroup (Identity a) where
  (Identity a1) <> (Identity a2) = Identity (a1 <> a2)

instance Arbitrary (Identity a) where
  arbitrary = return (Identity a)

type IdentityAssoc =
  (Identity (NonEmpty Int)) -> (Identity (NonEmpty Int)) -> (Identity (NonEmpty Int)) -> Bool

main :: IO ()
main =
  quickCheck (semigroupAssoc :: IdentityAssoc)

to make the parameterized types' parameters concrete. But it does not work either.

For the third, I do not know how to write them. But I think it is similar to the second one.

Can someone explain on these so that I can understand how to write the instance of parameterized Semigroups and their quickTest arbitrary?

cmal
  • 2,062
  • 1
  • 18
  • 35
  • 1
    What do you mean that 'it does not work'? Please edit your question to describe the actual problem(s) you're seeing. – Mark Seemann Oct 22 '18 at 11:45
  • sorry for confusing you. I am also confused by the intent of these questions. So when I say it works, I really mean that these code compiles. And when I say it does not work, they cannot compile. But I also want to know the intent of these exercise, so I used it does not work. But it is somewhat confusing, too. Sorry for that. – cmal Oct 22 '18 at 15:16
  • 1
    These types are not higher-kinded. They are parameterized, but their parameters are types; to be higher-kinded, their parameters would need to themselves be parameterized types. I've fixed your question up for you. – Daniel Wagner Oct 22 '18 at 17:43

1 Answers1

3

This is wrong:

instance Arbitrary (Identity a) where
  arbitrary = return (Identity a)

a is not a value variable, it is a type variable. We need a value of type a to pass to the Identity constructor, not the a type itself.

So we need something like

instance Arbitrary a => Arbitrary (Identity a) where
  arbitrary = do
     x <- arbitrary         -- generate a value of type a
     return (Identity x)    -- turn it into a value of type (Identity a)

(or, more concisely, arbitrary = Identity <$> arbitrary)

Note how we have to require that a is a type for which we can generate random samples (adding Arbitrary a => after Instance). Otherwise, we can't use x <- arbitrary to generate a sample for a.

Further:

type IdentityAssoc =
  (Identity a0) -> (Identity a1) -> (Identity a2) -> Bool

Here we can't refer to a1,a1,a2, since we haven't defined those types anywhere. We need to choose concrete types, like Int. Further, these three types must be the same type, since (<>) takes two values of the same type, and returns a value in that type.

chi
  • 111,837
  • 3
  • 133
  • 218
  • Hi, @chi. Should the instance of `Semigroup` use `a1`, `a2`? If so, why is it different from the instance of type `IdentityAssoc`? like in this: `instance (Semigroup a) => Semigroup (Identity a) where (Identity a1) <> (Identity a2) = Identity (a1 <> a2)` – cmal Oct 23 '18 at 02:07
  • @cmal No in should be `instance Semigroup a => Semigroup (Identity a)`. There is no instance for `IdentityAssoc`, that is a function type for which we do not need a semigroup. – chi Oct 23 '18 at 09:35