Home > Enterprise >  Haskell gives type error for simple function
Haskell gives type error for simple function

Time:09-17

I have the following code:

module FunctorsApplicativeFunctorsAndMonoids(List(..), combineLists) where

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

combineLists:: List a -> List a -> List a
combineLists (Value a rest) b = Value a (combineLists rest b)
combineLists Empty b = b

I wrote this test to ensure the behavior works as I expect:

module FunctorsApplicativeFunctorsAndMonoidsSpec where

import Test.Hspec
import FunctorsApplicativeFunctorsAndMonoids

spec :: Spec
spec = do
  describe "List" $ do
    it "should implement combineLists" $ do
      combineLists (Value 1 Empty) (Value 2 Empty) `shouldBe` (Value 1 (Value 2 Empty))
      combineLists Empty (Value 1 Empty) `shouldBe` (Value 1 Empty)
      combineLists (Value 1 Empty) Empty `shouldBe` (Value 1 Empty)
      combineLists Empty Empty `shouldBe` Empty

The last test fails with the following error:

stack test
exercises> build (lib   test)
Preprocessing library for exercises-0.1.0.0..
Building library for exercises-0.1.0.0..
Preprocessing test suite 'exercises-test' for exercises-0.1.0.0..
Building test suite 'exercises-test' for exercises-0.1.0.0..
[10 of 11] Compiling FunctorsApplicativeFunctorsAndMonoidsSpec

/Users/jerred/git/learn-you-a-haskell-exercises/test/FunctorsApplicativeFunctorsAndMonoidsSpec.hs:17:32: error:
    • Ambiguous type variable ‘a0’ arising from a use of ‘shouldBe’
      prevents the constraint ‘(Show a0)’ from being solved.
      Probable fix: use a type annotation to specify what ‘a0’ should be.
      These potential instances exist:
        instance [safe] Show a => Show (List a)
          -- Defined in ‘FunctorsApplicativeFunctorsAndMonoids’
        instance Show Ordering -- Defined in ‘GHC.Show’
        instance Show a => Show (Maybe a) -- Defined in ‘GHC.Show’
        ...plus 24 others
        ...plus 50 instances involving out-of-scope types
        (use -fprint-potential-instances to see them all)
    • In a stmt of a 'do' block:
        combineLists Empty Empty `shouldBe` Empty
      In the second argument of ‘($)’, namely
        ‘do combineLists (Value 1 Empty) (Value 2 Empty)
              `shouldBe` (Value 1 (Value 2 Empty))
            combineLists Empty (Value 1 Empty) `shouldBe` (Value 1 Empty)
            combineLists (Value 1 Empty) Empty `shouldBe` (Value 1 Empty)
            combineLists Empty Empty `shouldBe` EmptyIn a stmt of a 'do' block:
        it "should implement combineLists"
          $ do combineLists (Value 1 Empty) (Value 2 Empty)
                 `shouldBe` (Value 1 (Value 2 Empty))
               combineLists Empty (Value 1 Empty) `shouldBe` (Value 1 Empty)
               combineLists (Value 1 Empty) Empty `shouldBe` (Value 1 Empty)
               combineLists Empty Empty `shouldBe` Empty
   |
17 |       combineLists Empty Empty `shouldBe` Empty
   |                                ^^^^^^^^^^
Progress 1/2

--  While building package exercises-0.1.0.0 (scroll up to its section to see the error) using:
      /Users/jerred/.asdf/installs/haskell/9.0.1/stack/setup-exe-cache/x86_64-osx/Cabal-simple_mPHDZzAJ_3.4.0.0_ghc-9.0.1 --builddir=.stack-work/dist/x86_64-osx/Cabal-3.4.0.0 build lib:exercises test:exercises-test --ghc-options " -fdiagnostics-color=always"
    Process exited with code: ExitFailure 1

I'm a little bit confused on why this error is occurring. Is it because the List type constructor takes an a argument, but an error occurs because Empty doesn't? Why do the other tests work as expected?

CodePudding user response:

Yes, it is because List has an argument and Empty does not have enough information to work out what that argument is.

We have the following types:

combineLists :: List a -> List a -> List a
shouldBe :: a -> a -> SomethingLMAO -- and therefore:
shouldBe :: List a -> List a -> SomethingLMAO

Together, these types mean that in a term of the form

combineLists x y `shouldBe` z

we know that all three of x, y, and z will be lists with the same element type. This means that if any one of the three has enough information to determine an element type, the element type is known for the others, too. But in your problematic example...

combineLists Empty Empty `shouldBe` Empty

None of the three has any elements, and therefore the element type is left indeterminate!

There are a few more wrinkles you may notice as you continue your studies: "defaulting" is sometimes allowed to silently disambiguate some ambiguous types, and types which are not constrained by a typeclass are never considered ambiguous in the first place. I'll leave it up to you whether you want to check out the Report/GHC manual to learn all the details of that now or wait until it comes up.

CodePudding user response:

The type signature of shouldBe is like this:

shouldBe :: (HasCallStack, Show a, Eq a) => a -> a -> Expectation

Hence, any argument of shouldBe must be Showable.

The (arguably long) error message of GHC tells us where the problem lies:

Ambiguous type variable ‘a0’ arising from a use of ‘shouldBe’
      prevents the constraint ‘(Show a0)’ from being solved.
...
   |
17 |       combineLists Empty Empty `shouldBe` Empty
   |                                ^^^^^^^^^^

though we have to use the vertical slider to see the essential line number in the text of your question.

Now, is Empty showable ? Empty is of type List a for some type a, but which one ? No, the compiler won't take a clue from the source line just above.

So, if you manually force the type of Empty to be something reasonable, the code works.

      combineLists Empty Empty  `shouldBe`  (Empty :: List Integer)

As mentioned in the excellent answer by Daniel, the type of the rightmost operand propagates to the other side of shouldBe. This is why the 3 other tests do not cause any problems.

Self-sufficient compilable version of the source code:

import Test.Hspec
import Test.Hspec.Expectations

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

combineLists:: List a -> List a -> List a
combineLists (Value a rest) b = Value a (combineLists rest b)
combineLists Empty b = b

spec :: Spec
spec = do
  describe "List" $ do
    it "should implement combineLists" $ do
      combineLists (Value 1 Empty) (Value 2 Empty)  `shouldBe`  (Value 1 (Value 2 Empty))
      combineLists Empty (Value 1 Empty)  `shouldBe`  (Value 1 Empty)
      combineLists (Value 1 Empty) Empty  `shouldBe`  (Value 1 Empty)
      combineLists Empty Empty  `shouldBe`  (Empty :: List Integer)

main:: IO ()
main = do
    putStrLn $ "Hello impure world !"

Addendum: a table-oriented approach

As written above, the compiler cannot propagate typing info between the various checks. But if we arrange the tests as as list of ((operand1, operand2), result) tuples, the typing info can propagate, because in Haskell lists, all elements are required to have the same type. Furthermore, this separates the list of expected results from the mechanics of checking them.

Like this:

spec2 :: Spec
spec2 = 
  let  truthTable =
         [
            ( (Value 1 Empty, Value 2 Empty)     , Value 1 (Value 2 Empty)   )
          , ( (Empty, Empty)                     , Empty                     )
          , ( (Empty, Value 1 Empty)             , Value 1 Empty             )
          , ( (Value 1 Empty, Empty)             , Value 1 Empty             )
         ]
       checkFn = \((op1, op2), result) -> shouldBe (combineLists op1 op2) result
       checks  = sequence_ (map checkFn truthTable)
  in
      do
        describe "List" $ do
          it "should implement combineLists" $ checks

Here, the integer literals 1 and 2 benefit from the Haskell implicit default clause. And so the compiler gets to understand that everybody has to be of type List Integer, including the Empty terms.

  • Related