diff options
author | Kavon Farvardin <kavon@farvard.in> | 2018-09-23 15:29:37 -0500 |
---|---|---|
committer | Kavon Farvardin <kavon@farvard.in> | 2018-09-23 15:29:37 -0500 |
commit | 84c2ad99582391005b5e873198b15e9e9eb4f78d (patch) | |
tree | caa8c2f2ec7e97fbb4977263c6817c9af5025cf4 /testsuite/tests/codeGen/should_run/T15038/test | |
parent | 8ddb47cfcf5776e9a3c55fd37947c8a95e00fa12 (diff) | |
parent | e68b439fe5de61b9a2ca51af472185c62ccb8b46 (diff) | |
download | haskell-wip/T13904.tar.gz |
update to current master againwip/T13904
Diffstat (limited to 'testsuite/tests/codeGen/should_run/T15038/test')
-rw-r--r-- | testsuite/tests/codeGen/should_run/T15038/test/Main.hs | 4 | ||||
-rw-r--r-- | testsuite/tests/codeGen/should_run/T15038/test/Parser.hs | 61 |
2 files changed, 65 insertions, 0 deletions
diff --git a/testsuite/tests/codeGen/should_run/T15038/test/Main.hs b/testsuite/tests/codeGen/should_run/T15038/test/Main.hs new file mode 100644 index 0000000000..56acd042db --- /dev/null +++ b/testsuite/tests/codeGen/should_run/T15038/test/Main.hs @@ -0,0 +1,4 @@ +import qualified Parser as Parser + +main :: IO () +main = print (iterate Parser.byteParserBadOnce 5 !! 100000) diff --git a/testsuite/tests/codeGen/should_run/T15038/test/Parser.hs b/testsuite/tests/codeGen/should_run/T15038/test/Parser.hs new file mode 100644 index 0000000000..70f9f3336b --- /dev/null +++ b/testsuite/tests/codeGen/should_run/T15038/test/Parser.hs @@ -0,0 +1,61 @@ +{-# LANGUAGE BangPatterns #-} +{-# LANGUAGE BinaryLiterals #-} +{-# LANGUAGE MagicHash #-} +{-# LANGUAGE RankNTypes #-} +{-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE TypeInType #-} +{-# LANGUAGE UnboxedSums #-} +{-# LANGUAGE UnboxedTuples #-} + +{-# OPTIONS_GHC -Wall #-} + +module Parser + ( byteParserBadOnce + ) where + +import Control.Monad.ST (runST) +import Data.Word (Word8) +import Packed.Bytes (Bytes) +import Packed.Bytes.Parser (Parser) +import Packed.Bytes.Stream.ST (ByteStream) +import qualified Data.Char +import qualified Packed.Bytes as B +import qualified Packed.Bytes.Parser as P +import qualified Packed.Bytes.Stream.ST as Stream + +-- from common directory +import qualified Data.Trie.Naive as Naive + +snmptrapdNaive :: Naive.Trie (Parser Word) +snmptrapdNaive = Naive.fromStringList + [ ("STRING: ", P.any >>= \_ -> return 5) + ] + +runExampleParser :: Parser a -> (forall s. ByteStream s) -> (Maybe a, Maybe String) +runExampleParser parser stream = runST $ do + P.Result mleftovers r <- P.parseStreamST stream parser + mextra <- case mleftovers of + Nothing -> return Nothing + Just (P.Leftovers chunk remainingStream) -> do + bs <- Stream.unpack remainingStream + return (Just (map word8ToChar (B.unpack chunk ++ bs))) + return (r,mextra) + +byteParserBadOnce :: Int -> Int +byteParserBadOnce x = do + let sample = ("STRING: _6_ " ++ show x) + stream = Stream.fromBytes (s2b sample) + expected = 6 + (r,mextra) = runExampleParser (Naive.parser snmptrapdNaive) stream + a1 = if Nothing == mextra then 1 else 0 + a2 = if Just expected == r then 1 else 0 + in a1 + (a2 + x) + +s2b :: String -> Bytes +s2b = B.pack . map charToWord8 + +charToWord8 :: Char -> Word8 +charToWord8 = fromIntegral . Data.Char.ord + +word8ToChar :: Word8 -> Char +word8ToChar = Data.Char.chr . fromIntegral |