{-# LANGUAGE CApiFFI #-}
module Graphics.Text.Font.Choose.Weight(weightFromOpenTypeDouble,
weightToOpenTypeDouble, weightFromOpenType, weightToOpenType) where
foreign import capi "fontconfig/fontconfig.h FcWeightFromOpenTypeDouble"
weightFromOpenTypeDouble :: Double -> Double
foreign import capi "fontconfig/fontconfig.h FcWeightToOpenTypeDouble"
weightToOpenTypeDouble :: Double -> Double
weightFromOpenType :: Int -> Int
weightFromOpenType :: Int -> Int
weightFromOpenType = Double -> Int
forall a. Enum a => a -> Int
fromEnum (Double -> Int) -> (Int -> Double) -> Int -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Double -> Double
weightFromOpenTypeDouble (Double -> Double) -> (Int -> Double) -> Int -> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Double
forall a. Enum a => Int -> a
toEnum
weightToOpenType :: Int -> Int
weightToOpenType :: Int -> Int
weightToOpenType = Double -> Int
forall a. Enum a => a -> Int
fromEnum (Double -> Int) -> (Int -> Double) -> Int -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Double -> Double
weightToOpenTypeDouble (Double -> Double) -> (Int -> Double) -> Int -> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Double
forall a. Enum a => Int -> a
toEnum