{-| Module : FPPrac.Graphics.NormalizeNumber Description : Used in the FPPrac module to normalize any instance of a Num type to float. It is used for the "EventLoop" module. Copyright : (c) Sebastiaan la Fleur, 2014 License : BSD3 Maintainer : sebastiaan.la.fleur@gmail.com Stability : experimental Portability : All In the "EventLoop" module, 'Float's are used to express positions and other characteristics. As that package is also used in the functional programming lab at the University of Twente, compatibility with the "FPPrac" module is needed. That module expresses a 'Number' type which abstracts from 'Int' and 'Double' types. This module is used to normalize both the 'Number' type and the original 'Num' class instances defined in Haskell. -} module FPPrac.Graphics.NormalizeNumber where import GHC.Float import FPPrac.Prelude.Number {-| Class to express that the instance 'a' is able to be normalized to a 'Float'. -} class (Num a) => NormalizeNumber a where -- | The function that can be used to normalize 'a' to a 'Float'. normalize :: a -> Float {-# MINIMAL normalize #-} -- | How to normalize a 'Float' instance NormalizeNumber Float where normalize f = f -- | How to normalize an 'Int' instance NormalizeNumber Int where normalize = fromIntegral -- | How to normalize an 'Integer' instance NormalizeNumber Integer where normalize = fromIntegral -- | How to normalize a 'Double' instance NormalizeNumber Double where normalize = double2Float -- | How to normalize a 'Number'. This is definied in "FPPrac.Prelude.Number" in the twentefp-number package instance NormalizeNumber Number where normalize (I i) = fromIntegral i normalize (F d) = double2Float d