From fe21435473d34c0f32f22d19f7ee5ac4f64b6046 Mon Sep 17 00:00:00 2001 From: "Adam C. Foltzer" Date: Sun, 20 Nov 2011 13:30:25 -0500 Subject: [PATCH] initial import --- .gitignore | 3 + Graphics/Formats/OFF/Simple.hs | 164 ++++++++++++ LICENSE | 30 +++ README.md | 4 + Setup.hs | 2 + off-simple.cabal | 31 +++ tests/Main.hs | 51 ++++ tests/Setup.hs | 2 + tests/TestData.hs | 25 ++ tests/off-simple-tests.cabal | 21 ++ tests/samples/cube.off | 16 ++ tests/samples/cube.offc | 16 ++ tests/samples/dodec.off | 35 +++ tests/samples/mushroom.off | 468 +++++++++++++++++++++++++++++++++ tests/samples/tetra.off | 13 + tests/samples/tetra.offc | 10 + 16 files changed, 891 insertions(+) create mode 100644 .gitignore create mode 100644 Graphics/Formats/OFF/Simple.hs create mode 100644 LICENSE create mode 100644 README.md create mode 100644 Setup.hs create mode 100644 off-simple.cabal create mode 100644 tests/Main.hs create mode 100644 tests/Setup.hs create mode 100644 tests/TestData.hs create mode 100644 tests/off-simple-tests.cabal create mode 100644 tests/samples/cube.off create mode 100644 tests/samples/cube.offc create mode 100644 tests/samples/dodec.off create mode 100644 tests/samples/mushroom.off create mode 100644 tests/samples/tetra.off create mode 100644 tests/samples/tetra.offc diff --git a/.gitignore b/.gitignore new file mode 100644 index 0000000..781a134 --- /dev/null +++ b/.gitignore @@ -0,0 +1,3 @@ +cabal-dev/ +dist/ +*~ diff --git a/Graphics/Formats/OFF/Simple.hs b/Graphics/Formats/OFF/Simple.hs new file mode 100644 index 0000000..929590d --- /dev/null +++ b/Graphics/Formats/OFF/Simple.hs @@ -0,0 +1,164 @@ +{-# LANGUAGE NamedFieldPuns #-} + +-- | A simple datatype and parser for 3D OFF files. A single type is +-- used for OFF information with or without color. Loosely based on +-- , but uses the +-- file header to determine whether the object's faces contain color +-- values. +module Graphics.Formats.OFF.Simple ( + OFF (..) + , Face (..) + , vertexCount + , faceCount + , hasColor + , parseOFF + , readOFFFile +) where + +import Control.Applicative hiding ( (<|>), many, optional ) + +import qualified Data.Vector as V +import Data.Vector ( Vector ) + +import Numeric + +import Text.Parsec +import Text.Parsec.String ( Parser ) + +-- | A vertex is just a triple of 'Double's. +type Vertex = (Double, Double, Double) + +-- | A color is a 4-tuple of 'Double's representing RGB values. +type Color = (Double, Double, Double) + +-- | A face is a vector of vertex indices and an optional color value. +data Face = Face (Vector Int) (Maybe Color) + deriving (Show, Eq, Ord) + +-- | Representation of an object in OFF format; a pair of vectors +-- containing the vertices and the faces of the object. +data OFF = OFF { + vertices :: Vector Vertex + , faces :: Vector Face + } + deriving (Show, Eq, Ord) + +-- | The number of vertices in an 'OFF' object. +vertexCount :: OFF -> Int +vertexCount (OFF { vertices }) = V.length vertices + +-- | The number of faces in an 'OFF' object. +faceCount :: OFF -> Int +faceCount (OFF { faces }) = V.length faces + +-- | Returns 'True' if the 'OFF' object has color values associated +-- with its faces. +hasColor :: OFF -> Bool +hasColor (OFF { faces }) = + case faces V.!? 0 of + Just (Face _ (Just _)) -> True + _ -> False + +-- | Determines whether we're handling color files. +parseHeader :: Parser Bool +parseHeader = string "OFF" *> (char 'C' *> return True + <|> return False) + +-- | Comments span from @#@ to the end of the line. +parseComment :: Parser () +parseComment = char '#' >> manyTill anyChar newline >> return () + +-- | Parse the vertex and face counts. +parseCounts :: Parser (Int, Int) +parseCounts = do + vc <- parseInt + spaces + fc <- parseInt + optional (many (oneOf "\t ") >> parseInt) -- edges ignored + return (vc, fc) + "vertex, face, and edge count" + +-- | Parse a line of vertex coordinates. +parseVertex :: Parser Vertex +parseVertex = do + [x, y, z] <- count 3 (parseDouble <* spaces) + return (x, y, z) + "x, y, z coordinates" + +-- | Parse the given number of vertex lines +parseVertices :: Int -> Parser (Vector Vertex) +parseVertices n = V.replicateM n (parseVertex <* eatWhitespace) + show n ++ " vertices" + +-- | Parse a line of non-colored vertex indices defining a face. +parseFace :: Parser Face +parseFace = do + numVerts <- parseInt + spaces + verts <- V.replicateM numVerts (parseInt <* spaces) + return $ Face verts Nothing + "vertex indices" + +-- | First parse the indices of a face, then parse three additional +-- 'Double's representing the color value. +parseFaceC :: Parser Face +parseFaceC = do + (Face verts Nothing) <- parseFace + [r, g, b] <- count 3 (parseDouble <* spaces) + return $ Face verts (Just (r, g, b)) + "3 color components" + +-- | Parse the given number of non-colored faces. +parseFaces :: Int -> Parser (Vector Face) +parseFaces n = V.replicateM n (parseFace <* eatWhitespace) + show n ++ " faces" + +-- | Parse the given number of colored faces. +parseFacesC :: Int -> Parser (Vector Face) +parseFacesC n = V.replicateM n (parseFaceC <* eatWhitespace) + show n ++ " faces" + +-- | Parse a 'Text' string representing an OFF object. +parseOFF :: Parser OFF +parseOFF = do + eatWhitespace + isColor <- parseHeader + eatWhitespace + (numVerts, numFaces) <- parseCounts + eatWhitespace + verts <- parseVertices numVerts + eatWhitespace + faces <- if isColor + then parseFacesC numFaces + else parseFaces numFaces + eatWhitespace >> eof + return $ OFF verts faces + +-- | Read an OFF object from the given 'FilePath', returning either +-- the corresponding 'OFF' value or a 'ParseError'. +readOFFFile :: FilePath -> IO (Either ParseError OFF) +readOFFFile f = parse parseOFF f <$> readFile f + +-- | Parse and discard whitespace and comments up until the next +-- non-comment, non-whitespace character. +eatWhitespace :: Parser () +eatWhitespace = try (spaces >> parseComment >> eatWhitespace) + <|> spaces + <|> return () + +-- | Parse an unsigned decimal 'Int'. +parseInt :: Parser Int +parseInt = do + s <- getInput + case readDec s of + [(n, s')] -> n <$ setInput s' + _ -> empty + +-- | Parse a signed 'Double'. +parseDouble :: Parser Double +parseDouble = do + s <- getInput + case readSigned readFloat s of + [(n, s')] -> n <$ setInput s' + _ -> empty + diff --git a/LICENSE b/LICENSE new file mode 100644 index 0000000..492b7db --- /dev/null +++ b/LICENSE @@ -0,0 +1,30 @@ +Copyright (c)2011, Adam C. Foltzer + +All rights reserved. + +Redistribution and use in source and binary forms, with or without +modification, are permitted provided that the following conditions are met: + + * Redistributions of source code must retain the above copyright + notice, this list of conditions and the following disclaimer. + + * Redistributions in binary form must reproduce the above + copyright notice, this list of conditions and the following + disclaimer in the documentation and/or other materials provided + with the distribution. + + * Neither the name of Adam C. Foltzer nor the names of other + contributors may be used to endorse or promote products derived + from this software without specific prior written permission. + +THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS +"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT +LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR +A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT +OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, +SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT +LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, +DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY +THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT +(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE +OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. diff --git a/README.md b/README.md new file mode 100644 index 0000000..22e878d --- /dev/null +++ b/README.md @@ -0,0 +1,4 @@ +## off-simple + +Two primary interfaces are exposed for reading `OFF` files; see +haddock in `Graphics/Formats/OFF/Simple.hs` for details. \ No newline at end of file diff --git a/Setup.hs b/Setup.hs new file mode 100644 index 0000000..9a994af --- /dev/null +++ b/Setup.hs @@ -0,0 +1,2 @@ +import Distribution.Simple +main = defaultMain diff --git a/off-simple.cabal b/off-simple.cabal new file mode 100644 index 0000000..13f020e --- /dev/null +++ b/off-simple.cabal @@ -0,0 +1,31 @@ +Name: off-simple +Version: 0.1 +Synopsis: A parser for simplified-syntax OFF files +Description: A simple datatype and parser for 3D OFF files, + loosely based on + , + but uses the file header to determine whether the object's + faces contain color values. +License: BSD3 +License-file: LICENSE +Author: Adam C. Foltzer +Maintainer: acfoltzer@gmail.com +Category: Graphics +Build-type: Simple +Cabal-version: >=1.8 +Extra-source-files: tests/Main.hs + tests/TestData.hs + tests/off-simple-tests.cabal + tests/Setup.hs + tests/samples/cube.off + tests/samples/cube.offc + tests/samples/dodec.off + tests/samples/mushroom.off + tests/samples/tetra.off + tests/samples/tetra.offc + +Library + exposed-modules: Graphics.Formats.OFF.Simple + build-depends: base == 4.*, + parsec3 == 1.*, + vector == 0.9.* \ No newline at end of file diff --git a/tests/Main.hs b/tests/Main.hs new file mode 100644 index 0000000..dcf9f4c --- /dev/null +++ b/tests/Main.hs @@ -0,0 +1,51 @@ +module Main where + +import Graphics.Formats.OFF.Simple + +import Control.Arrow + +import Data.Vector ( Vector ) +import qualified Data.Vector as V + +import Test.HUnit ( assertFailure, (@?=) ) +import Test.Framework +import Test.Framework.Providers.HUnit + +import System.FilePath + +import TestData + +samplePrefix = "samples" + +fileMatches :: FilePath -> OFF -> Test +fileMatches file off = testCase file $ do + eoff <- readOFFFile (samplePrefix file) + case eoff of + Left err -> assertFailure (show err) + Right off' -> off' @?= off + +makeOFF :: ([(Double, Double, Double)], [[Int]]) -> OFF +makeOFF (vs, fs) = + OFF { vertices = V.fromList vs + , faces = V.map (flip Face Nothing) $ V.fromList (map V.fromList fs) + } + +makeOFFC :: ( [(Double, Double, Double)] + , [([Int], (Double, Double, Double))]) + -> OFF +makeOFFC (vs, fs) = + OFF { vertices = V.fromList vs + , faces = V.map (uncurry Face) $ + V.fromList (map (first V.fromList . second Just) fs) + } + +tests = [ "cube.off" `fileMatches` makeOFF cubeData + , "cube.offc" `fileMatches` makeOFFC cubecData + , "dodec.off" `fileMatches` makeOFF dodecData + , "mushroom.off" `fileMatches` makeOFFC mushroomData + , "tetra.off" `fileMatches` makeOFF tetraData + , "tetra.offc" `fileMatches` makeOFFC tetracData + ] + +main :: IO () +main = defaultMain tests \ No newline at end of file diff --git a/tests/Setup.hs b/tests/Setup.hs new file mode 100644 index 0000000..9a994af --- /dev/null +++ b/tests/Setup.hs @@ -0,0 +1,2 @@ +import Distribution.Simple +main = defaultMain diff --git a/tests/TestData.hs b/tests/TestData.hs new file mode 100644 index 0000000..b0a0862 --- /dev/null +++ b/tests/TestData.hs @@ -0,0 +1,25 @@ +module TestData where + +type Vertex = (Double, Double, Double) +type Color = (Double, Double, Double) + +type MonoData = ([Vertex], [[Int]]) +type ColorData = ([Vertex], [([Int], Color)]) + +cubeData :: MonoData +cubeData = ([(1.0, 1.0, 1.0), (-1.0, 1.0, 1.0), (-1.0, -1.0, 1.0), (1.0, -1.0, 1.0), (1.0, 1.0, -1.0), (-1.0, 1.0, -1.0), (-1.0, -1.0, -1.0), (1.0, -1.0, -1.0)], [[0, 1, 2, 3], [7, 6, 5, 4], [0, 3, 7, 4], [3, 2, 6, 7], [2, 1, 5, 6], [0, 4, 5, 1]]) + +cubecData :: ColorData +cubecData = ([(1.0, 1.0, 1.0), (-1.0, 1.0, 1.0), (-1.0, -1.0, 1.0), (1.0, -1.0, 1.0), (1.0, 1.0, -1.0), (-1.0, 1.0, -1.0), (-1.0, -1.0, -1.0), (1.0, -1.0, -1.0)], [([0, 1, 2, 3], (1, 0, 0)), ([7, 6, 5, 4], (0, 1, 0)), ([0, 3, 7, 4], (0, 0, 1)), ([3, 2, 6, 7], (1, 1, 0)), ([2, 1, 5, 6], (1, 0, 1)), ([0, 4, 5, 1], (0, 1, 1))]) + +dodecData :: MonoData +dodecData = ([(1.214124, 0.000000, 1.589309), (0.375185, 1.154701, 1.589309), (-0.982247, 0.713644, 1.589309), (-0.982247, -0.713644, 1.589309), (0.375185, -1.154701, 1.589309), (1.964494, 0.000000, 0.375185), (0.607062, 1.868345, 0.375185), (-1.589309, 1.154701, 0.375185), (-1.589309, -1.154701, 0.375185), (0.607062, -1.868345, 0.375185), (1.589309, 1.154701, -0.375185), (-0.607062, 1.868345, -0.375185), (-1.964494, 0.000000, -0.375185), (-0.607062, -1.868345, -0.375185), (1.589309, -1.154701, -0.375185), (0.982247, 0.713644, -1.589309), (-0.375185, 1.154701, -1.589309), (-1.214124, 0.000000, -1.589309), (-0.375185, -1.154701, -1.589309), (0.982247, -0.713644, -1.589309)], [[0, 1, 2, 3, 4], [0, 5, 10, 6, 1], [1, 6, 11, 7, 2], [2, 7, 12, 8, 3], [3, 8, 13, 9, 4], [4, 9, 14, 5, 0], [15, 10, 5, 14, 19], [16, 11, 6, 10, 15], [17, 12, 7, 11, 16], [18, 13, 8, 12, 17], [19, 14, 9, 13, 18], [19, 18, 17, 16, 15]]) + +mushroomData :: ColorData +mushroomData = ([(0.000000, 0.471660, 0.000000), (0.246229, 0.459663, -0.006919), (0.451282, 0.380737, -0.012681), (0.587984, 0.289183, -0.016522), (0.695863, 0.205838, -0.019554), (0.686805, 0.133226, -0.019299), (0.643983, 0.082083, -0.018096), (0.485869, 0.097236, -0.013653), (0.226464, 0.140172, -0.006364), (0.063410, 0.107339, -0.001782), (0.059293, -0.023362, -0.001666), (0.162231, -0.244985, -0.004559), (0.216582, -0.399048, -0.006086), (0.168819, -0.452717, -0.004744), (0.098821, -0.458400, -0.002777), (0.000000, -0.455243, 0.000000), (0.207595, 0.459663, 0.095878), (0.380476, 0.380737, 0.175722), (0.495730, 0.289183, 0.228952), (0.586683, 0.205838, 0.270959), (0.579045, 0.133226, 0.267431), (0.542942, 0.082083, 0.250757), (0.409636, 0.097236, 0.189190), (0.190932, 0.140172, 0.088182), (0.053461, 0.107339, 0.024691), (0.049990, -0.023362, 0.023088), (0.136777, -0.244985, 0.063170), (0.182601, -0.399048, 0.084334), (0.142331, -0.452717, 0.065736), (0.083316, -0.458400, 0.038479), (0.142896, 0.459663, 0.142087), (0.261897, 0.380737, 0.260413), (0.341231, 0.289183, 0.339298), (0.403838, 0.205838, 0.401550), (0.398581, 0.133226, 0.396322), (0.373729, 0.082083, 0.371612), (0.281969, 0.097236, 0.280372), (0.131426, 0.140172, 0.130682), (0.036799, 0.107339, 0.036591), (0.034410, -0.023362, 0.034215), (0.094149, -0.244985, 0.093616), (0.125691, -0.399048, 0.124979), (0.097972, -0.452717, 0.097417), (0.057350, -0.458400, 0.057025), (0.064001, 0.459663, 0.223138), (0.117299, 0.380737, 0.408962), (0.152831, 0.289183, 0.532845), (0.180872, 0.205838, 0.630607), (0.178517, 0.133226, 0.622398), (0.167387, 0.082083, 0.583592), (0.126289, 0.097236, 0.440306), (0.058864, 0.140172, 0.205227), (0.016482, 0.107339, 0.057464), (0.015412, -0.023362, 0.053732), (0.042168, -0.244985, 0.147017), (0.056295, -0.399048, 0.196272), (0.043880, -0.452717, 0.152988), (0.025686, -0.458400, 0.089554), (0.000000, 0.459663, 0.271818), (0.000000, 0.380737, 0.498182), (0.000000, 0.289183, 0.649091), (0.000000, 0.205838, 0.768182), (0.000000, 0.133226, 0.758182), (0.000000, 0.082083, 0.710909), (0.000000, 0.097236, 0.536364), (0.000000, 0.140172, 0.250000), (0.000000, 0.107339, 0.070000), (0.000000, -0.023362, 0.065455), (0.000000, -0.244985, 0.179091), (0.000000, -0.399048, 0.239091), (0.000000, -0.452717, 0.186364), (0.000000, -0.458400, 0.109091), (-0.097968, 0.459663, 0.251127), (-0.179554, 0.380737, 0.460260), (-0.233944, 0.289183, 0.599682), (-0.276867, 0.205838, 0.709707), (-0.273263, 0.133226, 0.700469), (-0.256225, 0.082083, 0.656794), (-0.193315, 0.097236, 0.495535), (-0.090105, 0.140172, 0.230970), (-0.025229, 0.107339, 0.064672), (-0.023591, -0.023362, 0.060472), (-0.064548, -0.244985, 0.165458), (-0.086173, -0.399048, 0.220891), (-0.067169, -0.452717, 0.172178), (-0.039318, -0.458400, 0.100787), (-0.161049, 0.459663, 0.180883), (-0.295167, 0.380737, 0.331517), (-0.384579, 0.289183, 0.431940), (-0.455139, 0.205838, 0.511190), (-0.449215, 0.133226, 0.504536), (-0.421206, 0.082083, 0.473078), (-0.317790, 0.097236, 0.356926), (-0.148122, 0.140172, 0.166364), (-0.041474, 0.107339, 0.046582), (-0.038781, -0.023362, 0.043557), (-0.106109, -0.244985, 0.119177), (-0.141659, -0.399048, 0.159104), (-0.110418, -0.452717, 0.124017), (-0.064635, -0.458400, 0.072595), (-0.201079, 0.459663, 0.110951), (-0.368533, 0.380737, 0.203349), (-0.480169, 0.289183, 0.264947), (-0.568267, 0.205838, 0.313558), (-0.560869, 0.133226, 0.309476), (-0.525899, 0.082083, 0.290180), (-0.396778, 0.097236, 0.218934), (-0.184939, 0.140172, 0.102045), (-0.051783, 0.107339, 0.028573), (-0.048420, -0.023362, 0.026717), (-0.132483, -0.244985, 0.073102), (-0.176869, -0.399048, 0.097593), (-0.137864, -0.452717, 0.076070), (-0.080701, -0.458400, 0.044529), (-0.215974, 0.459663, 0.020757), (-0.395831, 0.380737, 0.038043), (-0.515736, 0.289183, 0.049567), (-0.610360, 0.205838, 0.058661), (-0.602415, 0.133226, 0.057898), (-0.564854, 0.082083, 0.054288), (-0.426169, 0.097236, 0.040959), (-0.198638, 0.140172, 0.019091), (-0.055619, 0.107339, 0.005345), (-0.052007, -0.023362, 0.004998), (-0.142297, -0.244985, 0.013676), (-0.189970, -0.399048, 0.018258), (-0.148076, -0.452717, 0.014231), (-0.086678, -0.458400, 0.008331), (-0.210854, 0.459663, -0.093160), (-0.386447, 0.380737, -0.170741), (-0.503510, 0.289183, -0.222461), (-0.595891, 0.205838, -0.263277), (-0.588134, 0.133226, -0.259850), (-0.551463, 0.082083, -0.243648), (-0.416066, 0.097236, -0.183826), (-0.193929, 0.140172, -0.085682), (-0.054300, 0.107339, -0.023991), (-0.050774, -0.023362, -0.022433), (-0.138924, -0.244985, -0.061379), (-0.185467, -0.399048, -0.081943), (-0.144565, -0.452717, -0.063872), (-0.084624, -0.458400, -0.037388), (-0.181022, 0.459663, -0.192204), (-0.331772, 0.380737, -0.352268), (-0.432273, 0.289183, -0.458976), (-0.511583, 0.205838, -0.543186), (-0.504923, 0.133226, -0.536115), (-0.473441, 0.082083, -0.502688), (-0.357200, 0.097236, -0.379266), (-0.166492, 0.140172, -0.176777), (-0.046618, 0.107339, -0.049497), (-0.043591, -0.023362, -0.046283), (-0.119268, -0.244985, -0.126636), (-0.159226, -0.399048, -0.169063), (-0.124112, -0.452717, -0.131779), (-0.072651, -0.458400, -0.077139), (-0.099841, 0.459663, -0.231293), (-0.182987, 0.380737, -0.423907), (-0.238417, 0.289183, -0.552317), (-0.282160, 0.205838, -0.653653), (-0.278487, 0.133226, -0.645144), (-0.261123, 0.082083, -0.604919), (-0.197011, 0.097236, -0.456397), (-0.091827, 0.140172, -0.212727), (-0.025712, 0.107339, -0.059564), (-0.024042, -0.023362, -0.055696), (-0.065782, -0.244985, -0.152390), (-0.087820, -0.399048, -0.203445), (-0.068453, -0.452717, -0.158579), (-0.040070, -0.458400, -0.092826), (0.000000, 0.459663, -0.236729), (0.000000, 0.380737, -0.433871), (0.000000, 0.289183, -0.565299), (0.000000, 0.205838, -0.669017), (0.000000, 0.133226, -0.660307), (0.000000, 0.082083, -0.619137), (0.000000, 0.097236, -0.467124), (0.000000, 0.140172, -0.217727), (0.000000, 0.107339, -0.060964), (0.000000, -0.023362, -0.057005), (0.000000, -0.244985, -0.155972), (0.000000, -0.399048, -0.208226), (0.000000, -0.452717, -0.162306), (0.000000, -0.458400, -0.095008), (0.082387, 0.459663, -0.203864), (0.150996, 0.380737, -0.373636), (0.196736, 0.289183, -0.486818), (0.232831, 0.205838, -0.576136), (0.229801, 0.133226, -0.568636), (0.215472, 0.082083, -0.533182), (0.162569, 0.097236, -0.402273), (0.075774, 0.140172, -0.187500), (0.021217, 0.107339, -0.052500), (0.019839, -0.023362, -0.049091), (0.054281, -0.244985, -0.134318), (0.072467, -0.399048, -0.179318), (0.056486, -0.452717, -0.139773), (0.033065, -0.458400, -0.081818), (0.171522, 0.459663, -0.165809), (0.314362, 0.380737, -0.303891), (0.409588, 0.289183, -0.395945), (0.484737, 0.205838, -0.468591), (0.478427, 0.133226, -0.462491), (0.448597, 0.082083, -0.433655), (0.338455, 0.097236, -0.327182), (0.157755, 0.140172, -0.152500), (0.044171, 0.107339, -0.042700), (0.041303, -0.023362, -0.039927), (0.113010, -0.244985, -0.109245), (0.150871, -0.399048, -0.145845), (0.117599, -0.452717, -0.113682), (0.068838, -0.458400, -0.066545), (0.236516, 0.459663, -0.104020), (0.433481, 0.380737, -0.190646), (0.564791, 0.289183, -0.248396), (0.668416, 0.205838, -0.293970), (0.659714, 0.133226, -0.290143), (0.618581, 0.082083, -0.272053), (0.466704, 0.097236, -0.205257), (0.217532, 0.140172, -0.095671), (0.060909, 0.107339, -0.026788), (0.056954, -0.023362, -0.025048), (0.155832, -0.244985, -0.068535), (0.208039, -0.399048, -0.091496), (0.162160, -0.452717, -0.071318), (0.094923, -0.458400, -0.041747)], [([0, 16, 1], (1.000000, 0.000000, 1.000000)) ,([2, 1, 16, 17], (1.000000, 0.000000, 1.000000)) ,([3, 2, 17, 18], (1.000000, 0.000000, 1.000000)) ,([4, 3, 18, 19], (1.000000, 0.000000, 1.000000)) ,([5, 4, 19, 20], (1.000000, 0.000000, 1.000000)) ,([6, 5, 20, 21], (1.000000, 0.000000, 1.000000)) ,([7, 6, 21, 22], (1.000000, 0.000000, 1.000000)) ,([8, 7, 22, 23], (1.000000, 0.000000, 1.000000)) ,([9, 8, 23, 24], (1.000000, 0.000000, 1.000000)) ,([10, 9, 24, 25], (1.000000, 0.000000, 1.000000)) ,([11, 10, 25, 26], (1.000000, 0.000000, 1.000000)) ,([12, 11, 26, 27], (1.000000, 0.000000, 1.000000)) ,([13, 12, 27, 28], (1.000000, 0.000000, 1.000000)) ,([14, 13, 28, 29], (1.000000, 0.000000, 1.000000)) ,([14, 29, 15], (1.000000, 0.000000, 1.000000)) ,([0, 30, 16], (1.000000, 0.000000, 1.000000)) ,([17, 16, 30, 31], (1.000000, 0.000000, 1.000000)) ,([18, 17, 31, 32], (1.000000, 0.000000, 1.000000)) ,([19, 18, 32, 33], (1.000000, 0.000000, 1.000000)) ,([20, 19, 33, 34], (1.000000, 0.000000, 1.000000)) ,([21, 20, 34, 35], (1.000000, 0.000000, 1.000000)) ,([22, 21, 35, 36], (1.000000, 0.000000, 1.000000)) ,([23, 22, 36, 37], (1.000000, 0.000000, 1.000000)) ,([24, 23, 37, 38], (1.000000, 0.000000, 1.000000)) ,([25, 24, 38, 39], (1.000000, 0.000000, 1.000000)) ,([26, 25, 39, 40], (1.000000, 0.000000, 1.000000)) ,([27, 26, 40, 41], (1.000000, 0.000000, 1.000000)) ,([28, 27, 41, 42], (1.000000, 0.000000, 1.000000)) ,([29, 28, 42, 43], (1.000000, 0.000000, 1.000000)) ,([29, 43, 15], (1.000000, 0.000000, 1.000000)) ,([0, 44, 30], (1.000000, 0.000000, 1.000000)) ,([31, 30, 44, 45], (1.000000, 0.000000, 1.000000)) ,([32, 31, 45, 46], (1.000000, 0.000000, 1.000000)) ,([33, 32, 46, 47], (1.000000, 0.000000, 1.000000)) ,([34, 33, 47, 48], (1.000000, 0.000000, 1.000000)) ,([35, 34, 48, 49], (1.000000, 0.000000, 1.000000)) ,([36, 35, 49, 50], (1.000000, 0.000000, 1.000000)) ,([37, 36, 50, 51], (1.000000, 0.000000, 1.000000)) ,([38, 37, 51, 52], (1.000000, 0.000000, 1.000000)) ,([39, 38, 52, 53], (1.000000, 0.000000, 1.000000)) ,([40, 39, 53, 54], (1.000000, 0.000000, 1.000000)) ,([41, 40, 54, 55], (1.000000, 0.000000, 1.000000)) ,([42, 41, 55, 56], (1.000000, 0.000000, 1.000000)) ,([43, 42, 56, 57], (1.000000, 0.000000, 1.000000)) ,([43, 57, 15], (1.000000, 0.000000, 1.000000)) ,([0, 58, 44], (1.000000, 0.000000, 1.000000)) ,([45, 44, 58, 59], (1.000000, 0.000000, 1.000000)) ,([46, 45, 59, 60], (1.000000, 0.000000, 1.000000)) ,([47, 46, 60, 61], (1.000000, 0.000000, 1.000000)) ,([48, 47, 61, 62], (1.000000, 0.000000, 1.000000)) ,([49, 48, 62, 63], (1.000000, 0.000000, 1.000000)) ,([50, 49, 63, 64], (1.000000, 0.000000, 1.000000)) ,([51, 50, 64, 65], (1.000000, 0.000000, 1.000000)) ,([52, 51, 65, 66], (1.000000, 0.000000, 1.000000)) ,([53, 52, 66, 67], (1.000000, 0.000000, 1.000000)) ,([54, 53, 67, 68], (1.000000, 0.000000, 1.000000)) ,([55, 54, 68, 69], (1.000000, 0.000000, 1.000000)) ,([56, 55, 69, 70], (1.000000, 0.000000, 1.000000)) ,([57, 56, 70, 71], (1.000000, 0.000000, 1.000000)) ,([57, 71, 15], (1.000000, 0.000000, 1.000000)) ,([0, 72, 58], (1.000000, 0.000000, 1.000000)) ,([59, 58, 72, 73], (1.000000, 0.000000, 1.000000)) ,([60, 59, 73, 74], (1.000000, 0.000000, 1.000000)) ,([61, 60, 74, 75], (1.000000, 0.000000, 1.000000)) ,([62, 61, 75, 76], (1.000000, 0.000000, 1.000000)) ,([63, 62, 76, 77], (1.000000, 0.000000, 1.000000)) ,([64, 63, 77, 78], (1.000000, 0.000000, 1.000000)) ,([65, 64, 78, 79], (1.000000, 0.000000, 1.000000)) ,([66, 65, 79, 80], (1.000000, 0.000000, 1.000000)) ,([67, 66, 80, 81], (1.000000, 0.000000, 1.000000)) ,([68, 67, 81, 82], (1.000000, 0.000000, 1.000000)) ,([69, 68, 82, 83], (1.000000, 0.000000, 1.000000)) ,([70, 69, 83, 84], (1.000000, 0.000000, 1.000000)) ,([71, 70, 84, 85], (1.000000, 0.000000, 1.000000)) ,([71, 85, 15], (1.000000, 0.000000, 1.000000)) ,([0, 86, 72], (1.000000, 0.000000, 1.000000)) ,([73, 72, 86, 87], (1.000000, 0.000000, 1.000000)) ,([74, 73, 87, 88], (1.000000, 0.000000, 1.000000)) ,([75, 74, 88, 89], (1.000000, 0.000000, 1.000000)) ,([76, 75, 89, 90], (1.000000, 0.000000, 1.000000)) ,([77, 76, 90, 91], (1.000000, 0.000000, 1.000000)) ,([78, 77, 91, 92], (1.000000, 0.000000, 1.000000)) ,([79, 78, 92, 93], (1.000000, 0.000000, 1.000000)) ,([80, 79, 93, 94], (1.000000, 0.000000, 1.000000)) ,([81, 80, 94, 95], (1.000000, 0.000000, 1.000000)) ,([82, 81, 95, 96], (1.000000, 0.000000, 1.000000)) ,([83, 82, 96, 97], (1.000000, 0.000000, 1.000000)) ,([84, 83, 97, 98], (1.000000, 0.000000, 1.000000)) ,([85, 84, 98, 99], (1.000000, 0.000000, 1.000000)) ,([85, 99, 15], (1.000000, 0.000000, 1.000000)) ,([0, 100, 86], (1.000000, 0.000000, 1.000000)) ,([87, 86, 100, 101], (1.000000, 0.000000, 1.000000)) ,([88, 87, 101, 102], (1.000000, 0.000000, 1.000000)) ,([89, 88, 102, 103], (1.000000, 0.000000, 1.000000)) ,([90, 89, 103, 104], (1.000000, 0.000000, 1.000000)) ,([91, 90, 104, 105], (1.000000, 0.000000, 1.000000)) ,([92, 91, 105, 106], (1.000000, 0.000000, 1.000000)) ,([93, 92, 106, 107], (1.000000, 0.000000, 1.000000)) ,([94, 93, 107, 108], (1.000000, 0.000000, 1.000000)) ,([95, 94, 108, 109], (1.000000, 0.000000, 1.000000)) ,([96, 95, 109, 110], (1.000000, 0.000000, 1.000000)) ,([97, 96, 110, 111], (1.000000, 0.000000, 1.000000)) ,([98, 97, 111, 112], (1.000000, 0.000000, 1.000000)) ,([99, 98, 112, 113], (1.000000, 0.000000, 1.000000)) ,([99, 113, 15], (1.000000, 0.000000, 1.000000)) ,([0, 114, 100], (1.000000, 0.000000, 1.000000)) ,([101, 100, 114, 115], (1.000000, 0.000000, 1.000000)) ,([102, 101, 115, 116], (1.000000, 0.000000, 1.000000)) ,([103, 102, 116, 117], (1.000000, 0.000000, 1.000000)) ,([104, 103, 117, 118], (1.000000, 0.000000, 1.000000)) ,([105, 104, 118, 119], (1.000000, 0.000000, 1.000000)) ,([106, 105, 119, 120], (1.000000, 0.000000, 1.000000)) ,([107, 106, 120, 121], (1.000000, 0.000000, 1.000000)) ,([108, 107, 121, 122], (1.000000, 0.000000, 1.000000)) ,([109, 108, 122, 123], (1.000000, 0.000000, 1.000000)) ,([110, 109, 123, 124], (1.000000, 0.000000, 1.000000)) ,([111, 110, 124, 125], (1.000000, 0.000000, 1.000000)) ,([112, 111, 125, 126], (1.000000, 0.000000, 1.000000)) ,([113, 112, 126, 127], (1.000000, 0.000000, 1.000000)) ,([113, 127, 15], (1.000000, 0.000000, 1.000000)) ,([0, 128, 114], (1.000000, 0.000000, 1.000000)) ,([115, 114, 128, 129], (1.000000, 0.000000, 1.000000)) ,([116, 115, 129, 130], (1.000000, 0.000000, 1.000000)) ,([117, 116, 130, 131], (1.000000, 0.000000, 1.000000)) ,([118, 117, 131, 132], (1.000000, 0.000000, 1.000000)) ,([119, 118, 132, 133], (1.000000, 0.000000, 1.000000)) ,([120, 119, 133, 134], (1.000000, 0.000000, 1.000000)) ,([121, 120, 134, 135], (1.000000, 0.000000, 1.000000)) ,([122, 121, 135, 136], (1.000000, 0.000000, 1.000000)) ,([123, 122, 136, 137], (1.000000, 0.000000, 1.000000)) ,([124, 123, 137, 138], (1.000000, 0.000000, 1.000000)) ,([125, 124, 138, 139], (1.000000, 0.000000, 1.000000)) ,([126, 125, 139, 140], (1.000000, 0.000000, 1.000000)) ,([127, 126, 140, 141], (1.000000, 0.000000, 1.000000)) ,([127, 141, 15], (1.000000, 0.000000, 1.000000)) ,([0, 142, 128], (1.000000, 0.000000, 1.000000)) ,([129, 128, 142, 143], (1.000000, 0.000000, 1.000000)) ,([130, 129, 143, 144], (1.000000, 0.000000, 1.000000)) ,([131, 130, 144, 145], (1.000000, 0.000000, 1.000000)) ,([132, 131, 145, 146], (1.000000, 0.000000, 1.000000)) ,([133, 132, 146, 147], (1.000000, 0.000000, 1.000000)) ,([134, 133, 147, 148], (1.000000, 0.000000, 1.000000)) ,([135, 134, 148, 149], (1.000000, 0.000000, 1.000000)) ,([136, 135, 149, 150], (1.000000, 0.000000, 1.000000)) ,([137, 136, 150, 151], (1.000000, 0.000000, 1.000000)) ,([138, 137, 151, 152], (1.000000, 0.000000, 1.000000)) ,([139, 138, 152, 153], (1.000000, 0.000000, 1.000000)) ,([140, 139, 153, 154], (1.000000, 0.000000, 1.000000)) ,([141, 140, 154, 155], (1.000000, 0.000000, 1.000000)) ,([141, 155, 15], (1.000000, 0.000000, 1.000000)) ,([0, 156, 142], (1.000000, 0.000000, 1.000000)) ,([143, 142, 156, 157], (1.000000, 0.000000, 1.000000)) ,([144, 143, 157, 158], (1.000000, 0.000000, 1.000000)) ,([145, 144, 158, 159], (1.000000, 0.000000, 1.000000)) ,([146, 145, 159, 160], (1.000000, 0.000000, 1.000000)) ,([147, 146, 160, 161], (1.000000, 0.000000, 1.000000)) ,([148, 147, 161, 162], (1.000000, 0.000000, 1.000000)) ,([149, 148, 162, 163], (1.000000, 0.000000, 1.000000)) ,([150, 149, 163, 164], (1.000000, 0.000000, 1.000000)) ,([151, 150, 164, 165], (1.000000, 0.000000, 1.000000)) ,([152, 151, 165, 166], (1.000000, 0.000000, 1.000000)) ,([153, 152, 166, 167], (1.000000, 0.000000, 1.000000)) ,([154, 153, 167, 168], (1.000000, 0.000000, 1.000000)) ,([155, 154, 168, 169], (1.000000, 0.000000, 1.000000)) ,([155, 169, 15], (1.000000, 0.000000, 1.000000)) ,([0, 170, 156], (1.000000, 0.000000, 1.000000)) ,([157, 156, 170, 171], (1.000000, 0.000000, 1.000000)) ,([158, 157, 171, 172], (1.000000, 0.000000, 1.000000)) ,([159, 158, 172, 173], (1.000000, 0.000000, 1.000000)) ,([160, 159, 173, 174], (1.000000, 0.000000, 1.000000)) ,([161, 160, 174, 175], (1.000000, 0.000000, 1.000000)) ,([162, 161, 175, 176], (1.000000, 0.000000, 1.000000)) ,([163, 162, 176, 177], (1.000000, 0.000000, 1.000000)) ,([164, 163, 177, 178], (1.000000, 0.000000, 1.000000)) ,([165, 164, 178, 179], (1.000000, 0.000000, 1.000000)) ,([166, 165, 179, 180], (1.000000, 0.000000, 1.000000)) ,([167, 166, 180, 181], (1.000000, 0.000000, 1.000000)) ,([168, 167, 181, 182], (1.000000, 0.000000, 1.000000)) ,([169, 168, 182, 183], (1.000000, 0.000000, 1.000000)) ,([169, 183, 15], (1.000000, 0.000000, 1.000000)) ,([0, 184, 170], (1.000000, 0.000000, 1.000000)) ,([171, 170, 184, 185], (1.000000, 0.000000, 1.000000)) ,([172, 171, 185, 186], (1.000000, 0.000000, 1.000000)) ,([173, 172, 186, 187], (1.000000, 0.000000, 1.000000)) ,([174, 173, 187, 188], (1.000000, 0.000000, 1.000000)) ,([175, 174, 188, 189], (1.000000, 0.000000, 1.000000)) ,([176, 175, 189, 190], (1.000000, 0.000000, 1.000000)) ,([177, 176, 190, 191], (1.000000, 0.000000, 1.000000)) ,([178, 177, 191, 192], (1.000000, 0.000000, 1.000000)) ,([179, 178, 192, 193], (1.000000, 0.000000, 1.000000)) ,([180, 179, 193, 194], (1.000000, 0.000000, 1.000000)) ,([181, 180, 194, 195], (1.000000, 0.000000, 1.000000)) ,([182, 181, 195, 196], (1.000000, 0.000000, 1.000000)) ,([183, 182, 196, 197], (1.000000, 0.000000, 1.000000)) ,([183, 197, 15], (1.000000, 0.000000, 1.000000)) ,([0, 198, 184], (1.000000, 0.000000, 1.000000)) ,([185, 184, 198, 199], (1.000000, 0.000000, 1.000000)) ,([186, 185, 199, 200], (1.000000, 0.000000, 1.000000)) ,([187, 186, 200, 201], (1.000000, 0.000000, 1.000000)) ,([188, 187, 201, 202], (1.000000, 0.000000, 1.000000)) ,([189, 188, 202, 203], (1.000000, 0.000000, 1.000000)) ,([190, 189, 203, 204], (1.000000, 0.000000, 1.000000)) ,([191, 190, 204, 205], (1.000000, 0.000000, 1.000000)) ,([192, 191, 205, 206], (1.000000, 0.000000, 1.000000)) ,([193, 192, 206, 207], (1.000000, 0.000000, 1.000000)) ,([194, 193, 207, 208], (1.000000, 0.000000, 1.000000)) ,([195, 194, 208, 209], (1.000000, 0.000000, 1.000000)) ,([196, 195, 209, 210], (1.000000, 0.000000, 1.000000)) ,([197, 196, 210, 211], (1.000000, 0.000000, 1.000000)) ,([197, 211, 15], (1.000000, 0.000000, 1.000000)) ,([0, 212, 198], (1.000000, 0.000000, 1.000000)) ,([199, 198, 212, 213], (1.000000, 0.000000, 1.000000)) ,([200, 199, 213, 214], (1.000000, 0.000000, 1.000000)) ,([201, 200, 214, 215], (1.000000, 0.000000, 1.000000)) ,([202, 201, 215, 216], (1.000000, 0.000000, 1.000000)) ,([203, 202, 216, 217], (1.000000, 0.000000, 1.000000)) ,([204, 203, 217, 218], (1.000000, 0.000000, 1.000000)) ,([205, 204, 218, 219], (1.000000, 0.000000, 1.000000)) ,([206, 205, 219, 220], (1.000000, 0.000000, 1.000000)) ,([207, 206, 220, 221], (1.000000, 0.000000, 1.000000)) ,([208, 207, 221, 222], (1.000000, 0.000000, 1.000000)) ,([209, 208, 222, 223], (1.000000, 0.000000, 1.000000)) ,([210, 209, 223, 224], (1.000000, 0.000000, 1.000000)) ,([211, 210, 224, 225], (1.000000, 0.000000, 1.000000)) ,([211, 225, 15], (1.000000, 0.000000, 1.000000)) ,([0, 1, 212], (1.000000, 0.000000, 1.000000)) ,([213, 212, 1, 2], (1.000000, 0.000000, 1.000000)) ,([214, 213, 2, 3], (1.000000, 0.000000, 1.000000)) ,([215, 214, 3, 4], (1.000000, 0.000000, 1.000000)) ,([216, 215, 4, 5], (1.000000, 0.000000, 1.000000)) ,([217, 216, 5, 6], (1.000000, 0.000000, 1.000000)) ,([218, 217, 6, 7], (1.000000, 0.000000, 1.000000)) ,([219, 218, 7, 8], (1.000000, 0.000000, 1.000000)) ,([220, 219, 8, 9], (1.000000, 0.000000, 1.000000)) ,([221, 220, 9, 10], (1.000000, 0.000000, 1.000000)) ,([222, 221, 10, 11], (1.000000, 0.000000, 1.000000)) ,([223, 222, 11, 12], (1.000000, 0.000000, 1.000000)) ,([224, 223, 12, 13], (1.000000, 0.000000, 1.000000)) ,([225, 224, 13, 14], (1.000000, 0.000000, 1.000000)) ,([225, 14, 15], (1.000000, 0.000000, 1.000000))]) + +tetraData :: MonoData +tetraData = ([(1.0, 0.0, 0.0),(0.0, 1.0, 0.0),(0.0, 0.0, 1.0),(0.0, 0.0, 0.0)],[[0, 1, 2],[0, 3, 1],[0, 2, 3],[1, 3, 2]]) + +tetracData :: ColorData +tetracData = ([(0.0, 0.0, 2.0),(1.632993, -0.942809, -0.666667),(0.000000, 1.885618, -0.666667),(-1.632993, -0.942809, -0.666667)], [([1, 0, 3], (0.784, 0.000, 0.000)), ([2, 0, 1], (0.000, 0.784, 0.000)), ([3, 0, 2], (0.000, 0.000, 0.784)), ([3, 2, 1], (0.784, 0.000, 0.784))]) \ No newline at end of file diff --git a/tests/off-simple-tests.cabal b/tests/off-simple-tests.cabal new file mode 100644 index 0000000..db9003b --- /dev/null +++ b/tests/off-simple-tests.cabal @@ -0,0 +1,21 @@ +Name: off-simple-tests +Version: 0.1 +Synopsis: Test suite for off-simple +License: BSD3 +License-file: LICENSE +Author: Adam C. Foltzer +Maintainer: acfoltzer@gmail.com +Category: Testing +Build-type: Simple +Cabal-version: >=1.8 + +Executable off-simple-tests + main-is: Main.hs + build-depends: base == 4.*, + filepath == 1.2.*, + HUnit == 1.2.*, + test-framework == 0.4.*, + test-framework-hunit == 0.2.*, + vector == 0.9.*, + off-simple + other-modules: TestData \ No newline at end of file diff --git a/tests/samples/cube.off b/tests/samples/cube.off new file mode 100644 index 0000000..3e4f15b --- /dev/null +++ b/tests/samples/cube.off @@ -0,0 +1,16 @@ +OFF +8 6 12 + 1.0 1.0 1.0 +-1.0 1.0 1.0 +-1.0 -1.0 1.0 + 1.0 -1.0 1.0 + 1.0 1.0 -1.0 +-1.0 1.0 -1.0 +-1.0 -1.0 -1.0 + 1.0 -1.0 -1.0 +4 0 1 2 3 +4 7 6 5 4 +4 0 3 7 4 +4 3 2 6 7 +4 2 1 5 6 +4 0 4 5 1 diff --git a/tests/samples/cube.offc b/tests/samples/cube.offc new file mode 100644 index 0000000..63e4b80 --- /dev/null +++ b/tests/samples/cube.offc @@ -0,0 +1,16 @@ +OFFC +8 6 12 + 1.0 1.0 1.0 +-1.0 1.0 1.0 +-1.0 -1.0 1.0 + 1.0 -1.0 1.0 + 1.0 1.0 -1.0 +-1.0 1.0 -1.0 +-1.0 -1.0 -1.0 + 1.0 -1.0 -1.0 +4 0 1 2 3 1 0 0 +4 7 6 5 4 0 1 0 +4 0 3 7 4 0 0 1 +4 3 2 6 7 1 1 0 +4 2 1 5 6 1 0 1 +4 0 4 5 1 0 1 1 diff --git a/tests/samples/dodec.off b/tests/samples/dodec.off new file mode 100644 index 0000000..e468bfa --- /dev/null +++ b/tests/samples/dodec.off @@ -0,0 +1,35 @@ +# dodecahedron +OFF +20 12 +1.214124 0.000000 1.589309 +0.375185 1.154701 1.589309 +-0.982247 0.713644 1.589309 +-0.982247 -0.713644 1.589309 +0.375185 -1.154701 1.589309 +1.964494 0.000000 0.375185 +0.607062 1.868345 0.375185 +-1.589309 1.154701 0.375185 +-1.589309 -1.154701 0.375185 +0.607062 -1.868345 0.375185 +1.589309 1.154701 -0.375185 +-0.607062 1.868345 -0.375185 +-1.964494 0.000000 -0.375185 +-0.607062 -1.868345 -0.375185 +1.589309 -1.154701 -0.375185 +0.982247 0.713644 -1.589309 +-0.375185 1.154701 -1.589309 +-1.214124 0.000000 -1.589309 +-0.375185 -1.154701 -1.589309 +0.982247 -0.713644 -1.589309 +5 0 1 2 3 4 +5 0 5 10 6 1 +5 1 6 11 7 2 +5 2 7 12 8 3 +5 3 8 13 9 4 +5 4 9 14 5 0 +5 15 10 5 14 19 +5 16 11 6 10 15 +5 17 12 7 11 16 +5 18 13 8 12 17 +5 19 14 9 13 18 +5 19 18 17 16 15 diff --git a/tests/samples/mushroom.off b/tests/samples/mushroom.off new file mode 100644 index 0000000..77a63a1 --- /dev/null +++ b/tests/samples/mushroom.off @@ -0,0 +1,468 @@ +OFFC +226 240 928 +0.000000 0.471660 0.000000 +0.246229 0.459663 -0.006919 +0.451282 0.380737 -0.012681 +0.587984 0.289183 -0.016522 +0.695863 0.205838 -0.019554 +0.686805 0.133226 -0.019299 +0.643983 0.082083 -0.018096 +0.485869 0.097236 -0.013653 +0.226464 0.140172 -0.006364 +0.063410 0.107339 -0.001782 +0.059293 -0.023362 -0.001666 +0.162231 -0.244985 -0.004559 +0.216582 -0.399048 -0.006086 +0.168819 -0.452717 -0.004744 +0.098821 -0.458400 -0.002777 +0.000000 -0.455243 0.000000 +0.207595 0.459663 0.095878 +0.380476 0.380737 0.175722 +0.495730 0.289183 0.228952 +0.586683 0.205838 0.270959 +0.579045 0.133226 0.267431 +0.542942 0.082083 0.250757 +0.409636 0.097236 0.189190 +0.190932 0.140172 0.088182 +0.053461 0.107339 0.024691 +0.049990 -0.023362 0.023088 +0.136777 -0.244985 0.063170 +0.182601 -0.399048 0.084334 +0.142331 -0.452717 0.065736 +0.083316 -0.458400 0.038479 +0.142896 0.459663 0.142087 +0.261897 0.380737 0.260413 +0.341231 0.289183 0.339298 +0.403838 0.205838 0.401550 +0.398581 0.133226 0.396322 +0.373729 0.082083 0.371612 +0.281969 0.097236 0.280372 +0.131426 0.140172 0.130682 +0.036799 0.107339 0.036591 +0.034410 -0.023362 0.034215 +0.094149 -0.244985 0.093616 +0.125691 -0.399048 0.124979 +0.097972 -0.452717 0.097417 +0.057350 -0.458400 0.057025 +0.064001 0.459663 0.223138 +0.117299 0.380737 0.408962 +0.152831 0.289183 0.532845 +0.180872 0.205838 0.630607 +0.178517 0.133226 0.622398 +0.167387 0.082083 0.583592 +0.126289 0.097236 0.440306 +0.058864 0.140172 0.205227 +0.016482 0.107339 0.057464 +0.015412 -0.023362 0.053732 +0.042168 -0.244985 0.147017 +0.056295 -0.399048 0.196272 +0.043880 -0.452717 0.152988 +0.025686 -0.458400 0.089554 +0.000000 0.459663 0.271818 +0.000000 0.380737 0.498182 +0.000000 0.289183 0.649091 +0.000000 0.205838 0.768182 +0.000000 0.133226 0.758182 +0.000000 0.082083 0.710909 +0.000000 0.097236 0.536364 +0.000000 0.140172 0.250000 +0.000000 0.107339 0.070000 +0.000000 -0.023362 0.065455 +0.000000 -0.244985 0.179091 +0.000000 -0.399048 0.239091 +0.000000 -0.452717 0.186364 +0.000000 -0.458400 0.109091 +-0.097968 0.459663 0.251127 +-0.179554 0.380737 0.460260 +-0.233944 0.289183 0.599682 +-0.276867 0.205838 0.709707 +-0.273263 0.133226 0.700469 +-0.256225 0.082083 0.656794 +-0.193315 0.097236 0.495535 +-0.090105 0.140172 0.230970 +-0.025229 0.107339 0.064672 +-0.023591 -0.023362 0.060472 +-0.064548 -0.244985 0.165458 +-0.086173 -0.399048 0.220891 +-0.067169 -0.452717 0.172178 +-0.039318 -0.458400 0.100787 +-0.161049 0.459663 0.180883 +-0.295167 0.380737 0.331517 +-0.384579 0.289183 0.431940 +-0.455139 0.205838 0.511190 +-0.449215 0.133226 0.504536 +-0.421206 0.082083 0.473078 +-0.317790 0.097236 0.356926 +-0.148122 0.140172 0.166364 +-0.041474 0.107339 0.046582 +-0.038781 -0.023362 0.043557 +-0.106109 -0.244985 0.119177 +-0.141659 -0.399048 0.159104 +-0.110418 -0.452717 0.124017 +-0.064635 -0.458400 0.072595 +-0.201079 0.459663 0.110951 +-0.368533 0.380737 0.203349 +-0.480169 0.289183 0.264947 +-0.568267 0.205838 0.313558 +-0.560869 0.133226 0.309476 +-0.525899 0.082083 0.290180 +-0.396778 0.097236 0.218934 +-0.184939 0.140172 0.102045 +-0.051783 0.107339 0.028573 +-0.048420 -0.023362 0.026717 +-0.132483 -0.244985 0.073102 +-0.176869 -0.399048 0.097593 +-0.137864 -0.452717 0.076070 +-0.080701 -0.458400 0.044529 +-0.215974 0.459663 0.020757 +-0.395831 0.380737 0.038043 +-0.515736 0.289183 0.049567 +-0.610360 0.205838 0.058661 +-0.602415 0.133226 0.057898 +-0.564854 0.082083 0.054288 +-0.426169 0.097236 0.040959 +-0.198638 0.140172 0.019091 +-0.055619 0.107339 0.005345 +-0.052007 -0.023362 0.004998 +-0.142297 -0.244985 0.013676 +-0.189970 -0.399048 0.018258 +-0.148076 -0.452717 0.014231 +-0.086678 -0.458400 0.008331 +-0.210854 0.459663 -0.093160 +-0.386447 0.380737 -0.170741 +-0.503510 0.289183 -0.222461 +-0.595891 0.205838 -0.263277 +-0.588134 0.133226 -0.259850 +-0.551463 0.082083 -0.243648 +-0.416066 0.097236 -0.183826 +-0.193929 0.140172 -0.085682 +-0.054300 0.107339 -0.023991 +-0.050774 -0.023362 -0.022433 +-0.138924 -0.244985 -0.061379 +-0.185467 -0.399048 -0.081943 +-0.144565 -0.452717 -0.063872 +-0.084624 -0.458400 -0.037388 +-0.181022 0.459663 -0.192204 +-0.331772 0.380737 -0.352268 +-0.432273 0.289183 -0.458976 +-0.511583 0.205838 -0.543186 +-0.504923 0.133226 -0.536115 +-0.473441 0.082083 -0.502688 +-0.357200 0.097236 -0.379266 +-0.166492 0.140172 -0.176777 +-0.046618 0.107339 -0.049497 +-0.043591 -0.023362 -0.046283 +-0.119268 -0.244985 -0.126636 +-0.159226 -0.399048 -0.169063 +-0.124112 -0.452717 -0.131779 +-0.072651 -0.458400 -0.077139 +-0.099841 0.459663 -0.231293 +-0.182987 0.380737 -0.423907 +-0.238417 0.289183 -0.552317 +-0.282160 0.205838 -0.653653 +-0.278487 0.133226 -0.645144 +-0.261123 0.082083 -0.604919 +-0.197011 0.097236 -0.456397 +-0.091827 0.140172 -0.212727 +-0.025712 0.107339 -0.059564 +-0.024042 -0.023362 -0.055696 +-0.065782 -0.244985 -0.152390 +-0.087820 -0.399048 -0.203445 +-0.068453 -0.452717 -0.158579 +-0.040070 -0.458400 -0.092826 +0.000000 0.459663 -0.236729 +0.000000 0.380737 -0.433871 +0.000000 0.289183 -0.565299 +0.000000 0.205838 -0.669017 +0.000000 0.133226 -0.660307 +0.000000 0.082083 -0.619137 +0.000000 0.097236 -0.467124 +0.000000 0.140172 -0.217727 +0.000000 0.107339 -0.060964 +0.000000 -0.023362 -0.057005 +0.000000 -0.244985 -0.155972 +0.000000 -0.399048 -0.208226 +0.000000 -0.452717 -0.162306 +0.000000 -0.458400 -0.095008 +0.082387 0.459663 -0.203864 +0.150996 0.380737 -0.373636 +0.196736 0.289183 -0.486818 +0.232831 0.205838 -0.576136 +0.229801 0.133226 -0.568636 +0.215472 0.082083 -0.533182 +0.162569 0.097236 -0.402273 +0.075774 0.140172 -0.187500 +0.021217 0.107339 -0.052500 +0.019839 -0.023362 -0.049091 +0.054281 -0.244985 -0.134318 +0.072467 -0.399048 -0.179318 +0.056486 -0.452717 -0.139773 +0.033065 -0.458400 -0.081818 +0.171522 0.459663 -0.165809 +0.314362 0.380737 -0.303891 +0.409588 0.289183 -0.395945 +0.484737 0.205838 -0.468591 +0.478427 0.133226 -0.462491 +0.448597 0.082083 -0.433655 +0.338455 0.097236 -0.327182 +0.157755 0.140172 -0.152500 +0.044171 0.107339 -0.042700 +0.041303 -0.023362 -0.039927 +0.113010 -0.244985 -0.109245 +0.150871 -0.399048 -0.145845 +0.117599 -0.452717 -0.113682 +0.068838 -0.458400 -0.066545 +0.236516 0.459663 -0.104020 +0.433481 0.380737 -0.190646 +0.564791 0.289183 -0.248396 +0.668416 0.205838 -0.293970 +0.659714 0.133226 -0.290143 +0.618581 0.082083 -0.272053 +0.466704 0.097236 -0.205257 +0.217532 0.140172 -0.095671 +0.060909 0.107339 -0.026788 +0.056954 -0.023362 -0.025048 +0.155832 -0.244985 -0.068535 +0.208039 -0.399048 -0.091496 +0.162160 -0.452717 -0.071318 +0.094923 -0.458400 -0.041747 +3 0 16 1 1.000000 0.000000 1.000000 +4 2 1 16 17 1.000000 0.000000 1.000000 +4 3 2 17 18 1.000000 0.000000 1.000000 +4 4 3 18 19 1.000000 0.000000 1.000000 +4 5 4 19 20 1.000000 0.000000 1.000000 +4 6 5 20 21 1.000000 0.000000 1.000000 +4 7 6 21 22 1.000000 0.000000 1.000000 +4 8 7 22 23 1.000000 0.000000 1.000000 +4 9 8 23 24 1.000000 0.000000 1.000000 +4 10 9 24 25 1.000000 0.000000 1.000000 +4 11 10 25 26 1.000000 0.000000 1.000000 +4 12 11 26 27 1.000000 0.000000 1.000000 +4 13 12 27 28 1.000000 0.000000 1.000000 +4 14 13 28 29 1.000000 0.000000 1.000000 +3 14 29 15 1.000000 0.000000 1.000000 +3 0 30 16 1.000000 0.000000 1.000000 +4 17 16 30 31 1.000000 0.000000 1.000000 +4 18 17 31 32 1.000000 0.000000 1.000000 +4 19 18 32 33 1.000000 0.000000 1.000000 +4 20 19 33 34 1.000000 0.000000 1.000000 +4 21 20 34 35 1.000000 0.000000 1.000000 +4 22 21 35 36 1.000000 0.000000 1.000000 +4 23 22 36 37 1.000000 0.000000 1.000000 +4 24 23 37 38 1.000000 0.000000 1.000000 +4 25 24 38 39 1.000000 0.000000 1.000000 +4 26 25 39 40 1.000000 0.000000 1.000000 +4 27 26 40 41 1.000000 0.000000 1.000000 +4 28 27 41 42 1.000000 0.000000 1.000000 +4 29 28 42 43 1.000000 0.000000 1.000000 +3 29 43 15 1.000000 0.000000 1.000000 +3 0 44 30 1.000000 0.000000 1.000000 +4 31 30 44 45 1.000000 0.000000 1.000000 +4 32 31 45 46 1.000000 0.000000 1.000000 +4 33 32 46 47 1.000000 0.000000 1.000000 +4 34 33 47 48 1.000000 0.000000 1.000000 +4 35 34 48 49 1.000000 0.000000 1.000000 +4 36 35 49 50 1.000000 0.000000 1.000000 +4 37 36 50 51 1.000000 0.000000 1.000000 +4 38 37 51 52 1.000000 0.000000 1.000000 +4 39 38 52 53 1.000000 0.000000 1.000000 +4 40 39 53 54 1.000000 0.000000 1.000000 +4 41 40 54 55 1.000000 0.000000 1.000000 +4 42 41 55 56 1.000000 0.000000 1.000000 +4 43 42 56 57 1.000000 0.000000 1.000000 +3 43 57 15 1.000000 0.000000 1.000000 +3 0 58 44 1.000000 0.000000 1.000000 +4 45 44 58 59 1.000000 0.000000 1.000000 +4 46 45 59 60 1.000000 0.000000 1.000000 +4 47 46 60 61 1.000000 0.000000 1.000000 +4 48 47 61 62 1.000000 0.000000 1.000000 +4 49 48 62 63 1.000000 0.000000 1.000000 +4 50 49 63 64 1.000000 0.000000 1.000000 +4 51 50 64 65 1.000000 0.000000 1.000000 +4 52 51 65 66 1.000000 0.000000 1.000000 +4 53 52 66 67 1.000000 0.000000 1.000000 +4 54 53 67 68 1.000000 0.000000 1.000000 +4 55 54 68 69 1.000000 0.000000 1.000000 +4 56 55 69 70 1.000000 0.000000 1.000000 +4 57 56 70 71 1.000000 0.000000 1.000000 +3 57 71 15 1.000000 0.000000 1.000000 +3 0 72 58 1.000000 0.000000 1.000000 +4 59 58 72 73 1.000000 0.000000 1.000000 +4 60 59 73 74 1.000000 0.000000 1.000000 +4 61 60 74 75 1.000000 0.000000 1.000000 +4 62 61 75 76 1.000000 0.000000 1.000000 +4 63 62 76 77 1.000000 0.000000 1.000000 +4 64 63 77 78 1.000000 0.000000 1.000000 +4 65 64 78 79 1.000000 0.000000 1.000000 +4 66 65 79 80 1.000000 0.000000 1.000000 +4 67 66 80 81 1.000000 0.000000 1.000000 +4 68 67 81 82 1.000000 0.000000 1.000000 +4 69 68 82 83 1.000000 0.000000 1.000000 +4 70 69 83 84 1.000000 0.000000 1.000000 +4 71 70 84 85 1.000000 0.000000 1.000000 +3 71 85 15 1.000000 0.000000 1.000000 +3 0 86 72 1.000000 0.000000 1.000000 +4 73 72 86 87 1.000000 0.000000 1.000000 +4 74 73 87 88 1.000000 0.000000 1.000000 +4 75 74 88 89 1.000000 0.000000 1.000000 +4 76 75 89 90 1.000000 0.000000 1.000000 +4 77 76 90 91 1.000000 0.000000 1.000000 +4 78 77 91 92 1.000000 0.000000 1.000000 +4 79 78 92 93 1.000000 0.000000 1.000000 +4 80 79 93 94 1.000000 0.000000 1.000000 +4 81 80 94 95 1.000000 0.000000 1.000000 +4 82 81 95 96 1.000000 0.000000 1.000000 +4 83 82 96 97 1.000000 0.000000 1.000000 +4 84 83 97 98 1.000000 0.000000 1.000000 +4 85 84 98 99 1.000000 0.000000 1.000000 +3 85 99 15 1.000000 0.000000 1.000000 +3 0 100 86 1.000000 0.000000 1.000000 +4 87 86 100 101 1.000000 0.000000 1.000000 +4 88 87 101 102 1.000000 0.000000 1.000000 +4 89 88 102 103 1.000000 0.000000 1.000000 +4 90 89 103 104 1.000000 0.000000 1.000000 +4 91 90 104 105 1.000000 0.000000 1.000000 +4 92 91 105 106 1.000000 0.000000 1.000000 +4 93 92 106 107 1.000000 0.000000 1.000000 +4 94 93 107 108 1.000000 0.000000 1.000000 +4 95 94 108 109 1.000000 0.000000 1.000000 +4 96 95 109 110 1.000000 0.000000 1.000000 +4 97 96 110 111 1.000000 0.000000 1.000000 +4 98 97 111 112 1.000000 0.000000 1.000000 +4 99 98 112 113 1.000000 0.000000 1.000000 +3 99 113 15 1.000000 0.000000 1.000000 +3 0 114 100 1.000000 0.000000 1.000000 +4 101 100 114 115 1.000000 0.000000 1.000000 +4 102 101 115 116 1.000000 0.000000 1.000000 +4 103 102 116 117 1.000000 0.000000 1.000000 +4 104 103 117 118 1.000000 0.000000 1.000000 +4 105 104 118 119 1.000000 0.000000 1.000000 +4 106 105 119 120 1.000000 0.000000 1.000000 +4 107 106 120 121 1.000000 0.000000 1.000000 +4 108 107 121 122 1.000000 0.000000 1.000000 +4 109 108 122 123 1.000000 0.000000 1.000000 +4 110 109 123 124 1.000000 0.000000 1.000000 +4 111 110 124 125 1.000000 0.000000 1.000000 +4 112 111 125 126 1.000000 0.000000 1.000000 +4 113 112 126 127 1.000000 0.000000 1.000000 +3 113 127 15 1.000000 0.000000 1.000000 +3 0 128 114 1.000000 0.000000 1.000000 +4 115 114 128 129 1.000000 0.000000 1.000000 +4 116 115 129 130 1.000000 0.000000 1.000000 +4 117 116 130 131 1.000000 0.000000 1.000000 +4 118 117 131 132 1.000000 0.000000 1.000000 +4 119 118 132 133 1.000000 0.000000 1.000000 +4 120 119 133 134 1.000000 0.000000 1.000000 +4 121 120 134 135 1.000000 0.000000 1.000000 +4 122 121 135 136 1.000000 0.000000 1.000000 +4 123 122 136 137 1.000000 0.000000 1.000000 +4 124 123 137 138 1.000000 0.000000 1.000000 +4 125 124 138 139 1.000000 0.000000 1.000000 +4 126 125 139 140 1.000000 0.000000 1.000000 +4 127 126 140 141 1.000000 0.000000 1.000000 +3 127 141 15 1.000000 0.000000 1.000000 +3 0 142 128 1.000000 0.000000 1.000000 +4 129 128 142 143 1.000000 0.000000 1.000000 +4 130 129 143 144 1.000000 0.000000 1.000000 +4 131 130 144 145 1.000000 0.000000 1.000000 +4 132 131 145 146 1.000000 0.000000 1.000000 +4 133 132 146 147 1.000000 0.000000 1.000000 +4 134 133 147 148 1.000000 0.000000 1.000000 +4 135 134 148 149 1.000000 0.000000 1.000000 +4 136 135 149 150 1.000000 0.000000 1.000000 +4 137 136 150 151 1.000000 0.000000 1.000000 +4 138 137 151 152 1.000000 0.000000 1.000000 +4 139 138 152 153 1.000000 0.000000 1.000000 +4 140 139 153 154 1.000000 0.000000 1.000000 +4 141 140 154 155 1.000000 0.000000 1.000000 +3 141 155 15 1.000000 0.000000 1.000000 +3 0 156 142 1.000000 0.000000 1.000000 +4 143 142 156 157 1.000000 0.000000 1.000000 +4 144 143 157 158 1.000000 0.000000 1.000000 +4 145 144 158 159 1.000000 0.000000 1.000000 +4 146 145 159 160 1.000000 0.000000 1.000000 +4 147 146 160 161 1.000000 0.000000 1.000000 +4 148 147 161 162 1.000000 0.000000 1.000000 +4 149 148 162 163 1.000000 0.000000 1.000000 +4 150 149 163 164 1.000000 0.000000 1.000000 +4 151 150 164 165 1.000000 0.000000 1.000000 +4 152 151 165 166 1.000000 0.000000 1.000000 +4 153 152 166 167 1.000000 0.000000 1.000000 +4 154 153 167 168 1.000000 0.000000 1.000000 +4 155 154 168 169 1.000000 0.000000 1.000000 +3 155 169 15 1.000000 0.000000 1.000000 +3 0 170 156 1.000000 0.000000 1.000000 +4 157 156 170 171 1.000000 0.000000 1.000000 +4 158 157 171 172 1.000000 0.000000 1.000000 +4 159 158 172 173 1.000000 0.000000 1.000000 +4 160 159 173 174 1.000000 0.000000 1.000000 +4 161 160 174 175 1.000000 0.000000 1.000000 +4 162 161 175 176 1.000000 0.000000 1.000000 +4 163 162 176 177 1.000000 0.000000 1.000000 +4 164 163 177 178 1.000000 0.000000 1.000000 +4 165 164 178 179 1.000000 0.000000 1.000000 +4 166 165 179 180 1.000000 0.000000 1.000000 +4 167 166 180 181 1.000000 0.000000 1.000000 +4 168 167 181 182 1.000000 0.000000 1.000000 +4 169 168 182 183 1.000000 0.000000 1.000000 +3 169 183 15 1.000000 0.000000 1.000000 +3 0 184 170 1.000000 0.000000 1.000000 +4 171 170 184 185 1.000000 0.000000 1.000000 +4 172 171 185 186 1.000000 0.000000 1.000000 +4 173 172 186 187 1.000000 0.000000 1.000000 +4 174 173 187 188 1.000000 0.000000 1.000000 +4 175 174 188 189 1.000000 0.000000 1.000000 +4 176 175 189 190 1.000000 0.000000 1.000000 +4 177 176 190 191 1.000000 0.000000 1.000000 +4 178 177 191 192 1.000000 0.000000 1.000000 +4 179 178 192 193 1.000000 0.000000 1.000000 +4 180 179 193 194 1.000000 0.000000 1.000000 +4 181 180 194 195 1.000000 0.000000 1.000000 +4 182 181 195 196 1.000000 0.000000 1.000000 +4 183 182 196 197 1.000000 0.000000 1.000000 +3 183 197 15 1.000000 0.000000 1.000000 +3 0 198 184 1.000000 0.000000 1.000000 +4 185 184 198 199 1.000000 0.000000 1.000000 +4 186 185 199 200 1.000000 0.000000 1.000000 +4 187 186 200 201 1.000000 0.000000 1.000000 +4 188 187 201 202 1.000000 0.000000 1.000000 +4 189 188 202 203 1.000000 0.000000 1.000000 +4 190 189 203 204 1.000000 0.000000 1.000000 +4 191 190 204 205 1.000000 0.000000 1.000000 +4 192 191 205 206 1.000000 0.000000 1.000000 +4 193 192 206 207 1.000000 0.000000 1.000000 +4 194 193 207 208 1.000000 0.000000 1.000000 +4 195 194 208 209 1.000000 0.000000 1.000000 +4 196 195 209 210 1.000000 0.000000 1.000000 +4 197 196 210 211 1.000000 0.000000 1.000000 +3 197 211 15 1.000000 0.000000 1.000000 +3 0 212 198 1.000000 0.000000 1.000000 +4 199 198 212 213 1.000000 0.000000 1.000000 +4 200 199 213 214 1.000000 0.000000 1.000000 +4 201 200 214 215 1.000000 0.000000 1.000000 +4 202 201 215 216 1.000000 0.000000 1.000000 +4 203 202 216 217 1.000000 0.000000 1.000000 +4 204 203 217 218 1.000000 0.000000 1.000000 +4 205 204 218 219 1.000000 0.000000 1.000000 +4 206 205 219 220 1.000000 0.000000 1.000000 +4 207 206 220 221 1.000000 0.000000 1.000000 +4 208 207 221 222 1.000000 0.000000 1.000000 +4 209 208 222 223 1.000000 0.000000 1.000000 +4 210 209 223 224 1.000000 0.000000 1.000000 +4 211 210 224 225 1.000000 0.000000 1.000000 +3 211 225 15 1.000000 0.000000 1.000000 +3 0 1 212 1.000000 0.000000 1.000000 +4 213 212 1 2 1.000000 0.000000 1.000000 +4 214 213 2 3 1.000000 0.000000 1.000000 +4 215 214 3 4 1.000000 0.000000 1.000000 +4 216 215 4 5 1.000000 0.000000 1.000000 +4 217 216 5 6 1.000000 0.000000 1.000000 +4 218 217 6 7 1.000000 0.000000 1.000000 +4 219 218 7 8 1.000000 0.000000 1.000000 +4 220 219 8 9 1.000000 0.000000 1.000000 +4 221 220 9 10 1.000000 0.000000 1.000000 +4 222 221 10 11 1.000000 0.000000 1.000000 +4 223 222 11 12 1.000000 0.000000 1.000000 +4 224 223 12 13 1.000000 0.000000 1.000000 +4 225 224 13 14 1.000000 0.000000 1.000000 +3 225 14 15 1.000000 0.000000 1.000000 diff --git a/tests/samples/tetra.off b/tests/samples/tetra.off new file mode 100644 index 0000000..b16260e --- /dev/null +++ b/tests/samples/tetra.off @@ -0,0 +1,13 @@ +# a simple OFF file +OFF # header keyword +4 4 6 # NVertices Nfaces (Nedges) +# vertices +1.0 0.0 0.0 +0.0 1.0 0.0 +0.0 0.0 1.0 +0.0 0.0 0.0 +# faces +3 0 1 2 +3 0 3 1 +3 0 2 3 +3 1 3 2 diff --git a/tests/samples/tetra.offc b/tests/samples/tetra.offc new file mode 100644 index 0000000..b593835 --- /dev/null +++ b/tests/samples/tetra.offc @@ -0,0 +1,10 @@ +OFFC +4 4 6 + 0.0 0.0 2.0 + 1.632993 -0.942809 -0.666667 + 0.000000 1.885618 -0.666667 + -1.632993 -0.942809 -0.666667 +3 1 0 3 0.784 0.000 0.000 +3 2 0 1 0.000 0.784 0.000 +3 3 0 2 0.000 0.000 0.784 +3 3 2 1 0.784 0.000 0.784