Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Data.VRML.Types
Documentation
Constructors
VRML | |
Fields
|
Instances
Eq VRML Source # | |
Show VRML Source # | |
Generic VRML Source # | |
Pretty VRML Source # | |
Defined in Data.VRML.Text | |
Pretty VRML Source # | |
Defined in Data.VRML.Proto | |
type Rep VRML Source # | |
Defined in Data.VRML.Types type Rep VRML = D1 (MetaData "VRML" "Data.VRML.Types" "VRML-0.1.0.0-IThIBRc3XqmAFQAuTjD7j0" False) (C1 (MetaCons "VRML" PrefixI True) (S1 (MetaSel (Just "version") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Just "statements") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Statement]))) |
Constructors
StNode NodeStatement | |
StProto ProtoStatement | |
StRoute Route |
Instances
Eq Statement Source # | |
Show Statement Source # | |
Generic Statement Source # | |
Pretty Statement Source # | |
Defined in Data.VRML.Text | |
Pretty Statement Source # | |
Defined in Data.VRML.Proto | |
NodeLike Statement Source # | |
Defined in Data.VRML.Types Methods node :: NodeTypeId -> [NodeBodyElement] -> Statement Source # | |
type Rep Statement Source # | |
Defined in Data.VRML.Types type Rep Statement = D1 (MetaData "Statement" "Data.VRML.Types" "VRML-0.1.0.0-IThIBRc3XqmAFQAuTjD7j0" False) (C1 (MetaCons "StNode" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 NodeStatement)) :+: (C1 (MetaCons "StProto" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ProtoStatement)) :+: C1 (MetaCons "StRoute" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Route)))) |
class NodeLike a where Source #
Methods
node :: NodeTypeId -> [NodeBodyElement] -> a Source #
Instances
NodeLike FieldValue Source # | |
Defined in Data.VRML.Types Methods node :: NodeTypeId -> [NodeBodyElement] -> FieldValue Source # | |
NodeLike Node Source # | |
Defined in Data.VRML.Types Methods node :: NodeTypeId -> [NodeBodyElement] -> Node Source # | |
NodeLike NodeStatement Source # | |
Defined in Data.VRML.Types Methods node :: NodeTypeId -> [NodeBodyElement] -> NodeStatement Source # | |
NodeLike Statement Source # | |
Defined in Data.VRML.Types Methods node :: NodeTypeId -> [NodeBodyElement] -> Statement Source # |
data NodeStatement Source #
Constructors
NodeStatement Node | |
DEF NodeNameId Node | |
USE NodeNameId |
Instances
data ProtoStatement Source #
Constructors
Proto NodeTypeId [Interface] [ProtoStatement] Node [Statement] | |
ExternProto NodeTypeId [ExternInterface] URLList |
Instances
data RestrictedInterface Source #
Constructors
RestrictedInterfaceEventIn FieldType EventInId | |
RestrictedInterfaceEventOut FieldType EventOutId | |
RestrictedInterfaceField FieldType FieldId FieldValue |
Instances
Constructors
InterfaceEventIn FieldType EventInId | |
InterfaceEventOut FieldType EventOutId | |
InterfaceField FieldType FieldId FieldValue | |
InterfaceExposedField FieldType FieldId FieldValue |
Instances
data ExternInterface Source #
Constructors
ExternInterfaceEventIn FieldType EventInId | |
ExternInterfaceEventOut FieldType EventOutId | |
ExternInterfaceField FieldType FieldId | |
ExternInterfaceExposedField FieldType FieldId |
Instances
Constructors
Route NodeNameId EventOutId NodeNameId EventInId |
Instances
Eq Route Source # | |
Show Route Source # | |
Generic Route Source # | |
Pretty Route Source # | |
Defined in Data.VRML.Text | |
Pretty Route Source # | |
Defined in Data.VRML.Proto | |
type Rep Route Source # | |
Defined in Data.VRML.Types type Rep Route = D1 (MetaData "Route" "Data.VRML.Types" "VRML-0.1.0.0-IThIBRc3XqmAFQAuTjD7j0" False) (C1 (MetaCons "Route" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 NodeNameId) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 EventOutId)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 NodeNameId) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 EventInId)))) |
Constructors
Node NodeTypeId [NodeBodyElement] | |
Script [ScriptBodyElement] |
Instances
Eq Node Source # | |
Show Node Source # | |
Generic Node Source # | |
Semigroup Node Source # | |
Monoid Node Source # | |
Pretty Node Source # | |
Defined in Data.VRML.Text | |
Pretty Node Source # | |
Defined in Data.VRML.Proto | |
ToNode Node Source # | |
NodeLike Node Source # | |
Defined in Data.VRML.Types Methods node :: NodeTypeId -> [NodeBodyElement] -> Node Source # | |
ToNode [Node] Source # | |
type Rep Node Source # | |
Defined in Data.VRML.Types type Rep Node = D1 (MetaData "Node" "Data.VRML.Types" "VRML-0.1.0.0-IThIBRc3XqmAFQAuTjD7j0" False) (C1 (MetaCons "Node" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 NodeTypeId) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [NodeBodyElement])) :+: C1 (MetaCons "Script" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ScriptBodyElement]))) |
data ScriptBodyElement Source #
Constructors
SBNode NodeBodyElement | |
SBRestrictedInterface RestrictedInterface | |
SBEventIn FieldType EventInId EventInId | |
SBEventOut FieldType EventOutId EventOutId | |
SBFieldId FieldType FieldId FieldId |
Instances
data NodeBodyElement Source #
Constructors
FV FieldId FieldValue | |
NBFieldId FieldId FieldId | |
NBEventIn EventInId EventInId | |
NBEventOut EventOutId EventOutId | |
NBRoute Route | |
NBProto ProtoStatement |
Instances
newtype NodeNameId Source #
Constructors
NodeNameId String |
Instances
Eq NodeNameId Source # | |
Defined in Data.VRML.Types | |
Show NodeNameId Source # | |
Defined in Data.VRML.Types Methods showsPrec :: Int -> NodeNameId -> ShowS # show :: NodeNameId -> String # showList :: [NodeNameId] -> ShowS # | |
IsString NodeNameId Source # | |
Defined in Data.VRML.Types Methods fromString :: String -> NodeNameId # | |
Generic NodeNameId Source # | |
Defined in Data.VRML.Types Associated Types type Rep NodeNameId :: Type -> Type # | |
Pretty NodeNameId Source # | |
Defined in Data.VRML.Text | |
Pretty NodeNameId Source # | |
Defined in Data.VRML.Proto | |
type Rep NodeNameId Source # | |
Defined in Data.VRML.Types type Rep NodeNameId = D1 (MetaData "NodeNameId" "Data.VRML.Types" "VRML-0.1.0.0-IThIBRc3XqmAFQAuTjD7j0" True) (C1 (MetaCons "NodeNameId" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))) |
newtype NodeTypeId Source #
Constructors
NodeTypeId String |
Instances
Eq NodeTypeId Source # | |
Defined in Data.VRML.Types | |
Show NodeTypeId Source # | |
Defined in Data.VRML.Types Methods showsPrec :: Int -> NodeTypeId -> ShowS # show :: NodeTypeId -> String # showList :: [NodeTypeId] -> ShowS # | |
IsString NodeTypeId Source # | |
Defined in Data.VRML.Types Methods fromString :: String -> NodeTypeId # | |
Generic NodeTypeId Source # | |
Defined in Data.VRML.Types Associated Types type Rep NodeTypeId :: Type -> Type # | |
Pretty NodeTypeId Source # | |
Defined in Data.VRML.Text | |
Pretty NodeTypeId Source # | |
Defined in Data.VRML.Proto | |
type Rep NodeTypeId Source # | |
Defined in Data.VRML.Types type Rep NodeTypeId = D1 (MetaData "NodeTypeId" "Data.VRML.Types" "VRML-0.1.0.0-IThIBRc3XqmAFQAuTjD7j0" True) (C1 (MetaCons "NodeTypeId" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))) |
Instances
Eq FieldId Source # | |
Show FieldId Source # | |
IsString FieldId Source # | |
Defined in Data.VRML.Types Methods fromString :: String -> FieldId # | |
Generic FieldId Source # | |
Pretty FieldId Source # | |
Defined in Data.VRML.Text | |
Pretty FieldId Source # | |
Defined in Data.VRML.Proto | |
type Rep FieldId Source # | |
Defined in Data.VRML.Types |
Instances
Eq EventInId Source # | |
Show EventInId Source # | |
IsString EventInId Source # | |
Defined in Data.VRML.Types Methods fromString :: String -> EventInId # | |
Generic EventInId Source # | |
Pretty EventInId Source # | |
Defined in Data.VRML.Text | |
Pretty EventInId Source # | |
Defined in Data.VRML.Proto | |
type Rep EventInId Source # | |
Defined in Data.VRML.Types |
newtype EventOutId Source #
Constructors
EventOutId String |
Instances
Eq EventOutId Source # | |
Defined in Data.VRML.Types | |
Show EventOutId Source # | |
Defined in Data.VRML.Types Methods showsPrec :: Int -> EventOutId -> ShowS # show :: EventOutId -> String # showList :: [EventOutId] -> ShowS # | |
IsString EventOutId Source # | |
Defined in Data.VRML.Types Methods fromString :: String -> EventOutId # | |
Generic EventOutId Source # | |
Defined in Data.VRML.Types Associated Types type Rep EventOutId :: Type -> Type # | |
Pretty EventOutId Source # | |
Defined in Data.VRML.Text | |
Pretty EventOutId Source # | |
Defined in Data.VRML.Proto | |
type Rep EventOutId Source # | |
Defined in Data.VRML.Types type Rep EventOutId = D1 (MetaData "EventOutId" "Data.VRML.Types" "VRML-0.1.0.0-IThIBRc3XqmAFQAuTjD7j0" True) (C1 (MetaCons "EventOutId" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))) |
Constructors
MFBool | |
MFColor | |
MFFloat | |
MFString | |
MFTime | |
MFVec2f | |
MFVec3f | |
MFNode | |
MFRotation | |
MFInt32 | |
SFBool | |
SFColor | |
SFFloat | |
SFImage | |
SFInt32 | |
SFNode | |
SFRotation | |
SFString | |
SFTime | |
SFVec2f | |
SFVec3f |
Instances
data FieldValue Source #
Constructors
Sbool Bool | |
Scolor Color | |
Sfloat Float | |
Simage [Int32] | |
Sint32 Int32 | |
Snode (Maybe NodeStatement) | |
Srotation (Float, Float, Float, Float) | |
Sstring String | |
Stime Time | |
Svec2f (Float, Float) | |
Svec3f (Float, Float, Float) | |
Mbool [Bool] | |
Mcolor [Color] | |
Mfloat [Float] | |
Mint32 [Int32] | |
Mnode [NodeStatement] | |
Mrotation [(Float, Float, Float, Float)] | |
Mstring [String] | |
Mtime [Time] | |
Mvec2f [(Float, Float)] | |
Mvec3f [(Float, Float, Float)] |
Instances
Minimal complete definition
Nothing
Methods
toNode :: NodeLike b => a -> b Source #
toNode :: (Generic a, ToNode' (Rep a), NodeLike b) => a -> b Source #
Instances
class ToNode' f where Source #
Instances
ToNode' (U1 :: Type -> Type) Source # | |
ToNode c => ToNode' (K1 i c :: Type -> Type) Source # | |
(ToNode' f, ToNode' g) => ToNode' (f :+: g) Source # | |
(ToNode' f, ToNode' g) => ToNode' (f :*: g) Source # | |
ToNode' f => ToNode' (M1 D c f) Source # | |
(Constructor c, ToNode' f) => ToNode' (M1 C c f) Source # | |
(Selector c, ToNode' f) => ToNode' (M1 S c f) Source # | |