Skip to content

Instantly share code, notes, and snippets.

@Nexmean
Last active January 24, 2020 15:36
Show Gist options
  • Save Nexmean/5631a44487b0710a0aef9cd0505ecc34 to your computer and use it in GitHub Desktop.
Save Nexmean/5631a44487b0710a0aef9cd0505ecc34 to your computer and use it in GitHub Desktop.
очень меееееедлееееенно
-- Main.hs
module Main where
import Lib
import System.Clock
main :: IO ()
main = do
start <- getTime Monotonic
parseAndWrite source1 output
end <- getTime Monotonic
print $ end `diffTimeSpec` start
where
source1 = "/home/almakarov/Documents/EMHIRES_PVGIS_TSh_CF_n2_19862015.csv"
source11 = "/home/almakarov/Documents/EMHIRES_PVGIS_TSh_CF_n2_19862015(1).csv"
source2 = "/home/odomontois/Documents/EMHIRESPV_TSh_CF_Country_19862015.csv"
output = "/home/almakarov/Documents/Output.txt"
-- Lib.hs
{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE NumericUnderscores #-}
module Lib
( parseAndWrite
) where
import Data.Function ((&))
import qualified Data.ByteString as BS
import qualified Data.Text as T
import Streamly
import qualified Streamly.Prelude as S
import qualified Streamly.FileSystem.Handle as S
import qualified Streamly.Data.Unicode.Stream as S
import qualified Streamly.Memory.Array as SA
import qualified Streamly.Data.Fold as SF
import System.IO (withFile, IOMode(..))
parseAndWrite ifp ofp =
withFile ifp ReadWriteMode \iHandle ->
withFile ofp ReadWriteMode \oHandle ->
S.unfold S.readWithBufferOf (500, iHandle)
& S.decodeUtf8
& lines
>>= S.fromList . fmap (<> "\n") . T.split (== ',')
>>= S.fromList . T.unpack
& S.encodeUtf8
& S.scan (S.writeWithBufferOf 10_000 oHandle)
& serially
& S.drain
where
lines = S.splitOn (== '\n') (T.pack <$> SF.toList)
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment