int to float problem
Mike T. Machenry
dskippy@ccs.neu.edu
Mon, 3 Mar 2003 10:52:20 -0500
Thank does sound like a pain, but it's better than putting fromIntegral
all over my code. Why can't Haskell unify a an expected float with an
infered int? It seems that this would make life alot easier.
-mike
On Sun, Mar 02, 2003 at 11:28:00AM +0000, Jorge Adriano wrote:
>
> > "Mike T. Machenry" <dskippy@ccs.neu.edu> writes:
> > > I recently desided I wanted a bunch function to return
> > > float instead of Int. [...] I found fromInteger but it
> > > didn't seem to work on the return value of the cardinality
> > > function for instance.
> >
> > Try fromIntegral, which works for Int and Integer, too.
>
>
> Casting an Integral value to a Fractional value to perform arithmetic
> operations, is a very common need and I don't like adding fromIntegral
> everywhere, so ended up writing a (very simple) module with generalized
> arithmetic operators (see attachment). The » next to the operations indicate
> a cast from an Integral to a Fractional value.
>
> J.A.
>
>
> module CrossTypeOps where
>
>
> -- Addition
> (+«) :: (Fractional a, Integral b)=> a -> b -> a
> (+«) x n = x+fromIntegral n
>
> (»+) :: (Integral a, Fractional b)=> a -> b -> b
> (»+) n x = fromIntegral n + x
>
> (»+«) :: (Integral a, Fractional b)=> a -> a -> b
> (»+«) m n = fromIntegral m+fromIntegral n
>
>
> -- Difference
> (-«) :: (Fractional a, Integral b)=> a -> b -> a
> (-«) x n = x-fromIntegral n
>
> (»-) :: (Integral a, Fractional b)=> a -> b -> b
> (»-) n x = fromIntegral n - x
>
> (»-«) :: (Integral a, Fractional b)=> a -> a -> b
> (»-«) m n = fromIntegral m-fromIntegral n
>
>
> -- Multiplication
> (*«) :: (Fractional a, Integral b)=> a -> b -> a
> (*«) x n = x*fromIntegral n
>
> (»*) :: (Integral a, Fractional b)=> a -> b -> b
> (»*) n x = fromIntegral n * x
>
> (»*«) :: (Integral a, Fractional b)=> a -> a -> b
> (»*«) m n = fromIntegral m*fromIntegral n
>
>
> -- Division
> (/«) :: (Fractional a, Integral b)=> a -> b -> a
> (/«) x n = x / fromIntegral n
>
> (»/) :: (Integral a, Fractional b)=> a -> b -> b
> (»/) n x = fromIntegral n / x
>
> (»/«) :: (Integral a, Fractional b)=> a -> a -> b
> (»/«) m n = fromIntegral m / fromIntegral n
>
>
> -- Priorities
> infixl 6 +«, »+, »+«, -«, »-, »-«
> infixl 7 *«, »*, »*«, /«, »/, »/«
>
>
>