[Haskell-cafe] stream interface vs string interface: references

oleg at okmij.org oleg at okmij.org
Tue Sep 3 10:36:47 CEST 2013


> For lazy I/O, using shows in Haskell is a good analogue of using
> #printOn: in Smalltalk.  The basic form is "include this as PART of
> a stream", with "convert this to a whole string" as a derived form.
>
> What the equivalent of this would be for Iteratees I don't yet
> understand.

Why not to try simple generators first, which are simpler, truly. It seems
generators reproduce the Smalltalk printing patterns pretty well --
even simpler since we don't have to specify any stream. The printing
takes linear time in input size. The same `printing' generator can be
used even if we don't actually want to see any output -- rather, we
only want the statistics (e.g., number of characters printed, or
number of lines, etc). Likewise, the same printing generator
print_yield can be used if we are to encode the output somehow (e.g.,
compress it). The entire pipeline can run in constant space (if
encoding is in constant space).

Here is the code

module PrintYield where

-- http://okmij.org/ftp/continuations/PPYield/
import GenT

import Data.Set as S
import Data.Foldable
import Control.Monad.State.Strict

type Producer m e            = GenT e m ()

class PrintYield a where
    print_yield :: Monad m => a -> Producer m String

instance PrintYield Int where
    print_yield = yield . show

instance (PrintYield a, PrintYield b) => PrintYield (Either a b) where
    print_yield (Left x)  = yield "Left "  >> print_yield x
    print_yield (Right x) = yield "Right " >> print_yield x

instance (PrintYield a) => PrintYield (Set a) where
    print_yield x = do
      yield "{"
      let f True  x = print_yield x >> return False
          f False x = yield ", " >> print_yield x >> return False
      foldlM f True x 
      yield "}"

instance PrintYield ISet where
    print_yield (ISet x) = print_yield x

newtype ISet = ISet (Either Int (Set ISet))
    deriving (Eq, Ord)

set1 :: Set ISet
set1 = Prelude.foldr 
       (\e s -> S.fromList [ISet (Left e), ISet (Right s)]) S.empty [1..200000]

-- Real printing
print_set :: Set ISet -> IO ()
print_set s = print_yield s `runGenT` putStr

t1 = print_set set1

-- Counting the number of characters
-- Could use Writer but the Writer is too lazy, may leak memory

count_printed :: Set ISet -> Integer
count_printed s = (print_yield s `runGenT` counter) `execState` 0
 where
 counter _ = get >>= put . succ_strict
 succ_strict x = x `seq` succ x

-- According to GHCi statistics, counting is linear in time
-- (space is harder to estimate: it is not clear what GHCi prints
-- for memory statistics; we need max bytes allocated rather than
-- total bytes allocated)
t2 = count_printed set1

-- Doesn't do anything but ensures the set is constructed
t3 :: IO ()
t3 = print_yield set1 `runGenT` (\x -> return ())







More information about the Haskell-Cafe mailing list