-- some of the Types are from http://hackage.haskell.org/package/GPipe-Collada -- adopted for possible future combination module Graphics.Formats.Collada.ColladaTypes ( Scene, SceneNode(..), NodeType(..), Transform(..), Camera(..), ViewSize(..), Z(..), Light(..), Attenuation(..), Controller(..), Geometry(..), Mesh(..), Vertices(..), LinePrimitive(..), Polygon(..), -- Polylist(..), Spline(..), TriangleMesh(..), TriFan(..), TriStrip(..), AnimChannel(..), ID, SID, Semantic, Profile(..), NewParam(..), TechniqueCommon(..), Material, Effect, C(..), Color(..), Animations(..), Fx_common_color_type(..), Fx_common_texture_type(..), Texture(..) ) where import Data.Tree import qualified Data.Vec as Vec import Data.Vec (Vec2, Vec3, Mat44, Mat33, (:.)(..), ) type Scene = Tree SceneNode data SceneNode = SceneNode { nodeId :: ID, nodeType :: NodeType, nodeLayers :: [String], nodeTransformations :: [(SID, Transform)], nodeCameras :: [Camera], nodeController :: [Controller], nodeGeometries :: [Geometry], nodeLights :: [Light] } -- deriving (Show) data NodeType = JOINT | NODE | NOTYPE deriving (Show) data Transform = LookAt { lookAtEye:: Vec3 Float, lookAtInterest :: Vec3 Float, lookAtUp :: Vec3 Float } | Matrix (Mat44 Float) | Rotate (Vec3 Float) Float (Vec3 Float) Float (Vec3 Float) Float | Scale (Vec3 Float) | Skew { skewAngle :: Float, skewRotation :: Vec3 Float, skewTranslation :: Vec3 Float } | Translate (Vec3 Float) deriving (Show, Eq) data Camera = Perspective { perspectiveID :: ID, perspectiveFov :: ViewSize, perspectiveZ :: Z } | Orthographic { orthographicID :: ID, orthographicViewSize :: ViewSize, orthographicZ :: Z } deriving (Show, Eq) data ViewSize = ViewSizeX Float | ViewSizeY Float | ViewSizeXY (Float,Float) deriving (Show, Eq) data Z = Z { zNear :: Float, zFar :: Float } deriving (Show, Eq) data Light = Ambient { ambientID :: ID, ambientColor :: Color } | Directional { directionalID :: ID, directionalColor :: Color } | Point { pointID :: ID, pointColor :: Color, pointAttenuation :: Attenuation } | Spot { spotID :: ID, spotColor :: Color, spotAttenuation :: Attenuation, spotFallOffAngle :: Float, spotFallOffExponent :: Float } deriving (Show, Eq) data Attenuation = Attenuation { attenuationConstant :: Float, attenuationLinear :: Float, attenuationQuadratic :: Float } deriving (Show, Eq) data Controller = Controller { contrId :: ID, skin :: [Skin], morph :: [Morph] } deriving (Show) data Skin = Skin { bindShapeMatrix :: [Mat44 Float], source :: [String], joint :: [Joint], vertexWeights :: String } deriving (Show) data Morph = Morph { geometrySource :: String, method :: MorphMethod, morphSource :: String, morphTargets :: [Input] } deriving (Show) data MorphMethod = Normalized | Relative deriving (Show) data Joint = Joint { jointID :: String, prismatic :: Prismatic, revolute :: Revolute } deriving (Show) type Prismatic = String type Revolute = String data Input = Input { offset :: Int, semantic :: Semantic, inputSource :: String, set :: Int } deriving (Show) data Semantic = BINORMAL | COLOR | CONTINUITY | IMAGE | INPUT | IN_TANGENT | INTERPOLATION | INV_BIND_MATRIX | ISJOINT | LINEAR_STEPS | MORPH_TARGET | MORPH_WEIGHT | NORMAL | OUTPUT | OUT_TANGENT | POSITION | TANGENT | TEXBINORMAL | TEXCOORD | TEXTANGENT | UV | VERTEX | WEIGHT deriving (Show) data Geometry = Geometry { meshID :: ID, -- convexMesh :: [Mesh], mesh :: [Mesh], vertices :: Vertices -- splines :: [Spline], -- breps :: [Brep] } -- deriving (Show) instance Eq Geometry where (Geometry mid1 _ _) == (Geometry mid2 _ _) = mid1 == mid2 data Mesh = LP LinePrimitive | LS LinePrimitive | P Polygon | PL LinePrimitive | Tr LinePrimitive | Trf LinePrimitive | Trs LinePrimitive | S LinePrimitive data Vertices = Vertices { name :: ID, verts :: [(Float,Float,Float)], normals :: [(Float,Float,Float)] } data LinePrimitive = LinePrimitive { lineP :: [[Int]], lineN :: [[Int]], ms :: [Material] } data Polygon = Polygon { poylgonP :: [[Int]], poylgonN :: [[Int]], polygonPh :: ([Int],[Int]), -- (indices, indices of a hole) polygonMs :: [Material] } type Material = (SID,Effect) type Effect = Profile -- (ID,Profile) type Animations = Tree (SID, AnimChannel) data AnimChannel = Bezier { -- these 5 items are called sampler in Collada -- we don't need the modularity to define everyone seperately input :: (ID,[Float],Accessor) , -- Accessor: "TIME" output :: (ID,[Float],Accessor), intangent :: (ID,[Float],Accessor), -- for bezier curves: smooth values at the beginnig transition outtangent :: (ID,[Float],Accessor), -- end interpolation :: (ID,[String],Accessor), -- target channels in Collada targets :: [(TargetID,AccessorName)] -- transfer values to several objects } type TargetID = String type Accessor = [[(AccessorName, AccessorType)]] type AccessorName = String type AccessorType = String data Profile = BRIDGE Asset Extra | CG Asset Code Include NewParam TechniqueCG Extra | COMMON Asset NewParam TechniqueCommon String | GLES Asset NewParam TechniqueCG Extra | GLES2 Asset Code Include NewParam TechniqueCG Extra | GLSL Asset Code Include NewParam TechniqueCG Extra type Asset = String type Code = String type Include = String data NewParam = Annotate | Semantic | Modifier | NoParam data TechniqueCommon = Constant | LambertCol [Fx_common_color_type] | LambertTex [Fx_common_texture_type] | PhongCol [Fx_common_color_type] | PhongTex [Fx_common_texture_type] | Blinn data TechniqueCG = IsAsset | IsAnnotate | Pass | Extra data Extra = String -- Asset | Technique data Technique = Profile -- XML -- | Xmlns Schema data Fx_common_color_type = CEmission C | CAmbient C | CDiffuse C | CSpecular C | CShininess Float | CReflective C | CReflectivity Float | CTransparent C | CTransparency Float | CIndex_of_refraction Float data Fx_common_texture_type = TEmission Texture | TAmbient Texture | TDiffuse Texture | TSpecular Texture | TShininess Float | TReflective Texture | TReflectivity Float | TTransparent Texture | TTransparency Float | TIndex_of_refraction Float data C = Color (Float, Float, Float, Float) data Texture = Texture { imageSID :: ID, path :: String -- ToDo: better type, embedded images } type ID = String type SID = String -- Maybe data Color = RGB Float Float Float deriving (Eq, Show)