Skip to content

Commit

Permalink
Remove INLINE pragmas from the CSV module
Browse files Browse the repository at this point in the history
These were increasing compile times without improving run times. They
also caused the GHC simplifier to blow up with an upcoming change to
Vinyl to [change](VinylRecords/Vinyl#154) the
`ElField` type from a GADT to a `newtype`.
  • Loading branch information
acowley committed Jun 3, 2021
1 parent c4d8171 commit c75f9db
Show file tree
Hide file tree
Showing 2 changed files with 10 additions and 12 deletions.
10 changes: 10 additions & 0 deletions Frames-notes.org
Original file line number Diff line number Diff line change
Expand Up @@ -231,3 +231,13 @@ that ~readTableOpt~ could then use. This works out quite nicely.
(replace-regexpf "^ type [^ ]+ = [^ ]+.*$" "
\\&"))
#+END_SRC

* Removing ~INLINE~ pragmas
These may be hurting compile times while not helping runtime performance. I'll be looking at the =benchdemo= executable.

| Code | Compile (s) | Run (s) |
|--------------------------+-------------+---------|
| vinyl-0.13.3 with ~INLINE~ | 8.8 | 0.37 |
| vinyl-0.13.3 no ~INLINE~ | 8.0 | 0.36 |
| vinyl-0.14.0 no ~INLINE~ | 10.8 | 0.38 |

12 changes: 0 additions & 12 deletions src/Frames/CSV.hs
Original file line number Diff line number Diff line change
Expand Up @@ -244,7 +244,6 @@ readTableMaybeOpt :: (P.MonadSafe m, ReadRec rs, RMap rs)
-> P.Producer (Rec (Maybe :. ElField) rs) m ()
readTableMaybeOpt opts csvFile =
produceTokens csvFile (columnSeparator opts) >-> pipeTableMaybeOpt opts
{-# INLINE readTableMaybeOpt #-}

-- | Stream lines of CSV data into rows of ’Rec’ values values where
-- any given entry can fail to parse.
Expand All @@ -256,7 +255,6 @@ pipeTableMaybeOpt opts = do
P.map (rmap (either (const (Compose Nothing))
(Compose . Just) . getCompose)
. readRec)
{-# INLINE pipeTableMaybeOpt #-}

-- | Stream lines of CSV data into rows of ’Rec’ values values where
-- any given entry can fail to parse. In the case of a parse failure, the
Expand All @@ -267,28 +265,24 @@ pipeTableEitherOpt :: (Monad m, ReadRec rs)
pipeTableEitherOpt opts = do
when (isNothing (headerOverride opts)) (() <$ P.await)
P.map (readRow opts)
{-# INLINE pipeTableEitherOpt #-}

-- | Produce rows where any given entry can fail to parse.
readTableMaybe :: (P.MonadSafe m, ReadRec rs, RMap rs)
=> FilePath -> P.Producer (Rec (Maybe :. ElField) rs) m ()
readTableMaybe = readTableMaybeOpt defaultParser
{-# INLINE readTableMaybe #-}

-- | Stream lines of CSV data into rows of ’Rec’ values where any
-- given entry can fail to parse.
pipeTableMaybe :: (Monad m, ReadRec rs, RMap rs)
=> P.Pipe [T.Text] (Rec (Maybe :. ElField) rs) m ()
pipeTableMaybe = pipeTableMaybeOpt defaultParser
{-# INLINE pipeTableMaybe #-}

-- | Stream lines of CSV data into rows of ’Rec’ values where any
-- given entry can fail to parse. In the case of a parse failure, the
-- raw 'T.Text' of that entry is retained.
pipeTableEither :: (Monad m, ReadRec rs)
=> P.Pipe T.Text (Rec (Either T.Text :. ElField) rs) m ()
pipeTableEither = pipeTableEitherOpt defaultParser
{-# INLINE pipeTableEither #-}

-- -- | Returns a `MonadPlus` producer of rows for which each column was
-- -- successfully parsed. This is typically slower than 'readTableOpt'.
Expand All @@ -305,36 +299,31 @@ pipeTableEither = pipeTableEitherOpt defaultParser
-- False -> let r = recMaybe . readRow opts <$> T.hGetLine h
-- in liftIO r >>= maybe go (flip mplus go . return)
-- go
-- {-# INLINE readTableOpt' #-}

-- -- | Returns a `MonadPlus` producer of rows for which each column was
-- -- successfully parsed. This is typically slower than 'readTable'.
-- readTable' :: forall m rs. (P.MonadSafe m, ReadRec rs)
-- => FilePath -> m (Record rs)
-- readTable' = readTableOpt' defaultParser
-- {-# INLINE readTable' #-}

-- | Returns a producer of rows for which each column was successfully
-- parsed.
readTableOpt :: (P.MonadSafe m, ReadRec rs, RMap rs)
=> ParserOptions -> FilePath -> P.Producer (Record rs) m ()
readTableOpt opts csvFile = readTableMaybeOpt opts csvFile P.>-> go
where go = P.await >>= maybe go (\x -> P.yield x >> go) . recMaybe
{-# INLINE readTableOpt #-}

-- | Pipe lines of CSV text into rows for which each column was
-- successfully parsed.
pipeTableOpt :: (ReadRec rs, RMap rs, Monad m)
=> ParserOptions -> P.Pipe [T.Text] (Record rs) m ()
pipeTableOpt opts = pipeTableMaybeOpt opts >-> P.map recMaybe >-> P.concat
{-# INLINE pipeTableOpt #-}

-- | Returns a producer of rows for which each column was successfully
-- parsed.
readTable :: (P.MonadSafe m, ReadRec rs, RMap rs)
=> FilePath -> P.Producer (Record rs) m ()
readTable = readTableOpt defaultParser
{-# INLINE readTable #-}

readRecEither :: (ReadRec rs, RMap rs)
=> [T.Text] -> Either (Rec (Either T.Text :. ElField) rs) (Record rs)
Expand Down Expand Up @@ -372,7 +361,6 @@ readTableDebug csvFile =
pipeTable :: (ReadRec rs, RMap rs, Monad m)
=> P.Pipe [T.Text] (Record rs) m ()
pipeTable = pipeTableOpt defaultParser
{-# INLINE pipeTable #-}

-- * Writing CSV Data

Expand Down

0 comments on commit c75f9db

Please sign in to comment.