~ubuntu-branches/ubuntu/precise/haskell-text/precise

« back to all changes in this revision

Viewing changes to tests/benchmarks/ReplaceTags.hs

  • Committer: Bazaar Package Importer
  • Author(s): Joachim Breitner
  • Date: 2011-04-13 11:38:29 UTC
  • mfrom: (4.1.3 sid)
  • Revision ID: james.westby@ubuntu.com-20110413113829-f4ss61ivg720e5bu
Tags: 0.11.0.6-1
New upstream release

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
-- Contributed by Ken Friis Larsen and Morten Ib Nielsen.
 
2
 
 
3
{-# LANGUAGE BangPatterns #-}
 
4
module Main (main) where
 
5
 
 
6
import System.Environment (getArgs)
 
7
import qualified Char
 
8
 
 
9
import qualified Data.Text as T
 
10
import qualified Data.Text.IO as T
 
11
 
 
12
import qualified Data.Text.Lazy as TL
 
13
import qualified Data.Text.Lazy.IO as TL
 
14
import qualified Data.ByteString.Lazy as BL
 
15
import qualified Data.Text.Lazy.Encoding as TLE
 
16
 
 
17
 
 
18
import qualified Data.ByteString.Char8 as BC
 
19
import qualified Data.ByteString as B
 
20
import qualified Data.Text.Encoding as TE
 
21
 
 
22
replaceTagsM file tag sub = 
 
23
  BC.readFile file >>= BC.putStr . replaceTags tag sub . TE.encodeUtf8 . T.toLower . TE.decodeUtf8 
 
24
  where 
 
25
    replaceTags tag replacement str = B.concat $ reverse $ replaceTags' [] (BC.pack $ '<' : tag) '>' (BC.pack replacement) str
 
26
    replaceTags' !res start end repl str =
 
27
      let (pre, post) = BC.breakSubstring start str
 
28
      in if BC.null post
 
29
           then  pre : res
 
30
           else replaceTags' (repl : pre : res) start end repl $ BC.drop 1 $
 
31
                BC.dropWhile (/= end) post
 
32
 
 
33
splitB sep str = seplen `seq` splitter str 
 
34
  where 
 
35
    splitter str = h : if B.null t then [] else splitter (B.drop seplen t)
 
36
      where (h,t) = B.breakSubstring sep str
 
37
    seplen = B.length sep
 
38
    
 
39
replaceTagsWrong file tagName sub = do
 
40
  content <- BC.readFile file
 
41
  let frags = map (BC.drop 1 . BC.dropWhile (/= '>')) 
 
42
              $ splitB (BC.pack $ '<' : tagName) (BC.map Char.toLower content)
 
43
  BC.putStr $ BC.intercalate (BC.pack sub) frags
 
44
 
 
45
replaceTagsK file tagName sub = do
 
46
  raw <- BC.readFile file 
 
47
  let content = (TE.encodeUtf8 . T.toLower . TE.decodeUtf8) raw
 
48
  let frags = map (BC.drop 1 . BC.dropWhile (/= '>')) 
 
49
              $ splitB (BC.pack $ '<' : tagName) content
 
50
  BC.putStr $ BC.intercalate (BC.pack sub) frags
 
51
 
 
52
replaceTagsO file tagName sub = do
 
53
  raw <- BC.readFile file 
 
54
  let content = (TE.encodeUtf8 . T.toLower . TE.decodeUtf8) raw
 
55
  let frags = splitB (BC.pack $ '<' : tagName) content
 
56
  BC.putStr $ BC.intercalate (BC.pack sub) frags
 
57
  where 
 
58
    splitB sep str = splitter str 
 
59
      where 
 
60
        splitter str = h : if BC.null t then [] else splitter (BC.drop 1 $ BC.dropWhile (/= '>') t)
 
61
          where (h,t) = B.breakSubstring sep str
 
62
 
 
63
 
 
64
    
 
65
replaceTagsT file tagName sub = do
 
66
  raw <- B.readFile file 
 
67
  let content = TE.decodeUtf8 raw
 
68
  let frags = map (T.drop 1 . T.dropWhile (/= '>')) 
 
69
              $ T.split (T.pack $ '<' : tagName) (T.toLower content)
 
70
  T.putStr $ T.intercalate (T.pack sub) frags
 
71
  
 
72
replaceTagsTL file tagName sub = do
 
73
  raw <- BL.readFile file 
 
74
  let content = TLE.decodeUtf8 raw
 
75
  let frags = map (TL.drop 1 . TL.dropWhile (/= '>')) 
 
76
              $ TL.split (TL.pack $ '<' : tagName) (TL.toLower content)
 
77
  TL.putStr $ TL.intercalate (TL.pack sub) frags
 
78
 
 
79
 
 
80
main = do
 
81
  (kind : file : tag : sub : _) <- getArgs
 
82
  case kind of
 
83
    "Text" -> replaceTagsT file tag sub
 
84
    "TextLazy" -> replaceTagsTL file tag sub
 
85
    "BytestringM" -> replaceTagsM file tag sub
 
86
    "BytestringK" -> replaceTagsK file tag sub
 
87
    "BytestringO" -> replaceTagsO file tag sub
 
88
    "TextNull" -> T.readFile file >>= T.putStr
 
89
    "ByteNull" -> B.readFile file >>= B.putStr
 
90
    "EncodeNull" -> B.readFile file >>= T.putStr . T.toLower . TE.decodeUtf8 
 
91