Skip to content

Commit

Permalink
Revert "Revamped to use Text."
Browse files Browse the repository at this point in the history
This reverts commit 250818b.
With Text it was unbelievably slow. Perhaps this will be fixed
soon in Text.
  • Loading branch information
jgm committed Aug 17, 2010
1 parent 250818b commit 2a10a92
Show file tree
Hide file tree
Showing 2 changed files with 11 additions and 20 deletions.
2 changes: 1 addition & 1 deletion HeX.cabal
Expand Up @@ -13,7 +13,7 @@ Extra-source-files: examples/test.lhs
Cabal-version: >=1.2
Library
Exposed-modules: Text.HeX
Build-depends: parsec >= 3.1, base >= 4, text >= 0.7.1 && < 0.8,
Build-depends: parsec >= 3.1, base >= 4,
filepath, directory, process, mtl, containers,
bytestring, utf8-string, blaze-builder >= 0.1 && < 0.2
if impl(ghc >= 6.12)
Expand Down
29 changes: 10 additions & 19 deletions Text/HeX.hs
@@ -1,5 +1,4 @@
{-# LANGUAGE DeriveDataTypeable, OverloadedStrings, FlexibleInstances,
MultiParamTypeClasses #-}
{-# LANGUAGE DeriveDataTypeable, OverloadedStrings #-}
{- |
Module : Text.HeX
Copyright : Copyright (C) 2010 John MacFarlane
Expand Down Expand Up @@ -37,18 +36,12 @@ import System.Environment
import System.Exit (ExitCode(..), exitWith)
import System.FilePath
import System.Directory
import qualified Data.Text as T
import qualified Data.Text.IO as T
import Data.Text (Text)

instance Monad m => Stream Text m Char where
uncons = return . T.uncons

data HeXState = HeXState { hexParsers :: [HeX Builder]
, hexFormat :: String
, hexVars :: M.Map String Dynamic }

type HeX = ParsecT Text HeXState IO
type HeX = ParsecT String HeXState IO

setVar :: Typeable a => String -> a -> HeX a
setVar name' v = do
Expand All @@ -72,7 +65,7 @@ updateVar name' f = getVar name' >>= setVar name' . f
setParsers :: [HeX Builder] -> HeX ()
setParsers parsers = updateState $ \s -> s{ hexParsers = parsers }

run :: [HeX Builder] -> String -> Text -> IO L.ByteString
run :: [HeX Builder] -> String -> String -> IO L.ByteString
run parsers format contents = do
result <- runParserT (do setParsers parsers
spaces
Expand All @@ -98,19 +91,17 @@ use parsers = do
format <- case args of
[x] -> return x
_ -> usage >> exitWith (ExitFailure 1)
txt <- liftM removeCode $ T.readFile prog'
txt <- liftM removeCode $ readFile prog'
res <- run parsers format txt
L.putStr res
exitWith ExitSuccess

removeCode :: Text -> Text
removeCode = T.unlines .
map (\ln -> if isCommentLine ln then ln else T.empty) . T.lines
where isCommentLine :: Text -> Bool
isCommentLine t = case T.uncons t of
Just ('>',_) -> False
Just ('#',_) -> False
_ -> True
removeCode :: String -> String
removeCode = unlines . map (\ln -> if isCommentLine ln then ln else "") . lines
where isCommentLine :: String -> Bool
isCommentLine ('>':_) = False
isCommentLine ('#':_) = False
isCommentLine _ = True

getInputFilePath :: IO FilePath
getInputFilePath = do
Expand Down

0 comments on commit 2a10a92

Please sign in to comment.