init
This commit is contained in:
40
src/Scene/Parser.hs
Normal file
40
src/Scene/Parser.hs
Normal file
@ -0,0 +1,40 @@
|
||||
module Scene.Parser where
|
||||
|
||||
import Data.Attoparsec
|
||||
import Data.Functor
|
||||
import Data.ByteString as B
|
||||
import Data.ByteString.Char8 as B8
|
||||
import Scene.Types
|
||||
|
||||
partitionEithers :: [Either a b] -> ([a],[b])
|
||||
partitionEithers e = go e ([],[])
|
||||
where
|
||||
go (Left a:as) (xs,ys) = go as (a:xs,ys)
|
||||
go (Right b:bs) (xs,ys) = go bs (xs,b:ys)
|
||||
|
||||
parseScene :: FilePath -> IO ([String],[SceneObject])
|
||||
parseScene f = do
|
||||
s <- B.readFile f
|
||||
return . partitionEithers $ eitherResult . parse parseObject <$> B8.lines s
|
||||
|
||||
parseObject :: Parser SceneObject
|
||||
parseObject = do
|
||||
t <- string "camera" <|>
|
||||
string "depth" <|>
|
||||
string "background" <|>
|
||||
string "ambience" <|>
|
||||
string "light" <|>
|
||||
string "sphere" <|>
|
||||
string "plane" <|>
|
||||
string "mesh"
|
||||
case t of
|
||||
"camera" -> parseCamera
|
||||
_ -> undefined
|
||||
|
||||
parseCamera :: Parser SceneObject
|
||||
parseCamera = do
|
||||
pos <- parseVector
|
||||
|
||||
parseVector :: Parser (V3 Float)
|
||||
parseVector = do
|
||||
undefined
|
55
src/Scene/Types.hs
Normal file
55
src/Scene/Types.hs
Normal file
@ -0,0 +1,55 @@
|
||||
module Scene.Types where
|
||||
|
||||
import Linear (V3)
|
||||
|
||||
type Color = V3 Float
|
||||
type Intensity = Float
|
||||
|
||||
data Camera = Camera
|
||||
{ eye :: V3 Float
|
||||
, center :: V3 Float
|
||||
, up :: V3 Float
|
||||
, fovy :: Float
|
||||
, width :: Int
|
||||
, height :: Int
|
||||
}
|
||||
|
||||
type RecursionDepth = Int
|
||||
|
||||
data Background = Background Color
|
||||
|
||||
data Ambience = Ambience Color
|
||||
|
||||
data Light = Light (V3 Float) Color (Maybe Intensity)
|
||||
|
||||
data Material = Material
|
||||
{ materialAmbience :: V3 Float
|
||||
, materialDiffuse :: V3 Float
|
||||
, materialSpec :: V3 Float
|
||||
, materialShinyness :: Int
|
||||
, materialReflection :: Float
|
||||
}
|
||||
|
||||
|
||||
data Sphere = Sphere
|
||||
{ sphereCenter :: V3 Float
|
||||
, sphereRadius :: Float
|
||||
, sphereMaterial :: Material
|
||||
}
|
||||
|
||||
data Plane = Plane
|
||||
{ planeCenter :: V3 Float
|
||||
, planeNormal :: V3 Float
|
||||
, planeMaterial :: Material
|
||||
}
|
||||
|
||||
data Shading = Flat | Phong
|
||||
|
||||
data Mesh = Mesh
|
||||
{ meshFilename :: String
|
||||
, meshShading :: Shading
|
||||
, material :: Material
|
||||
}
|
||||
|
||||
data SceneObject = S Sphere | P Plane | M Mesh | C Camera | L Light |
|
||||
|
Reference in New Issue
Block a user