Trying to write 'safeFromInteger'

Here's my code (in file "Test.hs") safeFromInteger :: (Num a, Integral a, Bounded a) => Integer -> Maybe a safeFromInteger i = if i > (toInteger maxBound) then Nothing else Just (fromInteger i) Here's the error from GHCi 6.10.1: Test.hs:3:19: Ambiguous type variable `a' in the constraints: `Bounded a' arising from a use of `maxBound' at Test.hs:3:19-26 `Integral a' arising from a use of `toInteger' at Test.hs:3:9-26 Probable fix: add a type signature that fixes these type variable(s) It's almost like GHC thinks that the type variable "a" can't be part of the "Bounded" lass and the "Integeral" class. I plan to use "safeFromInteger" for converting from Word8, Word16, Word32, etc.

-----BEGIN PGP SIGNED MESSAGE----- Hash: SHA1 On Apr 7, 2009, at 17:27 , Kannan Goundan wrote:
if i > (toInteger maxBound)
I think you have to tell it *which* maxBound you want. - -- 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 -----BEGIN PGP SIGNATURE----- Version: GnuPG v2.0.10 (Darwin) iEYEARECAAYFAknbxrAACgkQIn7hlCsL25VTbwCgwIFznypXKUvRzL1qqbkDdP9g P8QAn2He/JwKiDirOn65ggbwEc2fwWQ9 =nN6C -----END PGP SIGNATURE-----

On Tue, Apr 7, 2009 at 11:27 PM, Kannan Goundan
Here's my code (in file "Test.hs")
safeFromInteger :: (Num a, Integral a, Bounded a) => Integer -> Maybe a safeFromInteger i = if i > (toInteger maxBound) then Nothing else Just (fromInteger i)
Here's the error from GHCi 6.10.1:
Test.hs:3:19: Ambiguous type variable `a' in the constraints: `Bounded a' arising from a use of `maxBound' at Test.hs:3:19-26 `Integral a' arising from a use of `toInteger' at Test.hs:3:9-26 Probable fix: add a type signature that fixes these type variable(s)
It's almost like GHC thinks that the type variable "a" can't be part of the "Bounded" lass and the "Integeral" class.
That is not what it thinks. Ambiguous is not the same as conflicting (you could call them opposites: ambiguous means underconstrained, conflicting means overconstrained). The confusing thing here is that the `a' GHC is talking about is not the `a' in your code. The problem with your code is that the type of maxBound is unspecified. You need (maxBound `asTypeOf` i), or enable ScopedTypeVariables and use (maxBound :: a) (I think). --Max

Max Rabkin
The problem with your code is that the type of maxBound is unspecified. You need (maxBound `asTypeOf` i), or enable ScopedTypeVariables and use (maxBound :: a) (I think).
I tried doing the (maxBound :: a) thing, but got another confusing error: safeFromInteger :: (Num a, Integral a, Bounded a) => Integer -> Maybe a safeFromInteger i = if i > (toInteger (maxBound :: a)) then Nothing else Just (fromInteger i) # ghci -XScopedTypeVariables Test.hs Test.hs:3:20: Could not deduce (Bounded a1) from the context () arising from a use of `maxBound' at TestIntegerBounds.hs:3:20-27 Possible fix: add (Bounded a1) to the context of an expression type signature In the first argument of `toInteger', namely `(maxBound :: a)' In the second argument of `(>)', namely `(toInteger (maxBound :: a))' In the expression: i > (toInteger (maxBound :: a))

You must explicitly quantify the type parameters in the top level function
when you use this extension. This works:
{-# LANGUAGE ScopedTypeVariables #-}
safeFromInteger :: forall a . (Num a, Integral a, Bounded a) => Integer ->
Maybe a
safeFromInteger i =
if i > (toInteger (maxBound :: a))
then Nothing
else Just (fromInteger i)
On Tue, Apr 7, 2009 at 11:42 PM, Kannan Goundan
Max Rabkin
writes: The problem with your code is that the type of maxBound is unspecified. You need (maxBound `asTypeOf` i), or enable ScopedTypeVariables and use (maxBound :: a) (I think).
I tried doing the (maxBound :: a) thing, but got another confusing error:
safeFromInteger :: (Num a, Integral a, Bounded a) => Integer -> Maybe a safeFromInteger i = if i > (toInteger (maxBound :: a)) then Nothing else Just (fromInteger i)
# ghci -XScopedTypeVariables Test.hs
Test.hs:3:20: Could not deduce (Bounded a1) from the context () arising from a use of `maxBound' at TestIntegerBounds.hs:3:20-27 Possible fix: add (Bounded a1) to the context of an expression type signature In the first argument of `toInteger', namely `(maxBound :: a)' In the second argument of `(>)', namely `(toInteger (maxBound :: a))' In the expression: i > (toInteger (maxBound :: a))
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Tue, 7 Apr 2009, Max Rabkin wrote:
The problem with your code is that the type of maxBound is unspecified. You need (maxBound `asTypeOf` i), or enable ScopedTypeVariables and use (maxBound :: a) (I think).
i is Integer, so asTypeOf is not so easy to apply. I propose to write safeFromIntegerAux :: (Num a, Integral a) => a -> Integer -> Maybe a safeFromIntegerAux mb i = if i > toInteger mb then Nothing else Just (fromInteger i) safeFromInteger = safeFromIntegerAux maxBound Btw. this is another instance where my beloved toMaybe function is useful. :-) http://hackage.haskell.org/packages/archive/utility-ht/0.0.4/doc/html/Data-M...

On Tue, Apr 7, 2009 at 11:43 PM, Henning Thielemann
On Tue, 7 Apr 2009, Max Rabkin wrote:
The problem with your code is that the type of maxBound is unspecified. You need (maxBound `asTypeOf` i), or enable ScopedTypeVariables and use (maxBound :: a) (I think).
i is Integer, so asTypeOf is not so easy to apply.
Of course. It can, however, be done: safeFromInteger :: (Num b, Integral b, Bounded b) => Integer -> Maybe b safeFromInteger i = let result = fromInteger i in if i > (toInteger $ maxBound `asTypeOf` result) then Nothing else Just result Thank you, laziness!
(safeFromInteger 1000000000000000000000000) :: Maybe Int Nothing (safeFromInteger 100000) :: Maybe Int Just 100000
--Max

Hello Henning, Wednesday, April 8, 2009, 1:43:31 AM, you wrote:
i is Integer, so asTypeOf is not so easy to apply. I propose to write
safeFromInteger i = let mb = maxBound in if i > (toInteger mb) then Nothing else Just (fromInteger i `asTypeOf` mb) or you can do it opposite way: safeFromInteger i = let res = fromInteger i in if i > (toInteger (maxBound `asTypeOf` res)) then Nothing else Just res -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Hello Kannan, Wednesday, April 8, 2009, 1:27:21 AM, you wrote:
if i > (toInteger maxBound)
problem here is that GHC doesn't know what maxBound you mean. is it maxBound::Int8? or maxBound::Word128? it has nothing common with the value you return later so you need to use either scoped type variables or usual asTypeOf trick. look recent cafe threads for more info -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Of course your safeFromInteger isn't really safe, what about the minBound?
=)
On Tue, Apr 7, 2009 at 5:27 PM, Kannan Goundan
Here's my code (in file "Test.hs")
safeFromInteger :: (Num a, Integral a, Bounded a) => Integer -> Maybe a safeFromInteger i = if i > (toInteger maxBound) then Nothing else Just (fromInteger i)
Here's the error from GHCi 6.10.1:
Test.hs:3:19: Ambiguous type variable `a' in the constraints: `Bounded a' arising from a use of `maxBound' at Test.hs:3:19-26 `Integral a' arising from a use of `toInteger' at Test.hs:3:9-26 Probable fix: add a type signature that fixes these type variable(s)
It's almost like GHC thinks that the type variable "a" can't be part of the "Bounded" lass and the "Integeral" class.
I plan to use "safeFromInteger" for converting from Word8, Word16, Word32, etc.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

What about : sffi :: (Integral a,Num a) => Integer -> Maybe a sffi n = go n (fromInteger n) where go a b | toInteger b == a = Just b | otherwise = Nothing

That seems a really weird way to write it! Who decided all auxiliary functions should be called go? (I think I'm blaming dons) - why not: sffi :: (Integral a,Num a) => Integer -> Maybe a sffi n | toInteger n2 == n = Just n2 | otherwise = Nothing where n2 = fromInteger n No need for auxiliary function definitions. Thanks Neil

On Wed, Apr 8, 2009 at 2:55 PM, Neil Mitchell
That seems a really weird way to write it! Who decided all auxiliary functions should be called go? (I think I'm blaming dons) - why not:
sffi :: (Integral a,Num a) => Integer -> Maybe a sffi n | toInteger n2 == n = Just n2 | otherwise = Nothing where n2 = fromInteger n
I know I was too lazy to clean it up :-P ( I also blame Dons for 'go' )

On Wed, Apr 8, 2009 at 9:26 AM, david48
On Wed, Apr 8, 2009 at 2:55 PM, Neil Mitchell
wrote: That seems a really weird way to write it! Who decided all auxiliary functions should be called go? (I think I'm blaming dons) - why not:
sffi :: (Integral a,Num a) => Integer -> Maybe a sffi n | toInteger n2 == n = Just n2 | otherwise = Nothing where n2 = fromInteger n
I know I was too lazy to clean it up :-P ( I also blame Dons for 'go' )
I think the Common Lisp community tends to use 'foo-aux' instead of 'go' for these sort of axillary functions. But, then in Haskell we can't use hyphen as an identify character and underscore is not popular. For this reason I started using fooAux in Haskell, but after learning that a single quote is valid identifier character I started using foo'. Other than using go and foo', what do people use in Haskell? Jason

On Wed, Apr 08, 2009 at 09:38:25AM -0700, Jason Dagit wrote:
Other than using go and foo', what do people use in Haskell?
I frequently use f and g. -- Antti-Juhani Kaijanaho, Jyväskylä, Finland http://antti-juhani.kaijanaho.fi/newblog/ http://www.flickr.com/photos/antti-juhani/

Jason Dagit wrote:
On Wed, Apr 8, 2009 at 9:26 AM, david48
wrote: On Wed, Apr 8, 2009 at 2:55 PM, Neil Mitchell
wrote: That seems a really weird way to write it! Who decided all auxiliary functions should be called go? (I think I'm blaming dons) - why not:
sffi :: (Integral a,Num a) => Integer -> Maybe a sffi n | toInteger n2 == n = Just n2 | otherwise = Nothing where n2 = fromInteger n
I know I was too lazy to clean it up :-P ( I also blame Dons for 'go' )
I think the Common Lisp community tends to use 'foo-aux' instead of 'go' for these sort of axillary functions. But, then in Haskell we can't use hyphen as an identify character and underscore is not popular. For this reason I started using fooAux in Haskell, but after learning that a single quote is valid identifier character I started using foo'.
Other than using go and foo', what do people use in Haskell?
You could combine Lisp and Haskell and say foo'aux :-) Cheers Ben

That seems a really weird way to write it! Who decided all auxiliary functions should be called go? (I think I'm blaming dons) - why not:
sffi :: (Integral a,Num a) => Integer -> Maybe a sffi n | toInteger n2 == n = Just n2 | otherwise = Nothing where n2 = fromInteger n
I know I was too lazy to clean it up :-P ( I also blame Dons for 'go' )
I think the Common Lisp community tends to use 'foo-aux' instead of 'go' for these sort of axillary functions. But, then in Haskell we can't use hyphen as an identify character and underscore is not popular. For this reason I started using fooAux in Haskell, but after learning that a single quote is valid identifier character I started using foo'.
Other than using go and foo', what do people use in Haskell?
I use f, if I need several auxiliary functions I start at f and work my way up alphabetically. I tend to go back to f2 if I go past h. Be grateful you don't have to maintain my code :-) Thanks Neil PS. Here is some code from the filepath library I wrote, illustrating how fantastic my naming scheme looks. (I think if I was writing it today I'd have used a list comprehension for validChars, eliminating f.) makeValid path = joinDrive drv $ validElements $ validChars pth where (drv,pth) = splitDrive path validChars x = map f x f x | x `elem` badCharacters = '_' | otherwise = x validElements x = joinPath $ map g $ splitPath x g x = h (reverse b) ++ reverse a where (a,b) = span isPathSeparator $ reverse x h x = if map toUpper a `elem` badElements then a ++ "_" <.> b else x where (a,b) = splitExtensions x

Neil Mitchell
Other than using go and foo', what do people use in Haskell?
I tend to use 'go' for recursive or iterative functions. Which I belive is the original dons idiom. I occasionally use foo', but it is all too easy to write foo when you mean foo', and, which is worse, it occasionally happens to compile.
I use f, if I need several auxiliary functions I start at f and work my way up alphabetically.
:-)
makeValid path = joinDrive drv $ validElements $ validChars pth where (drv,pth) = splitDrive path
validChars x = map f x f x | x `elem` badCharacters = '_' | otherwise = x
In cases like this, I use names like 'foo1', since it does 'foo' for one element. So here I'd name 'f' something like 'valid1'. -k -- If I haven't seen further, it is by standing in the footprints of giants

On Wed, 8 Apr 2009, Neil Mitchell wrote:
That seems a really weird way to write it! Who decided all auxiliary functions should be called go? (I think I'm blaming dons) - why not:
sffi :: (Integral a,Num a) => Integer -> Maybe a sffi n | toInteger n2 == n = Just n2 | otherwise = Nothing where n2 = fromInteger n
I think it is a bug, that 'fromInteger' is defined for numbers outside the range of the target type. Why is it necessary to have, say fromInteger 1000 == (232 :: Word8) ? I would not rely on this behaviour and safeFromInteger should also work, when the fromInteger method yields undefined for some Integer input.
participants (14)
-
Antti-Juhani Kaijanaho
-
Ben Franksen
-
Brandon S. Allbery KF8NH
-
Bulat Ziganshin
-
david48
-
Edward Kmett
-
Henning Thielemann
-
Jason Dagit
-
Kannan Goundan
-
Ketil Malde
-
Martijn van Steenbergen
-
Max Rabkin
-
Neil Mitchell
-
Peter Verswyvelen