aboutsummaryrefslogtreecommitdiff
path: root/bbcode/src/BBCode.hs
diff options
context:
space:
mode:
authorGregor Kleen <gkleen@yggdrasil.li>2015-10-17 02:26:25 +0200
committerGregor Kleen <gkleen@yggdrasil.li>2015-10-17 02:26:25 +0200
commit005dc408dc09c3b479398ebe3e92efa2cd54846e (patch)
tree23dcfe7a545885c9aa145f1ccae6d33206a87820 /bbcode/src/BBCode.hs
parent2dcbb4482de2c352b76372b389fda20c63075295 (diff)
downloadthermoprint-005dc408dc09c3b479398ebe3e92efa2cd54846e.tar
thermoprint-005dc408dc09c3b479398ebe3e92efa2cd54846e.tar.gz
thermoprint-005dc408dc09c3b479398ebe3e92efa2cd54846e.tar.bz2
thermoprint-005dc408dc09c3b479398ebe3e92efa2cd54846e.tar.xz
thermoprint-005dc408dc09c3b479398ebe3e92efa2cd54846e.zip
Working prototype
Diffstat (limited to 'bbcode/src/BBCode.hs')
-rw-r--r--bbcode/src/BBCode.hs96
1 files changed, 96 insertions, 0 deletions
diff --git a/bbcode/src/BBCode.hs b/bbcode/src/BBCode.hs
new file mode 100644
index 0000000..750fb0f
--- /dev/null
+++ b/bbcode/src/BBCode.hs
@@ -0,0 +1,96 @@
1{-# LANGUAGE OverloadedStrings, OverloadedLists, RankNTypes, ImpredicativeTypes #-}
2
3module BBCode
4 ( parse
5 ) where
6
7import Thermoprint
8
9import BBCode.Tokenizer
10import BBCode.Syntax
11
12import Data.Maybe
13import Data.Monoid
14import Data.Either
15import Data.Bifunctor
16import Data.List
17import Data.Ord
18import Data.Foldable
19
20import Data.Function (on)
21
22import Data.CaseInsensitive ( CI )
23import qualified Data.CaseInsensitive as CI
24
25import Data.Map ( Map )
26import qualified Data.Map as Map
27
28import Prelude hiding (takeWhile)
29
30import Debug.Trace
31
32knownTags :: Map (CI String) (Either (Block String -> Block String) (Inline String -> Inline String))
33knownTags = [ ("center", Left Center)
34 , ("u", Right Underline)
35 ]
36
37isBlock, isInline :: String -> Bool
38isBlock = testTag isLeft
39isInline = testTag isRight
40testTag f k = fromMaybe False (f <$> Map.lookup (CI.mk k) knownTags)
41
42data Decorated c = Decorated c [String]
43 deriving (Show, Eq)
44
45parse :: String -> Either String (Block String)
46parse input = (remerge . blockify <$> (tokenize input >>= treeify)) >>= semantics
47
48blockify :: ContentForest -> [Decorated String]
49blockify = map sortDeco . concat . map (blockify' [])
50 where
51 blockify' _ Empty = []
52 blockify' initial (Content str) = [str `Decorated` initial]
53 blockify' initial (Tagged cs tag) = concat $ map (blockify' $ tag : initial) cs
54 sortDeco :: Decorated c -> Decorated c
55 sortDeco (Decorated c tags) = Decorated c $ (nubBy ((==) `on` CI.mk) . sortBy blockiness) tags
56 blockiness :: String -> String -> Ordering
57 blockiness a b = comparing isBlock a b <> comparing CI.mk a b -- sort also alphabetically for the benefit of remerge
58
59remerge :: [Decorated String] -> ContentForest
60remerge [] = []
61remerge [(Decorated c deco)] = [appEndo applyDeco $ Content c]
62 where
63 applyDeco = foldMap (\t -> Endo (\c -> Tagged [c] t)) $ reverse deco
64remerge xs = concat $ map toTree $ groupLasts xs
65 where
66 groupLasts = groupBy ((==) `on` (listToMaybe . reverse . (\(Decorated _ ds) -> ds)))
67 -- toTree :: [Decorated String] -> [ContentTree]
68 toTree [] = []
69 toTree (x@(Decorated _ []):xs) = map (Content . (\(Decorated c []) -> c)) (x:xs)
70 toTree (x@(Decorated _ ds):xs) = [Tagged content tag]
71 where
72 tag = last ds
73 content = toTree $ map stripLast (x:xs)
74 stripLast (Decorated c ds) = Decorated c (init ds)
75
76unknownTag :: forall a. String -> Either String a
77unknownTag tag = Left $ "Unknown tag: " ++ tag
78
79semantics :: ContentForest -> Either String (Block String)
80semantics forest = Over <$> mapM semantics' forest
81
82semantics' :: ContentTree -> Either String (Block String)
83semantics' Empty = Right $ Over []
84semantics' (Content str) = Right $ Paragraph (Cooked str)
85semantics' (Tagged cs tag) = case Map.lookup (CI.mk tag) knownTags of
86 Nothing -> unknownTag tag
87 Just (Left f) -> Over . map f <$> mapM semantics' cs
88 Just (Right f) -> Paragraph . Beside . map f<$> mapM iSemantics cs
89
90iSemantics :: ContentTree -> Either String (Inline String)
91iSemantics Empty = Right $ Beside []
92iSemantics (Content str) = Right $ Cooked str
93iSemantics (Tagged cs tag) = case Map.lookup (CI.mk tag) knownTags of
94 Nothing -> unknownTag tag
95 Just (Left f) -> error "Known inline tag sorted within block"
96 Just (Right f) -> Beside . map f <$> mapM iSemantics cs