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.UI.Handa.Setup

Contents

Description

Functions for setting up GLUT applications.

Synopsis

Functions

data Setup a Source #

The configuration for setting up the display.

Constructors

Setup 

Fields

Instances

Functor Setup Source # 

Methods

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

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

Eq a => Eq (Setup a) Source # 

Methods

(==) :: Setup a -> Setup a -> Bool #

(/=) :: Setup a -> Setup a -> Bool #

Data a => Data (Setup a) Source # 

Methods

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

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

toConstr :: Setup a -> Constr #

dataTypeOf :: Setup a -> DataType #

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

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

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

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

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

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

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

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

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

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

Read a => Read (Setup a) Source # 
Show a => Show (Setup a) Source # 

Methods

showsPrec :: Int -> Setup a -> ShowS #

show :: Setup a -> String #

showList :: [Setup a] -> ShowS #

Generic (Setup a) Source # 

Associated Types

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

Methods

from :: Setup a -> Rep (Setup a) x #

to :: Rep (Setup a) x -> Setup a #

(Generic a, FromJSON a) => FromJSON (Setup a) Source # 
(Generic a, Binary a) => Binary (Setup a) Source # 

Methods

put :: Setup a -> Put #

get :: Get (Setup a) #

putList :: [Setup a] -> Put #

Default (Setup a) Source # 

Methods

def :: Setup a #

type Rep (Setup a) Source # 

data Stereo Source #

The type of stereo.

Constructors

DLP

Frame-sequential DLP 3D ReadySync stereo.

QuadBuffer

Quad buffer stereo.

Cardboard

Google Cardboard stereo.

Mono

No stereo.

Instances

Bounded Stereo Source # 
Enum Stereo Source # 
Eq Stereo Source # 

Methods

(==) :: Stereo -> Stereo -> Bool #

(/=) :: Stereo -> Stereo -> Bool #

Data Stereo Source # 

Methods

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

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

toConstr :: Stereo -> Constr #

dataTypeOf :: Stereo -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Stereo Source # 
Read Stereo Source # 
Show Stereo Source # 
Generic Stereo Source # 

Associated Types

type Rep Stereo :: * -> * #

Methods

from :: Stereo -> Rep Stereo x #

to :: Rep Stereo x -> Stereo #

FromJSON Stereo Source # 
Binary Stereo Source # 

Methods

put :: Stereo -> Put #

get :: Get Stereo #

putList :: [Stereo] -> Put #

Default Stereo Source # 

Methods

def :: Stereo #

type Rep Stereo Source # 
type Rep Stereo = D1 (MetaData "Stereo" "Graphics.UI.Handa.Setup" "handa-opengl-0.1.12.1-1kPa5QvhFvW7EPEJhuE1zR" False) ((:+:) ((:+:) (C1 (MetaCons "DLP" PrefixI False) U1) (C1 (MetaCons "QuadBuffer" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Cardboard" PrefixI False) U1) (C1 (MetaCons "Mono" PrefixI False) U1)))

data Viewer Source #

The viewer information.

Constructors

Phone

A typical phone.

Laptop

A typical laptop.

Desktop

A typical desktop display.

Projector

A typical projector.

Instances

Bounded Viewer Source # 
Enum Viewer Source # 
Eq Viewer Source # 

Methods

(==) :: Viewer -> Viewer -> Bool #

(/=) :: Viewer -> Viewer -> Bool #

Data Viewer Source # 

Methods

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

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

toConstr :: Viewer -> Constr #

dataTypeOf :: Viewer -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Viewer Source # 
Read Viewer Source # 
Show Viewer Source # 
Generic Viewer Source # 

Associated Types

type Rep Viewer :: * -> * #

Methods

from :: Viewer -> Rep Viewer x #

to :: Rep Viewer x -> Viewer #

FromJSON Viewer Source # 
Binary Viewer Source # 

Methods

put :: Viewer -> Put #

get :: Get Viewer #

putList :: [Viewer] -> Put #

Default Viewer Source # 

Methods

def :: Viewer #

type Rep Viewer Source # 
type Rep Viewer = D1 (MetaData "Viewer" "Graphics.UI.Handa.Setup" "handa-opengl-0.1.12.1-1kPa5QvhFvW7EPEJhuE1zR" False) ((:+:) ((:+:) (C1 (MetaCons "Phone" PrefixI False) U1) (C1 (MetaCons "Laptop" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Desktop" PrefixI False) U1) (C1 (MetaCons "Projector" PrefixI False) U1)))

setup Source #

Arguments

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

The window title.

-> String

The program name.

-> [String]

The X11 arguments.

-> Setup a

The setup configuration.

-> IO (DlpEncoding, ViewerParameters a, [String])

An action returing the DLP encoding requested, the viewer parameters, and the uninterpretted arguments.

Set up a window with basic callbacks. This creates a double-buffered window with a depth buffer, a transparency blending function, a generic reshaping callback, and a redisplaying idle function. See handleArguments for information on how command-line arguments are interpretted.

handleArguments Source #

Arguments

:: [String]

The arguments.

-> (Setup a, [String])

The setup configuration and the remaining, uninterpretted, arguments.

Act on command-line arguments.

  • "--dlp" puts the application in frame-sequential DLP (3D ReadySync) stereo mode.
  • "--quadbuffer" puts the application in quad-buffer stereo mode.
  • "--cardboard" puts the application in side-by-side (Google Cardboard) stereo mode.
  • "--switchEyes" swaps the views of the left and right eyes.
  • "--phone" sets the frustum for a typical smartphone.
  • "--laptop" sets the frustum for a typical laptop.
  • "--desktop" sets the frustum for a typical desktop monitor.
  • "--projection" sets the frustum for a typical projector.
  • "--fullscreen" puts the application in full screen mode.

idle :: IdleCallback Source #

An idle callback that simply posts a request for redisplay.