module Control.Concurrent.SCC.Primitives (
fromFile, fromHandle, fromStdIn, fromBinaryHandle,
appendFile, toFile, toHandle, toStdOut, toBinaryHandle,
produceFrom,
suppress, erroneous, consumeInto,
parse, unparse, parseSubstring, OccurenceTag, count, toString,
group, concatenate, concatSeparate,
everything, nothing, marked, markedContent, markedWith, contentMarkedWith, one, substring,
lowercase, uppercase, whitespace, letters, digits, line, nonEmptyLine,
)
where
import Prelude hiding (appendFile, getLine, length, null, putStr, tail)
import Control.Applicative (Alternative ((<|>)))
import Control.Exception (assert)
import Control.Monad (forM_, unless, when)
import Control.Monad.Trans.Class (lift)
import Data.ByteString (ByteString)
import Data.Char (isAlpha, isDigit, isSpace, toLower, toUpper)
import Data.List (delete)
import Data.Monoid (Monoid(mappend, mempty), Sum(Sum))
import qualified Data.ByteString as ByteString
import qualified Data.Foldable as Foldable
import System.IO (Handle, IOMode (ReadMode, WriteMode, AppendMode), openFile, hClose, hIsEOF, hClose, isEOF)
import Data.Text (Text, singleton)
import Data.Text.IO (getLine, hGetLine, hPutStr, putStr)
import Data.Monoid.Null (MonoidNull(null))
import Data.Monoid.Cancellative (LeftReductiveMonoid (stripPrefix))
import Data.Monoid.Factorial (FactorialMonoid(splitPrimePrefix), length)
import Text.ParserCombinators.Incremental (string, takeWhile, (<<|>))
import Control.Concurrent.SCC.Streams
import Control.Concurrent.SCC.Types
import Debug.Trace (trace)
consumeInto :: forall m x. (Monad m, Monoid x) => Consumer m x x
consumeInto = Consumer getAll
produceFrom :: forall m x. (Monad m, MonoidNull x) => x -> Producer m x ()
produceFrom l = Producer ((>> return ()) . putAll l)
toStdOut :: Consumer IO Text ()
toStdOut = Consumer (mapMStreamChunks_ (lift . putStr))
fromStdIn :: Producer IO Text ()
fromStdIn = Producer (unmapMStreamChunks_ (lift $
isEOF >>= cond (return mempty) (fmap (`mappend` singleton '\n') getLine)))
fromFile :: String -> Producer IO Text ()
fromFile path = Producer $ \sink-> do handle <- lift (openFile path ReadMode)
produce (fromHandle handle) sink
lift (hClose handle)
fromHandle :: Handle -> Producer IO Text ()
fromHandle handle = Producer (unmapMStreamChunks_
(lift $
hIsEOF handle
>>= cond (return mempty) (fmap (`mappend` singleton '\n') $ hGetLine handle)))
fromBinaryHandle :: Handle -> Int -> Producer IO ByteString ()
fromBinaryHandle handle chunkSize = Producer p
where p sink = lift (ByteString.hGet handle chunkSize)
>>= \chunk-> unless (ByteString.null chunk)
(putChunk sink chunk
>>= \c-> when (ByteString.null c) (p sink))
toFile :: String -> Consumer IO Text ()
toFile path = Consumer $ \source-> do handle <- lift (openFile path WriteMode)
consume (toHandle handle) source
lift (hClose handle)
appendFile :: String -> Consumer IO Text ()
appendFile path = Consumer $ \source-> do handle <- lift (openFile path AppendMode)
consume (toHandle handle) source
lift (hClose handle)
toHandle :: Handle -> Consumer IO Text ()
toHandle handle = Consumer (mapMStreamChunks_ (lift . hPutStr handle))
toBinaryHandle :: Handle -> Consumer IO ByteString ()
toBinaryHandle handle = Consumer (mapMStreamChunks_ (lift . ByteString.hPut handle))
unparse :: forall m x b. (Monad m, Monoid x) => Transducer m [Markup b x] x
unparse = statelessTransducer removeTag
where removeTag (Content x) = x
removeTag _ = mempty
parse :: forall m x y. (Monad m, Monoid x) => Parser m x y
parse = statelessChunkTransducer ((: []) . Content)
suppress :: forall m x. Monad m => Consumer m x ()
suppress = Consumer (\(src :: Source m a x)-> pour_ src (nullSink :: Sink m a x))
erroneous :: forall m x. (Monad m, MonoidNull x) => String -> Consumer m x ()
erroneous message = Consumer (mapMStreamChunks_ (\x-> unless (null x) (error message)))
lowercase :: forall m. Monad m => Transducer m String String
lowercase = statelessChunkTransducer (map toLower)
uppercase :: forall m. Monad m => Transducer m String String
uppercase = statelessChunkTransducer (map toUpper)
count :: forall m x. (Monad m, FactorialMonoid x) => Transducer m x [Integer]
count = Transducer (\source sink-> foldStream (\n _-> succ n) 0 source >>= put sink)
toString :: forall m x. (Monad m, Show x) => Transducer m [x] [String]
toString = oneToOneTransducer (map show)
group :: forall m x. (Monad m, Monoid x) => Transducer m x [x]
group = Transducer (\source sink-> getAll source >>= put sink)
concatenate :: forall m x. (Monad m, Monoid x) => Transducer m [x] x
concatenate = statelessTransducer id
concatSeparate :: forall m x. (Monad m, MonoidNull x) => x -> Transducer m [x] x
concatSeparate separator = statefulTransducer (\seen chunk-> (True, if seen then mappend separator chunk else chunk))
False
whitespace :: forall m. Monad m => Splitter m String
whitespace = statelessSplitter isSpace
letters :: forall m. Monad m => Splitter m String
letters = statelessSplitter isAlpha
digits :: forall m. Monad m => Splitter m String
digits = statelessSplitter isDigit
nonEmptyLine :: forall m. Monad m => Splitter m String
nonEmptyLine = statelessSplitter (\ch-> ch /= '\n' && ch /= '\r')
line :: forall m. Monad m => Splitter m String
line = Splitter $ \source true false->
let loop = peek source >>= maybe (return ()) (( >> loop) . splitLine)
lineChar c = c /= '\r' && c /= '\n'
lineEndParser = string "\r\n" <<|> string "\n\r" <<|> string "\r" <<|> string "\n"
splitLine c = if lineChar c then pourWhile (lineChar . head) source true else putChunk true mempty
>> pourParsed lineEndParser source false
in loop
everything :: forall m x. Monad m => Splitter m x
everything = Splitter (\source true _false-> pour source true >>= flip unless (putChunk true mempty >> return ()))
nothing :: forall m x. (Monad m, Monoid x) => Splitter m x
nothing = Splitter (\source _true false-> pour_ source false)
one :: forall m x. (Monad m, FactorialMonoid x) => Splitter m x
one = Splitter (\source true false-> getWith source $
\x-> putChunk true x
>> mapMStream_ (\x-> putChunk false mempty >> putChunk true x) source)
marked :: forall m x y. (Monad m, Eq y) => Splitter m [Markup y x]
marked = markedWith (const True)
markedContent :: forall m x y. (Monad m, Eq y) => Splitter m [Markup y x]
markedContent = contentMarkedWith (const True)
markedWith :: forall m x y. (Monad m, Eq y) => (y -> Bool) -> Splitter m [Markup y x]
markedWith select = statefulSplitter transition ([], False)
where transition s@([], _) Content{} = (s, False)
transition s@(_, truth) Content{} = (s, truth)
transition s@([], _) (Markup (Point y)) = (s, select y)
transition s@(_, truth) (Markup (Point _)) = (s, truth)
transition ([], _) (Markup (Start y)) = (([y], select y), select y)
transition (open, truth) (Markup (Start y)) = ((y:open, truth), truth)
transition (open, truth) (Markup (End y)) = assert (elem y open) ((delete y open, truth), truth)
contentMarkedWith :: forall m x y. (Monad m, Eq y) => (y -> Bool) -> Splitter m [Markup y x]
contentMarkedWith select = statefulSplitter transition ([], False)
where transition s@(_, truth) Content{} = (s, truth)
transition s@(_, truth) (Markup Point{}) = (s, truth)
transition ([], _) (Markup (Start y)) = (([y], select y), False)
transition (open, truth) (Markup (Start y)) = ((y:open, truth), truth)
transition (open, truth) (Markup (End y)) = assert (elem y open) (let open' = delete y open
truth' = not (null open') && truth
in ((open', truth'), truth'))
data OccurenceTag = Occurence Int deriving (Eq, Show)
instance Enum OccurenceTag where
succ (Occurence n) = Occurence (succ n)
pred (Occurence n) = Occurence (pred n)
toEnum = Occurence
fromEnum (Occurence n) = n
parseSubstring :: forall m x. (Monad m, Eq x, LeftReductiveMonoid x, FactorialMonoid x) => x -> Parser m x OccurenceTag
parseSubstring s =
case splitPrimePrefix s
of Nothing -> Transducer $
\ source sink -> put sink marker >> mapStream (\x-> [Content x, marker]) source sink
where marker = Markup (Point (toEnum 1))
Just (first, rest)->
isolateTransducer $ \ source sink ->
pipe (\sink'->
let findFirst = pourWhile (/= first) source sink'
>> test
test = getParsed (string s) source
>>= \t-> if null t
then getWith source (\x-> put sink (Content x) >> findFirst)
else put sink (Markup (Start (toEnum 0)))
>> put sink prefixContent
>> if null shared then put sink (Markup (End (toEnum 0))) >> findFirst
else testOverlap 0
testOverlap n = getParsed (string postfix) source
>>= \t-> if null t
then forM_ [n maxOverlaps + 1 .. n]
(\i-> put sink sharedContent
>> put sink (Markup (End (toEnum i))))
>> findFirst
else let n' = succ n
in put sink (Markup (Start (toEnum n')))
>> put sink prefixContent
>> when (n' >= maxOverlaps)
(put sink (Markup (End (toEnum (n' maxOverlaps)))))
>> testOverlap n'
(prefix, shared, postfix) = overlap s s
maxOverlaps = (length s 1) `div` length prefix
prefixContent = Content prefix
sharedContent = Content shared
in findFirst)
(\src-> mapStreamChunks ((: []) . Content) src sink)
>> return ()
substring :: forall m x. (Monad m, Eq x, LeftReductiveMonoid x, FactorialMonoid x) => x -> Splitter m x
substring s =
Splitter $ \ source true false ->
case splitPrimePrefix s
of Nothing -> putChunk true mempty
>> mapMStream_ (\x-> putChunk false x >> putChunk true mempty) source
Just (first, rest) ->
let findFirst = pourWhile (/= first) source false
>> test
test = getParsed (string s) source
>>= \t-> if null t
then getWith source (\x-> putChunk false x >> findFirst)
else putChunk false mempty
>> putAll prefix true
>> if null shared then findFirst else testOverlap
testOverlap = getParsed (string postfix) source
>>= \t-> if null t
then putAll shared true >> findFirst
else putChunk false mempty
>> putAll prefix true
>> testOverlap
(prefix, shared, postfix) = overlap s s
in findFirst
overlap :: (LeftReductiveMonoid x, FactorialMonoid x) => x -> x -> (x, x, x)
overlap e s | null e = (e, e, s)
overlap s1 s2 = case splitPrimePrefix s1
of Nothing -> (s1, s1, s2)
Just (head, tail) -> case stripPrefix tail s2
of Just rest -> (head, tail, rest)
Nothing -> let (o1, o2, o3) = overlap tail s2
in (mappend head o1, o2, o3)
cond :: a -> a -> Bool -> a
cond x y test = if test then x else y