handa-opengl-0.1.12.1: Utility functions for OpenGL and GLUT

Copyright(c) 2015 Brian W Bush
LicenseMIT
MaintainerBrian W Bush <consult@brianwbush.info>
StabilityStable
PortabilityPortable
Safe HaskellNone
LanguageHaskell2010

Graphics.Rendering.Handa.Viewer

Contents

Description

Functions for managing perspectives and frusta.

Synopsis

Viewer Geometry

data ViewerParameters a Source #

Paramaters specifying a viewer, including the frustum of the view.

Constructors

ViewerParameters 

Fields

Instances

Functor ViewerParameters Source # 

Methods

fmap :: (a -> b) -> ViewerParameters a -> ViewerParameters b #

(<$) :: a -> ViewerParameters b -> ViewerParameters a #

Eq a => Eq (ViewerParameters a) Source # 
Data a => Data (ViewerParameters a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ViewerParameters a -> c (ViewerParameters a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ViewerParameters a) #

toConstr :: ViewerParameters a -> Constr #

dataTypeOf :: ViewerParameters a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (ViewerParameters a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ViewerParameters a)) #

gmapT :: (forall b. Data b => b -> b) -> ViewerParameters a -> ViewerParameters a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ViewerParameters a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ViewerParameters a -> r #

gmapQ :: (forall d. Data d => d -> u) -> ViewerParameters a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ViewerParameters a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ViewerParameters a -> m (ViewerParameters a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ViewerParameters a -> m (ViewerParameters a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ViewerParameters a -> m (ViewerParameters a) #

Read a => Read (ViewerParameters a) Source # 
Show a => Show (ViewerParameters a) Source # 
Generic (ViewerParameters a) Source # 

Associated Types

type Rep (ViewerParameters a) :: * -> * #

(FromJSON a, Generic a) => FromJSON (ViewerParameters a) Source # 
(Binary a, Generic a) => Binary (ViewerParameters a) Source # 
(Fractional a, Storable a) => Default (ViewerParameters a) Source # 

Methods

def :: ViewerParameters a #

type Rep (ViewerParameters a) Source # 

viewerGeometry Source #

Arguments

:: (Fractional a, Storable a) 
=> a

The width of the screen or display.

-> a

The height of the screen or display.

-> a

The distance from the eyes to the screen or display.

-> ViewerParameters a

The corresponding viewer parameters.

Construct viewer geometry from physical geometry.

displayAspectRatio Source #

Arguments

:: (AdditiveGroup a, RealFloat a, Storable a) 
=> ViewerParameters a

The viewer parameters.

-> a

The aspect ratio, namely the screen width divided by its height.

The aspect ratio of the viewer.

displayThrowRatio Source #

Arguments

:: (AdditiveGroup a, RealFloat a, Storable a) 
=> ViewerParameters a

The viewer parameters.

-> a

The throw ratio, namely the distance to the screen divided by its height.

The throw ratio of the viewer.

fieldOfView Source #

Arguments

:: (AdditiveGroup a, RealFloat a, Storable a) 
=> ViewerParameters a

The viewer parameters

-> a

The field of view, in degrees.

Compute the field of view for viewer parameters.

Typical Devices

phoneViewer :: (Fractional a, Storable a) => ViewerParameters a Source #

Viewer parameters for a typical smartphone screen.

laptopViewer :: (Fractional a, Storable a) => ViewerParameters a Source #

Viewer parameters for a typical laptop screen.

desktopViewer :: (Fractional a, Storable a) => ViewerParameters a Source #

Viewer parameters for a typical desktop monitor.

projectorViewer :: (Fractional a, Storable a) => ViewerParameters a Source #

Viewer parameters for a typical projector.

Callbacks and Rendering

reshape Source #

Arguments

:: (AdditiveGroup a, MatrixComponent a, RealFloat a, Storable a) 
=> ViewerParameters a

The viewer parameters.

-> ReshapeCallback

The reshape callback.

Construct a reshape callback from viewer parameters. This simply sets the frustum based on the viewer parameters and the size of the viewport.

loadViewer Source #

Arguments

:: (AdditiveGroup a, MatrixComponent a, RealFloat a, Storable a) 
=> Bool

Whether to use an on-axis projection.

-> ViewerParameters a

The viewer parameters.

-> DlpEye

The eye from which to view.

-> IO ()

An action for looking at the scene using the specified eye and viewer parameters.

Create an action look at the scene according to the viewer parameters.

dlpViewerDisplay Source #

Arguments

:: (AdditiveGroup a, MatrixComponent a, RealFloat a, Storable a) 
=> Bool

Whether to use on-axis projection.

-> DlpEncoding

The DLP encoding.

-> ViewerParameters a

The viewer parameters.

-> DisplayCallback

The display callback.

-> DlpDisplay

The DLP display data for using the specified encoding, viewer parameters, and display callback.

Construct a DLP display from a display callback.

dlpViewerDisplay' Source #

Arguments

:: (AdditiveGroup a, MatrixComponent a, RealFloat a, Storable a) 
=> Bool

Whether to use on-axis projection.

-> DlpEncoding

The DLP encoding.

-> IORef (ViewerParameters a)

A reference to the viewer parameters.

-> DisplayCallback

The display callback.

-> DlpDisplay

The DLP display data for using the specified encoding, viewer parameters, and display callback.

Construct a DLP display from a display callback.