Here's a little noodling. The desired operation is something like

     numberedChunkLoop 20 action2b documents

I don't think this is a particularly idiomatic implemenation, but the 
numbering
device is pleasantly simple and avoids using StateT and so on.  Also, the 
file handling part is completely dumb, but only one handle is open 
at a time.


      {-#LANGUAGE DeriveFunctor, OverloadedStrings #-}
      import qualified Pipes.Prelude as P
      import Pipes.Group 
      import Pipes.Parse as PP
      import Pipes
      import qualified Pipes.ByteString as PB
      import qualified Control.Foldl as L
      import Lens.Simple -- or Control.Lens or microlens etc.
      import Control.Monad.Trans.Free
      import Control.Monad.Trans.State.Strict
      import qualified Data.ByteString.Char8 as B
      import qualified System.IO as IO

      seven :: Monad m => Producer Int m ()
      seven = each [1..7::Int] 


      documents :: Monad m => Producer B.ByteString m ()
      documents = seven >-> P.map (B.pack . show) 

      seven_three :: Monad m => FreeT (Producer Int m) m ()
      seven_three =  view (chunksOf 3) seven

      seven_three_sums :: Monad m => Producer Int m ()
      seven_three_sums = L.purely folds L.sum seven_three


      -- probably reducible to standard combinators
      chunkLoop
        :: Monad m
        => Int
        -> (forall x . Producer a' m x -> m x)
        -> Producer a' m r -> m r
      chunkLoop n action p = loop (p ^. chunksOf n) where
        loop free = do 
          e <- runFreeT free
          case e of 
            Pure r -> return r
            Free ff -> do
              free2 <- action ff
              loop free2
        
      action0 p = do 
          (b, p') <- L.purely P.fold' L.sum p
          liftIO $ print b
          return p'
          
      -- >  chunkLoop 2 action0 seven
      -- 3
      -- 7
      -- 11
      -- 7
      -- [*Main]
      -- >  chunkLoop 5 action0 seven
      -- 15
      -- 13

      --  contained in standard combinators
      chunkLoop'
        :: Monad m
        => Int
        -> (forall x . Producer a m x -> Producer b m x)
        -> Producer a m r -> Producer b m r
      chunkLoop' n action = concats . maps action . view (chunksOf n) 

      action1 p = do
        x <- p
        liftIO $ putStrLn "I'm just a string marking end of group"
        return x
      -- > runEffect $ chunkLoop' 3 action1  seven >-> P.print
      -- 1
      -- 2
      -- 3
      -- I'm just a string marking end of group
      -- 4
      -- 5
      -- 6
      -- I'm just a string marking end of group
      -- 7
      -- I'm just a string marking end of group


      -- see implementation of numberedFrom below
      type ChunkSize = Int
      numberedChunkLoop
        :: Monad m
        => ChunkSize
        -> (forall x . Int -> Producer a' m x -> m x)
        -> Producer a' m r
        -> m r
      numberedChunkLoop chunk_size action p = loop numbered_chunky
       where
         numbered_chunky = numberFrom 1 (view (chunksOf chunk_size) p)
         loop free = do
           e <- runFreeT free
           case e of 
             Pure r -> return r
             Free (Number m ff) -> do
               free2 <- action m ff
               loop free2

      action2a  :: MonadIO m => Int -> Producer B.ByteString m a -> m a
      action2a n p = do 
        liftIO $ putStrLn $ "group " ++ show n
        fmap snd $ L.impurely P.foldM' printFold p
        where
          printFold = L.FoldM (\_ x-> liftIO $ putStr "    " >> print x) 
(return ()) return
    
      -- > numberedChunkLoop 3 action2a documents
      -- group 1
      --     "1"
      --     "2"
      --     "3"
      -- group 2
      --     "4"
      --     "5"
      --     "6"
      -- group 3
      --     "7"

      action2b :: MonadIO m => Int -> Producer B.ByteString m a -> m a
      action2b n p = do
       h <- liftIO $ IO.openFile ("xyz" ++ show n ++ ".txt") IO.WriteMode
       rest <- runEffect $ p >-> PB.toHandle h
       liftIO $ B.hPut h "\n"
       liftIO $ IO.hClose h
       return rest
 
       -- > numberedChunkLoop 3 action2b documents
       -- > :! ls | grep xyz
       -- xyz1.txt
       -- xyz2.txt
       -- xyz3.txt
       -- > :! cat xyz1.txt
       -- 123
       -- > :! cat xyz2.txt
       -- 456
       -- > :! cat xyz3.txt
       -- 7



      -- for the definition of 'numberedChunkLoop'
      -- one could use `Compose ((,) Int) f`
      data Numbered f r = Number !Int (f r)  deriving (Show, Eq, Ord, 
Functor)
      -- ghc derives : instance Functor f => Functor (Number f)

      numberFrom :: (Functor f, Monad m) => Int -> FreeT f m r -> FreeT 
(Numbered f) m r
      numberFrom = loop where
        loop n f = FreeT $ do
          p <- runFreeT f
          case p of
            Pure r -> return (Pure r)
            Free gg -> return $ Free $ Number n (fmap (loop (n+1)) gg)


-- 
You received this message because you are subscribed to the Google Groups 
"Haskell Pipes" group.
To unsubscribe from this group and stop receiving emails from it, send an email 
to haskell-pipes+unsubscr...@googlegroups.com.
To post to this group, send email to haskell-pipes@googlegroups.com.

Reply via email to