This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
chunkX.hs | |
==================== CorePrep ==================== | |
Result size of CorePrep | |
= {terms: 634, types: 1,774, coercions: 269} | |
Rec { | |
$snext2 | |
$snext2 = | |
\ @ a_XcUd @ r_XcUg p_sg9n eta_sg9o -> |
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
module Main where | |
import qualified Streaming.Prelude as Str | |
import qualified System.IO.Streams as IOS | |
import Conduit.Simple as S | |
import Control.Exception | |
import Criterion.Main | |
import Data.Conduit as C | |
import Data.Conduit.Combinators as C | |
import Fusion as F hiding ((&)) |
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
-- These examples are based on the tutorial module in the io-streams package | |
{-#LANGUAGE OverloadedStrings #-} | |
import Streaming | |
import Streaming.Prelude (yield, next, each, for, with, subst) | |
import qualified Streaming.Prelude as S | |
import qualified Data.ByteString.Char8 as B | |
import Data.ByteString.Streaming (ByteString) | |
import qualified Data.ByteString.Streaming.Char8 as Q | |
import System.IO (withFile, IOMode(..)) |
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
{-#LANGUAGE OverloadedStrings #-} | |
import Streaming | |
import Streaming.Prelude (each, next, yield) | |
import qualified Data.ByteString.Streaming.Char8 as Q | |
import qualified Data.ByteString.Char8 as B | |
import qualified Streaming.Prelude as S | |
import qualified Control.Foldl as L | |
import Data.ByteString.Streaming.HTTP -- git clone https://github.com/michaelt/streaming-http | |
-- cabal install ./streaming-http | |
infixl 5 >>>; (>>>) = flip (.) |
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
{-# LANGUAGE OverloadedStrings, PackageImports #-} | |
-- | | |
-- Copyright : (c) 2010-2011 Simon Meier | |
-- License : BSD3-style (see LICENSE) | |
-- | |
-- Maintainer : Simon Meier <[email protected]> | |
-- Stability : experimental | |
-- Portability : tested on GHC only | |
-- | |
-- Running example for documentation of Data.ByteString.Lazy.Builder |
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
{-# LANGUAGE OverloadedStrings, BangPatterns #-} | |
module Main (main) where | |
import Criterion.Main | |
import Control.Applicative | |
import Data.Attoparsec.ByteString as P | |
import Data.Attoparsec.ByteString.Char8 (char8, endOfLine, isDigit_w8) | |
import Data.ByteString (ByteString) | |
import Data.Word (Word8) |
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
import Streaming | |
import qualified Streaming.Prelude as S | |
import Control.Monad | |
main = do | |
S.effects (hilo 30 ) | |
putStrLn "Right, 30 is correct!" | |
hilo :: Int -> Stream (Of Int) IO () | |
hilo n = void $ S.break (== n) | |
$ S.chain (\a -> when (a < n) $ putStrLn $ "Too small!") |
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
module Main where | |
import qualified Streaming.Prelude as Str | |
import qualified System.IO.Streams as IOS | |
import qualified ListT as ListT | |
import Data.Conduit as C | |
import Data.Conduit.Combinators as C | |
import qualified Data.Machine as M | |
import qualified Data.Machine.Runner as M | |
import Pipes as P |
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
{-#LANGUAGE NoMonomorphismRestriction #-} | |
module Main (main) where | |
import Control.Monad (void) | |
import Control.Monad.Identity | |
import Criterion.Main | |
import qualified Data.Conduit as C | |
import qualified Data.Conduit.Combinators as CC | |
import qualified Data.Conduit.List as C | |
import qualified Data.Machine as M |
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
{-#LANGUAGE GADTs #-} | |
import Control.Monad (ap) | |
newtype Free req r = Free {runFree :: Either r (req (Free req r))} | |
data Lan f a = forall b. Lan (b -> a) (f b) | |
instance Functor (Lan f) where fmap f (Lan xa fx) = Lan (f . xa) fx | |
type Call_ req = Free (Lan req) | |
call_ :: forall a req . Call req a -> Call_ req a |