module Graphics.Formats.Collada.ColladaTypes
(
Scene(..),
SceneNode(..), NodeType(..),
Transform(..),
Camera(..),
ViewSize(..),
Z(..),
Light(..),
Attenuation(..),
Controller(..),
Geometry(..),
Mesh(..),
Vertices(..),
LinePrimitive(..), Polygon(..),
AnimChannel(..),
ID, SID,
Semantic,
Profile(..), NewParam(..), TechniqueCommon(..), Material, Effect,
C(..), Color(..),
Animation(..),
Fx_common_color_type(..), Fx_common_texture_type(..), Texture(..),
Interpolation(..),
)
where
import Data.Tree
import Data.Vector
import Graphics.Rendering.OpenGL (TextureObject)
import Graphics.Formats.Collada.Vector2D3D (V3(..), V4(..))
type Mat44 = ((Float,Float,Float,Float),
(Float,Float,Float,Float),
(Float,Float,Float,Float),
(Float,Float,Float,Float))
type Scene = Tree SceneNode
data SceneNode = SceneNode {
nodeId :: ID,
nodeType :: NodeType,
nodeLayers :: [String],
nodeTransformations :: [(SID, Transform)],
nodeCameras :: [Camera],
nodeController :: [Controller],
nodeGeometries :: [Geometry],
nodeLights :: [Light]
} | EmptyRoot
deriving (Show, Eq)
data NodeType = JOINT | NODE | NOTYPE deriving (Show, Eq)
data Transform = LookAt {
lookAtEye:: V3,
lookAtInterest :: V3,
lookAtUp :: V3
}
| Matrix Mat44
| Rotate V3 Float V3 Float V3 Float
| Scale V3
| Skew {
skewAngle :: Float,
skewRotation :: V3,
skewTranslation :: V3
}
| Translate V3
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, Eq)
data Skin = Skin {
bindShapeMatrix :: [Mat44],
source :: [String],
joint :: [Joint],
vertexWeights :: String
}
deriving (Show, Eq)
data Morph = Morph {
geometrySource :: String,
method :: MorphMethod,
morphSource :: String,
morphTargets :: [Input]
}
deriving (Show, Eq)
data MorphMethod = Normalized | Relative deriving (Show, Eq)
data Joint = Joint {
jointID :: String,
prismatic :: Prismatic,
revolute :: Revolute
}
deriving (Show, Eq)
type Prismatic = String
type Revolute = String
data Input = Input {
offset :: Int,
semantic :: Semantic,
inputSource :: String,
set :: Int
}
deriving (Show, Eq)
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, Eq)
data Geometry = Geometry {
meshID :: ID,
mesh :: [Mesh],
vertices :: Vertices
}
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
deriving (Show, Eq)
data Vertices = Vertices {
name :: ID,
verts :: Vector V3,
normals :: Vector V3
}
deriving (Show, Eq)
data LinePrimitive = LinePrimitive {
lineP :: Vector (Vector Int),
lineN :: Vector (Vector Int),
lineT :: Vector (Vector Int),
ms :: [Material]
}
deriving (Show, Eq)
data Polygon = Polygon {
poylgonP :: Vector (Vector Int),
poylgonN :: Vector (Vector Int),
polygonPh :: (Vector Int, Vector Int),
polygonMs :: [Material]
}
deriving (Show, Eq)
type Material = (SID,Effect)
type Effect = Profile
type Animation = Tree (SID, AnimChannel)
data AnimChannel = AnimChannel {
input :: (ID,[Float],Accessor) ,
output :: (ID,[Float],Accessor),
interp :: [Interpolation],
targets :: [(TargetID,AccessorName)]
} | EmptyAnim
deriving (Show, Eq)
data Interpolation = Step | Linear | Bezier [Float] [Float] deriving (Show, Eq)
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
deriving (Show, Eq)
type Asset = String
type Code = String
type Include = String
data NewParam = Annotat | Semantic | Modifier | NoParam deriving (Show, Eq)
data TechniqueCommon = Constant | LambertCol [Fx_common_color_type]
| LambertTex [Fx_common_texture_type] [[Float]]
| PhongCol [Fx_common_color_type]
| PhongTex [Fx_common_texture_type] [[Float]]
| Blinn
deriving (Show, Eq)
data TechniqueCG = IsAsset | IsAnnotate | Pass | Extra deriving (Show, Eq)
data Extra = String deriving (Show, Eq)
data Technique = Profile deriving (Show, Eq)
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
deriving (Show, Eq)
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
deriving (Show, Eq)
data C = Color V4 deriving (Show, Eq)
data Texture = Texture {
imageSID :: ID,
path :: String,
texObj :: Maybe TextureObject
}
deriving (Show, Eq)
type ID = String
type SID = String
data Color = RGB Float Float Float deriving (Eq, Show)