Skip to content

Instantly share code, notes, and snippets.

@snoyberg
Last active August 29, 2015 13:56
Show Gist options
  • Save snoyberg/8888998 to your computer and use it in GitHub Desktop.
Save snoyberg/8888998 to your computer and use it in GitHub Desktop.
{-# LANGUAGE RankNTypes #-}
import Debug.Trace
import Control.Applicative
import Control.Lens (view, from, zoom, iso, Iso')
import Control.Monad.State.Strict (evalState)
import Pipes
import Pipes.Core as Pc
import qualified Pipes.Parse as Pp
import qualified Pipes.Prelude as P
newtype A = A Int
deriving Show
newtype B = B Int
deriving Show
atob (A i) = traceShow ("atob", i) (B i)
btoa (B i) = traceShow ("btoa", i) (A i)
ab :: Iso' A B
ab = iso atob btoa
piso :: Monad m => Iso' a b -> Iso' (Producer a m r) (Producer b m r)
piso i = iso (P.map (view i) <-<) (>-> P.map (view $ from i))
main :: IO ()
main = do
let src = P.map A <-< each [1..10]
let parser = (,,,) <$> zoom (piso ab) Pp.peek
<*> zoom (Pp.splitAt 3) Pp.drawAll
<*> zoom (Pp.splitAt 3 . piso ab) Pp.drawAll
<*> Pp.drawAll
let res = evalState parser src
print res
("atob",1)
("btoa",1)
("atob",2)
("btoa",2)
("atob",3)
("btoa",3)
("atob",4)
("btoa",4)
("atob",4)
("atob",5)
("btoa",5)
("atob",5)
("atob",6)
("btoa",6)
("atob",6)
("atob",7)
("btoa",7)
("atob",8)
("btoa",8)
("atob",9)
("btoa",9)
("atob",10)
("btoa",10)
(Just (B 1),[A 1,A 2,A 3],[B 4,B 5,B 6],[A 7,A 8,A 9,A 10])
@Davorak
Copy link

Davorak commented Feb 8, 2014

Chaning the parser to:

let parser = (,,,) <$> fmap (fmap atob) Pp.peek
                   <*> zoom (Pp.splitAt 3) Pp.drawAll
                   <*> zoom (Pp.splitAt 3 . piso ab) Pp.drawAll
                   <*> Pp.drawAll

results in what I would expect the output to be:

("atob",1)
("atob",4)
("atob",5)
("atob",6)
(Just (B 1),[A 1,A 2,A 3],[B 4,B 5,B 6],[A 7,A 8,A 9,A 10])

I have not yet used the new pipes-parse api in depth yet however so I do not have insight into why this is the case.

@Davorak
Copy link

Davorak commented Feb 8, 2014

Ok I think I understand, zoom (piso ab) Pp.peek is being applied to the entire stream. You need to delimit it to only the first element if that is all you want it to effect. So the parser:

  let parser = (,,,) <$> zoom (Pp.splitAt 1 . piso ab) Pp.peek
                     <*> zoom (Pp.splitAt 3) Pp.drawAll
                     <*> zoom (Pp.splitAt 3 . piso ab) Pp.drawAll
                     <*> Pp.drawAll

results in:

("atob",1)
("btoa",1)
("atob",4)
("atob",5)
("atob",6)
(Just (B 1),[A 1,A 2,A 3],[B 4,B 5,B 6],[A 7,A 8,A 9,A 10])

The fmap solution looks a little bit better since take a round trip from A to B to A is pointless in the case of an isomorphism. Off the top of my head I am unsure if this should be the default behavior of Pp.peek.

@snoyberg
Copy link
Author

snoyberg commented Feb 9, 2014

That's true for this specific example. But it's not generally true. Consider if, instead of a one-to-one isomorphism like we have here, the incoming stream was UTF8-encoded bytes, and you needed to peek at the first character. Peeking at the first byte (or equivalently using splitAt 1) would be insufficient. And more specifically, the reason I'm looking at this is to understand pipes-parse's ability to handle leftover preserving.

For a slightly more realistic example, I was playing with the following in conduit: https://gist.github.com/snoyberg/8888288.

@Davorak
Copy link

Davorak commented Feb 9, 2014

Sure this does not work at times when you do not have an isomorphism for the type your are streaming.

The basic idea is that I have an isomorphism, and I'd like to map all input values to convert from type A to type B.

This sentence in your stackoverflow question is where I, I would bet the same is true for J. Abrahamson, made the assumption that A is isomorphic to B in your problem case.

In the cases you care about it is not an isomorphism of the types you are streaming but from isomorphism between two streams. In which case it seems like you need a different approach then the one taken here or on stackoverflow(http://stackoverflow.com/a/21650705/128583).

Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment