javelin-io-0.1.1.1: IO operations for the `javelin` package
Copyright(c) Laurent P. René de Cotret
LicenseMIT
Maintainerlaurent.decotret@outlook.com
Portabilityportable
Safe HaskellSafe-Inferred
LanguageGHC2021

Data.Series.Generic.IO

Description

This module contains functions to serialize/deserialize generic Series to/from bytes.

Use this module if you want to support all types of Series. Otherwise, you should use either the modules Data.Series.IO or Data.Series.Unboxed.IO.

Synopsis

Deserialize Series

readCSV :: (Vector v a, Ord k, FromNamedRecord k, FromNamedRecord a) => ByteString -> Either String (Series v 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:

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, (.:) )

instance FromNamedRecord LatLong where
    parseNamedRecord r = MkLatLong <$> r .: "latitude"
                                   <*> r .: "longitude"


instance FromNamedRecord City where
    parseNamedRecord r = MkCity <$> r .: "city"

Finally, we're ready to read our stream:

import Data.Series.Generic
import Data.Series.Generic.IO
import Data.Vector 

main :: IO ()
main = do
    stream <- (...) -- Read the bytestring from somewhere
    let (latlongs  :: Series Vector City LatLong) = either error id (readCSV stream)
    print latlongs

readCSVFromFile :: (MonadIO m, Vector v a, Ord k, FromNamedRecord k, FromNamedRecord a) => FilePath -> m (Either String (Series v 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.Generic
import Data.Series.Generic.IO
import Data.Vector

main :: IO ()
main = do
    let (latlongs  :: Series Vector City LatLong) = either error id <$> readCSVFromFile "somefile.csv"
    print latlongs

Serialize Series

writeCSV :: (Vector v a, ToNamedRecord k, ToNamedRecord a) => Series v k a -> ByteString Source #

Serialize a Series to bytes.

writeCSVToFile :: (MonadIO m, Vector v a, ToNamedRecord k, ToNamedRecord a) => FilePath -> Series v k a -> m () Source #

This is a helper function to write a Series directly to a file.