How to fix ambiguous type variable?

Hi everyone, I was playing around with some tests and run into code that looks really similar to the following function someCheck :: (Show a, Read a, Eq a) => String -> a -> Bool someCheck s v = (read . show . read $ s) == v But obviously, it's not clear what instance to use in the right-most read and the show functions. So it doesn't compile. Out of curiosity, is it possible to make this function compile? I've struggled some time and could not find an answer by myself, so here I am. Thanks in advance! Cheers, boris@d12frosted.io

This seems to work for me... someCheck :: forall a . (Show a, Read a, Eq a) => String -> a -> Bool someCheck s v = (read . show . (read :: String -> a) $ s) == v Probably requires 'ScopedTypeVariables'... On 13/06/19 11:06 AM, Boris wrote:
someCheck :: (Show a, Read a, Eq a) => String -> a -> Bool someCheck s v = (read . show . read $ s) == v

On Thu, Jun 13, 2019 at 11:15:23AM +0530, Sandeep.C.R via Haskell-Cafe wrote:
This seems to work for me...
someCheck :: forall a. (Show a, Read a, Eq a) => String -> a -> Bool someCheck s v = (read . show . (read :: String -> a) $ s) == v
Probably requires 'ScopedTypeVariables'...
Yes. Another variant is: {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeApplications #-} someCheck :: (Show a, Read a, Eq a) => String -> a -> Bool someCheck s (v :: a) = (read . show $ read @a s) == v which amounts to the same thing, but is perhaps simpler. For fun, with GHC 8.6 and "BlockArguments" we can drop some parentheses: {-# LANGUAGE BlockArguments #-} {-# LANGUAGE TypeApplications #-} {-# LANGUAGE ScopedTypeVariables #-} someCheck :: forall a. (Show a, Read a, Eq a) => String -> a -> Bool someCheck s v = v == do read $ show $ read @a s -- Viktor.

Hi everyone!
Thank you for your quick and (as always) helpful responses!
--------------------------------------------------------------------------------
Sandeep,
> This seems to work for me...
>
> someCheck :: forall a . (Show a, Read a, Eq a) => String -> a -> Bool
>
> someCheck s v = (read . show . (read :: String -> a) $ s) == v
>
> Probably requires 'ScopedTypeVariables'...
I clearly tried using `forall a`, but without `ScopedTypeVariables`. That's the missing thing. Thank you very much!
--------------------------------------------------------------------------------
Viktor, thank you for providing even more options!
I was looking for something like `TypeApplications`!
--------------------------------------------------------------------------------
Marian,
Agree, a good point. And actually, your variant works without any extensions.
Cheers,
boris@d12frosted.io
‐‐‐‐‐‐‐ Original Message ‐‐‐‐‐‐‐
On Thursday, June 13, 2019 8:45 AM, Sandeep.C.R via Haskell-Cafe

On Jun 13, 2019, at 4:25 AM, Boris
wrote: Agree, a good point. And actually, your variant works without any extensions.
Well, in a sense it is working with an "extension", just one that happens to be on by default and is required in Haskell 98. Namely, what makes it work is the "MonomorphismRestriction". If you specify: {-# LANGUAGE NoMonomorphismRestriction #-} then the example stops working. I like the posted example as an exceptionally clear illustration of the MonomorphismRestriction. -- Viktor.

On Thu, Jun 13, 2019 at 04:46:25AM -0400, Viktor Dukhovni wrote:
On Jun 13, 2019, at 4:25 AM, Boris
wrote: Agree, a good point. And actually, your variant works without any extensions.
Well, in a sense it is working with an "extension", just one that happens to be on by default and is required in Haskell 98. Namely, what makes it work is the "MonomorphismRestriction". If you specify:
{-# LANGUAGE NoMonomorphismRestriction #-}
then the example stops working. I like the posted example as an exceptionally clear illustration of the MonomorphismRestriction.
And for the record, this version requires no extension nor unextension: {-# LANGUAGE NoMonomorphismRestriction #-} module Check where someCheck :: (Show a, Read a, Eq a) => String -> a -> Bool someCheck = someCheck' read where someCheck' r s v = (r . show . r $ s) == v

Tom,
Haha, nice. Now we have someCheck defined for so many scenarios. I like it.
Didn't expect to get so many answers ;) Thanks everyone!
Cheers,
boris@d12frosted.io
‐‐‐‐‐‐‐ Original Message ‐‐‐‐‐‐‐
On Thursday, June 13, 2019 12:53 PM, Tom Ellis
On Thu, Jun 13, 2019 at 04:46:25AM -0400, Viktor Dukhovni wrote:
On Jun 13, 2019, at 4:25 AM, Boris boris@d12frosted.io wrote: Agree, a good point. And actually, your variant works without any extensions.
Well, in a sense it is working with an "extension", just one that happens to be on by default and is required in Haskell 98. Namely, what makes it work is the "MonomorphismRestriction". If you specify: {-# LANGUAGE NoMonomorphismRestriction #-} then the example stops working. I like the posted example as an exceptionally clear illustration of the MonomorphismRestriction.
And for the record, this version requires no extension nor unextension:
{-# LANGUAGE NoMonomorphismRestriction #-}
module Check where
someCheck :: (Show a, Read a, Eq a) => String -> a -> Bool
someCheck = someCheck' read where someCheck' r s v = (r . show . r $ s) == v
Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

On 6/13/19 6:36 AM, Boris wrote:
someCheck :: (Show a, Read a, Eq a) => String -> a -> Bool someCheck s v = (read . show . read $ s) == v
someCheck :: (Show a, Read a, Eq a) => String -> a -> Bool someCheck s v = (r . show . r $ s) == v where r = read I believe you do intend to use the same read in both cases anyway, and letting a different read to slip in would be a bug. Marian
participants (5)
-
Boris
-
Marian Jancar
-
Sandeep.C.R
-
Tom Ellis
-
Viktor Dukhovni