| Safe Haskell | Safe |
|---|---|
| Language | Haskell2010 |
Data.VRML.Nodes
Documentation
Constructors
| Anchor | |
Instances
| Eq Anchor Source # | |
| Show Anchor Source # | |
| Generic Anchor Source # | |
| ToNode Anchor Source # | |
| type Rep Anchor Source # | |
Defined in Data.VRML.Nodes type Rep Anchor = D1 (MetaData "Anchor" "Data.VRML.Nodes" "VRML-0.1.0.0-IThIBRc3XqmAFQAuTjD7j0" False) (C1 (MetaCons "Anchor" PrefixI True) ((S1 (MetaSel (Just "children") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Node]) :*: (S1 (MetaSel (Just "description") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Just "parameter") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [String]))) :*: (S1 (MetaSel (Just "url") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [String]) :*: (S1 (MetaSel (Just "bboxCenter") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Float, Float, Float)) :*: S1 (MetaSel (Just "bboxSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Float, Float, Float)))))) | |
data Appearance Source #
Constructors
| Appearance | |
Instances
| Eq Appearance Source # | |
Defined in Data.VRML.Nodes | |
| Show Appearance Source # | |
Defined in Data.VRML.Nodes Methods showsPrec :: Int -> Appearance -> ShowS # show :: Appearance -> String # showList :: [Appearance] -> ShowS # | |
| Generic Appearance Source # | |
Defined in Data.VRML.Nodes Associated Types type Rep Appearance :: Type -> Type # | |
| ToNode Appearance Source # | |
Defined in Data.VRML.Nodes Methods toNode :: NodeLike b => Appearance -> b Source # | |
| type Rep Appearance Source # | |
Defined in Data.VRML.Nodes type Rep Appearance = D1 (MetaData "Appearance" "Data.VRML.Nodes" "VRML-0.1.0.0-IThIBRc3XqmAFQAuTjD7j0" False) (C1 (MetaCons "Appearance" PrefixI True) (S1 (MetaSel (Just "material") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Node)) :*: (S1 (MetaSel (Just "texture") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Node)) :*: S1 (MetaSel (Just "textureTransform") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Node))))) | |
Constructors
| AudioClip | |
Instances
| Eq AudioClip Source # | |
| Show AudioClip Source # | |
| Generic AudioClip Source # | |
| ToNode AudioClip Source # | |
| type Rep AudioClip Source # | |
Defined in Data.VRML.Nodes type Rep AudioClip = D1 (MetaData "AudioClip" "Data.VRML.Nodes" "VRML-0.1.0.0-IThIBRc3XqmAFQAuTjD7j0" False) (C1 (MetaCons "AudioClip" PrefixI True) ((S1 (MetaSel (Just "description") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: (S1 (MetaSel (Just "loop") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool) :*: S1 (MetaSel (Just "pitch") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Float))) :*: (S1 (MetaSel (Just "startTime") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Time) :*: (S1 (MetaSel (Just "stopTime") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Time) :*: S1 (MetaSel (Just "url") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [String]))))) | |
Constructors
| Billboard | |
Instances
| Eq Billboard Source # | |
| Show Billboard Source # | |
| Generic Billboard Source # | |
| ToNode Billboard Source # | |
| type Rep Billboard Source # | |
Defined in Data.VRML.Nodes type Rep Billboard = D1 (MetaData "Billboard" "Data.VRML.Nodes" "VRML-0.1.0.0-IThIBRc3XqmAFQAuTjD7j0" False) (C1 (MetaCons "Billboard" PrefixI True) ((S1 (MetaSel (Just "axisOfRotation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Float, Float, Float)) :*: S1 (MetaSel (Just "children") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Node])) :*: (S1 (MetaSel (Just "bboxCenter") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Float, Float, Float)) :*: S1 (MetaSel (Just "bboxSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Float, Float, Float))))) | |
Constructors
| Collision | |
Instances
| Eq Collision Source # | |
| Show Collision Source # | |
| Generic Collision Source # | |
| ToNode Collision Source # | |
| type Rep Collision Source # | |
Defined in Data.VRML.Nodes type Rep Collision = D1 (MetaData "Collision" "Data.VRML.Nodes" "VRML-0.1.0.0-IThIBRc3XqmAFQAuTjD7j0" False) (C1 (MetaCons "Collision" PrefixI True) ((S1 (MetaSel (Just "children") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Node]) :*: S1 (MetaSel (Just "collide") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) :*: (S1 (MetaSel (Just "bboxCenter") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Float, Float, Float)) :*: (S1 (MetaSel (Just "bboxSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Float, Float, Float)) :*: S1 (MetaSel (Just "proxy") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Node)))))) | |
data ColorInterpolator Source #
Constructors
| ColorInterpolator | |
Instances
Instances
| Eq Cone Source # | |
| Show Cone Source # | |
| Generic Cone Source # | |
| ToNode Cone Source # | |
| type Rep Cone Source # | |
Defined in Data.VRML.Nodes type Rep Cone = D1 (MetaData "Cone" "Data.VRML.Nodes" "VRML-0.1.0.0-IThIBRc3XqmAFQAuTjD7j0" False) (C1 (MetaCons "Cone" PrefixI True) ((S1 (MetaSel (Just "bottomRadius") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Float) :*: S1 (MetaSel (Just "height") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Float)) :*: (S1 (MetaSel (Just "side") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool) :*: S1 (MetaSel (Just "bottom") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)))) | |
data Coordinate Source #
Constructors
| Coordinate | |
Instances
| Eq Coordinate Source # | |
Defined in Data.VRML.Nodes | |
| Show Coordinate Source # | |
Defined in Data.VRML.Nodes Methods showsPrec :: Int -> Coordinate -> ShowS # show :: Coordinate -> String # showList :: [Coordinate] -> ShowS # | |
| Generic Coordinate Source # | |
Defined in Data.VRML.Nodes Associated Types type Rep Coordinate :: Type -> Type # | |
| ToNode Coordinate Source # | |
Defined in Data.VRML.Nodes Methods toNode :: NodeLike b => Coordinate -> b Source # | |
| type Rep Coordinate Source # | |
Defined in Data.VRML.Nodes type Rep Coordinate = D1 (MetaData "Coordinate" "Data.VRML.Nodes" "VRML-0.1.0.0-IThIBRc3XqmAFQAuTjD7j0" False) (C1 (MetaCons "Coordinate" PrefixI True) (S1 (MetaSel (Just "point") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(Float, Float, Float)]))) | |
data CoordinateInterpolator Source #
Instances
Instances
| Eq Cylinder Source # | |
| Show Cylinder Source # | |
| Generic Cylinder Source # | |
| ToNode Cylinder Source # | |
| type Rep Cylinder Source # | |
Defined in Data.VRML.Nodes type Rep Cylinder = D1 (MetaData "Cylinder" "Data.VRML.Nodes" "VRML-0.1.0.0-IThIBRc3XqmAFQAuTjD7j0" False) (C1 (MetaCons "Cylinder" PrefixI True) ((S1 (MetaSel (Just "bottom") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool) :*: S1 (MetaSel (Just "height") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Float)) :*: (S1 (MetaSel (Just "radius") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Float) :*: (S1 (MetaSel (Just "side") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool) :*: S1 (MetaSel (Just "top") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool))))) | |
data CylinderSensor Source #
Constructors
| CylinderSensor | |
Instances
data DirectionalLight Source #
Constructors
| DirectionalLight | |
Instances
data ElevationGrid Source #
Constructors
| ElevationGrid | |
Instances
Constructors
| Extrusion | |
Instances
Instances
| Eq Fog Source # | |
| Show Fog Source # | |
| Generic Fog Source # | |
| ToNode Fog Source # | |
| type Rep Fog Source # | |
Defined in Data.VRML.Nodes type Rep Fog = D1 (MetaData "Fog" "Data.VRML.Nodes" "VRML-0.1.0.0-IThIBRc3XqmAFQAuTjD7j0" False) (C1 (MetaCons "Fog" PrefixI True) (S1 (MetaSel (Just "color") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Color) :*: (S1 (MetaSel (Just "fogType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Just "visibilityRange") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Float)))) | |
Constructors
| FontStyle | |
Instances
Constructors
| Group | |
Instances
| Eq Group Source # | |
| Show Group Source # | |
| Generic Group Source # | |
| ToNode Group Source # | |
| type Rep Group Source # | |
Defined in Data.VRML.Nodes type Rep Group = D1 (MetaData "Group" "Data.VRML.Nodes" "VRML-0.1.0.0-IThIBRc3XqmAFQAuTjD7j0" False) (C1 (MetaCons "Group" PrefixI True) (S1 (MetaSel (Just "children") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Node]) :*: (S1 (MetaSel (Just "bboxCenter") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Float, Float, Float)) :*: S1 (MetaSel (Just "bboxSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Float, Float, Float))))) | |
data ImageTexture Source #
Instances
| Eq ImageTexture Source # | |
Defined in Data.VRML.Nodes | |
| Show ImageTexture Source # | |
Defined in Data.VRML.Nodes Methods showsPrec :: Int -> ImageTexture -> ShowS # show :: ImageTexture -> String # showList :: [ImageTexture] -> ShowS # | |
| Generic ImageTexture Source # | |
Defined in Data.VRML.Nodes Associated Types type Rep ImageTexture :: Type -> Type # | |
| ToNode ImageTexture Source # | |
Defined in Data.VRML.Nodes Methods toNode :: NodeLike b => ImageTexture -> b Source # | |
| type Rep ImageTexture Source # | |
Defined in Data.VRML.Nodes type Rep ImageTexture = D1 (MetaData "ImageTexture" "Data.VRML.Nodes" "VRML-0.1.0.0-IThIBRc3XqmAFQAuTjD7j0" False) (C1 (MetaCons "ImageTexture" PrefixI True) (S1 (MetaSel (Just "url") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [String]) :*: (S1 (MetaSel (Just "repeatS") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool) :*: S1 (MetaSel (Just "repeatT") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)))) | |
data IndexedFaceSet Source #
Constructors
| IndexedFaceSet | |
Fields
| |
Instances
data IndexedLineSet Source #
Constructors
| IndexedLineSet | |
Fields
| |
Instances
Constructors
| Inline | |
Instances
| Eq Inline Source # | |
| Show Inline Source # | |
| Generic Inline Source # | |
| ToNode Inline Source # | |
| type Rep Inline Source # | |
Defined in Data.VRML.Nodes type Rep Inline = D1 (MetaData "Inline" "Data.VRML.Nodes" "VRML-0.1.0.0-IThIBRc3XqmAFQAuTjD7j0" False) (C1 (MetaCons "Inline" PrefixI True) (S1 (MetaSel (Just "url") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [String]) :*: (S1 (MetaSel (Just "bboxCenter") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Float, Float, Float)) :*: S1 (MetaSel (Just "bboxSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Float, Float, Float))))) | |
Instances
| Eq LOD Source # | |
| Show LOD Source # | |
| Generic LOD Source # | |
| ToNode LOD Source # | |
| type Rep LOD Source # | |
Defined in Data.VRML.Nodes type Rep LOD = D1 (MetaData "LOD" "Data.VRML.Nodes" "VRML-0.1.0.0-IThIBRc3XqmAFQAuTjD7j0" False) (C1 (MetaCons "LOD" PrefixI True) (S1 (MetaSel (Just "level") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Node]) :*: (S1 (MetaSel (Just "center") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Float, Float, Float)) :*: S1 (MetaSel (Just "range") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Float])))) | |
Constructors
| Material | |
Fields
| |
Instances
| Eq Material Source # | |
| Show Material Source # | |
| Generic Material Source # | |
| ToNode Material Source # | |
| type Rep Material Source # | |
Defined in Data.VRML.Nodes type Rep Material = D1 (MetaData "Material" "Data.VRML.Nodes" "VRML-0.1.0.0-IThIBRc3XqmAFQAuTjD7j0" False) (C1 (MetaCons "Material" PrefixI True) ((S1 (MetaSel (Just "ambientIntensity") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Float) :*: (S1 (MetaSel (Just "diffuseColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Color) :*: S1 (MetaSel (Just "emissiveColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Color))) :*: (S1 (MetaSel (Just "shininess") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Float) :*: (S1 (MetaSel (Just "specularColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Color) :*: S1 (MetaSel (Just "transparency") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Float))))) | |
data MovieTexture Source #
Constructors
| MovieTexture | |
Instances
data NavigationInfo Source #
Constructors
| NavigationInfo | |
Fields
| |
data NormalInterpolator Source #
Instances
data OrientationInterpolator Source #
Instances
data PixelTexture Source #
Instances
| Eq PixelTexture Source # | |
Defined in Data.VRML.Nodes | |
| Show PixelTexture Source # | |
Defined in Data.VRML.Nodes Methods showsPrec :: Int -> PixelTexture -> ShowS # show :: PixelTexture -> String # showList :: [PixelTexture] -> ShowS # | |
| Generic PixelTexture Source # | |
Defined in Data.VRML.Nodes Associated Types type Rep PixelTexture :: Type -> Type # | |
| ToNode PixelTexture Source # | |
Defined in Data.VRML.Nodes Methods toNode :: NodeLike b => PixelTexture -> b Source # | |
| type Rep PixelTexture Source # | |
Defined in Data.VRML.Nodes type Rep PixelTexture = D1 (MetaData "PixelTexture" "Data.VRML.Nodes" "VRML-0.1.0.0-IThIBRc3XqmAFQAuTjD7j0" False) (C1 (MetaCons "PixelTexture" PrefixI True) (S1 (MetaSel (Just "image") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Int32]) :*: (S1 (MetaSel (Just "repeatS") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool) :*: S1 (MetaSel (Just "repeatT") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)))) | |
data PlaneSensor Source #
Constructors
| PlaneSensor | |
Fields
| |
Instances
data PointLight Source #
Constructors
| PointLight | |
Instances
Instances
| Eq PointSet Source # | |
| Show PointSet Source # | |
| Generic PointSet Source # | |
| ToNode PointSet Source # | |
| type Rep PointSet Source # | |
Defined in Data.VRML.Nodes type Rep PointSet = D1 (MetaData "PointSet" "Data.VRML.Nodes" "VRML-0.1.0.0-IThIBRc3XqmAFQAuTjD7j0" False) (C1 (MetaCons "PointSet" PrefixI True) (S1 (MetaSel (Just "color") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Node)) :*: S1 (MetaSel (Just "coord") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Node)))) | |
data PositionInterpolator Source #
Instances
data ProximitySensor Source #
Constructors
| ProximitySensor | |
Instances
data ScalarInterpolator Source #
Constructors
| ScalarInterpolator | |
Instances
Instances
| Eq Shape Source # | |
| Show Shape Source # | |
| Generic Shape Source # | |
| ToNode Shape Source # | |
| type Rep Shape Source # | |
Defined in Data.VRML.Nodes type Rep Shape = D1 (MetaData "Shape" "Data.VRML.Nodes" "VRML-0.1.0.0-IThIBRc3XqmAFQAuTjD7j0" False) (C1 (MetaCons "Shape" PrefixI True) (S1 (MetaSel (Just "appearance") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Node)) :*: S1 (MetaSel (Just "geometry") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Node)))) | |
Constructors
| Sound | |
Instances
data SphereSensor Source #
Constructors
| SphereSensor | |
Instances
| Eq SphereSensor Source # | |
Defined in Data.VRML.Nodes | |
| Show SphereSensor Source # | |
Defined in Data.VRML.Nodes Methods showsPrec :: Int -> SphereSensor -> ShowS # show :: SphereSensor -> String # showList :: [SphereSensor] -> ShowS # | |
| Generic SphereSensor Source # | |
Defined in Data.VRML.Nodes Associated Types type Rep SphereSensor :: Type -> Type # | |
| ToNode SphereSensor Source # | |
Defined in Data.VRML.Nodes Methods toNode :: NodeLike b => SphereSensor -> b Source # | |
| type Rep SphereSensor Source # | |
Defined in Data.VRML.Nodes type Rep SphereSensor = D1 (MetaData "SphereSensor" "Data.VRML.Nodes" "VRML-0.1.0.0-IThIBRc3XqmAFQAuTjD7j0" False) (C1 (MetaCons "SphereSensor" PrefixI True) (S1 (MetaSel (Just "autoOffset") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool) :*: (S1 (MetaSel (Just "enabled") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool) :*: S1 (MetaSel (Just "offset") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Float, Float, Float, Float))))) | |
Constructors
| SpotLight | |
Instances
Constructors
| Switch | |
Fields
| |
Instances
| Eq Switch Source # | |
| Show Switch Source # | |
| Generic Switch Source # | |
| ToNode Switch Source # | |
| type Rep Switch Source # | |
Defined in Data.VRML.Nodes type Rep Switch = D1 (MetaData "Switch" "Data.VRML.Nodes" "VRML-0.1.0.0-IThIBRc3XqmAFQAuTjD7j0" False) (C1 (MetaCons "Switch" PrefixI True) (S1 (MetaSel (Just "choice") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Node]) :*: S1 (MetaSel (Just "whichChoice") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int32))) | |
Constructors
| Text | |
Instances
| Eq Text Source # | |
| Show Text Source # | |
| Generic Text Source # | |
| ToNode Text Source # | |
| type Rep Text Source # | |
Defined in Data.VRML.Nodes type Rep Text = D1 (MetaData "Text" "Data.VRML.Nodes" "VRML-0.1.0.0-IThIBRc3XqmAFQAuTjD7j0" False) (C1 (MetaCons "Text" PrefixI True) ((S1 (MetaSel (Just "string") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [String]) :*: S1 (MetaSel (Just "fontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Node))) :*: (S1 (MetaSel (Just "length") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Float]) :*: S1 (MetaSel (Just "maxExtent") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Float)))) | |
data TextureCoordinate Source #
Constructors
| TextureCoordinate | |
Instances
data TextureTransform Source #
Constructors
| TextureTransform | |
Instances
data TimeSensor Source #
Constructors
| TimeSensor | |
Instances
data TouchSensor Source #
Constructors
| TouchSensor | |
Instances
| Eq TouchSensor Source # | |
Defined in Data.VRML.Nodes | |
| Show TouchSensor Source # | |
Defined in Data.VRML.Nodes Methods showsPrec :: Int -> TouchSensor -> ShowS # show :: TouchSensor -> String # showList :: [TouchSensor] -> ShowS # | |
| Generic TouchSensor Source # | |
Defined in Data.VRML.Nodes Associated Types type Rep TouchSensor :: Type -> Type # | |
| ToNode TouchSensor Source # | |
Defined in Data.VRML.Nodes Methods toNode :: NodeLike b => TouchSensor -> b Source # | |
| type Rep TouchSensor Source # | |
Defined in Data.VRML.Nodes type Rep TouchSensor = D1 (MetaData "TouchSensor" "Data.VRML.Nodes" "VRML-0.1.0.0-IThIBRc3XqmAFQAuTjD7j0" False) (C1 (MetaCons "TouchSensor" PrefixI True) (S1 (MetaSel (Just "enabled") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool))) | |
Constructors
| Transform | |
Instances
Constructors
| Viewpoint | |
Fields
| |
Instances
| Eq Viewpoint Source # | |
| Show Viewpoint Source # | |
| Generic Viewpoint Source # | |
| ToNode Viewpoint Source # | |
| type Rep Viewpoint Source # | |
Defined in Data.VRML.Nodes type Rep Viewpoint = D1 (MetaData "Viewpoint" "Data.VRML.Nodes" "VRML-0.1.0.0-IThIBRc3XqmAFQAuTjD7j0" False) (C1 (MetaCons "Viewpoint" PrefixI True) ((S1 (MetaSel (Just "fieldOfView") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Float) :*: S1 (MetaSel (Just "jump") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) :*: (S1 (MetaSel (Just "orientation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Float, Float, Float, Float)) :*: (S1 (MetaSel (Just "position") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Float, Float, Float)) :*: S1 (MetaSel (Just "description") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))))) | |
data VisibilitySensor Source #
Constructors
| VisibilitySensor | |
Instances
Instances
| Eq WorldInfo Source # | |
| Show WorldInfo Source # | |
| Generic WorldInfo Source # | |
| ToNode WorldInfo Source # | |
| type Rep WorldInfo Source # | |
Defined in Data.VRML.Nodes type Rep WorldInfo = D1 (MetaData "WorldInfo" "Data.VRML.Nodes" "VRML-0.1.0.0-IThIBRc3XqmAFQAuTjD7j0" False) (C1 (MetaCons "WorldInfo" PrefixI True) (S1 (MetaSel (Just "info") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [String]) :*: S1 (MetaSel (Just "title") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))) | |