导管-将多个来源/生产者合而为一 [英] Conduit - Combining multiple Sources/Producers into one

查看:85
本文介绍了导管-将多个来源/生产者合而为一的处理方法,对大家解决问题具有一定的参考价值,需要的朋友们下面随着小编来一起学习吧!

问题描述

我正在使用sourceFile从文件中读取内容,但是我还需要将随机性引入处理操作中.我认为最好的方法是让生产者属于这种类型

I'm reading from a file using sourceFile, but I also need to introduce randomness into the processing operation. The best approach I believe is to have a producer that is of the type

Producer m (StdGen, ByteString)

其中StdGen用于生成随机数.

where StdGen is used to generate the random number.

我打算让生产者执行sourceFile的任务,并产生一个新的种子以在每次向下游发送数据时产生.

I'm intending for the producer to perform the task of sourceFile, as well as producing a new seed to yield everytime it sends data downstream.

我的问题是,似乎没有像zipSink这样的汇宿源合并器.阅读导管概述,似乎暗示您可以将Source嵌入到Conduit内,但是在示例中我看不到它是如何完成的.

My problem is, there doesn't seem to be a source-combiner like zipSink for sinks. Reading through Conduit Overview, it seems to be suggesting that you can embed a Source inside a Conduit, but I'm failing to see how it is done in the example.

任何人都可以提供一个示例,说明您将两个或多个IO源融合到一个Producer/Source中吗?

Can anyone provide an example of which you fuse two or more IO sources into one single Producer/Source?

一个例子:

{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE OverloadedStrings #-}

import System.Random (StdGen(..), split, newStdGen, randomR)
import ClassyPrelude.Conduit as Prelude
import Control.Monad.Trans.Resource (runResourceT, ResourceT(..))
import qualified Data.ByteString as BS

-- generate a infinite source of random number seeds
sourceStdGen :: MonadIO m => Source m StdGen
sourceStdGen = do
    g <- liftIO newStdGen
    loop g
    where loop gin = do
            let g' = fst (split gin)
            yield gin
            loop g'

-- combine the sources into one
sourceInput :: (MonadResource m, MonadIO m) => FilePath -> Source m (StdGen, ByteString)
sourceInput fp = getZipSource $ (,)
    <$> ZipSource sourceStdGen
    <*> ZipSource (sourceFile fp)

-- a simple conduit, which generates a random number from provide StdGen
-- and append the byte value to the provided ByteString
simpleConduit :: Conduit (StdGen, ByteString) (ResourceT IO) ByteString
simpleConduit = mapC process 

process :: (StdGen, ByteString) -> ByteString
process (g, bs) =
    let rnd = fst $ randomR (40,50) g
    in bs ++ pack [rnd]

main :: IO ()
main = do
    runResourceT $ sourceInput "test.txt" $$ simpleConduit =$ sinkFile "output.txt"

因此,此示例获取输入文件中的内容并将其写入输出文件,并在文件末尾附加40到50之间的随机ASCII值. (不要问我为什么)

So this example takes what's in the input file and write it to the output file, as well as appending a random ASCII value between 40 and 50 to the end of the file. (Don't ask me why)

推荐答案

您可以使用

You can use ZipSource for this. In your case, it might look something like:

sourceStdGens :: Source m StdGen
sourceBytes :: Source m ByteString
sourceBoth :: Source m (StdGen, ByteString)
sourceBoth = getZipSource $ (,)
    <$> ZipSource sourceStdGens
    <*> ZipSource sourceBytes

这篇关于导管-将多个来源/生产者合而为一的文章就介绍到这了,希望我们推荐的答案对大家有所帮助,也希望大家多多支持IT屋!

查看全文
登录 关闭
扫码关注1秒登录
发送“验证码”获取 | 15天全站免登陆