{-| Module : Geometry.Shapefile.Internal Description : Some functions for reuse inside the library Author : Sam van Herwaarden -} module Geometry.Shapefile.Internal ( getInt8 , getIntBE , getInt16BE , getIntLE , getInt16LE , getString , getPoint , getCharVal , getPointList , steps , Point ) where import Control.Monad (replicateM) import Data.Binary.Get hiding (getInt8) import Data.Binary.IEEE754 (getFloat64le) import qualified Data.ByteString.Char8 as ASCII -- | 8-bit Int value getInt8 :: Get Int getInt8 = fromIntegral <$> getWord8 -- | 32-bit big-endian Int getIntBE :: Get Int getIntBE = fromIntegral <$> getWord32be -- | 16-bit big-endian Int getInt16BE :: Get Int getInt16BE = fromIntegral <$> getWord16be -- | 32-bit little-endian Int getIntLE :: Get Int getIntLE = fromIntegral <$> getWord32le -- | 16-bit little-endian Int getInt16LE :: Get Int getInt16LE = fromIntegral <$> getWord16le -- | String of length `l` getString :: Int -> Get String getString = fmap (filter (/= '\NUL') . ASCII.unpack) . getByteString -- | Char (presumably 8-bit) getCharVal :: Get Char getCharVal = ASCII.head <$> getByteString 1 type Point = (Double, Double) -- | Two doubles making up a point with two coordinates getPoint :: Get Point getPoint = (,) <$> getFloat64le <*> getFloat64le -- | Get the increments between list values steps :: Num a => [a] -> [a] steps [] = [] steps [_] = [] steps (x1:x2:xs) = x2 - x1 : steps (x2:xs) -- | List of points of length `numPoints` getPointList :: Int -> Get [Point] getPointList = flip replicateM getPoint