
Hi Michael, michael rice wrote:
as opposed to an "inferred type"?
Can you deduce from the following example?
Prelude> let foo = () :: Int <interactive>:1:10: Couldn't match expected type `Int' against inferred type `()' In the expression: () :: Int In the definition of `foo': foo = () :: Int
Hope this helps! Martijn.

I really dislike this error message, and I think the terms are
ambiguous. I think the words 'expected' and 'inferred' apply equally
well to the term, and the context in which it has been found. Both of
the incompatible types were 'inferred', and 'unexpected' is a property
of the combination, not a property of one or the other.
--
Dan
On Sun, Jun 28, 2009 at 8:24 AM, Martijn van
Steenbergen
Hi Michael,
michael rice wrote:
as opposed to an "inferred type"?
Can you deduce from the following example?
Prelude> let foo = () :: Int <interactive>:1:10: Couldn't match expected type `Int' against inferred type `()' In the expression: () :: Int In the definition of `foo': foo = () :: Int
Hope this helps!
Martijn.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Could you suggest a better word pair to describe the dichotomy then? How about 'calculated' vs 'user-imposed' (or even, 'explicitly- signatured')? Dan Piponi-2 wrote:
I really dislike this error message, and I think the terms are ambiguous. I think the words 'expected' and 'inferred' apply equally well to the term, and the context in which it has been found. Both of the incompatible types were 'inferred', and 'unexpected' is a property of the combination, not a property of one or the other. -- Dan
On Sun, Jun 28, 2009 at 8:24 AM, Martijn van Steenbergen
wrote: Hi Michael,
michael rice wrote:
as opposed to an "inferred type"?
Can you deduce from the following example?
Prelude> let foo = () :: Int <interactive>:1:10: Couldn't match expected type `Int' against inferred type `()' In the expression: () :: Int In the definition of `foo': foo = () :: Int
Hope this helps!
Martijn.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- View this message in context: http://www.nabble.com/What-is-an-%22expected-type%22-...-tp24242359p24244820... Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

Hello Kim-Ee, Sunday, June 28, 2009, 11:52:57 PM, you wrote: we already had a *long* discussion on this topic. afaik, it's dichotomy between type of term itself and type of position where it's used (f.e. argument of some function)
Could you suggest a better word pair to describe the dichotomy then? How about 'calculated' vs 'user-imposed' (or even, 'explicitly- signatured')?
Dan Piponi-2 wrote:
I really dislike this error message, and I think the terms are ambiguous. I think the words 'expected' and 'inferred' apply equally well to the term, and the context in which it has been found. Both of the incompatible types were 'inferred', and 'unexpected' is a property of the combination, not a property of one or the other. -- Dan
On Sun, Jun 28, 2009 at 8:24 AM, Martijn van Steenbergen
wrote: Hi Michael,
michael rice wrote:
as opposed to an "inferred type"?
Can you deduce from the following example?
Prelude> let foo = () :: Int <interactive>:1:10: Couldn't match expected type `Int' against inferred type `()' In the expression: () :: Int In the definition of `foo': foo = () :: Int
Hope this helps!
Martijn.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Bulat Ziganshin wrote:
Hello Kim-Ee,
Sunday, June 28, 2009, 11:52:57 PM, you wrote:
we already had a *long* discussion on this topic. afaik, it's dichotomy between type of term itself and type of position where it's used (f.e. argument of some function)
Could you suggest a better word pair to describe the dichotomy then? How about 'calculated' vs 'user-imposed' (or even, 'explicitly- signatured')?
How about "'Int' used in '()'-shaped hole"? "'Int' from usage, '()' from definition of 'foo' could not be reconciled"? Arne D Halvorsen
Dan Piponi-2 wrote:
I really dislike this error message, and I think the terms are ambiguous. I think the words 'expected' and 'inferred' apply equally well to the term, and the context in which it has been found. Both of the incompatible types were 'inferred', and 'unexpected' is a property of the combination, not a property of one or the other. -- Dan
On Sun, Jun 28, 2009 at 8:24 AM, Martijn van Steenbergen
wrote: Hi Michael,
michael rice wrote:
as opposed to an "inferred type"?
Can you deduce from the following example?
Prelude> let foo = () :: Int <interactive>:1:10: Couldn't match expected type `Int' against inferred type `()' In the expression: () :: Int In the definition of `foo': foo = () :: Int
Hope this helps!
Martijn.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

When Haskell runs it's type checker, it tries to "guess" the type of each function. Thats why you can write: map (+1) and it knows that you're talking about a function of type: Num a => [a] -> [a] Another thing, called 'defaulting' resolves this, but you didn't ask about that, so I won't go into it. An expected type is one that you provide to the compiler in the form of a type signature, this can be used to specialize a general type (like the one I showed) or to resolve ambiguous types the compiler can't, or just for documentation/good practice. So when I write: foo :: Num a => [a] -> [a] foo ls = map (+1) ls The "expected type" for `foo` is `Num a => [a] -> [a]`. I imagine you're asking this because you got an error which said your expected type doesn't match your inferred type. That might, for instance, happen if I wrote: bar :: String bar = 'a' 'a' has type `Char`, since `String` is not `Char`, the type checker infers that 'a' has type char, but _expects_ it to be type String. Two solutions are as follows: --- Method 1 bar :: Char bar = 'a' --- Method 2 bar :: String bar = "a" Can you see why those two changes fix the problem? Also, just as a matter of process, I forwarded this to the haskell-beginners list, as I imagine type errors like these come up a lot, and someone probably has a better explanation over there. /Joe michael rice wrote:
as opposed to an "inferred type"?
Michael
------------------------------------------------------------------------
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hey Joe, all,
Got it. Thanks!
An associated question: In programming a local "helper" or "auxilliary" function such as dec2bin' in
dec2bin :: Integer -> [Integer]
dec2bin n = dec2bin' n []
where dec2bin' n acc
| n == 0 = acc
| otherwise = let r = rem n 2
m = div (n - r) 2
in dec2bin' m (r : acc)
is there any way to assign a type signature to the helper function?
Michael
--- On Sun, 6/28/09, Joe Fredette
as opposed to an "inferred type"?
Michael
------------------------------------------------------------------------
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Jun 28, 2009, at 12:02 , michael rice wrote:
dec2bin :: Integer -> [Integer] dec2bin n = dec2bin' n [] where dec2bin' n acc | n == 0 = acc | otherwise = let r = rem n 2 m = div (n - r) 2 in dec2bin' m (r : acc)
is there any way to assign a type signature to the helper function?
Same way you do for a top level binding:
dec2bin :: Integer -> [Integer] dec2bin n = dec2bin' n [] where dec2bin' :: Integer -> [Integer] -> [Integer] dec2bin' n acc | n == 0 = acc | otherwise = let r = rem n 2 m = div (n - r) 2 in dec2bin' m (r : acc)
-- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

How else? ;-)
Thanks,
Michael
--- On Sun, 6/28/09, Brandon S. Allbery KF8NH

Am Sonntag 28 Juni 2009 18:06:52 schrieb Brandon S. Allbery KF8NH:
On Jun 28, 2009, at 12:02 , michael rice wrote:
dec2bin :: Integer -> [Integer] dec2bin n = dec2bin' n [] where dec2bin' n acc
| n == 0 = acc | otherwise = let r = rem n 2
m = div (n - r) 2 in dec2bin' m (r : acc)
is there any way to assign a type signature to the helper function?
Same way you do for a top level binding:
dec2bin :: Integer -> [Integer] dec2bin n = dec2bin' n [] where dec2bin' :: Integer -> [Integer] -> [Integer] dec2bin' n acc
| n == 0 = acc | otherwise = let r = rem n 2
m = div (n - r) 2 in dec2bin' m (r : acc)
But, to mention it before it bites, putting type signatures involving type variables on local helper functions is not entirely straightforward. Consider inBase :: Integral a => a -> a -> [a] 0 `inBase` b = [0] n `inBase` b = local n [] where local 0 acc = acc local m acc = case m `divMod` b of (q,r) -> local q (r:acc) Now try giving a type signature to local. You can't. What is the type of local? It's (type of b) -> [type of b] -> [type of b], but "type of b" isn't available. If you try local :: a -> [a] -> [a] or local :: Integral a => a -> [a] -> [a], you are saying that local works for *every* type a (or for every type a which is an instance of Integral), because the 'a' from local's type signature is a new (implicitly forall'd) type variable. To be able to give local a type signature, you must bring the type variable 'a' into scope: {-# LANGUAGE ScopedTypeVariables #-} inBase :: forall a. Integral a => a -> a -> [a] 0 `inBase` b = [0] n `inBase` b = local n [] where local :: a -> [a] -> [a] -- now this a is the same a as the one above local 0 acc = acc local m acc = case m `divMod` b of (q,r) -> local q (r:acc)

On Sun, Jun 28, 2009 at 17:14, michael rice
as opposed to an "inferred type"?
There was a thread on haskell-cafe about this a few weeks ago. Here it is in the archives: http://www.haskell.org/pipermail/haskell-cafe/2009-May/062012.html Maybe some post in there might help. Maybe they will all confuse you... :) Thomas
participants (10)
-
Arne Dehli Halvorsen
-
Brandon S. Allbery KF8NH
-
Bulat Ziganshin
-
Dan Piponi
-
Daniel Fischer
-
Joe Fredette
-
Kim-Ee Yeoh
-
Martijn van Steenbergen
-
michael rice
-
Thomas ten Cate