module Graphics.Gloss.Data.Point.Arithmetic
(
Point
, (+)
, ()
, (*)
, negate
) where
import Prelude (Float)
import qualified Prelude as P
import Graphics.Gloss.Rendering (Point)
infixl 6 +,
infixl 7 *
(+) :: Point -> Point -> Point
(x1, y1) + (x2, y2) =
let
!x = x1 P.+ x2
!y = y1 P.+ y2
in (x, y)
() :: Point -> Point -> Point
(x1, y1) (x2, y2) =
let
!x = x1 P.- x2
!y = y1 P.- y2
in (x, y)
negate :: Point -> Point
negate (x, y) =
let
!x' = P.negate x
!y' = P.negate y
in (x', y')
(*) :: Float -> Point -> Point
(*) s (x, y) =
let
!x' = s P.* x
!y' = s P.* y
in (x', y')