-- | Type conversion operations module Feldspar.Core.Functions.Conversion where import qualified Prelude import Data.Tagged import Feldspar.Range import Feldspar.Prelude import Feldspar.Core.Types import Feldspar.Core.Representation import Feldspar.Core.Constructs import Feldspar.Core.Functions.Num import Feldspar.Core.Functions.Integral i2f :: (Integral a, Size a ~ Range a) => Data a -> Data Float i2f = i2n f2i :: Integral a => Data Float -> Data a f2i = function1 "f2i" fullProp (Prelude.truncate) i2n :: forall a b . (Integral a, Numeric b, Size a ~ Range a) => Data a -> Data b i2n = function1 "i2n" (unTag . prop) (fromInteger.toInteger) where prop r = rangeToSize (mapMonotonic toInteger r) unTag :: Tagged b (Size b) -> Size b unTag (Tagged sz) = sz b2i :: Integral a => Data Bool -> Data a b2i = function1 "b2i" fullProp (\b -> if b then 1 else 0) truncate :: Integral a => Data Float -> Data a truncate = f2i round :: Integral a => Data Float -> Data a round = function1 "round" fullProp (Prelude.round) ceiling :: Integral a => Data Float -> Data a ceiling = function1 "ceiling" fullProp (Prelude.ceiling) floor :: Integral a => Data Float -> Data a floor = function1 "floor" fullProp (Prelude.floor)