module Graphics.UI.GLUT.Objects (
Flavour(..),
Object(..),
Sides, Rings, NumLevels,
renderObject
) where
import Control.Monad.IO.Class ( MonadIO(..) )
import Foreign.C.Types ( CInt )
import Foreign.Marshal.Utils ( with )
import Foreign.Ptr ( Ptr, castPtr )
import Graphics.Rendering.OpenGL (
Height, Radius, Slices, Stacks, Vertex3(..), GLdouble, GLint )
import Graphics.UI.GLUT.Raw
data Flavour
=
Solid
|
Wireframe
deriving ( Flavour -> Flavour -> Bool
(Flavour -> Flavour -> Bool)
-> (Flavour -> Flavour -> Bool) -> Eq Flavour
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Flavour -> Flavour -> Bool
$c/= :: Flavour -> Flavour -> Bool
== :: Flavour -> Flavour -> Bool
$c== :: Flavour -> Flavour -> Bool
Eq, Eq Flavour
Eq Flavour
-> (Flavour -> Flavour -> Ordering)
-> (Flavour -> Flavour -> Bool)
-> (Flavour -> Flavour -> Bool)
-> (Flavour -> Flavour -> Bool)
-> (Flavour -> Flavour -> Bool)
-> (Flavour -> Flavour -> Flavour)
-> (Flavour -> Flavour -> Flavour)
-> Ord Flavour
Flavour -> Flavour -> Bool
Flavour -> Flavour -> Ordering
Flavour -> Flavour -> Flavour
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Flavour -> Flavour -> Flavour
$cmin :: Flavour -> Flavour -> Flavour
max :: Flavour -> Flavour -> Flavour
$cmax :: Flavour -> Flavour -> Flavour
>= :: Flavour -> Flavour -> Bool
$c>= :: Flavour -> Flavour -> Bool
> :: Flavour -> Flavour -> Bool
$c> :: Flavour -> Flavour -> Bool
<= :: Flavour -> Flavour -> Bool
$c<= :: Flavour -> Flavour -> Bool
< :: Flavour -> Flavour -> Bool
$c< :: Flavour -> Flavour -> Bool
compare :: Flavour -> Flavour -> Ordering
$ccompare :: Flavour -> Flavour -> Ordering
$cp1Ord :: Eq Flavour
Ord, Int -> Flavour -> ShowS
[Flavour] -> ShowS
Flavour -> String
(Int -> Flavour -> ShowS)
-> (Flavour -> String) -> ([Flavour] -> ShowS) -> Show Flavour
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Flavour] -> ShowS
$cshowList :: [Flavour] -> ShowS
show :: Flavour -> String
$cshow :: Flavour -> String
showsPrec :: Int -> Flavour -> ShowS
$cshowsPrec :: Int -> Flavour -> ShowS
Show )
data Object
=
Cube Height
|
Dodecahedron
|
Icosahedron
|
Octahedron
|
Tetrahedron
|
RhombicDodecahedron
|
Sphere' Radius Slices Stacks
|
Cone Radius Height Slices Stacks
|
Cylinder' Radius Height Slices Stacks
|
Torus Radius Radius Sides Rings
|
Teapot Height
|
Teacup Height
|
Teaspoon Height
|
SierpinskiSponge NumLevels
deriving ( Object -> Object -> Bool
(Object -> Object -> Bool)
-> (Object -> Object -> Bool) -> Eq Object
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Object -> Object -> Bool
$c/= :: Object -> Object -> Bool
== :: Object -> Object -> Bool
$c== :: Object -> Object -> Bool
Eq, Eq Object
Eq Object
-> (Object -> Object -> Ordering)
-> (Object -> Object -> Bool)
-> (Object -> Object -> Bool)
-> (Object -> Object -> Bool)
-> (Object -> Object -> Bool)
-> (Object -> Object -> Object)
-> (Object -> Object -> Object)
-> Ord Object
Object -> Object -> Bool
Object -> Object -> Ordering
Object -> Object -> Object
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Object -> Object -> Object
$cmin :: Object -> Object -> Object
max :: Object -> Object -> Object
$cmax :: Object -> Object -> Object
>= :: Object -> Object -> Bool
$c>= :: Object -> Object -> Bool
> :: Object -> Object -> Bool
$c> :: Object -> Object -> Bool
<= :: Object -> Object -> Bool
$c<= :: Object -> Object -> Bool
< :: Object -> Object -> Bool
$c< :: Object -> Object -> Bool
compare :: Object -> Object -> Ordering
$ccompare :: Object -> Object -> Ordering
$cp1Ord :: Eq Object
Ord, Int -> Object -> ShowS
[Object] -> ShowS
Object -> String
(Int -> Object -> ShowS)
-> (Object -> String) -> ([Object] -> ShowS) -> Show Object
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Object] -> ShowS
$cshowList :: [Object] -> ShowS
show :: Object -> String
$cshow :: Object -> String
showsPrec :: Int -> Object -> ShowS
$cshowsPrec :: Int -> Object -> ShowS
Show )
type Sides = GLint
type Rings = GLint
type NumLevels = GLint
renderObject :: MonadIO m => Flavour -> Object -> m ()
renderObject :: Flavour -> Object -> m ()
renderObject Flavour
Solid (Cube Height
h) = Height -> m ()
forall (m :: * -> *). MonadIO m => Height -> m ()
glutSolidCube Height
h
renderObject Flavour
Wireframe (Cube Height
h) = Height -> m ()
forall (m :: * -> *). MonadIO m => Height -> m ()
glutWireCube Height
h
renderObject Flavour
Solid Object
Dodecahedron = m ()
forall (m :: * -> *). MonadIO m => m ()
glutSolidDodecahedron
renderObject Flavour
Wireframe Object
Dodecahedron = m ()
forall (m :: * -> *). MonadIO m => m ()
glutWireDodecahedron
renderObject Flavour
Solid Object
Icosahedron = m ()
forall (m :: * -> *). MonadIO m => m ()
glutSolidIcosahedron
renderObject Flavour
Wireframe Object
Icosahedron = m ()
forall (m :: * -> *). MonadIO m => m ()
glutWireIcosahedron
renderObject Flavour
Solid Object
Octahedron = m ()
forall (m :: * -> *). MonadIO m => m ()
glutSolidOctahedron
renderObject Flavour
Wireframe Object
Octahedron = m ()
forall (m :: * -> *). MonadIO m => m ()
glutWireOctahedron
renderObject Flavour
Solid Object
Tetrahedron = m ()
forall (m :: * -> *). MonadIO m => m ()
glutSolidTetrahedron
renderObject Flavour
Wireframe Object
Tetrahedron = m ()
forall (m :: * -> *). MonadIO m => m ()
glutWireTetrahedron
renderObject Flavour
Solid Object
RhombicDodecahedron = m ()
forall (m :: * -> *). MonadIO m => m ()
glutSolidRhombicDodecahedron
renderObject Flavour
Wireframe Object
RhombicDodecahedron = m ()
forall (m :: * -> *). MonadIO m => m ()
glutWireRhombicDodecahedron
renderObject Flavour
Solid (Sphere' Height
r Slices
s Slices
t) = Height -> Slices -> Slices -> m ()
forall (m :: * -> *).
MonadIO m =>
Height -> Slices -> Slices -> m ()
glutSolidSphere Height
r Slices
s Slices
t
renderObject Flavour
Wireframe (Sphere' Height
r Slices
s Slices
t) = Height -> Slices -> Slices -> m ()
forall (m :: * -> *).
MonadIO m =>
Height -> Slices -> Slices -> m ()
glutWireSphere Height
r Slices
s Slices
t
renderObject Flavour
Solid (Cone Height
r Height
h Slices
s Slices
t) = Height -> Height -> Slices -> Slices -> m ()
forall (m :: * -> *).
MonadIO m =>
Height -> Height -> Slices -> Slices -> m ()
glutSolidCone Height
r Height
h Slices
s Slices
t
renderObject Flavour
Wireframe (Cone Height
r Height
h Slices
s Slices
t) = Height -> Height -> Slices -> Slices -> m ()
forall (m :: * -> *).
MonadIO m =>
Height -> Height -> Slices -> Slices -> m ()
glutWireCone Height
r Height
h Slices
s Slices
t
renderObject Flavour
Solid (Cylinder' Height
r Height
h Slices
s Slices
t) = Height -> Height -> Slices -> Slices -> m ()
forall (m :: * -> *).
MonadIO m =>
Height -> Height -> Slices -> Slices -> m ()
glutSolidCylinder Height
r Height
h Slices
s Slices
t
renderObject Flavour
Wireframe (Cylinder' Height
r Height
h Slices
s Slices
t) = Height -> Height -> Slices -> Slices -> m ()
forall (m :: * -> *).
MonadIO m =>
Height -> Height -> Slices -> Slices -> m ()
glutWireCylinder Height
r Height
h Slices
s Slices
t
renderObject Flavour
Solid (Torus Height
i Height
o Slices
s Slices
r) = Height -> Height -> Slices -> Slices -> m ()
forall (m :: * -> *).
MonadIO m =>
Height -> Height -> Slices -> Slices -> m ()
glutSolidTorus Height
i Height
o Slices
s Slices
r
renderObject Flavour
Wireframe (Torus Height
i Height
o Slices
s Slices
r) = Height -> Height -> Slices -> Slices -> m ()
forall (m :: * -> *).
MonadIO m =>
Height -> Height -> Slices -> Slices -> m ()
glutWireTorus Height
i Height
o Slices
s Slices
r
renderObject Flavour
Solid (Teapot Height
h) = Height -> m ()
forall (m :: * -> *). MonadIO m => Height -> m ()
glutSolidTeapot Height
h
renderObject Flavour
Wireframe (Teapot Height
h) = Height -> m ()
forall (m :: * -> *). MonadIO m => Height -> m ()
glutWireTeapot Height
h
renderObject Flavour
Solid (Teacup Height
h) = Height -> m ()
forall (m :: * -> *). MonadIO m => Height -> m ()
glutSolidTeacup Height
h
renderObject Flavour
Wireframe (Teacup Height
h) = Height -> m ()
forall (m :: * -> *). MonadIO m => Height -> m ()
glutWireTeacup Height
h
renderObject Flavour
Solid (Teaspoon Height
h) = Height -> m ()
forall (m :: * -> *). MonadIO m => Height -> m ()
glutSolidTeaspoon Height
h
renderObject Flavour
Wireframe (Teaspoon Height
h) = Height -> m ()
forall (m :: * -> *). MonadIO m => Height -> m ()
glutWireTeaspoon Height
h
renderObject Flavour
Solid (SierpinskiSponge Slices
n) = Slices -> m ()
forall (m :: * -> *). MonadIO m => Slices -> m ()
solidSierpinskiSponge Slices
n
renderObject Flavour
Wireframe (SierpinskiSponge Slices
n) = Slices -> m ()
forall (m :: * -> *). MonadIO m => Slices -> m ()
wireSierpinskiSponge Slices
n
solidSierpinskiSponge :: MonadIO m => NumLevels -> m ()
solidSierpinskiSponge :: Slices -> m ()
solidSierpinskiSponge = (CInt -> Ptr Height -> Height -> IO ()) -> Slices -> m ()
forall (m :: * -> *).
MonadIO m =>
(CInt -> Ptr Height -> Height -> IO ()) -> Slices -> m ()
sierpinskiSponge CInt -> Ptr Height -> Height -> IO ()
forall (m :: * -> *).
MonadIO m =>
CInt -> Ptr Height -> Height -> m ()
glutSolidSierpinskiSponge
wireSierpinskiSponge :: MonadIO m => NumLevels -> m ()
wireSierpinskiSponge :: Slices -> m ()
wireSierpinskiSponge = (CInt -> Ptr Height -> Height -> IO ()) -> Slices -> m ()
forall (m :: * -> *).
MonadIO m =>
(CInt -> Ptr Height -> Height -> IO ()) -> Slices -> m ()
sierpinskiSponge CInt -> Ptr Height -> Height -> IO ()
forall (m :: * -> *).
MonadIO m =>
CInt -> Ptr Height -> Height -> m ()
glutWireSierpinskiSponge
sierpinskiSponge :: MonadIO m => (CInt -> Ptr GLdouble -> Height -> IO ()) -> NumLevels -> m ()
sierpinskiSponge :: (CInt -> Ptr Height -> Height -> IO ()) -> Slices -> m ()
sierpinskiSponge CInt -> Ptr Height -> Height -> IO ()
f Slices
n = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$
Vertex3 Height -> (Ptr (Vertex3 Height) -> IO ()) -> IO ()
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with (Height -> Height -> Height -> Vertex3 Height
forall a. a -> a -> a -> Vertex3 a
Vertex3 Height
0 Height
0 Height
0) ((Ptr (Vertex3 Height) -> IO ()) -> IO ())
-> (Ptr (Vertex3 Height) -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr (Vertex3 Height)
offsetBuf ->
CInt -> Ptr Height -> Height -> IO ()
f (Slices -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Slices
n) ((Ptr (Vertex3 Height) -> Ptr Height
forall a b. Ptr a -> Ptr b
castPtr :: Ptr (Vertex3 GLdouble) -> Ptr GLdouble) Ptr (Vertex3 Height)
offsetBuf) Height
1