int to float problem

Jorge Adriano jadrian@mat.uc.pt
Sun, 2 Mar 2003 11:28:00 +0000


--Boundary-00=_AreY+/Q9GP022GY
Content-Type: text/plain;
  charset="iso-8859-1"
Content-Transfer-Encoding: quoted-printable
Content-Disposition: inline


> "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=20
operations, is a very common need and I don't like adding fromIntegral=20
everywhere, so ended up writing a (very simple) module with generalized=20
arithmetic operators (see attachment). The =BB next to the operations indic=
ate=20
a cast from an Integral to a Fractional value.=20

J.A.



--Boundary-00=_AreY+/Q9GP022GY
Content-Type: text/plain;
  charset="iso-8859-1";
  name="CrossTypeOps.hs"
Content-Transfer-Encoding: quoted-printable
Content-Disposition: attachment; filename="CrossTypeOps.hs"

module CrossTypeOps where


=2D- Addition
(+=AB)     :: (Fractional a, Integral b)=3D> a -> b -> a
(+=AB) x n =3D x+fromIntegral n

(=BB+)     :: (Integral a, Fractional b)=3D> a -> b -> b
(=BB+) n x =3D fromIntegral n + x

(=BB+=AB)     :: (Integral a, Fractional b)=3D> a -> a -> b
(=BB+=AB) m n =3D fromIntegral m+fromIntegral n


=2D- Difference
(-=AB)     :: (Fractional a, Integral b)=3D> a -> b -> a
(-=AB) x n =3D x-fromIntegral n

(=BB-)     :: (Integral a, Fractional b)=3D> a -> b -> b
(=BB-) n x =3D fromIntegral n - x

(=BB-=AB)     :: (Integral a, Fractional b)=3D> a -> a -> b
(=BB-=AB) m n =3D fromIntegral m-fromIntegral n


=2D- Multiplication
(*=AB)     :: (Fractional a, Integral b)=3D> a -> b -> a
(*=AB) x n =3D x*fromIntegral n

(=BB*)     :: (Integral a, Fractional b)=3D> a -> b -> b
(=BB*) n x =3D fromIntegral n * x

(=BB*=AB)     :: (Integral a, Fractional b)=3D> a -> a -> b
(=BB*=AB) m n =3D fromIntegral m*fromIntegral n


=2D- Division=20
(/=AB)     :: (Fractional a, Integral b)=3D> a -> b -> a
(/=AB) x n =3D x / fromIntegral n

(=BB/)     :: (Integral a, Fractional b)=3D> a -> b -> b
(=BB/) n x =3D fromIntegral n / x

(=BB/=AB)     :: (Integral a, Fractional b)=3D> a -> a -> b
(=BB/=AB) m n =3D fromIntegral m / fromIntegral n


=2D- Priorities
infixl 6  +=AB, =BB+, =BB+=AB, -=AB, =BB-, =BB-=AB
infixl 7  *=AB, =BB*, =BB*=AB, /=AB, =BB/, =BB/=AB




--Boundary-00=_AreY+/Q9GP022GY--