On 10.02.2013 02:30, Nicolas Bock wrote:
Hi Aleksey,

could you show me how I would use ByteString? I can't get the script to
compile. It's complaining that:

No instance for (RegexContext
                        Regex Data.ByteString.ByteString
(AllTextSubmatches [] a0))

which is too cryptic for me. Is it not able to form a regular expression
with a ByteString argument? From the documentation of Text.Regex.Posix
it seems that it should be. Maybe it's because I am trying to "read
(r!!1) :: Double" which I am having issues with also. Is (r!!1) a
ByteString? And if so, how would I convert that to a Double?

It's error message from regex library you use. I can't say what exactly it means, I never used it. But most likely it cannot work with bytestrings.

Most other languages rely on regexp as go to tool for parsing. In haskell main parsing tools are parser combinators such as parsec[1] or
attoparsec[2]. Parsec is more generic and attoparsec is much faster.

In attachment program which uses attoparsec for parsing it's about 2times slower than C++ example posted in the thread.

[1] http://hackage.haskell.org/package/parsec
[2] http://hackage.haskell.org/package/attoparsec
{-# LANGUAGE OverloadedStrings #-}
import Control.Applicative
import Data.Histogram.Fill
import Data.Histogram      (Histogram)

import Data.Attoparsec.Text.Lazy        (parse,Result(..))
import Data.Attoparsec.Text      hiding (parse,Done,Fail)

import qualified Data.Text.Lazy    as T
import qualified Data.Text.Lazy.IO as T
import Prelude hiding (takeWhile)


hb :: HBuilder Double (Histogram LogBinD Int)
hb = forceInt -<< mkSimple (logBinDN 1e-8 10 10)

streamBS :: T.Text -> [Double]
streamBS bs
  | T.null bs = []
  | otherwise  = case parse go bs of
                   Done rest x -> x : streamBS rest
                   Fail _ cxt e -> error $ e ++ " " ++ show cxt
  where
    num = decimal :: Parser Int
    go =  string "matrix("
       *> num *> char ',' *> num *> char ')'
       *> takeWhile (==' ') *> char '=' *> takeWhile (== ' ') *> double <* endOfLine

main :: IO ()
main = do
  print . fillBuilder hb . streamBS =<< T.getContents





_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to