module Main where import qualified System.Process as P import System.IO import qualified Data.ByteString.Lazy.Char8 as L import SimpleRegex import Control.Concurrent main = do lines <- L.readFile "testdata" res <- testAction lines putStrLn $ show res return () interactive_test = do let text = "cat testdata" (hin, hout, _, ph) <- P.runInteractiveProcess "/bin/bash" [] Nothing Nothing hPutStr hin text lines <- L.hGetContents hout res <- testAction lines putStrLn $ show res ec <- P.waitForProcess ph return () test_rx = "([0-9]{4}-[0-9]{2}-[0-9]{2} ..:..:..),....+[[][0-9]+[]] ([^ ]+) +(incoming|outgoing) c[Aa]ll #([0-9]+)/R:(.+)/C:(.+)/L:([0-9-]+) BCH#(.+)/DCH#(.+):(.+)/BRD#(.+) .+ CRN ([0-9A-Za-z]+) @([-0-9]+) (from|local) (.+) (to|remote) (.+) [[][^ ]+ *(.*)$" testAction c = do rx <- compile "(incoming)" return $ map (submatches rx) (L.lines c) testAction2 c = do -- rx <- compile "([0-9]{4}-[0-9]{2}-[0-9]{2} ..:..:..),....+[[][0-9]+[]] ([^ ]+) +(incoming|outgoing) c[Aa]ll #([0-9]+)/R:(.+)/C:(.+)/L:([0-9-]+) BCH#(.+)/DCH#(.+):(.+)/BRD#(.+) .+ CRN ([0-9A-Za-z]+) @([-0-9]+) local (.+) remote (.+) [[][^ ]+ *(.*)$" rx <- compile "(incoming)" let sms = catSubmatches rx $ L.lines c return $ map (\ (ss, s) -> case ss of [] -> [s] _ -> ss) sms