module Language.C.Analysis.TypeConversions (
arithmeticConversion,
floatConversion,
intConversion
) where
import Language.C.Analysis.SemRep
arithmeticConversion :: TypeName -> TypeName -> Maybe TypeName
arithmeticConversion :: TypeName -> TypeName -> Maybe TypeName
arithmeticConversion (TyComplex t1 :: FloatType
t1) (TyComplex t2 :: FloatType
t2) =
TypeName -> Maybe TypeName
forall a. a -> Maybe a
Just (TypeName -> Maybe TypeName) -> TypeName -> Maybe TypeName
forall a b. (a -> b) -> a -> b
$ FloatType -> TypeName
TyComplex (FloatType -> TypeName) -> FloatType -> TypeName
forall a b. (a -> b) -> a -> b
$ FloatType -> FloatType -> FloatType
floatConversion FloatType
t1 FloatType
t2
arithmeticConversion (TyComplex t1 :: FloatType
t1) (TyFloating t2 :: FloatType
t2) =
TypeName -> Maybe TypeName
forall a. a -> Maybe a
Just (TypeName -> Maybe TypeName) -> TypeName -> Maybe TypeName
forall a b. (a -> b) -> a -> b
$ FloatType -> TypeName
TyComplex (FloatType -> TypeName) -> FloatType -> TypeName
forall a b. (a -> b) -> a -> b
$ FloatType -> FloatType -> FloatType
floatConversion FloatType
t1 FloatType
t2
arithmeticConversion (TyFloating t1 :: FloatType
t1) (TyComplex t2 :: FloatType
t2) =
TypeName -> Maybe TypeName
forall a. a -> Maybe a
Just (TypeName -> Maybe TypeName) -> TypeName -> Maybe TypeName
forall a b. (a -> b) -> a -> b
$ FloatType -> TypeName
TyComplex (FloatType -> TypeName) -> FloatType -> TypeName
forall a b. (a -> b) -> a -> b
$ FloatType -> FloatType -> FloatType
floatConversion FloatType
t1 FloatType
t2
arithmeticConversion t1 :: TypeName
t1@(TyComplex _) (TyIntegral _) = TypeName -> Maybe TypeName
forall a. a -> Maybe a
Just TypeName
t1
arithmeticConversion (TyIntegral _) t2 :: TypeName
t2@(TyComplex _) = TypeName -> Maybe TypeName
forall a. a -> Maybe a
Just TypeName
t2
arithmeticConversion (TyFloating t1 :: FloatType
t1) (TyFloating t2 :: FloatType
t2) =
TypeName -> Maybe TypeName
forall a. a -> Maybe a
Just (TypeName -> Maybe TypeName) -> TypeName -> Maybe TypeName
forall a b. (a -> b) -> a -> b
$ FloatType -> TypeName
TyFloating (FloatType -> TypeName) -> FloatType -> TypeName
forall a b. (a -> b) -> a -> b
$ FloatType -> FloatType -> FloatType
floatConversion FloatType
t1 FloatType
t2
arithmeticConversion t1 :: TypeName
t1@(TyFloating _) (TyIntegral _) = TypeName -> Maybe TypeName
forall a. a -> Maybe a
Just TypeName
t1
arithmeticConversion (TyIntegral _) t2 :: TypeName
t2@(TyFloating _) = TypeName -> Maybe TypeName
forall a. a -> Maybe a
Just TypeName
t2
arithmeticConversion (TyIntegral t1 :: IntType
t1) (TyIntegral t2 :: IntType
t2) =
TypeName -> Maybe TypeName
forall a. a -> Maybe a
Just (TypeName -> Maybe TypeName) -> TypeName -> Maybe TypeName
forall a b. (a -> b) -> a -> b
$ IntType -> TypeName
TyIntegral (IntType -> TypeName) -> IntType -> TypeName
forall a b. (a -> b) -> a -> b
$ IntType -> IntType -> IntType
intConversion IntType
t1 IntType
t2
arithmeticConversion (TyEnum _) (TyEnum _) = TypeName -> Maybe TypeName
forall a. a -> Maybe a
Just (TypeName -> Maybe TypeName) -> TypeName -> Maybe TypeName
forall a b. (a -> b) -> a -> b
$ IntType -> TypeName
TyIntegral IntType
TyInt
arithmeticConversion (TyEnum _) t2 :: TypeName
t2 = TypeName -> Maybe TypeName
forall a. a -> Maybe a
Just TypeName
t2
arithmeticConversion t1 :: TypeName
t1 (TyEnum _) = TypeName -> Maybe TypeName
forall a. a -> Maybe a
Just TypeName
t1
arithmeticConversion _ _ = Maybe TypeName
forall a. Maybe a
Nothing
floatConversion :: FloatType -> FloatType -> FloatType
floatConversion :: FloatType -> FloatType -> FloatType
floatConversion = FloatType -> FloatType -> FloatType
forall a. Ord a => a -> a -> a
max
intConversion :: IntType -> IntType -> IntType
intConversion :: IntType -> IntType -> IntType
intConversion t1 :: IntType
t1 t2 :: IntType
t2 = IntType -> IntType -> IntType
forall a. Ord a => a -> a -> a
max IntType
TyInt (IntType -> IntType -> IntType
forall a. Ord a => a -> a -> a
max IntType
t1 IntType
t2)