Function for complex and real

If I write this function:

square :: Floating a => a -> a
square x = x**2

It works with both reals and complex

square 3 -- 9.0
square (3:+2) -- 5.000000000000001 :+ 12.0

If I write this:

genericAbs :: Num a => a -> a
genericAbs x 
    | r :+ i = abs r :+ abs i
    | otherwise = abs x

It doesn’t compile. Why?
How can I write that function?

It seems you don’t quite understand how guard work (the | ... = ... notation). I’d recommend consulting learning resources, e.g. this section of LYAH.

Also note that abs itself already works for reals and complex numbers:

ghci> abs 3
3
ghci> abs (3:+2)
3.605551275463989 :+ 0.0

That second result might not be what you expected. If you really want to independently take the absolute value of both components, then you’re not really looking for a complex number but instead a two dimensional vector. The linear package provides those:

$ cabal repl -b linear
ghci> import Linear
ghci> abs (V2 (-3) (-2))
V2 3 2
1 Like

Ok, I have to understand guards.


Even without guards it doesn’t work:

genericAbs :: Num a => a -> a
genericAbs (r :+ i) = abs r :+ abs i
genericAbs x = abs x

Only for Complex numbers this works:

absComplex :: Num a => Complex a -> Complex a
absComplex = fmap abs

absComplex ((-2):+(-4)) -- 2 :+ 4

However I would like to have a function for both complex and reals.
Edit: If the input is complex I want a complex, if it is real I want a real

1 Like

I think the only other option left is to define your own type class:

class GenericAbs a where
  genericAbs :: a -> a

And then write instances for all the types you want to use it on:

instance GenericAbs Double where
  genericAbs = abs

instance GenericAbs a => GenericAbs (Complex a) where
  genericAbs = fmap genericAbs

Note that I’m using fmap genericAbs instead of fmap abs as you suggested, because there might be nesting, e.g.: Complex (Complex Double).

1 Like

Is your intentaion something like this?

# pseudo-python
def genericAbs(x):
  if isinstance(x, complex):
    ...
  elif isinstance(x, float):
    ...

If that the case, you can’t do that in Haskell (nor many other languages). If you write something like

genericAbs :: Num a => a -> a
genericAbs = ...

you are saying:

I am writing one implementation for all numeric types

I think what you want to achive is

I am writing one implementation for each numeric types

If that’s the case, you have to follow @jaror answer

3 Likes

So if I have a type which can have both complex and real types but has different behaviors depending on the type it has:

data G a = G a a a

Should I define two different types, one complex and one real?

data RealG a = RealG a a a
data ComplexG a = ComplexG a a a

It depends on what you actually want to do. Finding a good representation of your types is difficult. If you only have Reals and Complex then you could define a sum of these and then work on top of that

data Field = Reals | Complex
data G a = G Field a a a

someFunction :: G a -> a
someFunction G Reals x y z = x
someFunction G Complex x y z = y

Whether or not this is a good representation depends on what you want to achive

1 Like

I’d just like to note that it is in fact possible to write this in Haskell :slight_smile: though likely not what OP was looking for; you need to branch on the type at runtime, which can be done with Typeable. However, we need to make sure the function works for all (Num a => Complex a), not just for e.g. Complex Int
So this works, but it isn’t pretty:

{-# LANGUAGE ScopedTypeVariables, GADTs, QuantifiedConstraints, UndecidableInstances #-}

import Data.Functor.Identity
import Data.Complex
import Data.Typeable

-- Not what OP is looking for!
genericAbs :: forall a. Typeable a => a -> a
genericAbs x
  | Just Refl <- eqT @a @(Some Complex)
  , Some (r :+ i) <- x
  = Some (abs r :+ abs i)

  | Just Refl <- eqT @a @(Some Identity)
  , Some x' <- x
  = Some (abs x')

  | otherwise
  = undefined

data Some f where
  Some :: (Show a, Num a) => f a -> Some f
deriving instance (forall a. Show a => Show (f a)) => Show (Some f)

Then the function can be invoked like

> genericAbs (Some ((-5) :+ (-1)))
Some (5 :+ 1)
> genericAbs (Some (Identity (-2)))
Some (Identity 2)

Again, if we decided we only cared about Complex Double (which is likely what the python version does), then it looks a bit better…

-- like the python
genericAbs' :: forall a. Typeable a => a -> a
genericAbs' x
  | Just Refl <- eqT @a @(Complex Double)
  , r :+ i <- x
  = abs r :+ abs i

  | Just Refl <- eqT @a @Double
  = abs x

  | otherwise
  = undefined

It is still a mouthful, so we could instead use TypeRepOf (CLC proposal link) to get something closer to the python version:

{-# LANGUAGE PatternSynonyms, ViewPatterns, GADTs, UnicodeSyntax #-}
import Data.Complex
import Data.Kind
import Type.Reflection

genericAbs :: ∀ a. Typeable a => a -> a
genericAbs x = case typeRep @a of

  TypeRepOf
    @(Complex Double)
    | r :+ i <- x
    -> abs r :+ abs i

  TypeRepOf
    @Double
    -> abs x


-- https://github.com/haskell/core-libraries-committee/issues/197
pattern TypeRepOf :: forall {a :: Type} (b :: Type). Typeable b => (b ~ a) => TypeRep a
pattern TypeRepOf <- ( eqTypeRep @_ @_ @b @a ( typeRep @b ) -> Just HRefl )
  where TypeRepOf = typeRep @a

Also, as @jaror said, this is not a correct implementation of abs for Complex numberse if i’m not mistaken.

We could use the last two as

ghci> genericAbs ((-5) :+ 2 :: Complex Double)
5.0 :+ 2.0
ghci> genericAbs (-5 :: Double)
5.0
3 Likes