I’d just like to note that it is in fact possible to write this in Haskell 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