{-# LANGUAGE DerivingVia #-}
module Language.Fortran.Repr.Value.Scalar.Complex where
import Language.Fortran.Repr.Value.Scalar.Common
import Language.Fortran.Repr.Type.Scalar.Real
import Language.Fortran.Repr.Value.Scalar.Real
import GHC.Float ( float2Double )
import GHC.Generics ( Generic )
import Data.Data ( Data )
import Data.Binary ( Binary )
import Text.PrettyPrint.GenericPretty ( Out )
data FComplex
= FComplex8 Float Float
| FComplex16 Double Double
deriving stock (Int -> FComplex -> ShowS
[FComplex] -> ShowS
FComplex -> String
(Int -> FComplex -> ShowS)
-> (FComplex -> String) -> ([FComplex] -> ShowS) -> Show FComplex
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FComplex -> ShowS
showsPrec :: Int -> FComplex -> ShowS
$cshow :: FComplex -> String
show :: FComplex -> String
$cshowList :: [FComplex] -> ShowS
showList :: [FComplex] -> ShowS
Show, (forall x. FComplex -> Rep FComplex x)
-> (forall x. Rep FComplex x -> FComplex) -> Generic FComplex
forall x. Rep FComplex x -> FComplex
forall x. FComplex -> Rep FComplex x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. FComplex -> Rep FComplex x
from :: forall x. FComplex -> Rep FComplex x
$cto :: forall x. Rep FComplex x -> FComplex
to :: forall x. Rep FComplex x -> FComplex
Generic, Typeable FComplex
Typeable FComplex =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FComplex -> c FComplex)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FComplex)
-> (FComplex -> Constr)
-> (FComplex -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FComplex))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FComplex))
-> ((forall b. Data b => b -> b) -> FComplex -> FComplex)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FComplex -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FComplex -> r)
-> (forall u. (forall d. Data d => d -> u) -> FComplex -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> FComplex -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> FComplex -> m FComplex)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FComplex -> m FComplex)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FComplex -> m FComplex)
-> Data FComplex
FComplex -> Constr
FComplex -> DataType
(forall b. Data b => b -> b) -> FComplex -> FComplex
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> FComplex -> u
forall u. (forall d. Data d => d -> u) -> FComplex -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FComplex -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FComplex -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> FComplex -> m FComplex
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FComplex -> m FComplex
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FComplex
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FComplex -> c FComplex
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FComplex)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FComplex)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FComplex -> c FComplex
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FComplex -> c FComplex
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FComplex
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FComplex
$ctoConstr :: FComplex -> Constr
toConstr :: FComplex -> Constr
$cdataTypeOf :: FComplex -> DataType
dataTypeOf :: FComplex -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FComplex)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FComplex)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FComplex)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FComplex)
$cgmapT :: (forall b. Data b => b -> b) -> FComplex -> FComplex
gmapT :: (forall b. Data b => b -> b) -> FComplex -> FComplex
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FComplex -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FComplex -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FComplex -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FComplex -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> FComplex -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> FComplex -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> FComplex -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> FComplex -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> FComplex -> m FComplex
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> FComplex -> m FComplex
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FComplex -> m FComplex
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FComplex -> m FComplex
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FComplex -> m FComplex
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FComplex -> m FComplex
Data)
deriving anyclass (Get FComplex
[FComplex] -> Put
FComplex -> Put
(FComplex -> Put)
-> Get FComplex -> ([FComplex] -> Put) -> Binary FComplex
forall t. (t -> Put) -> Get t -> ([t] -> Put) -> Binary t
$cput :: FComplex -> Put
put :: FComplex -> Put
$cget :: Get FComplex
get :: Get FComplex
$cputList :: [FComplex] -> Put
putList :: [FComplex] -> Put
Binary, Int -> FComplex -> Doc
[FComplex] -> Doc
FComplex -> Doc
(Int -> FComplex -> Doc)
-> (FComplex -> Doc) -> ([FComplex] -> Doc) -> Out FComplex
forall a. (Int -> a -> Doc) -> (a -> Doc) -> ([a] -> Doc) -> Out a
$cdocPrec :: Int -> FComplex -> Doc
docPrec :: Int -> FComplex -> Doc
$cdoc :: FComplex -> Doc
doc :: FComplex -> Doc
$cdocList :: [FComplex] -> Doc
docList :: [FComplex] -> Doc
Out)
instance FKinded FComplex where
type FKindedT FComplex = FTReal
type FKindedC FComplex a = RealFloat a
fKind :: FComplex -> FKindedT FComplex
fKind = \case
FComplex8{} -> FTReal
FKindedT FComplex
FTReal4
FComplex16{} -> FTReal
FKindedT FComplex
FTReal8
instance Eq FComplex where == :: FComplex -> FComplex -> Bool
(==) = (forall a. FKindedC FComplex a => a -> a -> Bool)
-> (Bool -> Bool -> Bool) -> FComplex -> FComplex -> Bool
forall b r.
(forall a. FKindedC FComplex a => a -> a -> b)
-> (b -> b -> r) -> FComplex -> FComplex -> r
fComplexBOp a -> a -> Bool
forall a. Eq a => a -> a -> Bool
forall a. FKindedC FComplex a => a -> a -> Bool
(==) Bool -> Bool -> Bool
(&&)
fComplexFromReal :: FReal -> FComplex
fComplexFromReal :: FReal -> FComplex
fComplexFromReal = \case FReal4 Float
x -> Float -> Float -> FComplex
FComplex8 Float
x Float
0.0
FReal8 Double
x -> Double -> Double -> FComplex
FComplex16 Double
x Double
0.0
fComplexBOp'
:: (Float -> Float -> a)
-> (a -> a -> r)
-> (Double -> Double -> b)
-> (b -> b -> r)
-> FComplex -> FComplex -> r
fComplexBOp' :: forall a r b.
(Float -> Float -> a)
-> (a -> a -> r)
-> (Double -> Double -> b)
-> (b -> b -> r)
-> FComplex
-> FComplex
-> r
fComplexBOp' Float -> Float -> a
k8f a -> a -> r
k8g Double -> Double -> b
k16f b -> b -> r
k16g FComplex
l FComplex
r =
case (FComplex
l, FComplex
r) of
(FComplex8 Float
lr Float
li, FComplex8 Float
rr Float
ri) -> a -> a -> r
k8g (Float -> Float -> a
k8f Float
lr Float
rr) (Float -> Float -> a
k8f Float
li Float
ri)
(FComplex16 Double
lr Double
li, FComplex16 Double
rr Double
ri) -> b -> b -> r
k16g (Double -> Double -> b
k16f Double
lr Double
rr) (Double -> Double -> b
k16f Double
li Double
ri)
(FComplex8 Float
lr Float
li, FComplex16 Double
rr Double
ri) ->
let lr' :: Double
lr' = Float -> Double
float2Double Float
lr
li' :: Double
li' = Float -> Double
float2Double Float
li
in b -> b -> r
k16g (Double -> Double -> b
k16f Double
lr' Double
rr) (Double -> Double -> b
k16f Double
li' Double
ri)
(FComplex16 Double
lr Double
li, FComplex8 Float
rr Float
ri) ->
let rr' :: Double
rr' = Float -> Double
float2Double Float
rr
ri' :: Double
ri' = Float -> Double
float2Double Float
ri
in b -> b -> r
k16g (Double -> Double -> b
k16f Double
lr Double
rr') (Double -> Double -> b
k16f Double
li Double
ri')
fComplexBOpInplace'
:: (Float -> Float -> Float)
-> (Double -> Double -> Double)
-> FComplex -> FComplex -> FComplex
fComplexBOpInplace' :: (Float -> Float -> Float)
-> (Double -> Double -> Double) -> FComplex -> FComplex -> FComplex
fComplexBOpInplace' Float -> Float -> Float
k8f Double -> Double -> Double
k16f = (Float -> Float -> Float)
-> (Float -> Float -> FComplex)
-> (Double -> Double -> Double)
-> (Double -> Double -> FComplex)
-> FComplex
-> FComplex
-> FComplex
forall a r b.
(Float -> Float -> a)
-> (a -> a -> r)
-> (Double -> Double -> b)
-> (b -> b -> r)
-> FComplex
-> FComplex
-> r
fComplexBOp' Float -> Float -> Float
k8f Float -> Float -> FComplex
FComplex8 Double -> Double -> Double
k16f Double -> Double -> FComplex
FComplex16
fComplexBOp
:: (forall a. FKindedC FComplex a => a -> a -> b)
-> (b -> b -> r)
-> FComplex -> FComplex -> r
fComplexBOp :: forall b r.
(forall a. FKindedC FComplex a => a -> a -> b)
-> (b -> b -> r) -> FComplex -> FComplex -> r
fComplexBOp forall a. FKindedC FComplex a => a -> a -> b
f b -> b -> r
g = (Float -> Float -> b)
-> (b -> b -> r)
-> (Double -> Double -> b)
-> (b -> b -> r)
-> FComplex
-> FComplex
-> r
forall a r b.
(Float -> Float -> a)
-> (a -> a -> r)
-> (Double -> Double -> b)
-> (b -> b -> r)
-> FComplex
-> FComplex
-> r
fComplexBOp' Float -> Float -> b
forall a. FKindedC FComplex a => a -> a -> b
f b -> b -> r
g Double -> Double -> b
forall a. FKindedC FComplex a => a -> a -> b
f b -> b -> r
g
fComplexBOpInplace
:: (forall a. FKindedC FComplex a => a -> a -> a)
-> FComplex -> FComplex -> FComplex
fComplexBOpInplace :: (forall a. FKindedC FComplex a => a -> a -> a)
-> FComplex -> FComplex -> FComplex
fComplexBOpInplace forall a. FKindedC FComplex a => a -> a -> a
f = (Float -> Float -> Float)
-> (Double -> Double -> Double) -> FComplex -> FComplex -> FComplex
fComplexBOpInplace' Float -> Float -> Float
forall a. FKindedC FComplex a => a -> a -> a
f Double -> Double -> Double
forall a. FKindedC FComplex a => a -> a -> a
f