{-# LANGUAGE FlexibleInstances #-} ----------------------------------------------------------------------------- -- | -- Module : BLAS.Elem.Base -- Copyright : Copyright (c) 2008, Patrick Perry -- License : BSD3 -- Maintainer : Patrick Perry -- Stability : experimental -- module BLAS.Elem.Base ( Elem(..), module BLAS.Conj, ) where import BLAS.Conj import Data.Complex ( Complex(..), magnitude ) import Foreign ( Storable ) import Foreign.Storable.Complex () -- | The base class for elements. class (Storable e, Fractional e, Conj e) => Elem e where -- | Get the magnitude of a value. norm :: e -> Double -- | Get the l1 norm of a value. norm1 :: e -> Double -- | Convert a double to an element fromReal :: Double -> e -- | Coerce an element to a double toReal :: e -> Double instance Elem Double where norm = abs norm1 = abs fromReal = id toReal = id instance Elem (Complex Double) where norm = magnitude norm1 (x :+ y) = abs x + abs y fromReal x = x :+ 0 toReal (x :+ _) = x