shady-graphics-0.5.0: Functional GPU programming - DSEL & compiler

Stabilityexperimental
Maintainerconal@conal.net

Shady.Lighting

Description

Lighting/shading. Adapted from Vertigo.

Synopsis

Documentation

data LightInfo Source

Info about how one light affects a given point. The surface lighter decides what to do with the light info. Attenuation and relation of light position (if finitely distant) to surface position are already accounted for. liDir is the direction to the light (normalized).

Constructors

LI 

Fields

liColor :: Color
 
liDir :: Dir3E
 

type Light = R3E -> LightInfoSource

A light is something that provides light info to every point in space (though to some points it provides blackness), independent of obstructions. Should probably also take an atmosphere argument.

data View Source

Viewing environment: ambient, eye, lights

Constructors

View 

data SurfInfo Source

Info about a surface at a point: position, normal, color

Constructors

SurfInfo 

type Lighter a = View -> SurfInfo -> aSource

View-dependent lighter

type LLighter a = LightInfo -> Lighter aSource

Light- and view-dependent lighter

ambient :: Lighter ColorSource

Ambient color

eye :: Lighter R3ESource

Eye point

surfP :: Lighter R3ESource

Surface point

surfN :: Lighter Dir3ESource

Surface normal

intrinsic :: Lighter ColorSource

Surface Color

colorL :: LLighter ColorSource

Light color

dirL :: LLighter R3ESource

Direction to light

illuminance :: (AdditiveGroup a, IfB BoolE a) => LLighter a -> Lighter aSource

Combine contributions from multiple lights. Patterned after Renderman's illuminance construct.

diffuse :: Lighter ColorSource

Pure diffuse

ambDiff :: (Color, Color) -> Lighter ColorSource

Weighted combination of ambient and diffuse

eyeDir :: Lighter Dir3ESource

The Stanford rtsl version, with ambient and weights:

surface float4 lightmodel_diffuse (float4 ka, float4 kd) { perlight float diffuse = dot(N,L); perlight float4 fr = kd * select(diffuse > 0, diffuse, 0); return ka * Ca + integrate(fr * Cl); }

Direction from surface point to eye

eyeLight :: LLighter Dir3ESource

Eye/light vector average (CGPP p 731)

reflection :: LLighter Dir3ESource

Reflection vector (CGPP p 730)

specularG :: LLighter FloatE -> FloatE -> Lighter ColorSource

Pure specular. Ignores intrinsic surface color. There are different ways to compute the power base.

specularNH :: FloatE -> Lighter ColorSource

Or the N.H model:

type BasicSh = (Color, Color, Color, FloatE) -> Lighter ColorSource

surface floatv lightmodel_specular (floatv s, floatv e, float sh) { perlight float diffuse = dot(N,DIRL); perlight float specular = pow(max(dot(N,H),0),sh); perlight floatv fr = select(diffuse > 0, s * specular, Zero); return integrate(fr * Cl) + e; }

basic :: LLighter FloatE -> BasicShSource

Combine intrinsic, ambient, diffuse and specular, with weightings

class Liftable k f whereSource

surface float4 lightmodel (float4 a, float4 d, float4 s, float4 e, float sh) { perlight float diffuse = dot(N,DIRL); perlight float specular = pow(max(dot(N,H),0),sh); perlight float4 fr = d * max(diffuse, 0) + s * select(diffuse > 0, specular, 0); return a * Ca + integrate(fr * Cl) + e; }

Methods

lift :: k -> fSource

Instances

Liftable a a 
Liftable d (a -> b -> c -> d) 
Liftable c (a -> b -> c) 
Liftable b (a -> b) 

type Dir3E = R3ESource

Direction. Assumed normalized.

dirLight :: Color -> Dir3E -> LightSource

Directional light, given the direction from the light (opposite dirL)

pointLight :: Color -> R3E -> LightSource

Point light

stdView :: R3E -> [Light] -> ViewSource

View with white ambient light and given eye position and lights

view1 :: R3E -> ViewSource

View with white ambient light, one directional light, and given eye position. For now, light position is like eye position but more so.