
No, the token will still be Char. You'll need to unpack Text into [Char] beforehand, and pack the result back if appropriate. On 11/02/15 13:07, Konstantine Rybnikov wrote:
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
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe