Logo Questions Linux Laravel Mysql Ubuntu Git Menu
 

Preventing an argument to be a complex number

Tags:

haskell

I have a function like this:

hypergeom ::
     forall a. (Eq a, Fractional a)
  => Int  -- truncation weight
  -> a    -- alpha parameter (usually 2)
  -> [a]  -- "upper" parameters
  -> [a]  -- "lower" parameters
  -> [a]  -- variables (the eigen values)
  -> IO a
hypergeom m alpha a b x = do
  ......

I choosed the constraint Fractional a because I want the possibility to take a of type Float, Double, Rational or Complex (for example Complex Double or Complex Rational).

But now, I would like to allow Complex except for the parameter alpha. But if a is the type Complex b then alpha must be of type b. For example:

hypergeom ::
  => Int               -- truncation weight
  -> Double            -- alpha parameter (usually 2)
  -> [Complex Double]  -- "upper" parameters
  -> [Complex Double]  -- "lower" parameters
  -> [Complex Double]  -- variables (the eigen values)
  -> IO (Complex Double)

I hope I'm clear. How could I do that in a neat way ?

like image 699
StΓ©phane Laurent Avatar asked Sep 23 '19 05:09

StΓ©phane Laurent


People also ask

How do you write an argument for a complex number?

The argument ΞΈ of the complex number Z = a + ib is equal to the inverse tan of the imaginary part (b) divided by the real part(a) of the complex number. The argument of a complex number is ΞΈ = Tan-1(b/a).

What does arg mean in complex numbers?

In mathematics (particularly in complex analysis), the argument of a complex number z, denoted arg(z), is the angle between the positive real axis and the line joining the origin and z, represented as a point in the complex plane, shown as. in Figure 1.

How do you find the argument of a complex number in different quadrants?

The argument of a complex number 𝑧 = π‘Ž + 𝑏 𝑖 can be obtained using the inverse tangent function in each quadrant as follows: If 𝑧 lies in the first or the fourth quadrant, a r g a r c t a n ( 𝑧 ) = ο€½ 𝑏 π‘Ž  . If 𝑧 lies in the second quadrant, a r g a r c t a n ( 𝑧 ) = ο€½ 𝑏 π‘Ž  + πœ‹ .


2 Answers

Every Haskeller should know the vector-space library, and this is one application where it can be used.

hypergeom ::
     βˆ€ a. (VectorSpace a, Eq a, RealFrac (Scalar a))
  => Int       -- truncation weight
  -> Scalar a  -- alpha parameter (usually 2)
  -> [a]       -- "upper" parameters
  -> [a]       -- "lower" parameters
  -> [a]       -- variables (the eigen values)
  -> IO a
hypergeom m Ξ± a b x = do
  ......

This uses, in the complex case,

instance (RealFloat v, VectorSpace v) => VectorSpace (Complex v) where
  type Scalar (Complex v) = Scalar v
  s*^(u :+ v) = s*^u :+ s*^v

However, caveat: I personally am not a fan of that particular instance. Because complex numbers are a division algebra, it is quite often useful to consider them as a scalar type, i.e.

instance RealFloat a => VectorSpace (Complex a) where
  type Scalar (Complex a) = Complex a
  (*^) = (*)

The reason this is preferrable is that free vector spaces over the complex number (e.g. tuples) will then actually be complex vector spaces, not real vector spaces as they are as of version 0.16 of the library.

If the instance were defined as I would do it, then it would not work. This was actually discussed, maybe it'll change in the future.

like image 183
leftaroundabout Avatar answered Nov 16 '22 04:11

leftaroundabout


Code

If I am understanding correctly, you could use a type class with an associated type family for this:

{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE DefaultSignatures #-}

import           Data.Complex
import           Data.Ratio

class BaseFrac a where
  type family BaseFracType a
  type BaseFracType a = a -- Default type family instance (unless overridden)

  inject :: BaseFracType a -> a

  default inject :: BaseFracType a ~ a => BaseFracType a -> a
  inject = id

instance Integral a => BaseFrac (Ratio a)
instance BaseFrac Float
instance BaseFrac Double

-- etc...

instance Num a => BaseFrac (Complex a) where
  type BaseFracType (Complex a) = a

  inject x = x :+ 0


hypergeom ::
     forall a. (Eq a, Fractional a, BaseFrac a)
  => Int  -- truncation weight
  -> BaseFracType a    -- alpha parameter (usually 2)
  -> [a]  -- "upper" parameters
  -> [a]  -- "lower" parameters
  -> [a]  -- variables (the eigen values)
  -> IO a
hypergeom m alpha a b x = ...

It is possible that you will need to add additional methods to the type class, but I think inject should provide some important utility.

Explanation

Writing this explanation, I realized that I probably compressed several ideas into a small area without giving the background information I should have given. Hopefully this helps and if you have any questions or are confused, you should let me know!

There are two main interacting ideas here. The first is that of a type class. I will assume some basic background on type classes (there are many resources going over the basics on that. If you would like, I can find some to link here).

The other is the idea of a type family. A type family is essentially a sort of function from types to types. Sometimes they are inside type classes (as they are here), but they don't have to be. Also, sometimes they are "open" and sometimes they are "closed" (if they are inside a type class, they are essentially open)

Closed type families

I think it is instructive to look at a closed type family which is not in a type class first. Consider this:

type family Example :: * -> * where
  Example Int = Bool
  Example a   = a

This is very much like a regular Haskell function definition, except it happens to operate on types instead of values. If its input is the type Int it gives back the type Bool. Otherwise, it gives back the same type as the type it got as an argument.

We can see this using the :kind! command in GHCi:

Ξ» > :kind! Example Int
Example Int :: *
= Bool
Ξ» >
Ξ» > :kind! Example Char
Example Char :: *
= Char

You can also think of type synonyms as a very restricted form of type family.

That type family is called "closed" because you cannot add more "equations" to its definition (just like a "regular" Haskell function).

Open type families

But, you can also have "open" type families where you can add additional equations later on. For example:

type family OpenExample :: * -> *


type instance OpenExample [a] = a
type instance OpenExample Text = Char
type instance OpenExample IntSet = Int
-- ^ These just give you the "element type" inside some containers

We can later add on new equations with type instance (for instance, here if we add a new container type).

Type families associated with type classes

This brings us to the sort of type family we have here: a type class with an associated type family. This is much like an open type family, but the input is constrained by the type class. Also, each equation is inside an instance of the type class.

I have provided a default type instance (the 2nd line of the class BaseFrac) which will automatically be used if none is provided. To write out the Double instance explicitly (without using this default) it looks like:

instance BaseFrac Double where
  type BaseFracType Double = Double

Note how similar this is to the type instance syntax.

I have also provided a default implementation for the inject method. This default can only be used if BaseFracType a is the same as a (this is what the constraint BaseFracType a ~ a means in the default signature).

This constraint does hold for any instance that uses the default BaseFracType definition (since it is just type BaseFracType a = a), which is why those "empty" instance definitions just automatically work.

So, for the instances given so far, BaseFracType Double is the same as Double (from the (default) type family definition used in the Double instance of the BaseFrac class) and BaseFracType (Complex a) is the same as a (from the type family instance definition given in the Complex a instance of the BaseFrac class).

What inject is for

That kind of explains why the types work out, but the next questions are how do we actually use it and why does inject matter? Luckily, the answers to those two questions are linked.

inject essentially provides you a way to put a "basic" ("1-dimensional") fractional value into whatever type that has an instance of the BaseFrac class.

For most types, this is just the identity function (since Double is already a "basic" fractional value, etc). For Complex a, this is different. It just constructs a complex number with a zero in its imaginary component and its argument as its real component. In that case, it is a function of type inject :: Num a => a -> Complex a.

Here is a simple example of inject in action based on the function you gave, with its full generality (this function works with any BaseFrac inputs):

hypergeom :: forall a. (Eq a, Fractional a, BaseFrac a)
  => Int
  -> BaseFracType a
  -> [a]
  -> [a]
  -> [a]
  -> IO a
hypergeom m alpha a b x = return (inject alpha * head a)

If the type variable a is Rational, then:

  • alpha has type Rational (since BaseFracType Rational is the same as Rational)
  • inject alpha also has type Rational
  • The value of inject alpha is just alpha

If the type variable a is Complex Double, then:

  • alpha has type Double (since BaseFracType (Complex Double) is the same as Double)
  • inject alpha has the type Complex Double
  • The value of inject alpha is alpha :+ 0

You can also use the GHCi :kind! command here:

Ξ» > :kind! BaseFracType (Complex Double)
BaseFracType (Complex Double) :: *
= Double

If there's anything that's confusing, you can let me know and I should be able to clarify it.

Additional material

There is some more information on type families here. Probably the most relevant sections there would be the section on type synonym instances (which are the type families we talked about that were not associated with a type class), the subsection on closed type families and the subsection on associated type families.

Note that page also talks about data families, which are not particularly relevant here (data families are kind of like "open" GADTs).

like image 27
David Young Avatar answered Nov 16 '22 04:11

David Young