8 Commits

Author SHA1 Message Date
4f0ddbf75c chore: prepare v1.1.10 2024-05-02 12:56:24 -05:00
1ee358a55b fix: canceler in foreach 2024-05-02 12:56:14 -05:00
30f127788b chore: prepare v1.1.9 2024-05-02 12:00:04 -05:00
1eb6f2242f fix: generalize parser/stringifier to MonadAff 2024-05-02 11:59:50 -05:00
03cc9eba28 chore: prepare v1.1.8 2024-05-01 16:45:30 -05:00
488ea405ff fix: parse numbers properly 2024-05-01 16:45:20 -05:00
bb2274bf19 chore: prepare v1.1.7 2024-05-01 11:05:46 -05:00
8eaad8a39c fix: more bugs 2024-05-01 10:35:29 -05:00
6 changed files with 26 additions and 19 deletions

View File

@@ -1,6 +1,6 @@
{
"name": "purescript-csv-stream",
"version": "v1.1.6",
"version": "v1.1.10",
"dependencies": {
"csv-parse": "^5.5.5",
"csv-stringify": "^6.4.6"

View File

@@ -1,7 +1,7 @@
package:
name: csv-stream
publish:
version: '1.1.6'
version: '1.1.10'
license: 'GPL-3.0-or-later'
location:
githubOwner: 'cakekindel'

View File

@@ -42,7 +42,7 @@ instance (RowToList r (Cons k v tailrl), IsSymbol k, ReadCSV v, Lacks k tail, Co
pos <- liftMaybe (pure $ ForeignError $ "row too long; did not expect value " <> k) $ Map.lookup k cols
let valraw = fromMaybe "" $ Array.index vals pos
val <- readCSV @v valraw
tail <- readCSVRecord @tail @tailrl cols (fromMaybe [] $ Array.deleteAt pos vals)
tail <- readCSVRecord @tail @tailrl cols vals
pure $ Record.insert (Proxy @k) val tail
instance ReadCSVRecord () Nil where

View File

@@ -9,11 +9,12 @@ import Data.Int as Int
import Data.List.NonEmpty (NonEmptyList)
import Data.Maybe (Maybe(..), maybe)
import Data.Newtype (unwrap)
import Data.Number (fromString) as Number
import Data.Number.Format (toString) as Number
import Data.PreciseDateTime (fromDateTime, fromRFC3339String, toDateTimeLossy, toRFC3339String)
import Data.RFC3339String (RFC3339String(..))
import Data.String as String
import Foreign (ForeignError(..), readInt, readNumber, unsafeToForeign)
import Foreign (ForeignError(..))
class ReadCSV a where
readCSV :: String -> Except (NonEmptyList ForeignError) a
@@ -22,10 +23,10 @@ class WriteCSV a where
writeCSV :: a -> String
instance ReadCSV Int where
readCSV = readInt <<< unsafeToForeign
readCSV s = liftMaybe (pure $ ForeignError $ "invalid integer: " <> s) $ Int.fromString s
instance ReadCSV Number where
readCSV = readNumber <<< unsafeToForeign
readCSV s = liftMaybe (pure $ ForeignError $ "invalid number: " <> s) $ Number.fromString s
instance ReadCSV String where
readCSV = pure

View File

@@ -6,7 +6,7 @@ import Control.Alt ((<|>))
import Control.Monad.Error.Class (liftEither)
import Control.Monad.Except (runExcept)
import Control.Monad.Maybe.Trans (MaybeT(..), runMaybeT)
import Control.Monad.Rec.Class (whileJust)
import Control.Monad.Rec.Class (class MonadRec, whileJust)
import Control.Monad.ST.Global as ST
import Control.Monad.Trans.Class (lift)
import Data.Array as Array
@@ -16,18 +16,19 @@ import Data.CSV.Record (class ReadCSVRecord, readCSVRecord)
import Data.Either (Either(..))
import Data.Filterable (filter)
import Data.Map (Map)
import Data.Map as Map
import Data.Maybe (Maybe(..))
import Data.Nullable (Nullable)
import Data.Nullable as Nullable
import Data.Traversable (for_)
import Effect (Effect)
import Effect.Aff (Aff, makeAff)
import Effect.Aff (Canceler(..), makeAff)
import Effect.Aff.Class (class MonadAff, liftAff)
import Effect.Class (liftEffect)
import Effect.Exception (error)
import Effect.Uncurried (mkEffectFn1)
import Foreign (Foreign, unsafeToForeign)
import Foreign.Object (Object)
import Data.Map as Map
import Foreign.Object as Object
import Node.Encoding (Encoding(..))
import Node.EventEmitter (EventHandle(..))
@@ -86,7 +87,7 @@ make :: forall @r rl @config @missing @extra. RowToList r rl => ReadCSVRecord r
make = makeImpl <<< unsafeToForeign <<< Object.union (recordToForeign {columns: false, cast: false, cast_date: false}) <<< recordToForeign
-- | Synchronously parse a CSV string
parse :: forall @r rl @config missing extra. RowToList r rl => ReadCSVRecord r rl => Union config missing (Config extra) => { | config } -> String -> Aff (Array { | r })
parse :: forall @r rl @config missing extra m. MonadAff m => MonadRec m => RowToList r rl => ReadCSVRecord r rl => Union config missing (Config extra) => { | config } -> String -> m (Array { | r })
parse config csv = do
stream <- liftEffect $ make @r @config @missing @extra config
void $ liftEffect $ Stream.writeString stream UTF8 csv
@@ -94,10 +95,12 @@ parse config csv = do
readAll stream
-- | Loop until the stream is closed, invoking the callback with each record as it is parsed.
foreach :: forall @r rl x. RowToList r rl => ReadCSVRecord r rl => CSVParser r x -> ({ | r } -> Aff Unit) -> Aff Unit
foreach :: forall @r rl x m. MonadRec m => MonadAff m => RowToList r rl => ReadCSVRecord r rl => CSVParser r x -> ({ | r } -> m Unit) -> m Unit
foreach stream cb = whileJust do
isReadable <- liftEffect $ Stream.readable stream
when (not isReadable) $ makeAff \res -> mempty <* flip (Event.once Stream.readableH) stream $ res $ Right unit
liftAff $ when (not isReadable) $ makeAff \res -> do
stop <- flip (Event.once Stream.readableH) stream $ res $ Right unit
pure $ Canceler $ const $ liftEffect stop
whileJust do
r <- liftEffect $ read @r stream
for_ r cb
@@ -117,7 +120,7 @@ read stream = runMaybeT do
liftEither $ lmap (error <<< show) $ runExcept $ readCSVRecord @r @rl cols raw
-- | Collect all parsed records into an array
readAll :: forall @r rl a. RowToList r rl => ReadCSVRecord r rl => CSVParser r a -> Aff (Array { | r })
readAll :: forall @r rl a m. MonadRec m => MonadAff m => RowToList r rl => ReadCSVRecord r rl => CSVParser r a -> m (Array { | r })
readAll stream = do
records <- liftEffect $ ST.toEffect $ Array.ST.new
foreach stream $ void <<< liftEffect <<< ST.toEffect <<< flip Array.ST.push records

View File

@@ -2,7 +2,7 @@ module Node.Stream.CSV.Stringify where
import Prelude
import Control.Monad.Rec.Class (whileJust)
import Control.Monad.Rec.Class (class MonadRec, whileJust)
import Control.Monad.ST.Global as ST
import Data.Array as Array
import Data.Array.ST as Array.ST
@@ -13,7 +13,8 @@ import Data.Maybe (Maybe(..))
import Data.String.Regex (Regex)
import Data.Traversable (for_)
import Effect (Effect)
import Effect.Aff (Aff, makeAff)
import Effect.Aff (Canceler(..), makeAff)
import Effect.Aff.Class (class MonadAff, liftAff)
import Effect.Class (liftEffect)
import Foreign (Foreign, unsafeToForeign)
import Foreign.Object (Object)
@@ -67,7 +68,7 @@ make :: forall @r rl @config @missing @extra. Keys rl => RowToList r rl => Write
make = makeImpl <<< unsafeToForeign <<< Object.union (recordToForeign {columns: Array.fromFoldable $ keys (Proxy @r)}) <<< recordToForeign
-- | Synchronously stringify a collection of records
stringify :: forall @r rl f @config missing extra. Keys rl => Foldable f => RowToList r rl => WriteCSVRecord r rl => Union config missing (Config extra) => { | config } -> f { | r } -> Aff String
stringify :: forall @r rl f m @config missing extra. MonadAff m => MonadRec m => Keys rl => Foldable f => RowToList r rl => WriteCSVRecord r rl => Union config missing (Config extra) => { | config } -> f { | r } -> m String
stringify config records = do
stream <- liftEffect $ make @r @config @missing @extra config
liftEffect $ for_ records \r -> write stream r
@@ -82,10 +83,12 @@ write :: forall @r rl a. RowToList r rl => WriteCSVRecord r rl => CSVStringifier
write s = writeImpl s <<< writeCSVRecord @r @rl
-- | Loop until the stream is closed, invoking the callback with each chunk of stringified CSV text.
foreach :: forall r x. CSVStringifier r x -> (String -> Aff Unit) -> Aff Unit
foreach :: forall m r x. MonadAff m => MonadRec m => CSVStringifier r x -> (String -> m Unit) -> m Unit
foreach stream cb = whileJust do
isReadable <- liftEffect $ Stream.readable stream
when (not isReadable) $ makeAff \res -> mempty <* flip (Event.once Stream.readableH) stream $ res $ Right unit
liftAff $ when (not isReadable) $ makeAff \res -> do
stop <- flip (Event.once Stream.readableH) stream $ res $ Right unit
pure $ Canceler $ const $ liftEffect stop
whileJust do
s <- liftEffect $ (join <<< map blush) <$> Stream.readEither stream
for_ s cb
@@ -94,7 +97,7 @@ foreach stream cb = whileJust do
pure $ if isClosed then Nothing else Just unit
-- | Read the stringified chunks until end-of-stream, returning the entire CSV string.
readAll :: forall r a. CSVStringifier r a -> Aff String
readAll :: forall r a m. MonadAff m => MonadRec m => CSVStringifier r a -> m String
readAll stream = do
chunks <- liftEffect $ ST.toEffect $ Array.ST.new
foreach stream $ void <<< liftEffect <<< ST.toEffect <<< flip Array.ST.push chunks