Strange Pattern Match Error

I have a custom type called Weight.
It is defined like this:
data Weight = Weight ((Float, Float, Float, Float), Float) deriving Show

I have this function:
evaluate_individual :: StdGen → Weight → Weight
evaluate_individual gen ((w, x, y, z), f) =
let (fitness, _) = random gen :: (Float, StdGen)
in Weight ((w, x, y, z), fitness)

I get this error:
trader.hs:33:25: error: [GHC-83865]
• Couldn’t match expected type ‘Weight’
with actual type ‘((Float, Float, Float, Float), b0)’
• In the pattern: ((w, x, y, z), f)
In an equation for ‘evaluate_individual’:
evaluate_individual gen ((w, x, y, z), f)
= let (fitness, gen1) = … in Weight ((w, x, y, z), fitness)
|
33 | evaluate_individual gen ((w, x, y, z), f) =
| ^^^^^^^^^^^^^^^^^

This occurs even when I don’t call the function in main.
I have also verified that it occurs when calling it in main with an StdGen and a Weight. I know the StdGen and Weight are the types of the parameters I am passing this function because I commented out the function, loaded this into ghci, and used :step and :t var_name for each variable to verify I’m not crazy.

What could possibly be going in here?
What is the ‘b0’ the compiler is talking about?
I have no custom type called b0 in the entire program.

I am new to haskell, and this is the first major program I am writing in it, so I apologize if this is something silly.
I have read everything up to and through the IO section in Learn You a Haskell for Great Good, that is all I know.

Thank you for your time.

Hello.

evaluate_individual :: StdGen → Weight → Weight
evaluate_individual gen (Weight ((w, x, y, z), f))
  = let (fitness, _) = random gen :: (Float, StdGen)
     in Weight ((w, x, y, z), fitness)

You are missing the Weight constructor in the pattern matching.

The compiler is trying to match (Weight ((w, x, y, z), f)) which is type Weight, with ((w, x, y, z), f) which is type ((Float, Float, Float, Float), b0).

It’s a type like a0, a1, b0, b1: an automatically named type that the compiler gives to values with the most generic type (because they couldn’t infer anything else). All values have a type.
You will notice that the compiler attributed w, x, y, z as Float, Float, Float, Float. and that’s because it inferred it from Weight ((w, x, y, z), fitness) inside the let.
Since you were using those variables as Float, it makes sense they are Float! And it typechecks so those are Float.

Another thing:

data Weight = Weight ((Float, Float, Float, Float), Float) deriving Show

Generates two things.
A type: Weight.
A constructor: Weight :: ((Float, Float, Float, Float), Float) -> Weight.
You can rename them if it confuses you, to something like this:

data Weight = MkWeight ((Float, Float, Float, Float), Float) deriving Show

Those are different things but Haskell allows you to name them the same because they appear in different places (function signatures vs patterns and function bodies) so the ambiguity can be solved.

2 Likes

Welcome, tech_nerd, and what darkxero said.

On a point of Haskelliness, was the structure of that datatype given from an example or exercise? Asking because all those commas and parens giving data constructor Weight a single param look rather overkill. This might be more idiomatic:

data Weight = Weight (Float, Float, Float, Float) Float     deriving Show

Because of all the parens in your form, darkxero’s answer then must do this:

Those extra parens around Weight are unavoidable – otherwise bare Weight would be taken as a pattern to evaluate_individual. With my suggested parens-lite data decl, that would be

evaluate_individual gen (Weight  (w, x, y, z)  f)
  = let ...