Skip to content

Instantly share code, notes, and snippets.

@tibbe
Created February 24, 2013 19:03
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save tibbe/5025055 to your computer and use it in GitHub Desktop.
Save tibbe/5025055 to your computer and use it in GitHub Desktop.
{-# LANGUAGE BangPatterns #-}
module Main
( main
) where
import Control.Applicative
import Control.Monad (mzero)
import qualified Data.Vector as V
import Data.Vector (Vector)
import Data.AffineSpace.Point
import qualified Data.ByteString.Lazy as BS
import Data.Csv
import Data.Char
import Control.Exception
import Prelude hiding (id, round)
import System.Environment
type R2 = (Double, Double)
data FramePt = FramePt { fpId :: {-# UNPACK #-} !Int
, fpArea :: {-# UNPACK #-} !Int
, fpPos :: {-# UNPACK #-} !(Point R2)
, fpCirc :: {-# UNPACK #-} !Double
, fpFrame :: {-# UNPACK #-} !Int
, fpAR :: {-# UNPACK #-} !Double
, fpRound :: {-# UNPACK #-} !Double
, fpSolidity :: {-# UNPACK #-} !Double
}
deriving (Show)
framePt :: Int -> Int -> Double -> Double -> Double -> Int -> Double -> Double
-> Double -> FramePt
framePt !id !area !x !y !circ !frame !ar !round !solidity =
FramePt id area (P (x,y)) circ frame ar round solidity
(.!!) :: FromField a => Vector Field -> Int -> Parser a
a .!! b = parseField $! a `V.unsafeIndex` b
instance FromRecord FramePt where
parseRecord v
| V.length v == 9 = framePt <$> v .!! 0
<*> v .!! 1
<*> v .!! 2
<*> v .!! 3
<*> v .!! 4
<*> v .!! 5
<*> v .!! 6
<*> v .!! 7
<*> v .!! 8
| otherwise = mzero
{-# INLINABLE parse #-}
parse :: BS.ByteString -> Either String (Vector FramePt)
parse =
decodeWith opts False . BS.dropWhile (/= fromIntegral (ord '\n'))
where opts = defaultDecodeOptions { decDelimiter = fromIntegral $ ord '\t' }
{-# INLINABLE readFramePts #-}
readFramePts :: FilePath -> IO (Either String (Vector FramePt))
readFramePts f =
parse <$> BS.readFile f
main :: IO ()
main = do
[file] <- getArgs
(Right !v) <- readFramePts file
return ()
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment