1

I'm going to use C++ as an example here to show what I'm after. For complex arithmetic it has both complex and imaginary types:

https://en.cppreference.com/w/c/language/arithmetic_types#Imaginary_floating_types

These e.g. have the property that multiplying two numbers with type double imaginary will have the type double. This is almost but not quite the same as using complex numbers with the real part being 0.0 but not quite. Imaginary types don't explicitly store the real part which automatically eliminates unneeded computations with and storage of 0.0.

Additionally it prevents some problems with signed zeros. E.g. the computation (0.0+i*a)*(0.0+i*b) results in (-a*b-i*0.0) if a and b are negative and (-a*b+i*0.0) otherwise. This can be surprising if the result is fed into a function with a branch cut. An imaginary type avoids this unwanted negation of the zero.

My question is can you define a similar imaginary type in Haskell (in addition to a complex type) and also the operations (+), (-), (*), and (/) for it such that they behave like in C++? It seems that at least with the current definition of the Num and Fractional classes it's not possible because (+), (-), (*), and (/) have a -> a -> a as type signature so e.g. multiplying two imaginary numbers can't have a different type as a result. Could one, however, a different definition for these classes so that what I'm after would be possible?

I'm not asking this for a practical purpose. I just want to better understand what Haskell's type system is capable of.

QuantumWiz
  • 148
  • 9
  • Does this answer your question? [How to create a generic Complex type in haskell?](https://stackoverflow.com/questions/46826700/how-to-create-a-generic-complex-type-in-haskell) – monk May 07 '22 at 23:41
  • @monk No. That question asks about a complex type with both real and imaginary part whereas I'm asking about a type which would only have an imaginary part. – QuantumWiz May 08 '22 at 09:37

2 Answers2

6

Yes, of course you can define such a type. You just won't be able to use the Num interface for all its operations; but you are free to define whatever other functions you want with other types, perhaps even making them infix operators if desired.

Here's an example of a type that tracks at the type level whether it's imaginary or real, and supports addition and multiplication with an alternative name (subtraction and division don't require any new ideas not shown here):

{-# Language DataKinds #-}
{-# Language KindSignatures #-}
{-# Language TypeFamilies #-}

-- hide the Mindful data constructor
module Mindful (Mindful, real, iTimes, (+.), (*.), EqBool, KnownReality(isReal)) where

newtype Mindful (reality :: Bool) a = Mindful a deriving (Eq, Ord, Read, Show)

real :: a -> Mindful True a
real = Mindful

iTimes :: a -> Mindful False a
iTimes = Mindful

(+.) :: Num a => Mindful r a -> Mindful r a -> Mindful r a
Mindful x +. Mindful y = Mindful (x + y)

(*.) :: (KnownReality r, KnownReality r', Num a)
     => Mindful r a -> Mindful r' a -> Mindful (EqBool r r') a
xm@(Mindful x) *. ym@(Mindful y) = Mindful (iSquared * x * y) where
    iSquared = if isReal xm || isReal ym then 1 else -1

type family EqBool a b where
    EqBool False False = True
    EqBool False True = False
    EqBool True False = False
    EqBool True True = True

class KnownReality r where isReal :: Mindful r a -> Bool
instance KnownReality False where isReal _ = False
instance KnownReality True where isReal _ = True

If you must have the names be exactly + etc. for some reason (I do not recommend this, it will be a big pain), you could take a look at another answer of mine on controlling namespacing.

Daniel Wagner
  • 145,880
  • 9
  • 220
  • 380
  • The difficulty I'm having is defining (+), (-), (*), and (/) for this type which probably requires a redefinition of Num and Fractional if it's possible. I edited my question a bit to hopefully make it clearer. It would be a bit inconvenient to use different non-overloaded functions for every combination of types. – QuantumWiz May 08 '22 at 09:42
  • @QuantumWiz You don't **have** to use `Num` to provide definitions for `+`, `-`, etc, just because they're in the standard pride prelude. `Num` is just an ordinary class with ordinary methods and instances. You can provide your own definitions of those symbols (even your own class to define those symbols with many different types), if the usage you want doesn't fit into the constraints of the existing class. It's entirely up to you if the benefit of calling your operation `+` rather than picking a different symbol is worth the hassle of hiding the Prelude's definition. – Ben May 08 '22 at 12:10
  • @Ben The provided Num (and Fractional) definitions are clearly not sufficient. The problem I'm having is how to make my own definitions. I'm fairly sure that I would have to use my own classes since it seems I can't make overloaded functions without classes. However, I can't figure out how to write my own classes (in place of Num and Fractional) so that I could have imaginary and complex types with the desired behaviour. – QuantumWiz May 08 '22 at 13:34
  • @QuantumWiz Is it that you don't know how to write classes with the behaviour you want, or that you don't know how to use your own classes in place of Num and Fractional? – Ben May 08 '22 at 14:23
  • @QuantumWiz I have added some text describing one way to make such a type without using `Num`, and a link to some text about what to do if you really like the names that `Num` offers. I believe that addresses your updated question. – Daniel Wagner May 08 '22 at 17:07
  • @Ben The first one, i.e. I don't know how to write the classes with the behaviour I want. I will now read and try to understand the updated answer Daniel Wagner gave. It looks like it might be what I was after. – QuantumWiz May 08 '22 at 20:42
  • @DanielWagner Thanks. I think this is probably pretty much as close to what I wanted that can be achieved. There are a couple of issues: 1) With this definition of (+.) it seems that it's not possible to add real and imaginary numbers. However, I think I could fix that myself. One just needs to replace Bool with some type with 3 constructors to denote real, imaginary, and complex numbers. – QuantumWiz May 09 '22 at 23:14
  • @DanielWagner 2) It seems that with this definition it's not possible to directly add or multiply these types with plain Floats or Doubles without first wrapping them inside this type but I guess that's an unavoidable. I would have preferred that Num could be rewritten so you could directly use them but I guess Haskell's type system is too rigid (even though in many ways it very elegant). I'm accepting your answer because I think a better answer is probably not possible. – QuantumWiz May 09 '22 at 23:27
  • @QuantumWiz Correct, this method does not allow the addition of purely-real and purely-imaginary numbers. But beware generalizing that point; this definition was chosen carefully for its in-memory representation, and adding constructors will increase the size of the in-memory representation dramatically. I believe it is not Haskell's type system that is too rigid, but `Num` specifically that is too rigid. Alternative type classes that support mixed arguments are possible (and have been tried to death; have a look on Hackage). – Daniel Wagner May 10 '22 at 02:29
  • @DanielWagner "adding constructors will increase the size of the in-memory representation" Does it? I thought this solution did inference about the number being imaginary or real on type level and therefore presumably at compile time. If that wasn't necessary I could easily implement the desired type like this: `data MyNumber = Real Double | Imaginary Double | Complex Double Double` and then declare it instance of Num. It would solve the problem of signed zero for the real part of purely imaginary number but would still do stuff at runtime which could be done at compile time. – QuantumWiz May 10 '22 at 13:16
  • @DanielWagner "I believe it is not Haskell's type system that is too rigid, but Num specifically that is too rigid." If you're correct that's good news because a (hypothetical) rewrite of Num is what would feel like an ideal solution to me. However, at least I can't figure out how to rewrite Num so that it would do what I want here. – QuantumWiz May 10 '22 at 13:19
  • @QuantumWiz Correct, this solution does inference on the type level and therefore at compile time. But you are proposing changing this solution, and the change you are proposing will cost you. One way to rewrite `Num` is like `class Add a b where type Sum a b; (+) :: a -> b -> Sum a b` and similarly for multiplication. – Daniel Wagner May 10 '22 at 14:06
  • "Correct, this solution does inference on the type level and therefore at compile time. But you are proposing changing this solution" The change I wanted to make was just for reality to have 3 possible values rather than 2. It should still be on the type level and compile time, right? "One way to rewrite Num is like class Add a b where type Sum a b; (+) :: a -> b -> Sum a b" Ah, I didn't know that classes could have multiple parameters. Thanks. I've now read on MultiParamTypeClasses and I think I'll make some kind of solution using them and post it here. – QuantumWiz May 18 '22 at 13:13
  • @QuantumWiz The important part of the change you want to make is not switching from 2 alternatives to 3, but switching from 1 field to sometimes 1 and sometimes 2. The existing data type uses the same in-memory representation for both alternatives, whereas yours will have at least two possible representations (a single number or a pair of numbers), and there is a runtime cost to allowing that. – Daniel Wagner May 18 '22 at 17:43
  • @DanielWagner OK, then this solution doesn't quite do what I want. I think the multi parameter classes is a better solution. I'll try that once I have time. – QuantumWiz May 19 '22 at 11:55
  • @DanielWagner I now made a solution based rewriting `Num` by using MultiParamTypeClasses as you suggested in an earlier comment. I think I'll have to unaccept your current answer because it still falls somewhat short due to it e.g. not allowing real and imaginary values to be added. However, I'm still thankful for your answer because it was informative and came close to what I wanted even though it was ultimately your comments that gave the real answer. If you have any suggestions on how to improve my answer feel free to comment on it. – QuantumWiz May 24 '22 at 22:57
0

Daniel Wagner gave an answer that uses type families. The answer came close to what I was after but it was still a bit lacking since it didn't e.g. allow adding real and imaginary numbers. However, he mentioned that Haskell also has multi-parameter classes and these could be used to get a solution I want. So after reading on multi-parameter classes and functional dependencies I was able to come up with a solution.

I had to split the Num and Fractional classes into two parts with one having the functions with one argument and the other with two arguments. The functions fromInteger and fromRational had to be left undefined for imaginary numbers (except in case of 0). The solution became somewhat lengthy but I think there's no easy way around it. I made the solution only for Double as the underlying floating point type for simplicity though a more general type might be better.

This solution might not be perfect so suggestions of improvement are welcome.

{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FlexibleContexts #-}

import Data.Ratio
import Data.Complex

class MyNum1 a abs | a -> abs where
  myNegate :: a -> a
  myAbs :: a -> abs
  mySignum :: a -> a
  myFromInteger :: Integer -> a

class (MyNum1 a abs, MyNum1 b abs) => MyNum2 a b add mul abs | a b -> add, a b -> mul, a b -> abs where
  (+.), (-.) :: a -> b -> add
  (*.) :: a -> b -> mul
  x -. y = x +. myNegate y

class (MyNum1 a abs) => MyFractional1 a abs | a -> abs where
  myRecip :: a -> a
  myFromRational :: Rational -> a

class (MyFractional1 a abs, MyFractional1 b abs, MyNum2 a b add mul abs) => MyFractional2 a b add mul abs | a b -> add, a b -> mul, a b -> abs where
  (/.) :: a -> b -> mul
  x /. y = x *. myRecip y

newtype Imaginary a = I a
  deriving (Eq, Show)

instance MyNum1 Double Double where
  myNegate = negate
  myAbs = abs
  mySignum = signum
  myFromInteger = fromInteger

instance MyFractional1 Double Double where
  myRecip = recip
  myFromRational = fromRational

instance MyNum2 Double Double Double Double Double where
  (+.) = (+)
  (-.) = (-)
  (*.) = (*)

instance MyFractional2 Double Double Double Double Double where
  (/.) = (/)

instance MyNum1 (Imaginary Double) Double where
  myNegate (I y) = I (-y)
  myAbs (I y) = abs y
  mySignum (I y) = I (signum y)
  myFromInteger 0 = I 0.0
  myFromInteger _ = undefined --No reasonable definition possible.

instance MyFractional1 (Imaginary Double) Double where
  myRecip (I y) = I (-1/y)
  myFromRational 0 = I 0.0
  myFromRational _ = undefined --No reasonable definition possible.

instance MyNum2 (Imaginary Double) (Imaginary Double) (Imaginary Double) Double Double where
  (I y) +. (I y') = I (y+y')
  (I y) -. (I y') = I (y-y')
  (I y) *. (I y') = -y*y'

instance MyFractional2 (Imaginary Double) (Imaginary Double) (Imaginary Double) Double Double where
  (I y) /. (I y') = -y/y'

instance MyNum1 (Complex Double) Double where
  myNegate (x :+ y) = (-x) :+ (-y)
  myAbs (x :+ y) = sqrt (x^2+y^2) --Numerically less than ideal but that's not the main point here so I'm going for simplicity.
  mySignum (0 :+ 0) = 0 :+ 0
  mySignum (x :+ y) = (x/r) :+ (y/r)
    where r = myAbs (x :+ y)
  myFromInteger = (:+ 0.0) . fromInteger

instance MyFractional1 (Complex Double) Double where
  myRecip (x :+ y) = (x/rr) :+ (-y/rr)
    where rr = x^2+y^2
  myFromRational = (:+ 0.0) . fromRational

instance MyNum2 (Complex Double) (Complex Double) (Complex Double) (Complex Double) Double where
  (x :+ y) +. (x' :+ y') = (x+x') :+ (y+y')
  (x :+ y) -. (x' :+ y') = (x-x') :+ (y-y')
  (x :+ y) *. (x' :+ y') = (x*x'-y*y') :+ (x*y'+y*x')

instance MyFractional2 (Complex Double) (Complex Double) (Complex Double) (Complex Double) Double where
  (x :+ y) /. (x' :+ y') = ((x*x'+y*y')/rr) :+ ((y*x'-x*y')/rr)
    where rr = x'^2+y'^2

instance MyNum2 Double (Imaginary Double) (Complex Double) (Imaginary Double) Double where
  x +. (I y') = x :+ y'
  x -. (I y') = x :+ (-y')
  x *. (I y') = I (x*y')

instance MyFractional2 Double (Imaginary Double) (Complex Double) (Imaginary Double) Double where
  x /. (I y') = I (-x/y')

instance MyNum2 (Imaginary Double) Double (Complex Double) (Imaginary Double) Double where
  (I y) +. x' = x' :+ y
  (I y) -. x' = (-x') :+ y
  (I y) *. x' = I (x'*y)

instance MyFractional2 (Imaginary Double) Double (Complex Double) (Imaginary Double) Double where
  (I y) /. x' = I (y/x')

instance MyNum2 Double (Complex Double) (Complex Double) (Complex Double) Double where
  x +. (x' :+ y') = (x+x') :+ y'
  x -. (x' :+ y') = (x-x') :+ y'
  x *. (x' :+ y') = (x*x') :+ (x*y')

instance MyFractional2 Double (Complex Double) (Complex Double) (Complex Double) Double where
  x /. (x' :+ y') = (x*x'/rr) :+ (-x*y'/rr)
    where rr = x'^2+y'^2

instance MyNum2 (Complex Double) Double (Complex Double) (Complex Double) Double where
  (x :+ y) +. x' = (x+x') :+ y
  (x :+ y) -. x' = (x-x') :+ y
  (x :+ y) *. x' = (x*x') :+ (y*x')

instance MyFractional2 (Complex Double) Double (Complex Double) (Complex Double) Double where
  (x :+ y) /. x' = (x/x') :+ (y/x')

instance MyNum2 (Imaginary Double) (Complex Double) (Complex Double) (Complex Double) Double where
  (I y) +. (x' :+ y') = x' :+ (y+y')
  (I y) -. (x' :+ y') = (-x') :+ (y-y')
  (I y) *. (x' :+ y') = (-y*y') :+ (x'*y)

instance MyFractional2 (Imaginary Double) (Complex Double) (Complex Double) (Complex Double) Double where
  (I y) /. (x' :+ y') = (y*y'/rr) :+ (y*x'/rr)
    where rr = x'^2+y'^2

instance MyNum2 (Complex Double) (Imaginary Double) (Complex Double) (Complex Double) Double where
  (x :+ y) +. (I y') = x :+ (y+y')
  (x :+ y) -. (I y') = x :+ (y-y')
  (x :+ y) *. (I y') = (-y*y') :+ (x*y')

instance MyFractional2 (Complex Double) (Imaginary Double) (Complex Double) (Complex Double) Double where
  (x :+ y) /. (I y') = (y/y') :+ (-x/y')
QuantumWiz
  • 148
  • 9