Hello!
On Mon, Aug 03, 1998 at 04:18:49PM +0200, Hans Aberg wrote:
> [...]
> with a complex unit $i$. More explicitly, the complexification $R_\C$ will
> consist of pairs $r + i s$, where $r, s \in R$, $i$ is a formal symbol, and
> addition, multiplication and so on uses the rules for the usual complex
> numbers.
> So, why not add a type "Complexify(R)" of a ring R to Haskell?
Note that you can't divide in a ring. A type class *roughly* corresponding
to a ring is probably Num.
newtype Complexify t = Complexify (t,t)
instance Eq t => Eq (Complexify t) where
(Complexify (r1,i1)) == (Complexify (r2,i2)) = (r1 == r2) && (i1 == i2)
(Complexify (r1,i1)) /= (Complexify (r2,i2)) = (r1 /= r2) && (i1 /= i2)
instance Show t => Show (Complexify t) where
showsPrec p (Complexify (r,i)) = showChar '(' . shows r . showChar ',' .
shows i . showChar ')'
instance Num t => Num (Complexify t) where
(Complexify (r1,i1)) + (Complexify (r2,i2)) = Complexify (r1+r2, i1+i2)
(Complexify (r1,i1)) - (Complexify (r2,i2)) = Complexify (r1-r2, i1-i2)
(Complexify (r1,i1)) * (Complexify (r2,i2)) =
Complexify (r1*r2-i1*i2, r1*i2+r2*i1)
negate (Complexify (r,i)) = Complexify (-r,-i)
-- abs and signum are a bit more difficult
fromInteger a = Complexify (fromInteger a, 0)
That compiles with warnings that no methods for abs or signum are
defined.
Regards, Felix.