| Safe Haskell | None |
|---|
PCD.Header
Description
Define a data structure for a PCD file header and an associated parser.
- data DimType
- data DataFormat
- data FieldType
- class PCDType a where
- unsafeUnwrap :: FieldType -> a
- fromHaskell :: a -> (DimType, Int)
- fieldParser :: DimType -> Int -> Parser FieldType
- sequence' :: Monad m => [m a] -> m [a]
- data Header = Header {}
- width :: Lens' Header Integer
- viewpoint :: Lens' Header (V3 Double, Quaternion Double)
- version :: Lens' Header Text
- sizes :: Lens' Header [Int]
- points :: Lens' Header Integer
- height :: Lens' Header Int
- format :: Lens' Header DataFormat
- fields :: Lens' Header [Text]
- dimTypes :: Lens' Header [DimType]
- counts :: Lens' Header [Int]
- defaultVersion :: Text
- mkSimpleHeader :: [Text] -> (DimType, Int) -> Int -> Header
- mkHeaderXYZ :: PCDType a => a -> Int -> Header
- pointParser :: Header -> Parser [FieldType]
- filterFields :: (Text -> Bool) -> Header -> Header
- defaultHeader :: Header
- readVersion :: Parser Text
- readFields :: Parser [Text]
- readTypes :: Parser [DimType]
- namedIntegral :: Integral a => Text -> Parser a
- namedIntegrals :: Integral a => Text -> Parser [a]
- readViewpoint :: Parser (V3 Double, Quaternion Double)
- readFormat :: Parser DataFormat
- nextLine :: Handle -> IO Text
- readHeader :: Handle -> IO (Header, Maybe Text)
- writeHeader :: Header -> Text
- totalBinarySize :: Header -> Int
Documentation
Fields attached to a point may be signed integers (I), unsigned integers (U), or floating point (F).
Methods
unsafeUnwrap :: FieldType -> aSource
Extract a raw Haskell value from the FieldType variant. If you
know what you've got, this frees from having to pattern match on
the FieldType constructor. If you're wrong, you'll get an
exception.
fromHaskell :: a -> (DimType, Int)Source
Associate a DimType and a size (in bytes) for every instance
of PCDType. The argument to fromHaskell is never evaluated.
fieldParser :: DimType -> Int -> Parser FieldTypeSource
Construct a parser for a field based on its type and size.
Constructors
| Header | |
The default PCD version of 0.7.
mkSimpleHeader :: [Text] -> (DimType, Int) -> Int -> HeaderSource
Make a PCD header for a monotyped vector point
type. mkSimpleHeader fields (type,sz) n prepares a Header for
n points with field names fields, field type given by type,
and field size given by sz. Example to save 1000 3D points using
a single-precision floating point number (4 bytes) for each field:
mkSimpleHeader ["x","y","z"] (F,4) 1000
mkHeaderXYZ :: PCDType a => a -> Int -> HeaderSource
pointParser :: Header -> Parser [FieldType]Source
Assemble a parser for points by sequencing together all necessary field parsers.
filterFields :: (Text -> Bool) -> Header -> HeaderSource
Create a Header based on an existing one that keeps only the
fields whose names pass the supplied predicate.
readFields :: Parser [Text]Source
namedIntegral :: Integral a => Text -> Parser aSource
namedIntegrals :: Integral a => Text -> Parser [a]Source
readHeader :: Handle -> IO (Header, Maybe Text)Source
Parse a PCD header. Returns the Header and the rest of the file
contents.
writeHeader :: Header -> TextSource
Format a Header to be compatible with the PCD specification.
totalBinarySize :: Header -> IntSource
Compute the number of bytes this point cloud would occupy if
serialized with the Binary encoding.