1 On the Duality of Streams 2 3 How Can Linear Types Help to Solve the Lazy IO Problem? 4 5 Jean-Philippe Bernardy Josef Svenningsson 6 University of Gothenburg Chalmers University of Technology 7 Gothenburg 41255, Sweden Gothenburg ???, Sweden 8 9 ACM Reference format: transparency (as Kiselyov [17] has shown). For example, one 10 Jean-Philippe Bernardy and Josef Svenningsson. 2016. On the Du- may rightfully expect1 that both following programs have 11 ality of Streams. In Proceedings of ACM Conference, Washington, the same behavior: 12 DC, USA, July 2017 (Conference’17), 12 pages. main = do inFile ← openFile "foo" ReadMode 13 DOI: 10.1145/nnnnnnn.nnnnnnn contents ← hGetContents inFile 14 putStr contents 15 treams, Continuations, Linear Types 16 hClose inFile 17 1 Introduction main = do inFile ← openFile "foo" ReadMode 18 As Hughes [12] famously noted, the strength of functional contents ← hGetContents inFile 19 programming languages resides in the composition mecha- hClose inFile 20 nisms that they provide. That is, simple components can be putStr contents 21 built and understood in isolation; one does not need to worry Indeed, the putStr and hClose commands act on unrelated 22 about interference effects when composing them. In particu- resources, and thus swapping them should have no observable 23 lar, lazy evaluation affords to construct complex programs by effect. However, while the first program prints the foo file, 24 pipelining simple transformation functions. Indeed, whereas the second one prints nothing. Indeed, because hGetContents 25 strict evaluation forces to fully reify each intermediate result reads the file lazily, the hClose operation has the effect to 26 between each computational step, lazy evaluation allows to truncate the list. In the first program, printing the contents 27 run all the computations concurrently, often without ever forces reading the file. One may argue that hClose should 28 allocating more than a single intermediate element at a time. not be called in the first place — but then, closing the handle 29 Unfortunately, lazy evaluation suffers from two drawbacks. happens only when the contents list can be garbage collected 30 First, it has unpredictable memory behavior. Consider the (in full), and relying on garbage collection for cleaning re- 31 following function composition: 32 sources is brittle; furthermore this effect compounds badly 33 f :: [a ] → [b ] with the first issue discussed above (unpredictability of buffer- 34 g :: [b ] → [ ] ing). If one wants to use lazy effectful computations, again, 35 h = g ◦ f the compositionality principle is lost. 36 In this paper, we propose to tackle both of these issues One hopes that, at run-time, the intermediate list ([b]) will 37 by taking advantage of linear types. One way to read this only be allocated element-wise, as outlined above. Unfortu- 38 paper is as an advocacy for linear types support in Haskell. nately, this desired behavior does not always happen. Indeed, 39 Indeed, even though one can tackle the above issues by using a necessary condition is that the production pattern of f 40 Monad-based libraries [16] our linear-logic-based types natu- matches the consumption pattern of g; otherwise buffering 41 rally capture a wealth of useful production and consumption occurs. In practice, this means that a seemingly innocuous 42 patterns. change in either of the function definitions may drastically 43 The first noteworthy type, corresponding to on-demand change the memory behavior of the composition, without 44 production of elements, is called a source (Src). An adap- warning. If one cares about memory behavior, this means 45 tation of the first code example above to use sources would that the compositionality principle touted by Hughes breaks 46 look as follows. down. 47 Second, lazy evaluation does not extend nicely to effect- f :: Src a ( Src b 48 ful processing. That is, if (say) an input list is produced g :: Src b ( Src c 49 by reading a file lazily, one is exposed to losing referential h = g ◦ f 50 Thanks to type-checking, we get the guarantee that the 51 Permission to make digital or hard copies of all or part of this work 52 for personal or classroom use is granted without fee provided that composition does not allocate more memory than the sum copies are not made or distributed for profit or commercial advantage 53 of its components. The second useful type, driving the and that copies bear this notice and the full citation on the first page. 54 Copyrights for components of this work owned by others than ACM consumption of elements, is called a sink (Snk). For example, 55 must be honored. Abstracting with credit is permitted. To copy the standard output is naturally given a sink type: otherwise, or republish, to post on servers or to redistribute to lists, 56 requires prior specific permission and/or a fee. Request permissions stdoutSnk :: Snk String 57 from [email protected]. 1 58 Conference’17, Washington, DC, USA This expectation is expressed in a Stack Overflow question, accessible © 2016 ACM. 978-x-xxxx-xxxx-x/YY/MM. . . $15.00 at this URL: http://stackoverflow.com/questions/296792/haskell-io- 59 DOI: 10.1145/nnnnnnn.nnnnnnn and-closing-files 60 61 Conference’17, July 2017, Washington, DC, USA Jean-Philippe Bernardy and Josef Svenningsson

1 Using it, we can implement the printing of a file as follows. work and future work are discussed respectively in sections 7 2 and 8. We conclude in Sec. 9. main = fileSrc "foo" ‘fwd‘ stdoutSnk 3 4 Beyond frugal memory usage, we have the guarantee of a 2 Preliminary: negation and 5 timely release of resources, even in the presence of exceptions. continuations 6 In the above, fileSrc provides the contents of a file, and fwd In this section we recall the basics of continuation-based pro- 7 forwards data from a source to a sink. The types are as gramming. We introduce our notation, and justify effectful 8 follows: continuations. 9 fileSrc :: FilePath → Src String We begin by assuming a type of effects Eff , which we keep 10 fwd :: Src a ( Snk a ( IO () abstract for now. We can then define negation as follows: 11 12 Sources provide data on-demand, while sinks decide when type N a = a ( Eff 13 they are ready to consume data. This is an instance of the A shortcut for double negations is also convenient. 14 push/pull duality. In general, push-streams control the flow type NN a = N (N a) 15 of computation, while pull-streams respond to it. We will 16 see that this polarization does not need to match the flow of The basic idea (imported from classical logic) pervading this 17 data: for example we support data sources with push-flavor, paper is that in the presence of effects, producing a result of 18 called co-sources (CoSrc). Co-sources are useful for example type α is equivalent to consuming an argument of type Nα. 19 when a source data stream needs precise control over the Dually, consuming an argument of type α is equivalent to 20 execution of effects it embeds (see Sec. 6). For example, producing a result of type Nα. We call these equivalences 21 sources cannot be demultiplexed, but co-sources can. the duality principle. 22 In a program which uses both sources and co-sources, the In classical logic, negation is involutive; that is: NN α = α. 23 need might arise to compose a function which returns a co- However, because we work within Haskell, we do not have 3 24 source with a function which takes a source as input: this is this equality . We can come close enough though. First, 25 the situation where list-based programs would silently cause double negations can always be introduced, using the shift 26 memory allocation. In our approach, this mismatch is caught operator: by the type system, and the user must explicitly conjure a 27 shift :: a NN a buffer to be able to write the composition: ( 28 shift x k = k x 29 f :: Src a CoSrc b ( Second, it is possible to remove double negations, but only 30 g :: Src b Src c ( if an effect can be outputted. Equivalently, triple negations 31 h = g ◦ buffer ◦ f 32 can be collapsed to a single one: The contributions of this paper are 33 unshift :: N (NN a) ( N a 34 • The formulation of principles for compositional resource- unshift k x = k (shift x) 35 aware programming in Haskell (resources include mem- Aside. The above two functions are the return and join 36 ory and files), based on linearity and polarization. of the double negation monad4; indeed adding a double 37 While these principles are borrowed from linear logic, negation in the type corresponds to sending the return value 38 as far as we know they have not been applied to to its consumer. However, we will not be using this monadic 39 Haskell programming before. structure anywhere in the following, because single negations 40 • An embodiment of the above principles, in the form of 2 play a central role in our approach. The monadic structure 41 a Hask-LL library for streaming IO. Besides support- is a mere diversion. 42 ing compositionality as outlined above, our library 43 features two concrete novel aspects: 2.1 Structure of Effects 44 1. A more lightweight design than state-of-the-art When dealing with purely functional programs, continuations 45 co-routine based libraries. have no effects. In this case, one can let Eff remain abstract, 46 2. Support for explicit buffering and control struc- or define it to be the empty type: Eff = ⊥. This choice 47 tures, while still respecting compositionality (Sec. is also natural when interpreting the original linear logic of 48 6). Girard [10], Laurent [21]. 49 Outline The rest of the paper is structured as follows. In The pure logic treats effects purely abstractly, but in- 50 Sec. 2, we recall the notions of continuations in presence of terpretations may choose to impose a richer structure on 51 effects. In Sec. 3, we present our design for streams, and them. Such interpretations would then not be complete 52 justify it by appealing to linearity principles. In Sec. 4, we with respect to the logic — but they would remain sound. 53 give an API to program with streams, and analyze their In our case, we first require Eff to be a monoid. Its unit 54 algebraic structure. In Sec. 5, we show how to embed IO into (mempty) corresponds to program termination, while the 55 streams. In Sec. 6, we discuss polarity mismatch. Related operator (mappend) corresponds to sequential composition 56 57 2Hask-LL is an extension of Haskell to linear types fully described by 3Even though Munch-Maccagnoni [23] achieves an involutive negation 58 Bernardy et al. [4]. For the purposes of this paper, the main addition in an intuitionistic language, he does so by stack manipulation, which is the linear arrow ( ) for functions which guarantee to consume their is not available in Haskell. 59 ( argument exactly once. Pairs also become linear. 4for join, substitute N a for a in the type of unshift 60 61 On the Duality of Streams Conference’17, July 2017, Washington, DC, USA

1 of effects. (This structure is standard to interpret the halt by the other side of the stream before proceeding. This 2 and mix rules in linear logic [3, 22]) means that each production is matched by a consumption, 3 For users of the stream library, Eff shall remain an abstract and vice versa; element-wise. 4 monoid. However in this paper we develop concrete effectful 5 streams, and therefore we greatly extend the structure of 3.1 Linearity 6 effects. In fact, because we will provide streams interacting For streams to be used safely, one cannot discard nor du- 7 with files and other operating-system resources, and write the plicate them, for otherwise effects may be discarded and 8 whole code in standard Hask-LL, we must pick Eff = IO(), duplicated, which is dangerous. For example, the same file 9 and ensure that Eff can be treated as a linear monoid. could be closed twice, or not at all. Indeed, the last action 10 type Eff = IO () of a sink typically involves closing the file. Timely closing of 11 the sink can only be guaranteed if the actions are run until 12 class Monoid a where reaching the end of the pipe (either Full or Nil). 13 mempty :: a Linear types allow to capture such an invariant: all func- 14 (<>) :: a a a tions from our library treat sources and sinks linearly. We 15 ( ( instance Monoid Eff underline that even individual elements are declared linear, 16 which allow us to store even effects in them. 17 The parts of the code which know about Eff = IO() must 18 be carefully written, because the type system does not pro- 3.2 Basics 19 vide strong guarantees about such code. In fact these IO- As a first illustration, we present three basic functions to 20 interacting functions do not interpret ⊥ in a standard way: manipulate Sources and Sinks: one to read from sources, one 21 they are non-standard extensions of its model. to write to sinks, and one to connect sources and sinks. 22 23 3 Streams Reading One may attempt to write the following function, 24 Our main guiding design principle is duality. In fact we waiting for data to be produced by a source. The second 25 will make crucial use of duality in the later sections of this argument is the effect to run if no data is produced, and the 26 paper. The duality principle is reflected in the design of the third is the effect to run given the data and the remaining 27 streaming library: we not only have a type for sources of source. 28 data but also a type for sinks. For example, a simple stream await :: Source a ( Eff ( (a ( Source a ( Eff ) ( Eff 29 processor reading from a single source and writing to a single await Nil eof = eof 30 sink may be given the following type: await (Cons x cs) k = cs $ Cont $ λxs → k x xs 31 simple :: Src a ( Snk a ( Eff 32 However, the above function breaks linearity (eof and k are 33 We will make sure that Snk is the negation of a source (and not always used), so we cannot define it as such. Instead 34 vice versa), and thus the type of the above program may we have to arrange the types so that await can choose itself 35 equivalently be given the following type: between the eof continuation and k. To do so, we must pro- 36 simple :: Src a ( Src a vide them as a so-called additive conjunction. The additive 37 conjunction is the dual of the Either type: there is a choice, However, having explicit access to sinks allows us to (for 38 but this choice falls on the consumer rather than the producer example) dispatch a single source to multiple sinks, as in the 39 of the input. The additive conjunction, written &, can be following type signature: 40 encoded by sandwiching Either between two inversions of 41 forkSrc :: Src (a, b) ( Snk a ( Snk b ( Eff the control flow, thereby switching the party which makes 42 We define sources and sinks by mutual recursion. Producing the choice: 43 a source means to select if some more is available (Cons) or type a & b = N (Either (N a)(N b)) 44 not (Nil). If there is data, one must then produce a data 45 item and consume a sink. (One will recognize the similarity between this definition and 46 the De Morgan’s laws.) Await can then be written as follows: data Source a where 47 Nil :: Source a await :: Source a (Eff &(a Source a Eff )) Eff 48 ( ( ( ( 49 Cons :: a ( N (Sink a) ( Source a await Nil r = r $ Left $ λeof → eof 50 data Sink a where await (Cons x xs) r = r $ Right $ λc → xs (Cont (c x)) 51 Full :: Sink a 52 Cont :: (N (Source a)) ( Sink a Writing One can also write data into a sink, and obtain a new, (doubly negated) sink which represents the state of the 53 Producing a sink means to select whether one can accept sink after the “old” sink has consumed the data. If the sink 54 more elements (Cont) or not (Full). In the former case, one is full, the data is ignored. 55 must then be able to consume a source. The Full case is 56 useful when the sink bails out early, for example when it runs yield :: a → Sink a ( (Sink a ( Eff ) ( Eff 57 out of space. yield x (Cont c) k = c (Cons x k) 58 Note that, in order to produce (or consume) the next ele- yield x Full k = k Full 59 ment, the source (or sink) must handle the effects generated 60 61 Conference’17, July 2017, Washington, DC, USA Jean-Philippe Bernardy and Josef Svenningsson

1 3.3 Baking in negations nnElim :: Src (NN a) ( Src a 0 0 0 2 Programming with Source and Sink explicitly is inherently nnIntro :: Snk a ( Snk (NN a) 3 continuation-heavy. As we have seen in the definition of 0 4 unshift, double-negations cannot simply be removed: effects nnElim = flipSnk nnIntro 0 5 must be collected and thus most functions must return an nnIntro k Nil = k Nil 6 Eff. Thus it is convenient to introduce negated variants of nnIntro0 k (Cons x xs) = x $ λx 0 → k (Cons x 0 $ nnElim xs) 7 source and sink types. 8 4 Effect-Free Streams 9 type Src a = N (Sink a) 10 type Snk a = N (Src a) The functions seen so far make no use of the fact that Eff can 11 These definitions have the added advantage to perfect the embed IO actions. Indeed, a large number of useful functions 12 duality between sources and sinks, while not restricting the over streams can be implemented without relying on IO. We 13 programs one can write. A benefit of the above definitions give an overview of effect-free streams in this section. 14 is that it becomes possible to forward data from Src to Snk 4.1 List-Like API 15 without dropping elements: 16 To begin, we show that one can implement a list-like API for fwd :: Src a Snk a Eff 17 ( ( sources, as follows: fwd = shift 18 empty :: Src a 19 We additionally introduce the following type synonym, which empty Full = mempty 20 is used to write the types of functions which manipulate empty (Cont k) = k Nil 21 Sources directly. 22 type Snk 0 a = N (Source a) cons :: a ( Src a ( Src a 23 0 0 0 cons a s s = yield a s s 24 Functions over Snk can be lifted manipulate Src, and in 25 turn Snk. We can do so generically for endomorphisms: (Taking the head or tail is not meaningful due to the linearity constraints: await must be used instead.) 26 flipSnk :: (Snk 0 a Snk 0 b) → Src b Src a ( ( Another useful function is the equivalent of take on lists. 27 flipSrc :: (Src a Src b) → Snk b Snk a ( ( Given a source, we can create a new source which ignores all 28 flipSnk s Full = s Full 29 but its first n elements. Conversely, we can prune a sink to flipSnk f s (Cont k) = s $ Cont $ (f k) 30 consume only the first n elements of a source. We can even flipSrc f snk src = snk (f src) 31 do it without breaking linearity, because all streams support 32 As a particular case, consider the mapping functions: early stopping. 33 mapSrc :: (a ( b) → Src a ( Src b takeSrc :: Int → Src a ( Src a 34 mapSnk :: (b ( a) → Snk a ( Snk b takeSnk :: Int → Snk a ( Snk a 35 The natural implementation is again by mutual recursion. 36 Mapping sinks is defined by flipping the mapping of sources; The main subtlety is that, when reaching the nth element, 37 and mapping of sources is defined by flipping mapping of both ends of the stream must be notified of its closing. Note 38 negated sources: the use of the monoidal structure of Eff in this case. 39 mapSnk f = flipSrc (mapSrc f ) 40 mapSrc f = flipSnk (mapSnk 0 f ) takeSrc 0 s t = s Full <> empty t 41 takeSrc i s t = flipSnk (takeSnk 0 i) s t Mapping of negated sources is defined by case analysis on 42 the concrete source, and the recursive case conveniently calls 0 43 takeSnk s Nil = s Nil mapSrc. 44 takeSnk 0 i s (Cons a s0) = s (Cons a (takeSrc (i − 1) s0)) 0 45 mapSnk snk Nil = snk Nil 46 mapSnk 0 f snk (Cons a s) takeSnk n = flipSrc (takeSrc n) 47 = snk (Cons (f a)(mapSrc f s)) 48 4.2 Algebraic structure When using double negations, it is sometimes useful to insert 49 or remove them inside type constructor. Introduction of Streams form (linear) monoids under concatenation: 50 double negation in sources and its elimination in sinks is a 51 instance Monoid (Src a) where special case of mapping. 52 (<>) = appendSrc 53 nnIntro :: Src a ( Src (NN a) mempty = empty 54 nnIntro = mapSrc shift 55 instance Monoid (Snk a) where 0 56 nnElim :: Snk (NN a) ( Snk a (<>) = appendSnk 0 57 nnElim = mapSnk shift mempty = shift Full 58 The duals are implemented by case analysis, following the We have already encountered empty above; the appending op- 59 mutual recursion pattern introduced above. erations are defined below. Intuitively, appendSrc first gives 60 61 On the Duality of Streams Conference’17, July 2017, Washington, DC, USA

1 control to the first source until it runs out of elements and class Drop a where drop :: a ( b ( b 2 then turns control over to the second source. This behavior 3 is implemented in the helper function forwardThenSnk. zipSrc :: (Drop a, Drop b) ⇒ Src a ( Src b ( Src (a, b) 4 appendSrc :: Src a Src a Src a forkSnk :: (Drop a, Drop b) ⇒ Snk (a, b) ( Src a ( Snk b 5 ( ( appendSrc s1 s2 Full = s1 Full <> s2 Full 6 Zip two sinks, and the dual. appendSrc s1 s2 (Cont s) 7 0 forkSrc :: Src (a, b) ( Snk a ( Src b 8 = s1 (Cont (forwardThenSnk s s2 )) zipSnk :: Snk a ( Snk b ( Snk (a, b) 9 0 0 0 forwardThenSnk :: Snk a Src a Snk a 0 10 ( ( Equivalent of scanl for sources, and the dual forwardThenSnk 0 snk 0 src Nil = src (Cont snk 0) 11 0 0 scanSrc :: (b → a ( (b, c)) → b → Src a ( Src c 12 forwardThenSnk snk src (Cons a s) 0 scanSnk :: (b → a ( (b, c)) → b → Snk c ( Snk a 13 = snk (Cons a (appendSrc s src)) 0 14 Sinks can be appended is a similar fashion. Equivalent of foldl for sources, and the dual. 15 0 appendSnk 0 :: Snk 0 a Snk 0 a Snk 0 a foldSrc :: (b → a ( b) → b → Src a ( NN b 16 ( ( appendSnk 0 s1 s2 Nil = s1 Nil <> s2 Nil foldSnk 0 :: (b → a b) → b → N b Snk a 17 ( ( 0 18 appendSnk s1 s2 (Cons a s) Drop some elements from a source, and the dual. = s1 (Cons a (forwardThenSrc s2 s)) 19 dropSrc :: Drop a ⇒ Int → Src a Src a 20 ( forwardThenSrc :: Snk 0 a Src a Src a dropSnk :: Drop a ⇒ Int → Snk a Snk a 21 ( ( ( 0 22 forwardThenSrc s2 = flipSnk (appendSnk s2 ) Convert a list to a source, and vice versa. 23 appendSnk :: Snk a → Snk a → Snk a fromList :: [a ] Src a 24 ( appendSnk t1 t2 s = t1 $ λcase toList :: Src a NN [a ] 25 ( Full → t2 empty <> s Full 26 Split a source in lines, and the dual. 27 Cont k → flipSrc (forwardThenSrc k) t2 s linesSrc :: Src Char Src String 28 The operations forwardThenSnk and forwardThenSrc are ( unlinesSnk :: Snk String Snk Char 29 akin to taking the difference between a source and a sink. ( 30 Thus we find it convenient to give them the following aliases: Interleave two sources, and the dual. 31 (−?) :: Snk 0 a Src a Snk 0 a interleave :: Src a Src a Src a 32 ( ( ( ( t −? s = forwardThenSnk 0 t s 33 interleaveSnk :: Snk a ( Src a ( Snk a 34 0 Forward data coming from the input source to the result (−!) :: Snk a ( Src a ( Src a 35 t −! s = forwardThenSrc t s source and to the second argument sink. 36 tee :: (a ( (b, c)) → Src a ( Snk b ( Src c 37 infixr −! 38 infixl −? Filter a source, and the dual. 39 filterSrc :: (a Maybe b) Src a Src b 40 Appending and subtracting interact in the expected way. ( ( ( 41 That is, the following equalities hold observationally: filterSnk :: (a ( Maybe b) ( Snk b ( Snk a 42 t −?(s1 <> s2 ) ≡ t −? s2 −? s1 Turn a source of chunks of data into a single source; and the 43 (t1 <> t2 ) −! s ≡ t1 −! t2 −! s dual. 44 unchunk :: Src [a ] Src a 45 Functor We have already seen the mapping functions for ( 46 sources and sinks: sources are functors and sinks are con- chunkSnk :: Snk a ( Snk [a ] 47 travariant functors. (Given the implementation of the mor- 48 phism actions it is straightforward to check the functor laws.) 4.4 App: Stream-Based Parsing 49 To finish with effect-free functions, we give an example of a 4.3 Table of effect-free functions 50 stream processor which applies a parser to a source of symbols 51 The above gives already an extensive API for sources and and returns a source of parse results. This conversion is useful 52 sinks, many more useful effect-free functions can be imple- for example to turn an XML file, provided as a stream of 53 mented on this basis. We give here a menu of functions that characters into a stream of (opening and closing) tags. 54 we have implemented, and whose implementation is available We begin by defining a pure parsing structure, modeled 5 55 online . after the parallel parsing processes of Claessen [6]. The parser 56 Two sources can be zipped if some extra left-over elements is continuation based, but the effects being accumulated are 57 can be dropped. Equivalently, a sink can be forked in the parsing processes, defined as follows. The Sym constructor 58 same situation. parses Just a symbol, or Nothing if the end of stream is 59 5https://github.com/jyp/organ/blob/master/Organ-HaskeLL.lhs reached. A process may also Fail or return a Result. 60 61 Conference’17, July 2017, Washington, DC, USA Jean-Philippe Bernardy and Josef Svenningsson

1 data P s res = Sym (Maybe s → P s res) hPutStrLn h c 2 | Fail hFileSnk h s 3 | Result res 4 hFileSnk :: Handle → Snk String A parser is producing the double negation of a: 5 hFileSnk h = shift (Cont (hFileSnk 0 h)) 6 newtype Parser s a = P (∀res.(a → P s res) → P s res) A file sink is then simply: 7 The monadic interface can then be built in the standard way: 8 fileSnk :: FilePath → Snk String 9 instance Monad (Parser s) where fileSnk file s = do 10 return x = P $ λfut → fut x h ← openFile file WriteMode 11 P f >>= k = P (λfut → f (λa → let P g = k a in g fut)) hFileSnk h s 12 instance Applicative (Parser s) where And the sink for standard output is (the 1 indicates that 13 pure = return there is a single instance of this resource): 14 (< ∗ >) = ap 15 instance Functor (Parser s) where stdoutSnk :: 1 Snk String 16 fmap = (<$>) stdoutSnk = hFileSnk stdout 17 18 The essential parsing ingredient, choice, rests on the ability (For ease of experimenting with our functions, the data items 19 to weave processes together; picking that which succeeds first, are lines of text — but an production-strength version would 20 and that which fails as last resort: provide chunks of raw binary data, to be further parsed.) Conversely, a file source reads data from a file, as follows: 21 weave :: P s a → P s a → P s a 22 weave Fail x = x hFileSrc :: Handle → Src String 23 weave x Fail = x hFileSrc h Full = hClose h 24 weave (Result res) = Result res hFileSrc h (Cont c) = do 25 weave (Result res) = Result res e ← hIsEOF h 26 weave (Sym k1 )(Sym k2 ) if e then do hClose h 27 c Nil 28 = Sym (λs → weave (k1 s)(k2 s)) else do x ← hGetLine h 29 (<|>) :: Parser s a → Parser s a → Parser s a 30 c (Cons x $ hFileSrc h) P p <|> P q = P (λfut → weave (p fut)(q fut)) 31 fileSrc :: FilePath → Src String 32 Parsing then reconciles the execution of the process with the 33 traversal of the source. In particular, whenever a result is fileSrc file sink = do 34 encountered, it is fed to the sink. If the parser fails, both h ← openFile file ReadMode 35 ends of the stream are closed. hFileSrc h sink 36 parse :: ∀s a.Parser s a → Src s ( Src a Combining the above primitives, we can then implement file 37 parse src Full = src Full copy as follows: 38 parse q@(P p0 ) src (Cont k) = scan (p0 $ λx → Result x) k src 39 copyFile :: FilePath → FilePath → Eff 40 where copyFile source target = fwd (fileSrc source) 0 41 scan :: P s a → Snk a ( Src s ( Eff (fileSnk target) scan (Result res) ret xs = ret (Cons res (parse q xs)) 42 It should be emphasized at this point that when running 43 scan Fail ret xs = ret Nil <> xs Full copyFile reading and writing will be interleaved: in order to 44 scan (Sym f ) mres xs = xs $ Cont $ λcase produce the next line in the source (in this case by reading 45 Nil → scan (f Nothing) mres empty from the file), the current line must first be consumed in the 46 Cons x cs → scan (f $ Just x) mres cs sink (in this case by writing it to disk). The stream behaves 47 fully synchronously, and no intermediate data is buffered. 48 5 Effectful streams Whenever a sink is full, the source connected to it will be 49 finalized. The next example shows what happens when a sink So far, we have constructed only effect-free streams. That is, 50 closes the stream early. Instead of connecting the source to a effects could be any monoid, and in particular the unit type. 51 bottomless sink, we connect it to one which stops receiving In this section we bridge this gap and provide some useful 52 input after three lines. 53 sources and sinks performing IO effects, namely reading and 54 writing to files. read3Lines :: Eff 55 We first define the following helper function, which sends read3Lines = fwd (hFileSrc stdin) 56 data to a handle, thereby constructing a sink. (takeSnk 3 $ fileSnk "text.txt") 0 0 57 hFileSnk :: Handle → Snk String Indeed, testing the above program reveals that it properly 58 hFileSnk 0 h Nil = hClose h closes stdin after reading three lines. This early closing is 59 hFileSnk 0 h (Cons c s) = do critical to modular stream programming: it allows proper 60 61 On the Duality of Streams Conference’17, July 2017, Washington, DC, USA

1 finalization of one end when an exception occurs at the other matched by a consumption (and vice versa). In sum, syn- 2 end. chronicity restricts the kind of operations one can construct, 3 in exchange for two guarantees: 4 5.1 1. The effects of connected sources and sinks are run 5 While the above implementations of file source and sink are synchronously 6 fine for illustrative purposes, their production-strength ver- 2. No implicit memory allocation happens 7 sions should handle exceptions. Doing so is straightforward: While the guarantees have been discussed so far, it may 8 as shown above, our sinks and sources readily support early be unclear how synchronicity actually restricts the programs 9 closing of the stream. one can write. In the rest of the section we show by example 10 The following code fragment shows how to handle an how the restriction plays out. 11 exception when reading a line in a file source. 12 6.1 Example: demultiplexing 13 hFileSrcSafe :: Handle → Src String One operation supported by synchronous behavior is the 14 hFileSrcSafe h Full = hClose h demultiplexing of a source, by connecting it to two sinks 15 hFileSrcSafe h (Cont c) = do (and the dual operation of mutiplexing sinks). 16 e ← hIsEOF h 0 17 dmux :: Src (Either a b) → Sink a → Sink b → Eff if e then do 18 dmux 0 sab Full tb = sab Full <> empty tb hClose h 19 dmux 0 sab ta Full = sab Full <> empty ta c Nil 20 dmux 0 sab (Cont ta)(Cont tb) = sab $ Cont $ λs → dmux ta tb s 21 else do 22 mx ← catch (Just <$> hGetLine h) dmux :: Snk 0 a → Snk 0 b → Snk 0 (Either a b) 23 (λ( :: IOException) → return Nothing) dmux ta tb Nil = ta Nil <> tb Nil 24 case mx of dmux ta tb (Cons ab c) = case ab of 25 Nothing → c Nil Left a → ta (Cons a $ λta0 → dmux 0 c ta0 (Cont tb)) 26 Just x → c (Cons x $ hFileSrcSafe h) Right b → tb (Cons b $ λtb0 → dmux 0 c (Cont ta) tb0) 27 28 Exceptions raised in hIsEOF should be handled in the same The key ingredient is that demultiplexing starts by reading 29 way. The file sink is responsible for handling its own ex- the next value available on the source. Depending on its 30 ceptions so there is no need to insert a handler around the value, we feed the data to either of the sinks and proceed. 31 invocation of the continuation c. Thus, dealing with excep- Besides, as soon as any of the three parties closes the stream, 32 tions is done once and for all when implementing the library the other two are notified. 33 of streams. The programmer using the library does not have However, multiplexing sources cannot be implemented 34 to be concerned with exceptions as they are caught and while respecting synchronicity. To see why, let us attempt 35 communicated properly under the hood, even if one would anyway, using the following type signature: 36 probably have a component of the Eff type indicating the mux :: Src a ( Src b ( Src (Either a b) 37 nature of the exception encountered, if any. Yet we leave it mux sa sb = ? 38 out in the proof of concept implementation presented in this 39 paper. We can try to fill the hole by reading on a source. However, if 40 Using exception handlers, as in the above snippet, will we do this, it falls onto the multiplexer to choose which source 41 secure the library from synchronous exceptions arising from to run first. We may pick sa, however it may be blocking, 42 accessing the file, but not from asynchronous exceptions while sb is ready with data. This is not really multiplexing, at 43 which may come from other sources. Asynchronous exception- best this approach would give us interleaving of data sources, 44 safety requires more machinery. The region library presented by taking turns. 45 in Kiselyov and Shan [18] can be used for this purpose, as In order to make any progress, we can let the choice of 46 outlined in Kiselyov [15]. which source to pick fall on the consumer of the stream. 47 The type that we need for output data in this situation is 48 6 Synchronicity and Asynchronicity the additive conjunction. We can then amend the type of multiplexing: 49 One of the main benefits of streams as defined here is that 50 the details of synchronizing concrete sink and sources are mux :: Src a ( Src b ( Src (a & b) 51 abstracted over. That is, one can build a data source re- Unfortunately, we still cannot implement multiplexing with 52 gardless of how the data is be consumed, or dually one can 53 the above type. Indeed, consider the following attempt, where build a sink regardless of how the data is produced; but, we begin by asking the consumer if it desires a or b. If the 54 despite the independence of definitions, all the code can (and 55 answer is a, we can extract a value from sa and yield it; and is) executed synchronously: composing a source and a sink symmetrically for b. 56 require no concurrency (nor any external control structure). 57 As discussed above, a consequence of synchronicity is that mux sa sb (Cont tab) = tab $ Cons 58 the programmer cannot be implicitly buffering data when (λab → case ab of 59 connecting a source to a sink: every production must be Left ka → sa $ Cont $ λ(Cons a resta) → ka a 60 61 Conference’17, July 2017, Washington, DC, USA Jean-Philippe Bernardy and Josef Svenningsson

1 Right kb → sb $ Cont $ λ(Cons b restb) → kb b) Compared to fileSrc, the difference are that this function 2 (error "oops") decides the ordering of effects ran in a co-sink connected to it. 3 That is, even though there is no data dependency between However, there is no way to then make a recursive call (oops) 4 the lines (1) and (2), they are run in a specific, given order. to continue processing. Indeed the recursive call to make must 5 We will see in the next section how this situation generalizes. depend on the choice made by the consumer (in one case we 6 The second example is an infinite co-sink that sends data should be using resta, in the other restb). However the type 7 to a file. 8 of Cons forces us to produce its arguments independently. coFileSink :: Handle → CoSnk String 9 What we need to do is to reverse the control fully: we need coFileSink h Full = hClose h 10 a data source which is in control of the flow of execution. 11 coFileSink h (Cont c) = c (Cons (hPutStrLn h) 6.2 Co-Sources, Co-Sinks 12 (coFileSink h)) We call the structure that we are looking for a co-source. 13 Compared to fileSnk, the difference is that the program does Co-sources are the subject of this section. We remember that 14 not control the order of execution of effects. The effect of producing Na is equivalent to consuming a, thus that a sink 15 writing the current line is put in a data structure, and its of Na is a (different kind of) source of a. We define: 16 execution is up to the co-source which eventually connects to 17 type CoSrc a = Snk (N a) the co-sink. Thus, the order of writing lines in the file depends 18 type CoSnk a = Src (N a) on the order of effects chosen in the co-source connected to 19 this co-sink. Implementing multiplexing on co-sources is then straightfor- 20 In sum, shifting from streams to co-streams shifts the con- ward, by leveraging dmux 0: 21 trol flow responsibility from the sink to the (co-)source. It 0 22 mux :: CoSrc a ( CoSrc b ( CoSrc (a & b) should be stressed that, in the programs which use the func- 23 mux 0 sa sb tab = sa $ λsa0 → sb $ λsb0 → dmux 0 (nnElim tab) sa0 tionssb0 defined so far (even those that use IO), synchronicity 24 is preserved: no data is buffered implicitly, and reading and We use the rest of this section to study the property of co- 25 writing occur in lockstep. 26 sources and co-sinks. Firstly CoSrc is a functor, and CoSnk 27 is a contravariant functor. 6.3 Asynchronicity 28 mapCoSnk :: (b ( a) → CoSnk a ( CoSnk b We have seen so far that synchronicity gives useful guaran- 29 mapCoSnk f = mapSrc (λb0 → λa → b0 (f a)) tees, but restricts the kind of programs one can write. In 30 this section, we provide primitives which allow controlled 31 mapCoSrc :: (a ( b) → CoSrc a ( CoSrc b asynchronous programming within our framework. The main 32 mapCoSrc f snk src = snk (mapCoSnk f src) benefit of sticking to our framework in this case is that asyn- 33 chronous behavior is circumscribed to the explicit usages 34 Elements of a co-source are accessed only in when and in of these primitives. That is, the benefits of synchronous 35 the order that the co-source imposes. Consequently, one programming still hold locally. 36 cannot in general extract the contents of a co-source as a list. 37 Attempting to implement this extraction looks as follows. Scheduling Asynchronicity arises either from an excess or a deficit of control. Let us first examine the latter case, 38 coToList :: Snk 0 (N a) → NN [a ] which involves two streams that do not control the flow 39 coToList k1 k2 = k1 $ Cons (λa → k2 [a ]) (error "rest") 40 of execution. This means that effects must be scheduled coToList k1 k2 = k2 $ (error "a?"):(error "rest") 41 explicitly and externally to the streams. This situation arises 42 If one tries to begin by eliminating the co-source (first equa- for example converting a Src to a CoSrc, as we have seen in 43 tion), then there is no way to produce subsequent elements of the example above, when writing the file co-source. 44 the list. If one tries to begin by constructing the list (second In general, given a Schedule, we can implement the follow- 45 equation), then no data is available. ing two conversions: 46 Yet it is possible to define useful co-sources and co-sinks. srcToCoSrc :: Schedule a → Src a ( CoSrc a 47 The first example shows how to provide a file as a co-source: coSnkToSnk :: Schedule a → CoSnk a ( Snk a 48 coFileSrc :: Handle → CoSrc String We define a Schedule as the reconciliation between a source 49 coFileSrc h snk = do and a co-sink: 50 e ← hIsEOF h 51 type Schedule a = Source a ( CoSnk a ( Eff snk $ if ¬ e 52 Implementing the conversions is then straightforward: 53 then Full 54 else Cont $ λcase srcToCoSrc strat s0 s = s0 $ Cont (flip strat s) 55 Nil → hClose h coSnkToSnk strat s0 s = s $ Cont (flip strat s0 ) 56 Cons x xs → do What are possible scheduling strategies? The simplest, and 0 57 x ← hGetLine h most natural one is sequential execution. Namely, looping 58 x x 0 -- (1) through both sources and match the consumptions/productions 59 (coFileSrc h) xs -- (2) element-wise, as follows. 60 61 On the Duality of Streams Conference’17, July 2017, Washington, DC, USA

1 sequentially :: Drop a ⇒ Schedule a If one is prepared to use unbounded memory, one may use 2 sequentially Nil s = s Full Concurrent Haskell channels as a buffering means: 3 0 0 sequentially (Cons x xs) s = s $ Cont $ λs → case s of chanCoSnk :: Chan a → CoSnk a 4 0 0 Cons x xs → do chanCoSnk Full = return () 5 x 0 x 6 chanCoSnk h (Cont c) = c (Cons (writeChan h) xs $ Cont $ λt → sequentially t xs0 7 (chanCoSnk h)) 8 Nil → drop x (xs Full) chanSrc :: Chan a → Src a 9 For most streams, sequential execution is the only sensible 10 schedule: indeed, sources and sinks often expect their effects chanSrc Full = return () 11 to be run in the order prescribed by the stream. Swapping chanSrc h (Cont c) = do x ← readChan h 12 the arguments to <> in the above means that Full effects c (Cons x $ chanSrc h) 13 will be run first, spelling disaster. 14 However, in certain cases running effects out of order may chanBuffer :: CoSrc a ( Src a 15 make sense. If the monoid of effects is commutative (or chanBuffer f g = do 16 if the programmer is confident that execution order does c ← newChan 17 not matter) one can shuffle the order of execution of effects. forkIO $ f (chanCoSnk c) 18 This re-ordering can be taken advantage of to run effects chanSrc c g 19 concurrently, as follows: Note that it is easy to create a bounded channel-based buffer, 20 concurrently :: Drop a ⇒ Schedule a by guarding the writes with a semaphore. 21 concurrently Nil s = s Full 0 22 chanCoSnk :: Chan a → QSem → CoSnk a 0 0 concurrently (Cons x xs) s = s $ Cont $ λs → case s of 0 23 chanCoSnk Full = return () 0 0 24 Cons x xs → do chanCoSnk 0 h s (Cont c) = c (Cons write 0 25 forkIO (x x) (chanCoSnk 0 h s)) 0 26 xs $ Cont $ λt → concurrently t xs where write x = do waitQSem s 27 Nil → drop x (xs Full) writeChan h x 28 The above strategy is useful if the production or consumption 29 0 of elements is expensive and distributable over computation chanSrc :: Chan a → QSem → Src a 30 units. While the above implementation naively spawns a chanSrc0 Full = return () 31 thread for every element, in reality one should most likely chanSrc0 h s (Cont c) = do x ← readChan h 32 divide the stream into chunks before spawning threads. Be- signalQSem s 33 cause strategies are separate components, a bad choice is 0 34 c (Cons x $ chanSrc h s) easily remedied to by swapping one strategy for another. 35 boundedChanBuffer :: Int → CoSrc a Src a 36 Buffering Consider now the dual situation where we have ( boundedChanBuffer n f g = do 37 two streams and both of them want to control the execu- 38 tion flow, for example when converting a CoSrc to a Src. c ← newChan 39 The conciliation can only be implemented by running both s ← newQSem n 0 40 streams in concurrent threads, and have them communicate forkIO $ f (chanCoSnk c s) 0 41 via some form of buffer. Using the primitives seen so far, one chanSrc c s g 42 can implement a file-based buffer, as follows: In certain situations (for example for a stream yielding a 43 fileBuffer :: String → CoSrc String Src String status whose history does not matter, like mouse positions) 44 ( fileBuffer tmpFile f g = do one may want to ignore all but the latest datum. In this case 45 h0 ← openFile tmpFile WriteMode a single memory cell can serve as buffer: 46 0 47 forkIO $ f (coFileSink h ) varCoSnk :: IORef a → CoSnk a 48 h ← openFile tmpFile ReadMode varCoSnk Full = return () 49 hFileSrc h g varCoSnk h (Cont c) = c (Cons (writeIORef h) 50 It should be stressed that buffering is a risky operation: (varCoSnk h)) 51 it is a balancing act between the amount of resources one 52 is prepared to allocate and the dynamic behaviours of the varSrc :: IORef a → Src a 53 streams. In fact, our simple file-buffer above is likely to fail if varSrc Full = return () 54 the intermediate file is a regular file. Indeed, the reader may varSrc h (Cont c) = do x ← readIORef h 55 for example be faster than the writer and reach an end of file c (Cons x $ varSrc h) 56 prematurely. One can use instead a UNIX pipe, but then one 57 then faces the issue that pipes are of fixed maximum size: if varBuffer :: a → CoSrc a ( Src a 58 the writer outputs data in too large chunks, a deadlock will varBuffer initialValue f g = do 59 occur. c ← newIORef initialValue 60 61 Conference’17, July 2017, Washington, DC, USA Jean-Philippe Bernardy and Josef Svenningsson

1 forkIO $ f (varCoSnk c) forkIO $ s2 (chanCoSnk c) 2 varSrc c g chanSrc c t 3 4 The above buffering operations work on sources, but they We then have to send each message to both clients. This 5 can be generically inverted to work on sinks, as follows. may be done using the following effect-free function, which forwards everything sent to a sink to its two argument sinks. 6 flipBuffer :: (∀a.CoSrc a ( Src a) → Snk b ( CoSnk b 0 0 0 0 7 flipBuffer f s = f (s ◦ nnElim) collapseSnk :: (a ( (b, c)) → Snk b ( Snk c ( Snk a 8 collapseSnk 0 t1 t2 Nil = t1 Nil <> t2 Nil 9 6.4 Summary collapseSnk 0 dup t1 t2 (Cons x xs) 10 = t1 (Cons y $ λc1 → 11 In sum, we can classify streams according to polarity: t2 (Cons z $ tee0 dup xs c1 )) 12 • Pull: source and co-sinks 13 • Push: sinks and co-sources where (y, z) = dup x 14 We then have three situations when composing stream tee0 :: (a (b, c)) → Src a → Sink b → Src c 15 processors: ( 0 16 tee deal s1 t1 Full = s1 Full <> empty t1 1. Matching polarities (one pull, one push). In this case 0 17 tee deal s1 Full t2 = s1 Full <> empty t2 behavior is synchronous; no concurrency appears. 0 0 18 2. Two pull streams. In this case an explicit loop must tee deal s1 (Cont t1 )(Cont t2 ) = s1 $ Cont $ collapseSnk deal t1 t2 19 process the streams. If effects commute, the pro- The server can then be defined by composing the above two 20 grammer may run effects out of order, potentially functions. 21 concurrently. 22 3. Two push streams. In this case the streams must run server :: (a ( (a, a)) ( Client a ( Client a ( Eff 23 in independent threads, and the programmer needs server dup (i1 , o1 )(i2 , o2 ) = fwd (bufferedDmux i1 i2 ) 24 to make a choice for the communication buffer. One (collapseSnk dup o1 o2 ) 25 needs to be careful: if the buffer is too small a deadlock 26 may occur. 27 7 Related Work Therefore, when programming with streams, one should 28 7.1 Polarities, data structures and control consume push types when one can, and pull ones when one 29 must. Conversely, one should produce pull types when one One of keys ideas formalized in this paper is to classify 30 can, and push ones when one must. streams by polarity. The push polarity (sinks, co-sources) 31 controls the execution thread, whereas the pull one (sources, 32 6.5 App: idealized echo server co-sinks) provide data. This idea has been leveraged to 33 bring efficient array programming facilities to functional We finish the exposition of asynchronous behavior with a 34 programming [1, 3, 7]. small program sketching the skeleton of a client-server appli- 35 This concept is central in the literature on Girard’s linear cation. This is a small server with two clients, which echoes 36 logic [21, 29]. However, in the case of streams, this idea dates the requests of each client to both of them. 37 back at least to Jackson [13] (Kay [14] gives a good summary The server communicates with each client via two streams, 38 of Jacksons’ insight). one for inbound messages, one for outbound ones. We want 39 Our contribution is to bring this idea to stream program- each client to be able to send and receive messages in the 40 ming in Hask-LL. (While duality was used for Haskell array order that they like. That is, from their point of view, they 41 programming, it has not been taken advantage for stream are in control of the message processing order. Hence a client 42 programming, and there was no emphasis on linearity.) We should have a co-sink for sending messages to the server, 43 believe that our implementation brings together the practical and a source for receiving them. On the server side, types 44 applications that Jackson intended, while being faithful to are dualized and thus, a client is represented by a pair of a 45 the theoretical foundations in logic, via the double-negation co-source and a sink: 46 embedding. 47 type Client a = (CoSrc a, Snk a) 48 7.2 Transducers For simplicity we implement a chat server handling exactly 49 two clients. Shivers and Might [24] introduces a transducer library which 50 The first problem is to multiplex the inputs of the clients. enables fusing the transducers to avoid the overhead of com- 51 In the server, we do not actually want any client to be position. Transducers are defined on top of channels, a 52 controlling the processing order. Hence we have to multiplex recursive datatype reminiscent of our Source and Sink. In 53 the messages in real time, using a channel (note the similarity particular they use a type for continuations similar to N . 54 with chanBuffer): However, a channel is just one type and does not exhibit the 55 duality that our sources and sinks provide. Their library do 56 bufferedDmux :: CoSrc a ( CoSrc a ( Src a feature a notion of sources and sinks but they are not the 57 bufferedDmux s1 s2 t = do main abstraction. They are simply aids for providing and 58 c ← newChan consuming data from transducers, respectively. Transducers 59 forkIO $ s1 (chanCoSnk c) are “affine”; they can be used at most once. The reason 60 61 On the Duality of Streams Conference’17, July 2017, Washington, DC, USA

1 linearity is not required is that none of the transducers are ef- Yet, in that work, linearity is only briefly mentioned; the use 2 fectful, the library only provides pure transducers. Therefore of a monad rather than monoid persists; and mismatching 3 it is also not concerned with releasing resources in a timely polarities are not discussed, let alone taken advantage of. 4 fashion. Several production-strength libraries have been built upon 5 the concept of iteratees, including pipes [11], conduits [25] and 6 7.3 Iteratees machines [20]. While we focus our comparison with iteratees, 7 We consider that the state of the art in Haskell stream most of our analysis carries to the production libraries. There 8 processing is embodied by Kiselyov’s iteratees [2012]. is additionally a large body of non peer-reviewed literature 9 The type for iteratees can be given the following definitions: discussing and analyzing either iteratees or its variants. The 10 proliferation of libraries for IO streaming in Haskell indicates data I s m a = Done a | GetC (Maybe s → m (I s m a)) 11 that a unifying foundation for them is needed, and we hope 12 An iteratee I s m a roughly corresponds to a sink of s which that the present paper provides a basis for such a foundation. 13 also returns an a — but it uses a monad m rather than a 14 monoid Eff for effects. 7.4 Feldspar monadic streams 15 The above type contains a continuation in the GetC con- Feldspar, a DSL for digital signal processing, has a notion of 16 structor. Therefore, one must be careful about discarding or streams built on monads [2, 27]. In Haskell the stream type 17 duplicating iteratees. Hence, such libraries typically provide can be written as follows: 18 higher-level interfaces to discourage non-linear usages. type Stream a = IO (IO a) 19 A first advantage of our approach is the formulation and 20 emphasis on the linearity constraint, which is central to cor- Intuitively the outer monad can be understood as performing 21 rect use of effectful continuations. It appears that variants initialization which creates the inner monadic computation. 22 of iteratees (including the pipes library) make the represen- The inner computation is called iteratively to produce the 23 tation abstract, but at the cost of a complex interface for elements of the stream. 24 programming them. By stating the linearity requirement no Compared to the representation in the present paper, the 25 complex abstract API is necessary to guarantee safety. monadic streams only has one form of stream, corresponding 26 A second advantage of our library is that effects are not to a source. Also, there is no support for timely release of 27 required to be monads. Indeed, the use of continuations resources, such things need to be dealt with outside of the 28 already provide the necessary structure to combine compu- stream framework. Additionally, even conceptually effect-free 29 tations (recall in particular that double negation is already streams rely on running IO effects. 30 a monad). We believe that having a single way to bind in- 31 termediate results (continuations vs. both continuations and 7.5 Session Types 32 monads) is a simplification in design, which may make our In essence our pair of types for stream is an encoding of 33 library more approachable. a protocol for data transmission. This protocol is readily 34 The presence of source and sinks also clarifies how to expressible using linear types, following the ideas of Wadler 35 build complex types programs from basic blocks. Indeed, [28] and Caires et al. [5]: 36 iteratee-based libraries make heavy use of the following types: Source a = 1 ⊕ (a ⊗ N (Sink a)) 37 Sink a = 1 ⊕ N (Source a) 38 type Enumerator el m a = I el m a → m (I el m a) 39 type Enumeratee elo eli m a = For the translation to Haskell, we have chosen to use a 40 I eli m a → I elo m (I eli m a) lightweight encoding, assuming linearity of effectful variables; 41 It is our understanding that these types make up for the arguing at the same time for support of linearity in future 42 lack of explicit sources by putting iteratees (sinks) on the Haskell versions. Yet, other encodings could be chosen. For 43 left-hand-side of an arrow. Enumerators are advantageously example, we could have used the technique of Pucella and 44 replaced by sources, and enumeratees by simple functions Tov (Haskell session types with almost no class), which does 45 from source to source (or sink to sink). not require abiding to linearity. 46 A third advantage of our approach is that the need for 47 buffering (or the scheduling opportunities) are clearly indi- 8 Future Work 48 cated by the type system, as mismatching polarities. As we see it, a natural next step for the present work is to 49 In more recent work Kiselyov et al. [19] present a continuation- show that intermediate sources and sinks can be deforested. 50 based pretty printer, which fosters a more stylized used of As it stands, we believe that a standard approach [8, 9, 26] 51 continuations, closer to what we advocate here. Producers should work: 1. encode sources (and sinks) as non-recursive 52 and consumers (sources and sinks) are defined more simply, data types 2. show that standard evaluation rules remove 53 using types which correspond more directly to negations: the intermediate occurrences of the encoded types. However, 54 this work has not been carried out yet. 55 type GenT e m = ReaderT (e → m ()) m The duality principle exposed here as already been taken 56 type Producer m e = GenT e m () advantage of to support fusible array types [1, 3]. The present 57 type Consumer m e = e → m () paper has shown how to support effectful stream computa- 58 type Transducer m1 m2 e1 e2 = tions. One would naturally think that the same principle can 59 Producer m1 e1 → Producer m2 e2 be applied to other lazily-evaluated data structures, such as 60 61 Conference’17, July 2017, Washington, DC, USA Jean-Philippe Bernardy and Josef Svenningsson

1 the game trees discussed by Hughes [12]: as far as we know [15] O. Kiselyov. Combining monadic regions and iteratees. http: 2 this remains to be investigated. //okmij.org/ftp/Streams.html#regions, Jan 2012. [16] O. Kiselyov. Iteratees. In Funct. and Logic Prog. - 11th Inter- 3 national Symposium, FLOPS 2012, Kobe, Japan, May 23-25, 4 9 Conclusion 2012. Proc., pages 166–181, 2012. 5 [17] O. Kiselyov. Lazy io breaks equational reasoning, 2013. Manu- We have cast a new light on the current state of coroutine- script available on the author’s web page. 6 based computation in Haskell, which we have done by drawing [18] O. Kiselyov and C.-c. Shan. Lightweight monadic regions. In 7 Haskell Symposium. ACM, 2008. inspiration from classical linear logic. We have further shown [19] O. Kiselyov, S. L. Peyton Jones, and A. Sabry. Lazy v. yield: 8 that the concepts of duality and polarity provide design Incremental, linear pretty-printing. In Prog. Languages and 9 principles to structure continuation-based code. In particular, Systems - 10th Asian Symposium, APLAS 2012, Kyoto, Japan, 10 December 11-13, 2012. Proc., pages 190–206, 2012. we have shown that mismatches in polarity correspond to [20] E. A. Kmett, R. Bjarnason, and J. Cough. The machines package, 11 buffers and control structures, depending on the kind of 2015. 12 mismatch. [21] O. Laurent. Etude de la polarisation en logique. Th`esede 13 doctorat, Universit´eAix-Marseille II, 2002. Using effectful continuations is not a new idea; in fact it [22] P.-A. Melli`esand N. Tabareau. Resource modalities in tensor 14 was the standard way of writing effectful programs in Haskell logic. Ann. Pure Appl. Logic, 161(5):632–653, 2010. 15 [23] G. Munch-Maccagnoni. Formulae-as-types for an involutive nega- 1.2. Later versions of Haskell switched to a monadic approach. tion. In Joint Meeting of the Twenty-Third EACSL Annual 16 However, given the issues outlined in the introduction, and Conf. on Comp. Sci. Logic (CSL) and the Twenty-Ninth An- 17 especially the error-prone character of lazy monadic IO, many nual ACM/IEEE Symposium on Logic in Comp. Sci. (LICS), 18 CSL-LICS ’14, Vienna, Austria, July 14 - 18, 2014, pages libraries have reverted to explicitly using co-routines. 70:1–70:10, 2014. 19 A possible reason for selecting monads over co-routines is [24] O. Shivers and M. Might. Continuations and transducer compo- 20 that monads are rooted in solid theory (categories). However, sition. ACM SIGPLAN Notices, 41(6):295–307, 2006. 21 [25] M. Snoyman. The conduit package, 2015. we hope to have shown that co-routines are also rooted in [26] J. Svenningsson. Shortcut fusion for accumulating parameters & 22 solid theory, namely linear logic. If Haskell had support for zip-like functions. In Proc. of ICFP 2002, pages 124–132. ACM, 23 2002. linear types, co-routines could be used safely, without the [27] J. Svenningsson, E. Axelsson, A. Persson, and P. A. Jonsson. 24 quirks of lazy IO. Efficient monadic streams. In Presented at Trends in Functional 25 Programming, 2015. 26 [28] P. Wadler. Propositions as sessions. In Proc. of ICFP 2012, Acknowledgments ICFP ’12, pages 273–286. ACM, 2012. 27 We gratefully thank Koen Claessen, Atze van der Ploeg and [29] N. Zeilberger. The logical basis of evaluation order and pattern- 28 matching. PhD thesis, Carnegie Mellon University, 2009. Nicolas Pouillard for feedback on drafts of this paper. The 29 source code for this paper is a literate Haskell file, whose latest 30 version is available at this url: https://github.com/jyp/organ/blob/master/Organ- 31 HaskeLL.lhs 32 33 34 References [1] J. Ankner and J. D. Svenningsson. An edsl approach to high 35 performance haskell programming. In Proc. of the 2013 ACM 36 SIGPLAN symposium on Haskell, pages 1–12. ACM, 2013. 37 [2] E. Axelsson, K. Claessen, G. D´evai, Z. Horv´ath,K. Keijzer, B. Ly- ckeg˚ard,A. Persson, M. Sheeran, J. Svenningsson, and A. Vajda. 38 Feldspar: A domain specific language for digital signal process- 39 ing algorithms. In Formal Methods and Models for Codesign 40 (MEMOCODE), pages 169–178. IEEE, 2010. [3] J.-P. Bernardy, V. L´opez Juan, and J. Svenningsson. Composable 41 efficient array computations using linear types, 2015. Submitted 42 to ICFP 2015. Draft available online. [4] J.-P. Bernardy, A. Spiwack, M. Boespflug, R. Newton, and S. Pey- 43 ton Jones. Retrofitting linear types, 2017. Draft available online. 44 [5] L. Caires, F. Pfenning, and B. Toninho. Towards concurrent type 45 theory. In Proc. of the 8th ACM SIGPLAN workshop on Types in language design and implementation, pages 1–12. ACM, 2012. 46 [6] K. Claessen. Parallel parsing processes. J. of Funct. Prog., 14 47 (6):741–757, 2004. 48 [7] K. Claessen, M. Sheeran, and B. J. Svensson. Expressive array constructs in an embedded gpu kernel programming language. 49 In Proceedings of the 7th workshop on Declarative aspects and 50 applications of multicore programming, pages 21–30. ACM, 2012. [8] D. Coutts, R. Leshchinskiy, and D. Stewart. Stream fusion: From 51 lists to streams to nothing at all. In Haskell, pages 315–326. 52 ACM, 2007. 53 [9] A. Gill, J. Launchbury, and S. Peyton Jones. A short cut to deforestation. In Proc. of FPCA, pages 223–232. ACM, 1993. 54 [10] J.-Y. Girard. Linear logic. Theor. Comp. Sci., 50(1):1–101, 1987. 55 [11] G. Gonzalez. The pipes package, 2015. 56 [12] J. Hughes. Why funct. prog. matters. Comp. J., 32(2):98–107, 1989. 57 [13] M. A. Jackson. Principles of Program Design. Academic Press, 58 Inc., 1975. [14] M. Kay. You pull, I’ll push: on the polarity of pipelines. In 59 Proceeding of Balisage: The Markup Conf., 2008. 60 61