| Safe Haskell | None |
|---|---|
| Language | Haskell98 |
Vis
- data Options = Options {}
- data Antialiasing
- data Camera0 = Camera0 {}
- defaultOpts :: Options
- display :: Real b => Options -> VisObject b -> IO ()
- animate :: Real b => Options -> (Float -> VisObject b) -> IO ()
- simulate :: Real b => Options -> Double -> world -> (world -> VisObject b) -> (Float -> world -> world) -> IO ()
- play :: Real b => Options -> Double -> world -> (world -> (VisObject b, Maybe Cursor)) -> (Float -> world -> world) -> (world -> IO ()) -> Maybe (world -> Key -> KeyState -> Modifiers -> Position -> world) -> Maybe (world -> Position -> world) -> Maybe (world -> Position -> world) -> IO ()
- animateIO :: Real b => Options -> (Float -> IO (VisObject b)) -> IO ()
- simulateIO :: Real b => Options -> Double -> world -> (world -> IO (VisObject b)) -> (Float -> world -> IO world) -> IO ()
- playIO :: Real b => Options -> Double -> world -> (world -> IO (VisObject b, Maybe Cursor)) -> (Float -> world -> IO world) -> (world -> IO ()) -> Maybe (world -> Key -> KeyState -> Modifiers -> Position -> world) -> Maybe (world -> Position -> world) -> Maybe (world -> Position -> world) -> IO ()
- visMovie :: forall b. Real b => Options -> (Int -> FilePath) -> Double -> [VisObject b] -> Maybe Cursor -> IO ()
- data VisObject a
- = VisObjects [VisObject a]
- | Trans (V3 a) (VisObject a)
- | RotQuat (Quaternion a) (VisObject a)
- | RotDcm (M33 a) (VisObject a)
- | RotEulerRad (Euler a) (VisObject a)
- | RotEulerDeg (Euler a) (VisObject a)
- | Scale (a, a, a) (VisObject a)
- | Cylinder (a, a) Color
- | Box (a, a, a) Flavour Color
- | Cube a Flavour Color
- | Sphere a Flavour Color
- | Ellipsoid (a, a, a) Flavour Color
- | Line (Maybe a) [V3 a] Color
- | Line' (Maybe a) [(V3 a, Color)]
- | Arrow (a, a) (V3 a) Color
- | Axes (a, a)
- | Plane (V3 a) Color Color
- | Triangle (V3 a) (V3 a) (V3 a) Color
- | Quad (V3 a) (V3 a) (V3 a) (V3 a) Color
- | Text3d String (V3 a) BitmapFont Color
- | Text2d String (a, a) BitmapFont Color
- | Points [V3 a] (Maybe GLfloat) Color
- | ObjModel LoadedObjModel Color
- data SpecialKey :: *
- data BitmapFont :: *
- data Flavour :: *
- data LoadedObjModel
- loadObjModel :: Foldable f => f (V3 Double, V3 Double) -> LoadedObjModel
- module Vis.GlossColor
Documentation
Constructors
| Options | |
Fields
| |
defaultOpts :: Options Source #
Some reasonable default options. Consider changing the window name with something like:
myOptions = defaultOpts {optWindowName = "my rad program"}draw a static image
Arguments
| :: Real b | |
| => Options | user options |
| -> Double | sample rate |
| -> world | initial state |
| -> (world -> VisObject b) | draw function |
| -> (Float -> world -> world) | state propogation function (takes time since start and state as inputs) |
| -> IO () |
run a simulation
Arguments
| :: Real b | |
| => Options | user options |
| -> Double | sample time |
| -> world | initial state |
| -> (world -> (VisObject b, Maybe Cursor)) | draw function, can give a different cursor |
| -> (Float -> world -> world) | state propogation function (takes time since start and state as inputs) |
| -> (world -> IO ()) | set where camera looks |
| -> Maybe (world -> Key -> KeyState -> Modifiers -> Position -> world) | keyboard/mouse press callback |
| -> Maybe (world -> Position -> world) | mouse drag callback |
| -> Maybe (world -> Position -> world) | mouse move callback |
| -> IO () |
Arguments
| :: Real b | |
| => Options | user options |
| -> (Float -> IO (VisObject b)) | draw function (takes time since start as input) |
| -> IO () |
display an animation impurely
Arguments
| :: Real b | |
| => Options | user options |
| -> Double | sample rate |
| -> world | initial state |
| -> (world -> IO (VisObject b)) | draw function |
| -> (Float -> world -> IO world) | state propogation function (takes time since start and state as inputs) |
| -> IO () |
run a simulation impurely
Arguments
| :: Real b | |
| => Options | user options |
| -> Double | sample time |
| -> world | initial state |
| -> (world -> IO (VisObject b, Maybe Cursor)) | draw function, can give a different cursor |
| -> (Float -> world -> IO world) | state propogation function (takes time since start and state as inputs) |
| -> (world -> IO ()) | set where camera looks |
| -> Maybe (world -> Key -> KeyState -> Modifiers -> Position -> world) | keyboard/mouse press callback |
| -> Maybe (world -> Position -> world) | mouse drag callback |
| -> Maybe (world -> Position -> world) | mouse move callback |
| -> IO () |
Constructors
| VisObjects [VisObject a] | |
| Trans (V3 a) (VisObject a) | |
| RotQuat (Quaternion a) (VisObject a) | |
| RotDcm (M33 a) (VisObject a) | |
| RotEulerRad (Euler a) (VisObject a) | |
| RotEulerDeg (Euler a) (VisObject a) | |
| Scale (a, a, a) (VisObject a) | |
| Cylinder (a, a) Color | |
| Box (a, a, a) Flavour Color | |
| Cube a Flavour Color | |
| Sphere a Flavour Color | |
| Ellipsoid (a, a, a) Flavour Color | |
| Line (Maybe a) [V3 a] Color | |
| Line' (Maybe a) [(V3 a, Color)] | |
| Arrow (a, a) (V3 a) Color | |
| Axes (a, a) | |
| Plane (V3 a) Color Color | |
| Triangle (V3 a) (V3 a) (V3 a) Color | |
| Quad (V3 a) (V3 a) (V3 a) (V3 a) Color | |
| Text3d String (V3 a) BitmapFont Color | |
| Text2d String (a, a) BitmapFont Color | |
| Points [V3 a] (Maybe GLfloat) Color | |
| ObjModel LoadedObjModel Color |
data SpecialKey :: * #
Special keys
Constructors
| KeyF1 | |
| KeyF2 | |
| KeyF3 | |
| KeyF4 | |
| KeyF5 | |
| KeyF6 | |
| KeyF7 | |
| KeyF8 | |
| KeyF9 | |
| KeyF10 | |
| KeyF11 | |
| KeyF12 | |
| KeyLeft | |
| KeyUp | |
| KeyRight | |
| KeyDown | |
| KeyPageUp | |
| KeyPageDown | |
| KeyHome | |
| KeyEnd | |
| KeyInsert | |
| KeyNumLock | |
| KeyBegin | |
| KeyDelete | |
| KeyShiftL | |
| KeyShiftR | |
| KeyCtrlL | |
| KeyCtrlR | |
| KeyAltL | |
| KeyAltR | |
| KeyUnknown Int | You should actually never encounter this value, it is just here as a safeguard against future changes in the native GLUT library. |
Instances
data BitmapFont :: * #
The bitmap fonts available in GLUT. The exact bitmap to be used is defined by the standard X glyph bitmaps for the X font with the given name.
Constructors
| Fixed8By13 | A fixed width font with every character fitting in an 8
by 13 pixel rectangle.
( |
| Fixed9By15 | A fixed width font with every character fitting in an 9
by 15 pixel rectangle.
( |
| TimesRoman10 | A 10-point proportional spaced Times Roman font.
( |
| TimesRoman24 | A 24-point proportional spaced Times Roman font.
( |
| Helvetica10 | A 10-point proportional spaced Helvetica font.
( |
| Helvetica12 | A 12-point proportional spaced Helvetica font.
( |
| Helvetica18 | A 18-point proportional spaced Helvetica font.
( |
Instances
Flavour of object rendering
data LoadedObjModel Source #
Instances
loadObjModel :: Foldable f => f (V3 Double, V3 Double) -> LoadedObjModel Source #
turn a list of vertexnormal tuples into vertexnormal arrays
module Vis.GlossColor