是否可以在Haskell中定义一个纯虚类型?

Is it possible to define a purely imaginary type in Haskell?

我将在这里以 C++ 为例来说明我的意图。对于复数算术,它有复数和虚数类型:

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

这些例如属性 将两个虚数类型的数字相乘将得到双精度类型。这与使用实部为 0.0 但不完全相同的复数几乎但不完全相同。虚数类型不会显式存储实数部分,这会自动消除不需要的计算和存储 0.0。

此外,它还可以防止一些带符号零的问题。例如。如果 a 和 b 为负,则计算 (0.0+i*a)*(0.0+i*b) 的结果为 (-a*b-i*0.0),否则为 (-a*b+i*0.0)。如果将结果馈送到具有分支切割的函数中,这可能会令人惊讶。虚数类型避免了这种不需要的零取反。

我的问题是你能否在 Haskell 中定义一个类似的虚类型(除了复杂类型)以及操作 (+)(-)(*) , 和 (/) 这样它们的行为就像在 C++ 中一样?似乎至少根据 NumFractional 类 的当前定义,这是不可能的,因为 (+)(-)(*)(/)a -> a -> a 作为类型签名,例如因此,将两个虚数相乘不能有不同的类型。但是,是否可以对这些 类 进行不同的定义,以便实现我所追求的目标?

我问这个并不是出于实际目的。我只是想更好地了解 Haskell 的类型系统的功能。

是的,你当然可以定义这样的类型。您只是无法使用 Num 界面进行所有操作;但是您可以自由地使用其他类型定义您想要的任何其他函数,如果需要,甚至可以使它们成为中缀运算符。

下面是一个类型示例,它在类型级别跟踪它是虚数还是实数,并支持使用替代名称的加法和乘法(减法和除法不需要此处未显示的任何新想法):

{-# 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

如果你因为某些原因必须把名字精确地写成+等(我不推荐这样做,会很痛苦),你可以看看another answer of mine on controlling namespacing

Daniel Wagner 给出了使用类型族的答案。答案接近我所追求的,但它仍然有点缺乏,因为它没有,例如允许添加实数和虚数。然而,他提到 Haskell 也有 multi-parameter 类 并且这些可以用来获得我想要的解决方案。因此,在阅读 multi-parameter 类 和功能依赖项之后,我想出了一个解决方案。

我不得不将 NumFractional 类 分成两部分,一部分具有带一个参数的函数,另一部分具有两个参数。对于虚数,函数 fromIntegerfromRational 必须保留 undefined(0 除外)。解决方案变得有些冗长,但我认为没有简单的解决方法。为了简单起见,我只为 Double 作为基础浮点类型制定了解决方案,尽管更通用的类型可能更好。

此解决方案可能并不完美,欢迎提出改进建议。

{-# 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')