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 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