[Haskell-cafe] Regex-applicative and Data.Text

Konstantine Rybnikov k-bx at k-bx.com
Wed Feb 11 11:07:40 UTC 2015


I just tried some regex-applicative and it's amazing! Very nice library,
thanks Roman!

However, I can't figure out the best way to work with Data.Text.Text
instead of String. The token would be Text, I guess, but then it breaks in
composition, since type of `few anySym` would now return `[Text]`, not
`Text`.

Am I understanding this correctly that intention is to in issue #8? [0] Or
is there a clever way to work with them today?

Example code:

{-# LANGUAGE OverloadedStrings #-}

import qualified Data.Text as T
import Data.Text (Text)
import Text.Regex.Applicative

main = do
  let input = "foo:\n--- blablabla\ttheend"
  let r1 = sym "foo:\n"
                      *> sym "--- " *> few anySym <* sym "\t" <* few anySym
            :: RE Text Text

  putStrLn (show (input =~ r1))

Error is something like (this is an error for a bit different code, but
should be very similar):

Main.hs:14:40:
    Couldn't match type ‘[Text]’ with ‘Text’
    Expected type: RE Text Text
      Actual type: RE Text [Text]
    In the second argument of ‘(*>)’, namely ‘few anySym’
    In the first argument of ‘(<*)’, namely
      ‘few anySym *> sym "Actual stderr output differs from expected:"
       *> sym "--- "
       *> few anySym’

Thanks!

[0]: https://github.com/feuerbach/regex-applicative/issues/8
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20150211/0c018750/attachment.html>


More information about the Haskell-Cafe mailing list