| Copyright | (c) Laurent P. René de Cotret | 
|---|---|
| License | MIT | 
| Maintainer | laurent.decotret@outlook.com | 
| Portability | portable | 
| Safe Haskell | Safe-Inferred | 
| Language | GHC2021 | 
Data.Series.Unboxed.IO
Description
This module contains functions to serialize/deserialize unboxed Series
 to/from bytes.
Why use unboxed series?
Unboxed series can have much better performance, at the cost of less flexibility. For example,
 an unboxed series cannot contain values of type Maybe aFunctor or Foldable.
If you are hesitating, you should prefer the series implementation in the Data.Series module (and therefore the IO module Data.Series.IO).
Synopsis
- readCSV :: (Ord k, FromNamedRecord k, FromNamedRecord a, Unbox a) => ByteString -> Either String (Series k a)
- readCSVFromFile :: (MonadIO m, Ord k, FromNamedRecord k, FromNamedRecord a, Unbox a) => FilePath -> m (Either String (Series k a))
- writeCSV :: (ToNamedRecord k, ToNamedRecord a, Unbox a) => Series k a -> ByteString
- writeCSVToFile :: (MonadIO m, ToNamedRecord k, ToNamedRecord a, Unbox a) => FilePath -> Series k a -> m ()
Deserialize Series
readCSV :: (Ord k, FromNamedRecord k, FromNamedRecord a, Unbox a) => ByteString -> Either String (Series k a) Source #
Read a comma-separated value (CSV) bytestream into a series.
Consider the following bytestream read from a file:
latitude,longitude,city 48.856667,2.352222,Paris 40.712778,-74.006111,New York City 25.0375,121.5625,Taipei -34.603333,-58.381667,Buenos Aires
We want to get a series of the latitude an longitude, indexed by the column "city". First, we need to do is to create a datatype representing the latitude and longitude information, and our index:
import qualified Data.Vector.Unboxed         as U
import qualified Data.Vector.Unboxed.Mutable as UM
import qualified Data.Vector.Generic         as G
import qualified Data.Vector.Generic.Mutable as GM
newtype Latitude = MkLatitude Double
    deriving (Show)
-- Special code to ensure that Latitude is unboxed
-- This is only required for unboxed Series
newtype instance UM.MVector s Latitude = MV_Latitude (UM.MVector s Int)
newtype instance U.Vector Latitude = V_Latitude (U.Vector Int)
deriving instance GM.MVector UM.MVector Latitude
deriving instance G.Vector U.Vector Latitude 
instance U.Unbox Latitude
newtype City = MkCity String
    deriving ( Eq, Ord, Show )
Second, we need to create an instance of FromNamedRecord for our new types:
import Data.Csv (FromNamedRecord,(.:)) instanceFromNamedRecordLatitude whereparseNamedRecordr = MkLatitude <$> r .: "latitude" instanceFromNamedRecordCity whereparseNamedRecordr = MkCity <$> r .: "city"
Finally, we're ready to read our stream:
import Data.Series.Unboxed import Data.Series.Unboxed.IO main :: IO () main = do stream <- (...) -- Read the bytestring from somewhere let (latitudes ::SeriesCity Latitude) = either (error . show) id <$>readCSVstream print latitudes
readCSVFromFile :: (MonadIO m, Ord k, FromNamedRecord k, FromNamedRecord a, Unbox a) => FilePath -> m (Either String (Series k a)) Source #
This is a helper function to read a CSV directly from a filepath.
See the documentation for readCSV on how to prepare your types.
Then, for example, you can use readCSVFromFile as:
import Data.Series.Unboxed import Data.Series.Unboxed.IO main :: IO () main = do stream <- (...) -- Read the bytestring from somewhere let (latitudes ::SeriesCity Latitude) = either (error . show) id <$>readCSVstream print latitudes
Serialize Series
writeCSV :: (ToNamedRecord k, ToNamedRecord a, Unbox a) => Series k a -> ByteString Source #
Read a comma-separated value (CSV) bytestream into a series.
Consider the following bytestream read from a file:
latitude,longitude,city 48.856667,2.352222,Paris 40.712778,-74.006111,New York City 25.0375,121.5625,Taipei -34.603333,-58.381667,Buenos Aires
We want to get a series of the latitude an longitude, indexed by the column "city". First, we need to do is to create a datatype representing the latitude and longitude information, and our index:
data LatLong = MkLatLong { latitude  :: Double
                         , longitude :: Double
                         }
    deriving ( Show )
newtype City = MkCity String
    deriving ( Eq, Ord, Show )
Second, we need to create an instance of FromNamedRecord for our new types:
import Data.Csv (FromNamedRecord,(.:)) instanceFromNamedRecordLatLong whereparseNamedRecordr = MkLatLong <$> r .: "latitude" <*> r .: "longitude" instanceFromNamedRecordCity whereparseNamedRecordr = MkCity <$> r .: "city"
Finally, we're ready to read our stream:
import Data.Series
import Data.Series.IO
main :: IO ()
main = do
    stream <- (...) -- Read the bytestring from somewhere
    let (latlongs  :: Series City LatLong) = either (error . show) id <$> readCSV stream
    print latlongs
writeCSVToFile :: (MonadIO m, ToNamedRecord k, ToNamedRecord a, Unbox a) => FilePath -> Series k a -> m () Source #