aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorGregor Kleen <pngwjpgh@users.noreply.github.com>2017-01-23 16:11:37 +0100
committerGregor Kleen <pngwjpgh@users.noreply.github.com>2017-01-23 16:11:37 +0100
commit99fc4947543c1916e9fec952526a688eb7753490 (patch)
tree9361649ae4639a00cff06ad654cb42e3e07bc637
parent59a7e3d173c23096fe3122505b1b759f26e3292a (diff)
parent64b6ead0d1e157701f8569743eda496bc71b8351 (diff)
downloadthermoprint-99fc4947543c1916e9fec952526a688eb7753490.tar
thermoprint-99fc4947543c1916e9fec952526a688eb7753490.tar.gz
thermoprint-99fc4947543c1916e9fec952526a688eb7753490.tar.bz2
thermoprint-99fc4947543c1916e9fec952526a688eb7753490.tar.xz
thermoprint-99fc4947543c1916e9fec952526a688eb7753490.zip
Merge branch 'feat-markup'
-rw-r--r--client/thermoprint-client.cabal4
-rw-r--r--client/thermoprint-client.nix2
-rw-r--r--server/src/Thermoprint/Server/Printer/Generic.hs30
-rw-r--r--server/test/Thermoprint/Server/Printer/GenericSpec.hs69
-rw-r--r--server/thermoprint-server.cabal3
-rw-r--r--server/thermoprint-server.nix8
-rw-r--r--spec/src/Thermoprint/Printout.hs15
-rw-r--r--spec/thermoprint-spec.cabal2
-rw-r--r--spec/thermoprint-spec.nix2
-rw-r--r--tp-bbcode/src/Thermoprint/Printout/BBCode.hs27
-rw-r--r--tp-bbcode/test/Thermoprint/Printout/BBCodeSpec.hs2
-rw-r--r--tp-bbcode/thermoprint-bbcode.cabal4
12 files changed, 150 insertions, 18 deletions
diff --git a/client/thermoprint-client.cabal b/client/thermoprint-client.cabal
index 9c481e3..0920773 100644
--- a/client/thermoprint-client.cabal
+++ b/client/thermoprint-client.cabal
@@ -2,7 +2,7 @@
2-- documentation, see http://haskell.org/cabal/users-guide/ 2-- documentation, see http://haskell.org/cabal/users-guide/
3 3
4name: thermoprint-client 4name: thermoprint-client
5version: 1.0.0 5version: 1.0.1
6synopsis: Client for thermoprint-spec 6synopsis: Client for thermoprint-spec
7-- description: 7-- description:
8homepage: http://dirty-haskell.org/tags/thermoprint.html 8homepage: http://dirty-haskell.org/tags/thermoprint.html
@@ -21,7 +21,7 @@ library
21 -- other-modules: 21 -- other-modules:
22 -- other-extensions: 22 -- other-extensions:
23 build-depends: base >=4.8 && <5 23 build-depends: base >=4.8 && <5
24 , thermoprint-spec ==4.0.* 24 , thermoprint-spec ==5.0.*
25 , servant >=0.4.4 && <1 25 , servant >=0.4.4 && <1
26 , servant-client >=0.4.4 && <1 26 , servant-client >=0.4.4 && <1
27 , servant-server >=0.4.4 && <1 27 , servant-server >=0.4.4 && <1
diff --git a/client/thermoprint-client.nix b/client/thermoprint-client.nix
index 8e608cf..8aadafb 100644
--- a/client/thermoprint-client.nix
+++ b/client/thermoprint-client.nix
@@ -4,7 +4,7 @@
4}: 4}:
5mkDerivation { 5mkDerivation {
6 pname = "thermoprint-client"; 6 pname = "thermoprint-client";
7 version = "1.0.0"; 7 version = "1.0.1";
8 src = ./.; 8 src = ./.;
9 libraryHaskellDepends = [ 9 libraryHaskellDepends = [
10 base containers either exceptions http-client mtl servant 10 base containers either exceptions http-client mtl servant
diff --git a/server/src/Thermoprint/Server/Printer/Generic.hs b/server/src/Thermoprint/Server/Printer/Generic.hs
index f431e4f..ce818ee 100644
--- a/server/src/Thermoprint/Server/Printer/Generic.hs
+++ b/server/src/Thermoprint/Server/Printer/Generic.hs
@@ -6,6 +6,7 @@
6 6
7module Thermoprint.Server.Printer.Generic 7module Thermoprint.Server.Printer.Generic
8 ( genericPrint 8 ( genericPrint
9 , mkPrintout
9 ) where 10 ) where
10 11
11import Thermoprint.Printout 12import Thermoprint.Printout
@@ -31,6 +32,7 @@ import Data.Encoding
31import Data.Encoding.CP437 32import Data.Encoding.CP437
32import Data.Binary.Put 33import Data.Binary.Put
33import Data.Word 34import Data.Word
35import Data.Bits
34 36
35import Control.Monad 37import Control.Monad
36import Control.Monad.Reader 38import Control.Monad.Reader
@@ -47,6 +49,8 @@ import Control.Monad.Catch
47import Data.Foldable 49import Data.Foldable
48 50
49import Data.List (genericReplicate, genericLength, intercalate) 51import Data.List (genericReplicate, genericLength, intercalate)
52import Data.Set (Set)
53import qualified Data.Set as Set
50 54
51import Data.Monoid 55import Data.Monoid
52 56
@@ -69,7 +73,10 @@ genericPrint' path = flip catches handlers . withFile path . print
69 ] 73 ]
70 print printout handle = $(logDebug) (T.pack $ show printout') >> liftIO (slowPut handle printout' >> return Nothing) 74 print printout handle = $(logDebug) (T.pack $ show printout') >> liftIO (slowPut handle printout' >> return Nothing)
71 where 75 where
72 printout' = runPut $ initialize >> render printout >> finalize 76 printout' = mkPrintout printout
77
78mkPrintout :: Printout -> Lazy.ByteString
79mkPrintout printout = runPut $ initialize >> render printout >> finalize
73 80
74slowPut :: Handle -> Lazy.ByteString -> IO () 81slowPut :: Handle -> Lazy.ByteString -> IO ()
75slowPut h = slowPut' . LBS.split (LBS.last newl) 82slowPut h = slowPut' . LBS.split (LBS.last newl)
@@ -128,6 +135,7 @@ data Doc = Doc
128 , space :: Integer 135 , space :: Integer
129 , remainingSpace :: Integer 136 , remainingSpace :: Integer
130 , overflows :: Integer 137 , overflows :: Integer
138 , currentMarkup :: Set MarkupMode
131 } 139 }
132 140
133initDoc :: Integer -> Doc 141initDoc :: Integer -> Doc
@@ -136,6 +144,7 @@ initDoc space = Doc { lines = Seq.empty
136 , space = space 144 , space = space
137 , remainingSpace = space 145 , remainingSpace = space
138 , overflows = 0 146 , overflows = 0
147 , currentMarkup = Set.empty
139 } 148 }
140 149
141breakLine :: Doc -> Doc 150breakLine :: Doc -> Doc
@@ -151,6 +160,19 @@ renderDoc Doc{..} = intersperse' (newls' 1) id lines'
151 | remainingSpace == space = lines 160 | remainingSpace == space = lines
152 | otherwise = lines |> currentLine 161 | otherwise = lines |> currentLine
153 162
163escSequence' :: [Word8] -> State Doc ()
164escSequence' s = modify (\(doc@(Doc{..})) -> doc { currentLine = currentLine >> escSequence s })
165
166setMarkup :: Set MarkupMode -> State Doc ()
167setMarkup m = escSequence' [33, byte m] >> modify (\doc -> doc { currentMarkup = m })
168 where
169 byte = foldr (.|.) zeroBits . Set.map bitMask
170 bitMask Bold = 8
171 bitMask DoubleHeight = 16
172 bitMask DoubleWidth = 32
173 bitMask Underline = 128
174 bitMask _ = zeroBits
175
154renderBlock :: Block -> State Doc () 176renderBlock :: Block -> State Doc ()
155renderBlock (VSpace n) = sequence_ . genericReplicate n $ modify' breakLine 177renderBlock (VSpace n) = sequence_ . genericReplicate n $ modify' breakLine
156renderBlock (NewlSep xs) = intersperse' (modify' breakLine) renderBlock xs 178renderBlock (NewlSep xs) = intersperse' (modify' breakLine) renderBlock xs
@@ -165,6 +187,11 @@ renderLine (HSpace n) = modify' insertSpace
165 } 187 }
166 | remainingSpace == n = breakLine doc 188 | remainingSpace == n = breakLine doc
167 | otherwise = breakLine $ doc { overflows = overflows + 1 } 189 | otherwise = breakLine $ doc { overflows = overflows + 1 }
190renderLine (Markup ms l)
191 | Set.null ms = renderLine l
192 | otherwise = do
193 prevMarkup <- gets currentMarkup
194 setMarkup (prevMarkup <> ms) >> renderLine l >> setMarkup prevMarkup
168renderLine (JuxtaPos xs) = mapM_ renderLine xs 195renderLine (JuxtaPos xs) = mapM_ renderLine xs
169renderLine (cotext . Line -> word) = modify' $ insertWord 196renderLine (cotext . Line -> word) = modify' $ insertWord
170 where 197 where
@@ -192,4 +219,3 @@ renderLine (cotext . Line -> word) = modify' $ insertWord
192 } 219 }
193 | otherwise = doc 220 | otherwise = doc
194 encode'' = encode' . TL.unpack 221 encode'' = encode' . TL.unpack
195
diff --git a/server/test/Thermoprint/Server/Printer/GenericSpec.hs b/server/test/Thermoprint/Server/Printer/GenericSpec.hs
new file mode 100644
index 0000000..80096b0
--- /dev/null
+++ b/server/test/Thermoprint/Server/Printer/GenericSpec.hs
@@ -0,0 +1,69 @@
1{-# LANGUAGE OverloadedStrings, OverloadedLists #-}
2{-# LANGUAGE StandaloneDeriving #-}
3{-# LANGUAGE ViewPatterns #-}
4
5module Thermoprint.Server.Printer.GenericSpec (spec) where
6
7import Test.Hspec
8import Test.Hspec.QuickCheck (prop)
9import Test.QuickCheck (Property, Discard(..), property)
10import Test.QuickCheck.Instances
11
12import Thermoprint.Server.Printer.Generic
13import Thermoprint.Printout
14
15import Data.Text (Text)
16import qualified Data.Text.Lazy as TL (pack)
17
18import qualified Data.ByteString.Lazy as L (ByteString)
19import qualified Data.ByteString.Lazy as L.BS
20
21import Data.String (IsString(..))
22
23import Control.Monad (zipWithM_, join)
24import Data.Monoid ((<>))
25import Data.Function (on)
26
27import Data.Word
28
29import Data.Sequence (Seq)
30import qualified Data.Sequence as Seq
31
32import Debug.Trace
33
34instance IsString Line where
35 fromString = (\(Right l) -> l) . text . TL.pack
36
37spec :: Spec
38spec = do
39 describe "example printouts" $
40 zipWithM_ example [1..] examples
41 where
42 example n (s, ts) = let str = show s
43 in specify str $ traceDump (mkPrintout . Printout . fmap (Paragraph . Seq.singleton) . fmap Cooked $ s) == ts
44
45final, initial :: L.ByteString
46initial = esc [64] <> esc [64]
47final = "\n\n\n \n"
48
49esc :: [Word8] -> L.ByteString
50esc = L.BS.pack . (27:)
51
52p :: L.ByteString -> L.ByteString
53p = (<> final) . (initial <>)
54
55traceDump :: L.ByteString -> L.ByteString
56traceDump bs = traceShow (map (\b -> (b, (toEnum $ fromEnum b) :: Char)) $ L.BS.unpack bs) bs
57
58examples :: [(Seq Block, L.ByteString)]
59examples = [ ( [Line (JuxtaPos ["Hello", HSpace 1, "World!"])]
60 , p "Hello World!")
61 , ( [Line (JuxtaPos ["Hello", HSpace 4, "World!"])]
62 , p "Hello World!")
63 , ( [Line ("Par1"), Line ("Par2"), Line (JuxtaPos ["Par3", HSpace 1, "Word2"])]
64 , p "Par1\n\nPar2\n\nPar3 Word2")
65 , ( [Line (JuxtaPos ["Par1", HSpace 4]), NewlSep [VSpace 2, Line ("Par2")], Line (JuxtaPos ["Par3", HSpace 1, "Word2"])]
66 , p "Par1 \n\n\n\n\nPar2\n\nPar3 Word2")
67 , ( [Line (JuxtaPos [Markup [Bold] (JuxtaPos ["B",HSpace 1,Markup [Underline] "BM"]),HSpace 1,Markup [Bold,Underline] "BM"])]
68 , p $ esc [33, 8] <> "B " <> esc [33, 128 + 8] <> "BM" <> esc [33, 8] <> esc [33, 0] <> " " <> esc [33, 128 + 8] <> "BM" <> esc [33, 0])
69 ]
diff --git a/server/thermoprint-server.cabal b/server/thermoprint-server.cabal
index 259abf3..c80351b 100644
--- a/server/thermoprint-server.cabal
+++ b/server/thermoprint-server.cabal
@@ -50,7 +50,7 @@ library
50 , servant-server >=0.4.4 && <1 50 , servant-server >=0.4.4 && <1
51 , stm >=2.4.4 && <3 51 , stm >=2.4.4 && <3
52 , text >=1.2.1 && <2 52 , text >=1.2.1 && <2
53 , thermoprint-spec ==4.0.* 53 , thermoprint-spec ==5.0.*
54 , time >=1.5.0 && <2 54 , time >=1.5.0 && <2
55 , wai >=3.0.4 && <4 55 , wai >=3.0.4 && <4
56 , warp >=3.1.9 && <4 56 , warp >=3.1.9 && <4
@@ -94,6 +94,7 @@ Test-Suite tests
94 , containers >=0.5.6 && <1 94 , containers >=0.5.6 && <1
95 , async >=2.1.0 && <3 95 , async >=2.1.0 && <3
96 , http-types >=0.9.1 && <1 96 , http-types >=0.9.1 && <1
97 , bytestring >=0.10.6 && <1
97 98
98executable thermoprint-server 99executable thermoprint-server
99 main-is: Main.hs 100 main-is: Main.hs
diff --git a/server/thermoprint-server.nix b/server/thermoprint-server.nix
index a40dddb..71a4211 100644
--- a/server/thermoprint-server.nix
+++ b/server/thermoprint-server.nix
@@ -25,10 +25,10 @@ mkDerivation {
25 base monad-logger mtl persistent-sqlite resourcet 25 base monad-logger mtl persistent-sqlite resourcet
26 ]; 26 ];
27 testHaskellDepends = [ 27 testHaskellDepends = [
28 async base containers exceptions hspec http-types monad-logger mtl 28 async base bytestring containers exceptions hspec http-types
29 persistent-sqlite QuickCheck quickcheck-instances resourcet stm 29 monad-logger mtl persistent-sqlite QuickCheck quickcheck-instances
30 temporary text thermoprint-client thermoprint-spec transformers 30 resourcet stm temporary text thermoprint-client thermoprint-spec
31 warp 31 transformers warp
32 ]; 32 ];
33 homepage = "http://dirty-haskell.org/tags/thermoprint.html"; 33 homepage = "http://dirty-haskell.org/tags/thermoprint.html";
34 description = "Server for thermoprint-spec"; 34 description = "Server for thermoprint-spec";
diff --git a/spec/src/Thermoprint/Printout.hs b/spec/src/Thermoprint/Printout.hs
index 8c33e07..752ccb5 100644
--- a/spec/src/Thermoprint/Printout.hs
+++ b/spec/src/Thermoprint/Printout.hs
@@ -11,7 +11,9 @@ module Thermoprint.Printout
11 , Block(..) 11 , Block(..)
12 , Line( HSpace 12 , Line( HSpace
13 , JuxtaPos 13 , JuxtaPos
14 , Markup
14 ) 15 )
16 , MarkupMode(..)
15 , text, cotext 17 , text, cotext
16 , prop_text 18 , prop_text
17 ) where 19 ) where
@@ -48,6 +50,9 @@ import Data.Monoid (Monoid(..), (<>))
48 50
49import Data.List (dropWhile, dropWhileEnd, groupBy, genericLength, genericReplicate) 51import Data.List (dropWhile, dropWhileEnd, groupBy, genericLength, genericReplicate)
50 52
53import Data.Set (Set)
54import qualified Data.Set as Set
55
51import Data.Sequence as Seq (fromList, null, singleton) 56import Data.Sequence as Seq (fromList, null, singleton)
52import Data.Sequence (ViewL(..), viewl) 57import Data.Sequence (ViewL(..), viewl)
53 58
@@ -143,6 +148,7 @@ We don't export all constructors and instead encourage the use of 'text'.
143-} 148-}
144data Line = Word Text 149data Line = Word Text
145 | HSpace Integer 150 | HSpace Integer
151 | Markup (Set MarkupMode) Line
146 | JuxtaPos (Seq Line) 152 | JuxtaPos (Seq Line)
147 deriving (Generic, NFData, Show, CoArbitrary, FromJSON, ToJSON) 153 deriving (Generic, NFData, Show, CoArbitrary, FromJSON, ToJSON)
148 154
@@ -215,6 +221,7 @@ cotext (Line x) = cotext' x
215 where 221 where
216 cotext' (Word x) = x 222 cotext' (Word x) = x
217 cotext' (HSpace n) = TL.pack . genericReplicate n $ ' ' 223 cotext' (HSpace n) = TL.pack . genericReplicate n $ ' '
224 cotext' (Markup _ l) = cotext' l
218 cotext' (JuxtaPos xs) = mconcat . map cotext' . toList $ xs 225 cotext' (JuxtaPos xs) = mconcat . map cotext' . toList $ xs
219 226
220prop_text :: Text -> Bool 227prop_text :: Text -> Bool
@@ -231,6 +238,14 @@ prop_text x = (cotext . either id Line . text $ x') == x'
231 | otherwise = c 238 | otherwise = c
232 keep = [' ', '\n'] :: [Char] 239 keep = [' ', '\n'] :: [Char]
233 240
241data MarkupMode = Bold
242 | Underline
243 | DoubleHeight
244 | DoubleWidth
245 deriving (Generic, NFData, Show, Arbitrary, CoArbitrary, FromJSON, ToJSON
246 , Eq, Ord, Enum
247 )
248
234-- | We don't test 'Raw' 'Chunk's 249-- | We don't test 'Raw' 'Chunk's
235instance Arbitrary Chunk where 250instance Arbitrary Chunk where
236 shrink = genericShrink 251 shrink = genericShrink
diff --git a/spec/thermoprint-spec.cabal b/spec/thermoprint-spec.cabal
index 28680fb..d4ecda6 100644
--- a/spec/thermoprint-spec.cabal
+++ b/spec/thermoprint-spec.cabal
@@ -2,7 +2,7 @@
2-- documentation, see http://haskell.org/cabal/users-guide/ 2-- documentation, see http://haskell.org/cabal/users-guide/
3 3
4name: thermoprint-spec 4name: thermoprint-spec
5version: 4.0.0 5version: 5.0.0
6synopsis: A specification of the API and the payload datatypes and associated utilities 6synopsis: A specification of the API and the payload datatypes and associated utilities
7-- description: 7-- description:
8homepage: http://dirty-haskell.org/tags/thermoprint.html 8homepage: http://dirty-haskell.org/tags/thermoprint.html
diff --git a/spec/thermoprint-spec.nix b/spec/thermoprint-spec.nix
index 3480782..1a1611c 100644
--- a/spec/thermoprint-spec.nix
+++ b/spec/thermoprint-spec.nix
@@ -4,7 +4,7 @@
4}: 4}:
5mkDerivation { 5mkDerivation {
6 pname = "thermoprint-spec"; 6 pname = "thermoprint-spec";
7 version = "4.0.0"; 7 version = "5.0.0";
8 src = ./.; 8 src = ./.;
9 libraryHaskellDepends = [ 9 libraryHaskellDepends = [
10 aeson base base64-bytestring bytestring Cabal cabal-test-quickcheck 10 aeson base base64-bytestring bytestring Cabal cabal-test-quickcheck
diff --git a/tp-bbcode/src/Thermoprint/Printout/BBCode.hs b/tp-bbcode/src/Thermoprint/Printout/BBCode.hs
index dd5edb0..1770b6d 100644
--- a/tp-bbcode/src/Thermoprint/Printout/BBCode.hs
+++ b/tp-bbcode/src/Thermoprint/Printout/BBCode.hs
@@ -1,4 +1,5 @@
1{-# LANGUAGE OverloadedStrings #-} 1{-# LANGUAGE OverloadedStrings #-}
2{-# LANGUAGE OverloadedLists #-}
2{-# LANGUAGE DeriveGeneric #-} 3{-# LANGUAGE DeriveGeneric #-}
3{-# LANGUAGE GADTs #-} 4{-# LANGUAGE GADTs #-}
4 5
@@ -13,6 +14,9 @@ module Thermoprint.Printout.BBCode
13 14
14import Data.Text (Text) 15import Data.Text (Text)
15import Data.Map (Map) 16import Data.Map (Map)
17import qualified Data.Map as Map
18import Data.Set (Set)
19import qualified Data.Set as Set
16 20
17import qualified Data.Text.Lazy as Lazy (Text) 21import qualified Data.Text.Lazy as Lazy (Text)
18import qualified Data.Text.Lazy as TL (fromStrict) 22import qualified Data.Text.Lazy as TL (fromStrict)
@@ -31,6 +35,7 @@ import Data.Bifunctor (bimap, first)
31import Control.Monad (join) 35import Control.Monad (join)
32 36
33import Data.List (groupBy) 37import Data.List (groupBy)
38import Data.Maybe (mapMaybe)
34 39
35import Text.BBCode (DomForest, DomTree(..), TreeError(..)) 40import Text.BBCode (DomForest, DomTree(..), TreeError(..))
36import qualified Text.BBCode as Raw (bbcode, BBCodeError(..)) 41import qualified Text.BBCode as Raw (bbcode, BBCodeError(..))
@@ -140,9 +145,23 @@ parse BlockCtx = fmap mconcat . mapM mergeResult' . groupBy sameCtx . map parseD
140parse ctx = mergeResult ctx . map parseDom 145parse ctx = mergeResult ctx . map parseDom
141 146
142asBlock :: CI Text -> [DomTree] -> Map (CI Text) Text -> Either SemanticError Block 147asBlock :: CI Text -> [DomTree] -> Map (CI Text) Text -> Either SemanticError Block
143asBlock "VSpace" _ = Right . VSpace . lookupAttr "height" True 1 148asBlock "VSpace" _ attrs = Right . VSpace $ lookupAttr "height" True 1 attrs
144asBlock t _ = const $ Left . UnmappedBlockElement . CI.original $ t 149asBlock t _ _ = Left . UnmappedBlockElement . CI.original $ t
145 150
146asLine :: CI Text -> [DomTree] -> Map (CI Text) Text -> Either SemanticError Line 151asLine :: CI Text -> [DomTree] -> Map (CI Text) Text -> Either SemanticError Line
147asLine "HSpace" _ = Right . HSpace . lookupAttr "width" True 1 152asLine "HSpace" _ attrs = Right . HSpace $ lookupAttr "width" True 1 attrs
148asLine t _ = const $ Left . UnmappedLineElement . CI.original $ t 153asLine c t attrs
154 | (Just m) <- lookup c $ map (\(c, _, m) -> (CI.mk [c], m)) mTable
155 = Markup [m] <$> parse LineCtx t
156 | (Just m) <- lookup c $ map (\(_, a, m) -> (a, m)) mTable
157 = Markup [m] <$> parse LineCtx t
158 | "markup" <- c
159 , ms <- Set.fromList $ mapMaybe (\(_, a, m) -> m <$ Map.lookup a attrs) mTable
160 = Markup ms <$> parse LineCtx t
161 where
162 mTable = [ ('b', "bold", Bold)
163 , ('u', "underline", Underline)
164 , ('h', "doubleHeight", DoubleHeight)
165 , ('w', "doubleWidth", DoubleWidth)
166 ]
167asLine t _ _ = Left . UnmappedLineElement . CI.original $ t
diff --git a/tp-bbcode/test/Thermoprint/Printout/BBCodeSpec.hs b/tp-bbcode/test/Thermoprint/Printout/BBCodeSpec.hs
index 7909360..2f70ddc 100644
--- a/tp-bbcode/test/Thermoprint/Printout/BBCodeSpec.hs
+++ b/tp-bbcode/test/Thermoprint/Printout/BBCodeSpec.hs
@@ -64,4 +64,6 @@ examples = [ ("Hello World!"
64 , Right [Line ("Par1"), Line ("Par2"), Line (JuxtaPos ["Par3", HSpace 1, "Word2"])]) 64 , Right [Line ("Par1"), Line ("Par2"), Line (JuxtaPos ["Par3", HSpace 1, "Word2"])])
65 , ("Par1 [hspace=3/]\n\n[vspace=2/]Par2\n\nPar3 Word2" 65 , ("Par1 [hspace=3/]\n\n[vspace=2/]Par2\n\nPar3 Word2"
66 , Right [Line (JuxtaPos ["Par1", HSpace 4]), NewlSep [VSpace 2, Line ("Par2")], Line (JuxtaPos ["Par3", HSpace 1, "Word2"])]) 66 , Right [Line (JuxtaPos ["Par1", HSpace 4]), NewlSep [VSpace 2, Line ("Par2")], Line (JuxtaPos ["Par3", HSpace 1, "Word2"])])
67 , ("[b]B [u]BM[/u][/b] [markup bold=1 underline=1]BM[/markup]"
68 , Right [Line (JuxtaPos [Markup [Bold] (JuxtaPos ["B",HSpace 1,Markup [Underline] "BM"]),HSpace 1,Markup [Bold,Underline] "BM"])])
67 ] 69 ]
diff --git a/tp-bbcode/thermoprint-bbcode.cabal b/tp-bbcode/thermoprint-bbcode.cabal
index 29855e2..b476753 100644
--- a/tp-bbcode/thermoprint-bbcode.cabal
+++ b/tp-bbcode/thermoprint-bbcode.cabal
@@ -24,7 +24,7 @@ library
24 , OverloadedLists 24 , OverloadedLists
25 -- other-extensions: 25 -- other-extensions:
26 build-depends: base >=4.8.1 && <5 26 build-depends: base >=4.8.1 && <5
27 , thermoprint-spec ==4.0.* 27 , thermoprint-spec ==5.0.*
28 , bbcode >=3.1.1 && <4 28 , bbcode >=3.1.1 && <4
29 , containers -any 29 , containers -any
30 , text -any 30 , text -any
@@ -44,7 +44,7 @@ Test-Suite tests
44 , OverloadedLists 44 , OverloadedLists
45 build-depends: base >=4.8.1 && <5 45 build-depends: base >=4.8.1 && <5
46 , thermoprint-bbcode -any 46 , thermoprint-bbcode -any
47 , thermoprint-spec ==4.0.* 47 , thermoprint-spec ==5.0.*
48 , hspec >=2.2.1 && <3 48 , hspec >=2.2.1 && <3
49 , QuickCheck >=2.8.1 && <3 49 , QuickCheck >=2.8.1 && <3
50 , quickcheck-instances >=0.3.11 && <4 50 , quickcheck-instances >=0.3.11 && <4