ply-loader-0.3: PLY file loader.

Safe HaskellNone

PLY

Contents

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 Data.Vector.Storable (Vector)
 import Linear.V3
 import PLY

 loadVerts :: FilePath -> IO (Either String (Vector (V3 Float)))
 loadVerts = loadElementsV3 "vertex"

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

 fromConf :: FilePath -> IO (Either String (Vector (V3 Float)))
 fromConf = loadConfV3 "vertex"

Synopsis

Easy loading interface

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

loadElements elementName plyFile loads a Vector of each vertex of the requested element array from plyFile.

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

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

loadConfV3 :: forall a. (PLYType a, Fractional a, Conjugate a, RealFloat a) => ByteString -> FilePath -> 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.

Loading components

data PLYData Source

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

Instances

loadHeader :: FilePath -> IO (Either String PLYData)Source

Load a PLY header from a file.

preloadPly :: ByteString -> Either String PLYDataSource

Attempt to parse a PLY file from the given bytes. If the PLY header is successfully parsed, the PLYData value returned may be used with loadElements and loadElementsV3 to extract data.

plyHeader :: PLYData -> HeaderSource

Extract the Header from a partially loaded PLY file (as from preloadPly).

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

loadPlyElements elementName ply loads a Vector of each vertex of the requested element array. If you are extracting 3D data, consider using loadPlyElementsV3.

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

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