ply-loader-0.1.0.3: PLY file loader.

Safe HaskellNone

PLY.Data

Description

The loading of a ply file is broken down into two steps: header parsing, and data loading. The loadPLY function will, if successful, return a data structure that may be queried to extract numeric data using loadElements and loadElementsV3. For example,

 {-# LANGUAGE OverloadedStrings #-}
 import Control.Monad ((>=>))
 import Data.ByteString (ByteString)
 import qualified Data.Vector.Storable as VS
 import Linear.V3

 loadVerts :: ByteString -> Either String (VS.Vector (V3 Float))
 loadVerts = loadPLY >=> loadElementsV3 "vertex"

To load all vertex data from a series of ply files identified by a .conf file, consider using,

 loadConf :: FilePath -> IO (Either [String] (VS.Vector (V3 Float)))
 loadConf confFile = loadMeshesV3 confFile "vertex"

Synopsis

Documentation

data PLYData Source

A PLY header and the associated raw data. Use loadElements or loadElementsV3 to extract a particular element array.

Instances

loadPLY :: ByteString -> Either String PLYDataSource

If the PLY header is successfully parsed, the PLYData value returned may be used with loadElements and loadElementsV3 to extract data.

loadElements :: ByteString -> PLYData -> Either String (Vector (Vector Scalar))Source

loadElements elementName ply loads a Vector of each instance of the requested element array. If you are extracted 3D data, consider using loadElementsV3.

loadElementsV3 :: PLYType a => ByteString -> PLYData -> Either String (Vector (V3 a))Source

Like loadElements, but restricted to 3D vectors. When it can be used, this function is much more efficient than loadElements.

loadMeshesV3 :: forall a. (PLYType a, Fractional a) => FilePath -> ByteString -> IO (Either [String] (Vector (V3 a)))Source

Load all meshes identified by a .conf file in parallel, and transform vertex data into the coordinate frame specified by the .conf file. The application loadMeshesV3 confFile element loads confFile to identify every ply mesh to load. The ply files are loaded from the same directory that contained the .conf file, and the data associated with element (e.g. "vertex") is loaded, transformed, and concatenated from all the meshes.