module Graphics.Gloss.Data.ViewPort
( ViewPort(..)
, viewPortInit
, applyViewPortToPicture
, invertViewPort )
where
import Graphics.Gloss.Data.Picture
import qualified Graphics.Gloss.Data.Point.Arithmetic as Pt
data ViewPort
= ViewPort {
viewPortTranslate :: !(Float, Float)
, viewPortRotate :: !Float
, viewPortScale :: !Float
}
viewPortInit :: ViewPort
viewPortInit
= ViewPort
{ viewPortTranslate = (0, 0)
, viewPortRotate = 0
, viewPortScale = 1
}
applyViewPortToPicture :: ViewPort -> Picture -> Picture
applyViewPortToPicture
ViewPort { viewPortScale = vscale
, viewPortTranslate = (transX, transY)
, viewPortRotate = vrotate }
= Scale vscale vscale . Rotate vrotate . Translate transX transY
invertViewPort :: ViewPort -> Point -> Point
invertViewPort
ViewPort { viewPortScale = vscale
, viewPortTranslate = vtrans
, viewPortRotate = vrotate }
pos
= rotateV (degToRad vrotate) (mulSV (1 / vscale) pos) Pt.- vtrans
degToRad :: Float -> Float
degToRad d = d * pi / 180
{-# INLINE degToRad #-}
mulSV :: Float -> Vector -> Vector
mulSV s (x, y)
= (s * x, s * y)
{-# INLINE mulSV #-}
rotateV :: Float -> Vector -> Vector
rotateV r (x, y)
= ( x * cos r - y * sin r
, x * sin r + y * cos r)
{-# INLINE rotateV #-}