VRML-0.1.0.0: VRML parser and generator for Haskell

Safe HaskellSafe
LanguageHaskell2010

Data.VRML.Types

Documentation

data VRML Source #

Constructors

VRML 
Instances
Eq VRML Source # 
Instance details

Defined in Data.VRML.Types

Methods

(==) :: VRML -> VRML -> Bool #

(/=) :: VRML -> VRML -> Bool #

Show VRML Source # 
Instance details

Defined in Data.VRML.Types

Methods

showsPrec :: Int -> VRML -> ShowS #

show :: VRML -> String #

showList :: [VRML] -> ShowS #

Generic VRML Source # 
Instance details

Defined in Data.VRML.Types

Associated Types

type Rep VRML :: Type -> Type #

Methods

from :: VRML -> Rep VRML x #

to :: Rep VRML x -> VRML #

Pretty VRML Source # 
Instance details

Defined in Data.VRML.Text

Methods

pretty :: VRML -> Doc ann #

prettyList :: [VRML] -> Doc ann #

Pretty VRML Source # 
Instance details

Defined in Data.VRML.Proto

Methods

pretty :: VRML -> Doc ann #

prettyList :: [VRML] -> Doc ann #

type Rep VRML Source # 
Instance details

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])))

data Statement Source #

Instances
Eq Statement Source # 
Instance details

Defined in Data.VRML.Types

Show Statement Source # 
Instance details

Defined in Data.VRML.Types

Generic Statement Source # 
Instance details

Defined in Data.VRML.Types

Associated Types

type Rep Statement :: Type -> Type #

Pretty Statement Source # 
Instance details

Defined in Data.VRML.Text

Methods

pretty :: Statement -> Doc ann #

prettyList :: [Statement] -> Doc ann #

Pretty Statement Source # 
Instance details

Defined in Data.VRML.Proto

Methods

pretty :: Statement -> Doc ann #

prettyList :: [Statement] -> Doc ann #

NodeLike Statement Source # 
Instance details

Defined in Data.VRML.Types

type Rep Statement Source # 
Instance details

Defined in Data.VRML.Types

class NodeLike a where Source #

Methods

node :: NodeTypeId -> [NodeBodyElement] -> a Source #

Instances
NodeLike FieldValue Source # 
Instance details

Defined in Data.VRML.Types

NodeLike Node Source # 
Instance details

Defined in Data.VRML.Types

NodeLike NodeStatement Source # 
Instance details

Defined in Data.VRML.Types

NodeLike Statement Source # 
Instance details

Defined in Data.VRML.Types

data NodeStatement Source #

Instances
Eq NodeStatement Source # 
Instance details

Defined in Data.VRML.Types

Show NodeStatement Source # 
Instance details

Defined in Data.VRML.Types

Generic NodeStatement Source # 
Instance details

Defined in Data.VRML.Types

Associated Types

type Rep NodeStatement :: Type -> Type #

Pretty NodeStatement Source # 
Instance details

Defined in Data.VRML.Text

Methods

pretty :: NodeStatement -> Doc ann #

prettyList :: [NodeStatement] -> Doc ann #

Pretty NodeStatement Source # 
Instance details

Defined in Data.VRML.Proto

Methods

pretty :: NodeStatement -> Doc ann #

prettyList :: [NodeStatement] -> Doc ann #

NodeLike NodeStatement Source # 
Instance details

Defined in Data.VRML.Types

type Rep NodeStatement Source # 
Instance details

Defined in Data.VRML.Types

data ProtoStatement Source #

Instances
Eq ProtoStatement Source # 
Instance details

Defined in Data.VRML.Types

Show ProtoStatement Source # 
Instance details

Defined in Data.VRML.Types

Generic ProtoStatement Source # 
Instance details

Defined in Data.VRML.Types

Associated Types

type Rep ProtoStatement :: Type -> Type #

Pretty ProtoStatement Source # 
Instance details

Defined in Data.VRML.Text

Methods

pretty :: ProtoStatement -> Doc ann #

prettyList :: [ProtoStatement] -> Doc ann #

Pretty ProtoStatement Source # 
Instance details

Defined in Data.VRML.Proto

Methods

pretty :: ProtoStatement -> Doc ann #

prettyList :: [ProtoStatement] -> Doc ann #

type Rep ProtoStatement Source # 
Instance details

Defined in Data.VRML.Types

data RestrictedInterface Source #

Instances
Eq RestrictedInterface Source # 
Instance details

Defined in Data.VRML.Types

Show RestrictedInterface Source # 
Instance details

Defined in Data.VRML.Types

Generic RestrictedInterface Source # 
Instance details

Defined in Data.VRML.Types

Associated Types

type Rep RestrictedInterface :: Type -> Type #

Pretty RestrictedInterface Source # 
Instance details

Defined in Data.VRML.Text

Pretty RestrictedInterface Source # 
Instance details

Defined in Data.VRML.Proto

type Rep RestrictedInterface Source # 
Instance details

Defined in Data.VRML.Types

data Interface Source #

Instances
Eq Interface Source # 
Instance details

Defined in Data.VRML.Types

Show Interface Source # 
Instance details

Defined in Data.VRML.Types

Generic Interface Source # 
Instance details

Defined in Data.VRML.Types

Associated Types

type Rep Interface :: Type -> Type #

Pretty Interface Source # 
Instance details

Defined in Data.VRML.Text

Methods

pretty :: Interface -> Doc ann #

prettyList :: [Interface] -> Doc ann #

Pretty Interface Source # 
Instance details

Defined in Data.VRML.Proto

Methods

pretty :: Interface -> Doc ann #

prettyList :: [Interface] -> Doc ann #

type Rep Interface Source # 
Instance details

Defined in Data.VRML.Types

data ExternInterface Source #

Instances
Eq ExternInterface Source # 
Instance details

Defined in Data.VRML.Types

Show ExternInterface Source # 
Instance details

Defined in Data.VRML.Types

Generic ExternInterface Source # 
Instance details

Defined in Data.VRML.Types

Associated Types

type Rep ExternInterface :: Type -> Type #

Pretty ExternInterface Source # 
Instance details

Defined in Data.VRML.Text

Pretty ExternInterface Source # 
Instance details

Defined in Data.VRML.Proto

type Rep ExternInterface Source # 
Instance details

Defined in Data.VRML.Types

data Route Source #

Instances
Eq Route Source # 
Instance details

Defined in Data.VRML.Types

Methods

(==) :: Route -> Route -> Bool #

(/=) :: Route -> Route -> Bool #

Show Route Source # 
Instance details

Defined in Data.VRML.Types

Methods

showsPrec :: Int -> Route -> ShowS #

show :: Route -> String #

showList :: [Route] -> ShowS #

Generic Route Source # 
Instance details

Defined in Data.VRML.Types

Associated Types

type Rep Route :: Type -> Type #

Methods

from :: Route -> Rep Route x #

to :: Rep Route x -> Route #

Pretty Route Source # 
Instance details

Defined in Data.VRML.Text

Methods

pretty :: Route -> Doc ann #

prettyList :: [Route] -> Doc ann #

Pretty Route Source # 
Instance details

Defined in Data.VRML.Proto

Methods

pretty :: Route -> Doc ann #

prettyList :: [Route] -> Doc ann #

type Rep Route Source # 
Instance details

Defined in Data.VRML.Types

newtype URLList Source #

Constructors

URLList [String] 
Instances
Eq URLList Source # 
Instance details

Defined in Data.VRML.Types

Methods

(==) :: URLList -> URLList -> Bool #

(/=) :: URLList -> URLList -> Bool #

Show URLList Source # 
Instance details

Defined in Data.VRML.Types

Generic URLList Source # 
Instance details

Defined in Data.VRML.Types

Associated Types

type Rep URLList :: Type -> Type #

Methods

from :: URLList -> Rep URLList x #

to :: Rep URLList x -> URLList #

Pretty URLList Source # 
Instance details

Defined in Data.VRML.Text

Methods

pretty :: URLList -> Doc ann #

prettyList :: [URLList] -> Doc ann #

Pretty URLList Source # 
Instance details

Defined in Data.VRML.Proto

Methods

pretty :: URLList -> Doc ann #

prettyList :: [URLList] -> Doc ann #

type Rep URLList Source # 
Instance details

Defined in Data.VRML.Types

type Rep URLList = D1 (MetaData "URLList" "Data.VRML.Types" "VRML-0.1.0.0-IThIBRc3XqmAFQAuTjD7j0" True) (C1 (MetaCons "URLList" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [String])))

data Node Source #

Instances
Eq Node Source # 
Instance details

Defined in Data.VRML.Types

Methods

(==) :: Node -> Node -> Bool #

(/=) :: Node -> Node -> Bool #

Show Node Source # 
Instance details

Defined in Data.VRML.Types

Methods

showsPrec :: Int -> Node -> ShowS #

show :: Node -> String #

showList :: [Node] -> ShowS #

Generic Node Source # 
Instance details

Defined in Data.VRML.Types

Associated Types

type Rep Node :: Type -> Type #

Methods

from :: Node -> Rep Node x #

to :: Rep Node x -> Node #

Semigroup Node Source # 
Instance details

Defined in Data.VRML.Types

Methods

(<>) :: Node -> Node -> Node #

sconcat :: NonEmpty Node -> Node #

stimes :: Integral b => b -> Node -> Node #

Monoid Node Source # 
Instance details

Defined in Data.VRML.Types

Methods

mempty :: Node #

mappend :: Node -> Node -> Node #

mconcat :: [Node] -> Node #

Pretty Node Source # 
Instance details

Defined in Data.VRML.Text

Methods

pretty :: Node -> Doc ann #

prettyList :: [Node] -> Doc ann #

Pretty Node Source # 
Instance details

Defined in Data.VRML.Proto

Methods

pretty :: Node -> Doc ann #

prettyList :: [Node] -> Doc ann #

ToNode Node Source # 
Instance details

Defined in Data.VRML.Types

Methods

toNode :: NodeLike b => Node -> b Source #

NodeLike Node Source # 
Instance details

Defined in Data.VRML.Types

ToNode [Node] Source # 
Instance details

Defined in Data.VRML.Types

Methods

toNode :: NodeLike b => [Node] -> b Source #

type Rep Node Source # 
Instance details

Defined in Data.VRML.Types

data ScriptBodyElement Source #

Instances
Eq ScriptBodyElement Source # 
Instance details

Defined in Data.VRML.Types

Show ScriptBodyElement Source # 
Instance details

Defined in Data.VRML.Types

Generic ScriptBodyElement Source # 
Instance details

Defined in Data.VRML.Types

Associated Types

type Rep ScriptBodyElement :: Type -> Type #

Pretty ScriptBodyElement Source # 
Instance details

Defined in Data.VRML.Text

Pretty ScriptBodyElement Source # 
Instance details

Defined in Data.VRML.Proto

type Rep ScriptBodyElement Source # 
Instance details

Defined in Data.VRML.Types

type Rep ScriptBodyElement = D1 (MetaData "ScriptBodyElement" "Data.VRML.Types" "VRML-0.1.0.0-IThIBRc3XqmAFQAuTjD7j0" False) ((C1 (MetaCons "SBNode" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 NodeBodyElement)) :+: C1 (MetaCons "SBRestrictedInterface" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 RestrictedInterface))) :+: (C1 (MetaCons "SBEventIn" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FieldType) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 EventInId) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 EventInId))) :+: (C1 (MetaCons "SBEventOut" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FieldType) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 EventOutId) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 EventOutId))) :+: C1 (MetaCons "SBFieldId" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FieldType) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FieldId) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FieldId))))))

data NodeBodyElement Source #

Instances
Eq NodeBodyElement Source # 
Instance details

Defined in Data.VRML.Types

Show NodeBodyElement Source # 
Instance details

Defined in Data.VRML.Types

Generic NodeBodyElement Source # 
Instance details

Defined in Data.VRML.Types

Associated Types

type Rep NodeBodyElement :: Type -> Type #

Pretty NodeBodyElement Source # 
Instance details

Defined in Data.VRML.Text

Pretty NodeBodyElement Source # 
Instance details

Defined in Data.VRML.Proto

type Rep NodeBodyElement Source # 
Instance details

Defined in Data.VRML.Types

newtype NodeNameId Source #

Constructors

NodeNameId String 
Instances
Eq NodeNameId Source # 
Instance details

Defined in Data.VRML.Types

Show NodeNameId Source # 
Instance details

Defined in Data.VRML.Types

IsString NodeNameId Source # 
Instance details

Defined in Data.VRML.Types

Generic NodeNameId Source # 
Instance details

Defined in Data.VRML.Types

Associated Types

type Rep NodeNameId :: Type -> Type #

Pretty NodeNameId Source # 
Instance details

Defined in Data.VRML.Text

Methods

pretty :: NodeNameId -> Doc ann #

prettyList :: [NodeNameId] -> Doc ann #

Pretty NodeNameId Source # 
Instance details

Defined in Data.VRML.Proto

Methods

pretty :: NodeNameId -> Doc ann #

prettyList :: [NodeNameId] -> Doc ann #

type Rep NodeNameId Source # 
Instance details

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 # 
Instance details

Defined in Data.VRML.Types

Show NodeTypeId Source # 
Instance details

Defined in Data.VRML.Types

IsString NodeTypeId Source # 
Instance details

Defined in Data.VRML.Types

Generic NodeTypeId Source # 
Instance details

Defined in Data.VRML.Types

Associated Types

type Rep NodeTypeId :: Type -> Type #

Pretty NodeTypeId Source # 
Instance details

Defined in Data.VRML.Text

Methods

pretty :: NodeTypeId -> Doc ann #

prettyList :: [NodeTypeId] -> Doc ann #

Pretty NodeTypeId Source # 
Instance details

Defined in Data.VRML.Proto

Methods

pretty :: NodeTypeId -> Doc ann #

prettyList :: [NodeTypeId] -> Doc ann #

type Rep NodeTypeId Source # 
Instance details

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)))

newtype FieldId Source #

Constructors

FieldId String 
Instances
Eq FieldId Source # 
Instance details

Defined in Data.VRML.Types

Methods

(==) :: FieldId -> FieldId -> Bool #

(/=) :: FieldId -> FieldId -> Bool #

Show FieldId Source # 
Instance details

Defined in Data.VRML.Types

IsString FieldId Source # 
Instance details

Defined in Data.VRML.Types

Methods

fromString :: String -> FieldId #

Generic FieldId Source # 
Instance details

Defined in Data.VRML.Types

Associated Types

type Rep FieldId :: Type -> Type #

Methods

from :: FieldId -> Rep FieldId x #

to :: Rep FieldId x -> FieldId #

Pretty FieldId Source # 
Instance details

Defined in Data.VRML.Text

Methods

pretty :: FieldId -> Doc ann #

prettyList :: [FieldId] -> Doc ann #

Pretty FieldId Source # 
Instance details

Defined in Data.VRML.Proto

Methods

pretty :: FieldId -> Doc ann #

prettyList :: [FieldId] -> Doc ann #

type Rep FieldId Source # 
Instance details

Defined in Data.VRML.Types

type Rep FieldId = D1 (MetaData "FieldId" "Data.VRML.Types" "VRML-0.1.0.0-IThIBRc3XqmAFQAuTjD7j0" True) (C1 (MetaCons "FieldId" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))

newtype EventInId Source #

Constructors

EventInId String 
Instances
Eq EventInId Source # 
Instance details

Defined in Data.VRML.Types

Show EventInId Source # 
Instance details

Defined in Data.VRML.Types

IsString EventInId Source # 
Instance details

Defined in Data.VRML.Types

Generic EventInId Source # 
Instance details

Defined in Data.VRML.Types

Associated Types

type Rep EventInId :: Type -> Type #

Pretty EventInId Source # 
Instance details

Defined in Data.VRML.Text

Methods

pretty :: EventInId -> Doc ann #

prettyList :: [EventInId] -> Doc ann #

Pretty EventInId Source # 
Instance details

Defined in Data.VRML.Proto

Methods

pretty :: EventInId -> Doc ann #

prettyList :: [EventInId] -> Doc ann #

type Rep EventInId Source # 
Instance details

Defined in Data.VRML.Types

type Rep EventInId = D1 (MetaData "EventInId" "Data.VRML.Types" "VRML-0.1.0.0-IThIBRc3XqmAFQAuTjD7j0" True) (C1 (MetaCons "EventInId" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))

newtype EventOutId Source #

Constructors

EventOutId String 
Instances
Eq EventOutId Source # 
Instance details

Defined in Data.VRML.Types

Show EventOutId Source # 
Instance details

Defined in Data.VRML.Types

IsString EventOutId Source # 
Instance details

Defined in Data.VRML.Types

Generic EventOutId Source # 
Instance details

Defined in Data.VRML.Types

Associated Types

type Rep EventOutId :: Type -> Type #

Pretty EventOutId Source # 
Instance details

Defined in Data.VRML.Text

Methods

pretty :: EventOutId -> Doc ann #

prettyList :: [EventOutId] -> Doc ann #

Pretty EventOutId Source # 
Instance details

Defined in Data.VRML.Proto

Methods

pretty :: EventOutId -> Doc ann #

prettyList :: [EventOutId] -> Doc ann #

type Rep EventOutId Source # 
Instance details

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)))

data FieldType Source #

Instances
Eq FieldType Source # 
Instance details

Defined in Data.VRML.Types

Show FieldType Source # 
Instance details

Defined in Data.VRML.Types

Generic FieldType Source # 
Instance details

Defined in Data.VRML.Types

Associated Types

type Rep FieldType :: Type -> Type #

Pretty FieldType Source # 
Instance details

Defined in Data.VRML.Text

Methods

pretty :: FieldType -> Doc ann #

prettyList :: [FieldType] -> Doc ann #

Pretty FieldType Source # 
Instance details

Defined in Data.VRML.Proto

Methods

pretty :: FieldType -> Doc ann #

prettyList :: [FieldType] -> Doc ann #

type Rep FieldType Source # 
Instance details

Defined in Data.VRML.Types

type Rep FieldType = D1 (MetaData "FieldType" "Data.VRML.Types" "VRML-0.1.0.0-IThIBRc3XqmAFQAuTjD7j0" False) ((((C1 (MetaCons "MFBool" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "MFColor" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "MFFloat" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "MFString" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "MFTime" PrefixI False) (U1 :: Type -> Type)))) :+: ((C1 (MetaCons "MFVec2f" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "MFVec3f" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "MFNode" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "MFRotation" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "MFInt32" PrefixI False) (U1 :: Type -> Type))))) :+: (((C1 (MetaCons "SFBool" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "SFColor" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "SFFloat" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "SFImage" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "SFInt32" PrefixI False) (U1 :: Type -> Type)))) :+: ((C1 (MetaCons "SFNode" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "SFRotation" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "SFString" PrefixI False) (U1 :: Type -> Type))) :+: (C1 (MetaCons "SFTime" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "SFVec2f" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "SFVec3f" PrefixI False) (U1 :: Type -> Type))))))

newtype Color Source #

Constructors

Color (Float, Float, Float) 
Instances
Eq Color Source # 
Instance details

Defined in Data.VRML.Types

Methods

(==) :: Color -> Color -> Bool #

(/=) :: Color -> Color -> Bool #

Show Color Source # 
Instance details

Defined in Data.VRML.Types

Methods

showsPrec :: Int -> Color -> ShowS #

show :: Color -> String #

showList :: [Color] -> ShowS #

Generic Color Source # 
Instance details

Defined in Data.VRML.Types

Associated Types

type Rep Color :: Type -> Type #

Methods

from :: Color -> Rep Color x #

to :: Rep Color x -> Color #

ToNode Color Source # 
Instance details

Defined in Data.VRML.Types

Methods

toNode :: NodeLike b => Color -> b Source #

ToNode [Color] Source # 
Instance details

Defined in Data.VRML.Types

Methods

toNode :: NodeLike b => [Color] -> b Source #

type Rep Color Source # 
Instance details

Defined in Data.VRML.Types

type Rep Color = D1 (MetaData "Color" "Data.VRML.Types" "VRML-0.1.0.0-IThIBRc3XqmAFQAuTjD7j0" True) (C1 (MetaCons "Color" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Float, Float, Float))))

newtype Time Source #

Constructors

Time Double 
Instances
Eq Time Source # 
Instance details

Defined in Data.VRML.Types

Methods

(==) :: Time -> Time -> Bool #

(/=) :: Time -> Time -> Bool #

Show Time Source # 
Instance details

Defined in Data.VRML.Types

Methods

showsPrec :: Int -> Time -> ShowS #

show :: Time -> String #

showList :: [Time] -> ShowS #

Generic Time Source # 
Instance details

Defined in Data.VRML.Types

Associated Types

type Rep Time :: Type -> Type #

Methods

from :: Time -> Rep Time x #

to :: Rep Time x -> Time #

ToNode Time Source # 
Instance details

Defined in Data.VRML.Types

Methods

toNode :: NodeLike b => Time -> b Source #

ToNode [Time] Source # 
Instance details

Defined in Data.VRML.Types

Methods

toNode :: NodeLike b => [Time] -> b Source #

type Rep Time Source # 
Instance details

Defined in Data.VRML.Types

type Rep Time = D1 (MetaData "Time" "Data.VRML.Types" "VRML-0.1.0.0-IThIBRc3XqmAFQAuTjD7j0" True) (C1 (MetaCons "Time" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Double)))

data FieldValue Source #

Instances
Eq FieldValue Source # 
Instance details

Defined in Data.VRML.Types

Show FieldValue Source # 
Instance details

Defined in Data.VRML.Types

IsString FieldValue Source # 
Instance details

Defined in Data.VRML.Types

Generic FieldValue Source # 
Instance details

Defined in Data.VRML.Types

Associated Types

type Rep FieldValue :: Type -> Type #

Pretty FieldValue Source # 
Instance details

Defined in Data.VRML.Text

Methods

pretty :: FieldValue -> Doc ann #

prettyList :: [FieldValue] -> Doc ann #

Pretty FieldValue Source # 
Instance details

Defined in Data.VRML.Proto

Methods

pretty :: FieldValue -> Doc ann #

prettyList :: [FieldValue] -> Doc ann #

NodeLike FieldValue Source # 
Instance details

Defined in Data.VRML.Types

type Rep FieldValue Source # 
Instance details

Defined in Data.VRML.Types

type Rep FieldValue = D1 (MetaData "FieldValue" "Data.VRML.Types" "VRML-0.1.0.0-IThIBRc3XqmAFQAuTjD7j0" False) ((((C1 (MetaCons "Sbool" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) :+: C1 (MetaCons "Scolor" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Color))) :+: (C1 (MetaCons "Sfloat" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Float)) :+: (C1 (MetaCons "Simage" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Int32])) :+: C1 (MetaCons "Sint32" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int32))))) :+: ((C1 (MetaCons "Snode" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe NodeStatement))) :+: C1 (MetaCons "Srotation" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Float, Float, Float, Float)))) :+: (C1 (MetaCons "Sstring" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) :+: (C1 (MetaCons "Stime" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Time)) :+: C1 (MetaCons "Svec2f" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Float, Float))))))) :+: (((C1 (MetaCons "Svec3f" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Float, Float, Float))) :+: C1 (MetaCons "Mbool" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Bool]))) :+: (C1 (MetaCons "Mcolor" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Color])) :+: (C1 (MetaCons "Mfloat" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Float])) :+: C1 (MetaCons "Mint32" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Int32]))))) :+: ((C1 (MetaCons "Mnode" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [NodeStatement])) :+: (C1 (MetaCons "Mrotation" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(Float, Float, Float, Float)])) :+: C1 (MetaCons "Mstring" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [String])))) :+: (C1 (MetaCons "Mtime" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Time])) :+: (C1 (MetaCons "Mvec2f" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(Float, Float)])) :+: C1 (MetaCons "Mvec3f" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(Float, Float, Float)])))))))

class ToNode a where Source #

Minimal complete definition

Nothing

Methods

toNode :: NodeLike b => a -> b Source #

toNode :: (Generic a, ToNode' (Rep a), NodeLike b) => a -> b Source #

Instances
ToNode Bool Source # 
Instance details

Defined in Data.VRML.Types

Methods

toNode :: NodeLike b => Bool -> b Source #

ToNode Float Source # 
Instance details

Defined in Data.VRML.Types

Methods

toNode :: NodeLike b => Float -> b Source #

ToNode Int32 Source # 
Instance details

Defined in Data.VRML.Types

Methods

toNode :: NodeLike b => Int32 -> b Source #

ToNode String Source # 
Instance details

Defined in Data.VRML.Types

Methods

toNode :: NodeLike b => String -> b Source #

ToNode Time Source # 
Instance details

Defined in Data.VRML.Types

Methods

toNode :: NodeLike b => Time -> b Source #

ToNode Color Source # 
Instance details

Defined in Data.VRML.Types

Methods

toNode :: NodeLike b => Color -> b Source #

ToNode Node Source # 
Instance details

Defined in Data.VRML.Types

Methods

toNode :: NodeLike b => Node -> b Source #

ToNode WorldInfo Source # 
Instance details

Defined in Data.VRML.Nodes

Methods

toNode :: NodeLike b => WorldInfo -> b Source #

ToNode VisibilitySensor Source # 
Instance details

Defined in Data.VRML.Nodes

ToNode Viewpoint Source # 
Instance details

Defined in Data.VRML.Nodes

Methods

toNode :: NodeLike b => Viewpoint -> b Source #

ToNode Transform Source # 
Instance details

Defined in Data.VRML.Nodes

Methods

toNode :: NodeLike b => Transform -> b Source #

ToNode TouchSensor Source # 
Instance details

Defined in Data.VRML.Nodes

Methods

toNode :: NodeLike b => TouchSensor -> b Source #

ToNode TimeSensor Source # 
Instance details

Defined in Data.VRML.Nodes

Methods

toNode :: NodeLike b => TimeSensor -> b Source #

ToNode TextureTransform Source # 
Instance details

Defined in Data.VRML.Nodes

ToNode TextureCoordinate Source # 
Instance details

Defined in Data.VRML.Nodes

ToNode Text Source # 
Instance details

Defined in Data.VRML.Nodes

Methods

toNode :: NodeLike b => Text -> b Source #

ToNode Switch Source # 
Instance details

Defined in Data.VRML.Nodes

Methods

toNode :: NodeLike b => Switch -> b Source #

ToNode SpotLight Source # 
Instance details

Defined in Data.VRML.Nodes

Methods

toNode :: NodeLike b => SpotLight -> b Source #

ToNode SphereSensor Source # 
Instance details

Defined in Data.VRML.Nodes

Methods

toNode :: NodeLike b => SphereSensor -> b Source #

ToNode Sphere Source # 
Instance details

Defined in Data.VRML.Nodes

Methods

toNode :: NodeLike b => Sphere -> b Source #

ToNode Sound Source # 
Instance details

Defined in Data.VRML.Nodes

Methods

toNode :: NodeLike b => Sound -> b Source #

ToNode Shape Source # 
Instance details

Defined in Data.VRML.Nodes

Methods

toNode :: NodeLike b => Shape -> b Source #

ToNode ScalarInterpolator Source # 
Instance details

Defined in Data.VRML.Nodes

ToNode ProximitySensor Source # 
Instance details

Defined in Data.VRML.Nodes

Methods

toNode :: NodeLike b => ProximitySensor -> b Source #

ToNode PositionInterpolator Source # 
Instance details

Defined in Data.VRML.Nodes

ToNode PointSet Source # 
Instance details

Defined in Data.VRML.Nodes

Methods

toNode :: NodeLike b => PointSet -> b Source #

ToNode PointLight Source # 
Instance details

Defined in Data.VRML.Nodes

Methods

toNode :: NodeLike b => PointLight -> b Source #

ToNode PlaneSensor Source # 
Instance details

Defined in Data.VRML.Nodes

Methods

toNode :: NodeLike b => PlaneSensor -> b Source #

ToNode PixelTexture Source # 
Instance details

Defined in Data.VRML.Nodes

Methods

toNode :: NodeLike b => PixelTexture -> b Source #

ToNode OrientationInterpolator Source # 
Instance details

Defined in Data.VRML.Nodes

ToNode NormalInterpolator Source # 
Instance details

Defined in Data.VRML.Nodes

ToNode Normal Source # 
Instance details

Defined in Data.VRML.Nodes

Methods

toNode :: NodeLike b => Normal -> b Source #

ToNode NavigationInfo Source # 
Instance details

Defined in Data.VRML.Nodes

Methods

toNode :: NodeLike b => NavigationInfo -> b Source #

ToNode MovieTexture Source # 
Instance details

Defined in Data.VRML.Nodes

Methods

toNode :: NodeLike b => MovieTexture -> b Source #

ToNode Material Source # 
Instance details

Defined in Data.VRML.Nodes

Methods

toNode :: NodeLike b => Material -> b Source #

ToNode LOD Source # 
Instance details

Defined in Data.VRML.Nodes

Methods

toNode :: NodeLike b => LOD -> b Source #

ToNode Inline Source # 
Instance details

Defined in Data.VRML.Nodes

Methods

toNode :: NodeLike b => Inline -> b Source #

ToNode IndexedLineSet Source # 
Instance details

Defined in Data.VRML.Nodes

Methods

toNode :: NodeLike b => IndexedLineSet -> b Source #

ToNode IndexedFaceSet Source # 
Instance details

Defined in Data.VRML.Nodes

Methods

toNode :: NodeLike b => IndexedFaceSet -> b Source #

ToNode ImageTexture Source # 
Instance details

Defined in Data.VRML.Nodes

Methods

toNode :: NodeLike b => ImageTexture -> b Source #

ToNode Group Source # 
Instance details

Defined in Data.VRML.Nodes

Methods

toNode :: NodeLike b => Group -> b Source #

ToNode FontStyle Source # 
Instance details

Defined in Data.VRML.Nodes

Methods

toNode :: NodeLike b => FontStyle -> b Source #

ToNode Fog Source # 
Instance details

Defined in Data.VRML.Nodes

Methods

toNode :: NodeLike b => Fog -> b Source #

ToNode Extrusion Source # 
Instance details

Defined in Data.VRML.Nodes

Methods

toNode :: NodeLike b => Extrusion -> b Source #

ToNode ElevationGrid Source # 
Instance details

Defined in Data.VRML.Nodes

Methods

toNode :: NodeLike b => ElevationGrid -> b Source #

ToNode DirectionalLight Source # 
Instance details

Defined in Data.VRML.Nodes

ToNode CylinderSensor Source # 
Instance details

Defined in Data.VRML.Nodes

Methods

toNode :: NodeLike b => CylinderSensor -> b Source #

ToNode Cylinder Source # 
Instance details

Defined in Data.VRML.Nodes

Methods

toNode :: NodeLike b => Cylinder -> b Source #

ToNode CoordinateInterpolator Source # 
Instance details

Defined in Data.VRML.Nodes

ToNode Coordinate Source # 
Instance details

Defined in Data.VRML.Nodes

Methods

toNode :: NodeLike b => Coordinate -> b Source #

ToNode Cone Source # 
Instance details

Defined in Data.VRML.Nodes

Methods

toNode :: NodeLike b => Cone -> b Source #

ToNode ColorInterpolator Source # 
Instance details

Defined in Data.VRML.Nodes

ToNode Collision Source # 
Instance details

Defined in Data.VRML.Nodes

Methods

toNode :: NodeLike b => Collision -> b Source #

ToNode Box Source # 
Instance details

Defined in Data.VRML.Nodes

Methods

toNode :: NodeLike b => Box -> b Source #

ToNode Billboard Source # 
Instance details

Defined in Data.VRML.Nodes

Methods

toNode :: NodeLike b => Billboard -> b Source #

ToNode AudioClip Source # 
Instance details

Defined in Data.VRML.Nodes

Methods

toNode :: NodeLike b => AudioClip -> b Source #

ToNode Appearance Source # 
Instance details

Defined in Data.VRML.Nodes

Methods

toNode :: NodeLike b => Appearance -> b Source #

ToNode Anchor Source # 
Instance details

Defined in Data.VRML.Nodes

Methods

toNode :: NodeLike b => Anchor -> b Source #

ToNode [Bool] Source # 
Instance details

Defined in Data.VRML.Types

Methods

toNode :: NodeLike b => [Bool] -> b Source #

ToNode [Float] Source # 
Instance details

Defined in Data.VRML.Types

Methods

toNode :: NodeLike b => [Float] -> b Source #

ToNode [Int32] Source # 
Instance details

Defined in Data.VRML.Types

Methods

toNode :: NodeLike b => [Int32] -> b Source #

ToNode [(Float, Float)] Source # 
Instance details

Defined in Data.VRML.Types

Methods

toNode :: NodeLike b => [(Float, Float)] -> b Source #

ToNode [(Float, Float, Float)] Source # 
Instance details

Defined in Data.VRML.Types

Methods

toNode :: NodeLike b => [(Float, Float, Float)] -> b Source #

ToNode [(Float, Float, Float, Float)] Source # 
Instance details

Defined in Data.VRML.Types

Methods

toNode :: NodeLike b => [(Float, Float, Float, Float)] -> b Source #

ToNode [String] Source # 
Instance details

Defined in Data.VRML.Types

Methods

toNode :: NodeLike b => [String] -> b Source #

ToNode [Time] Source # 
Instance details

Defined in Data.VRML.Types

Methods

toNode :: NodeLike b => [Time] -> b Source #

ToNode [Color] Source # 
Instance details

Defined in Data.VRML.Types

Methods

toNode :: NodeLike b => [Color] -> b Source #

ToNode [Node] Source # 
Instance details

Defined in Data.VRML.Types

Methods

toNode :: NodeLike b => [Node] -> b Source #

ToNode a => ToNode (Maybe a) Source # 
Instance details

Defined in Data.VRML.Types

Methods

toNode :: NodeLike b => Maybe a -> b Source #

ToNode (Float, Float) Source # 
Instance details

Defined in Data.VRML.Types

Methods

toNode :: NodeLike b => (Float, Float) -> b Source #

ToNode (Float, Float, Float) Source # 
Instance details

Defined in Data.VRML.Types

Methods

toNode :: NodeLike b => (Float, Float, Float) -> b Source #

ToNode (Float, Float, Float, Float) Source # 
Instance details

Defined in Data.VRML.Types

Methods

toNode :: NodeLike b => (Float, Float, Float, Float) -> b Source #

class ToNode' f where Source #

Methods

toNode' :: f a -> Node Source #

Instances
ToNode' (U1 :: Type -> Type) Source # 
Instance details

Defined in Data.VRML.Types

Methods

toNode' :: U1 a -> Node Source #

ToNode c => ToNode' (K1 i c :: Type -> Type) Source # 
Instance details

Defined in Data.VRML.Types

Methods

toNode' :: K1 i c a -> Node Source #

(ToNode' f, ToNode' g) => ToNode' (f :+: g) Source # 
Instance details

Defined in Data.VRML.Types

Methods

toNode' :: (f :+: g) a -> Node Source #

(ToNode' f, ToNode' g) => ToNode' (f :*: g) Source # 
Instance details

Defined in Data.VRML.Types

Methods

toNode' :: (f :*: g) a -> Node Source #

ToNode' f => ToNode' (M1 D c f) Source # 
Instance details

Defined in Data.VRML.Types

Methods

toNode' :: M1 D c f a -> Node Source #

(Constructor c, ToNode' f) => ToNode' (M1 C c f) Source # 
Instance details

Defined in Data.VRML.Types

Methods

toNode' :: M1 C c f a -> Node Source #

(Selector c, ToNode' f) => ToNode' (M1 S c f) Source # 
Instance details

Defined in Data.VRML.Types

Methods

toNode' :: M1 S c f a -> Node Source #