aboutsummaryrefslogtreecommitdiff
path: root/bbcode/src/Text/BBCode/Lexer.hs
blob: d2aa2bccd9f2b562a065fb1a6b1850bdfc90bdb0 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DeriveGeneric, DeriveAnyClass #-}

-- | A parser to transform 'Text' into a stream of 'BBToken's
module Text.BBCode.Lexer
       ( BBToken(..)
       , token
       , escapedText
       , escapedText'
       ) where

import Data.Attoparsec.Text

import Data.Text (Text)
import qualified Data.Text as T (singleton, head, last, tail, null)

import Control.Applicative

import Test.QuickCheck (Arbitrary(..), CoArbitrary, genericShrink)
import Test.QuickCheck.Gen (oneof, suchThat)
import Test.QuickCheck.Instances
import GHC.Generics (Generic)

-- | Our lexicographical unit
data BBToken = BBOpen Text -- ^ Tag open
             | BBClose Text -- ^ Tag close
             | BBStr Text -- ^ Content of a tag
             deriving (Generic, Eq, Show, CoArbitrary)

-- | This instance does not produce:
--
--  * opening and closing tags whose 'Text' ends in @\\@
--  * empty 'BBStr's
instance Arbitrary BBToken where
  shrink = genericShrink
  arbitrary = oneof [ BBOpen <$> tagText
                    , BBClose <$> tagText
                    , BBStr <$> nonEmpty
                    ]
    where
      tagText = arbitrary `suchThat` (not . lastIsEscape)
      lastIsEscape t
        | T.null t = False
        | T.last t == '\\' = True
        | otherwise = False
      nonEmpty = (arbitrary `suchThat` (not . T.null))

token :: Parser BBToken
-- ^ Tokenizer
token = BBClose <$> (string "[/" *> escapedText' [']'] <* string "]")
        <|> BBOpen <$> (string "[" *> escapedText' [']'] <* string "]")
        <|> BBStr <$> escapedText ['[']

escapedText :: [Char] -> Parser Text
-- ^ @escapedText cs@ consumes 'Text' up to (not including) the first occurence of a character from @cs@ that is not escaped using @\\@
--
-- Always consumes at least one character
--
-- @\\@ needs to be escaped (prefixed with @\\@) iff it precedes a character from @cs@
escapedText [] = takeText
escapedText cs = recurse $ choice [ takeWhile1 (not . special)
                                  , escapeSeq
                                  , escapeChar'
                                  ]
  where
    escapeChar = '\\'
    special = inClass $ escapeChar : cs
    escapeChar' = string $ T.singleton escapeChar
    escapeSeq = escapeChar' >> (T.singleton <$> satisfy special) -- s/\\[:cs]/\1/
    recurse p = mappend <$> p <*> escapedText' cs

escapedText' :: [Char] -> Parser Text
-- ^ @'option' "" $ 'escapedText' cs@
escapedText' cs = option "" $ escapedText cs