diff options
| -rw-r--r-- | tp-bbcode/src/Thermoprint/Printout/BBCode.hs | 3 | ||||
| -rw-r--r-- | tp-bbcode/src/Thermoprint/Printout/BBCode/Inverse.hs | 53 | ||||
| -rw-r--r-- | tp-bbcode/test/Thermoprint/Printout/BBCodeSpec.hs | 27 | ||||
| -rw-r--r-- | tp-bbcode/thermoprint-bbcode.cabal | 2 | ||||
| -rw-r--r-- | tp-bbcode/thermoprint-bbcode.nix | 7 | 
5 files changed, 84 insertions, 8 deletions
| diff --git a/tp-bbcode/src/Thermoprint/Printout/BBCode.hs b/tp-bbcode/src/Thermoprint/Printout/BBCode.hs index ce2aa43..cbe2618 100644 --- a/tp-bbcode/src/Thermoprint/Printout/BBCode.hs +++ b/tp-bbcode/src/Thermoprint/Printout/BBCode.hs | |||
| @@ -8,6 +8,7 @@ module Thermoprint.Printout.BBCode | |||
| 8 | , BBCodeError(..) | 8 | , BBCodeError(..) | 
| 9 | , TreeError(..) | 9 | , TreeError(..) | 
| 10 | , SemanticError(..) | 10 | , SemanticError(..) | 
| 11 | , module Thermoprint.Printout.BBCode.Inverse | ||
| 11 | ) where | 12 | ) where | 
| 12 | 13 | ||
| 13 | import Data.Text (Text) | 14 | import Data.Text (Text) | 
| @@ -34,6 +35,8 @@ import Data.List (groupBy) | |||
| 34 | import Text.BBCode (DomForest, DomTree(..), TreeError(..)) | 35 | import Text.BBCode (DomForest, DomTree(..), TreeError(..)) | 
| 35 | import qualified Text.BBCode as Raw (bbcode, BBCodeError(..)) | 36 | import qualified Text.BBCode as Raw (bbcode, BBCodeError(..)) | 
| 36 | 37 | ||
| 38 | import Thermoprint.Printout.BBCode.Inverse | ||
| 39 | |||
| 37 | import Thermoprint.Printout | 40 | import Thermoprint.Printout | 
| 38 | 41 | ||
| 39 | import Thermoprint.Printout.BBCode.Attribute | 42 | import Thermoprint.Printout.BBCode.Attribute | 
| diff --git a/tp-bbcode/src/Thermoprint/Printout/BBCode/Inverse.hs b/tp-bbcode/src/Thermoprint/Printout/BBCode/Inverse.hs new file mode 100644 index 0000000..edd4c5a --- /dev/null +++ b/tp-bbcode/src/Thermoprint/Printout/BBCode/Inverse.hs | |||
| @@ -0,0 +1,53 @@ | |||
| 1 | {-# LANGUAGE ViewPatterns #-} | ||
| 2 | |||
| 3 | module Thermoprint.Printout.BBCode.Inverse | ||
| 4 | ( cobbcode | ||
| 5 | , UnicodeException(..) | ||
| 6 | ) where | ||
| 7 | |||
| 8 | import Data.Sequence (Seq) | ||
| 9 | import qualified Data.Sequence as Seq () | ||
| 10 | |||
| 11 | import Data.Text (Text) | ||
| 12 | import qualified Data.Text as T (pack, empty, isSuffixOf) | ||
| 13 | import qualified Data.Text.Lazy as LT (toStrict) | ||
| 14 | |||
| 15 | import Data.ByteString.Lazy as LBS (toStrict) | ||
| 16 | |||
| 17 | import Data.Text.Encoding | ||
| 18 | import Data.Text.Encoding.Error (UnicodeException(..)) | ||
| 19 | |||
| 20 | import Data.Foldable (toList) | ||
| 21 | import Data.List | ||
| 22 | import Data.Monoid | ||
| 23 | |||
| 24 | import Thermoprint.Printout | ||
| 25 | |||
| 26 | cobbcode :: Printout -> Either UnicodeException Text | ||
| 27 | cobbcode (toList -> ps) = mconcat . intersperse "\n\n" <$> mapM handlePar ps | ||
| 28 | |||
| 29 | handlePar :: Seq Chunk -> Either UnicodeException Text | ||
| 30 | handlePar (toList -> cs) = mconcat <$> mapM handleChunk cs | ||
| 31 | |||
| 32 | handleChunk :: Chunk -> Either UnicodeException Text | ||
| 33 | handleChunk (Cooked b) = Right $ handleBlock b | ||
| 34 | handleChunk (Raw bs) = decodeUtf8' $ LBS.toStrict bs | ||
| 35 | |||
| 36 | handleBlock :: Block -> Text | ||
| 37 | handleBlock (Line l) = handleLine l | ||
| 38 | handleBlock (VSpace i) | ||
| 39 | | i /= 0 = "[vspace=" <> T.pack (show i) <> "/]" | ||
| 40 | | otherwise = "" | ||
| 41 | handleBlock (NewlSep (toList -> bs)) = mconcat . intersperse "\n" $ map handleBlock bs | ||
| 42 | |||
| 43 | handleLine :: Line -> Text | ||
| 44 | handleLine = flip handleLine' T.empty | ||
| 45 | where | ||
| 46 | handleLine' (HSpace i) p | ||
| 47 | | i == 0 = "" | ||
| 48 | | i == 1 = " " | ||
| 49 | | " " `T.isSuffixOf` p = "[hspace=" <> T.pack (show i) <> "/]" | ||
| 50 | | i <= 2 = T.pack $ genericReplicate i ' ' | ||
| 51 | | otherwise = " [hspace=" <> T.pack (show $ i - 2) <> "/] " | ||
| 52 | handleLine' (JuxtaPos ls) p = foldl (\p l -> p <> handleLine' l p) "" ls | ||
| 53 | handleLine' (Line -> b) _ = LT.toStrict $ cotext b | ||
| diff --git a/tp-bbcode/test/Thermoprint/Printout/BBCodeSpec.hs b/tp-bbcode/test/Thermoprint/Printout/BBCodeSpec.hs index d2cdeed..09b3147 100644 --- a/tp-bbcode/test/Thermoprint/Printout/BBCodeSpec.hs +++ b/tp-bbcode/test/Thermoprint/Printout/BBCodeSpec.hs | |||
| @@ -1,10 +1,12 @@ | |||
| 1 | {-# LANGUAGE OverloadedStrings, OverloadedLists #-} | 1 | {-# LANGUAGE OverloadedStrings, OverloadedLists #-} | 
| 2 | {-# LANGUAGE StandaloneDeriving #-} | 2 | {-# LANGUAGE StandaloneDeriving #-} | 
| 3 | {-# LANGUAGE ViewPatterns #-} | ||
| 3 | 4 | ||
| 4 | module Thermoprint.Printout.BBCodeSpec (spec) where | 5 | module Thermoprint.Printout.BBCodeSpec (spec) where | 
| 5 | 6 | ||
| 6 | import Test.Hspec | 7 | import Test.Hspec | 
| 7 | import Test.Hspec.QuickCheck (prop) | 8 | import Test.Hspec.QuickCheck (prop) | 
| 9 | import Test.QuickCheck (Property, Discard(..), property) | ||
| 8 | import Test.QuickCheck.Instances | 10 | import Test.QuickCheck.Instances | 
| 9 | 11 | ||
| 10 | import Thermoprint.Printout.BBCode | 12 | import Thermoprint.Printout.BBCode | 
| @@ -15,11 +17,13 @@ import qualified Data.Text.Lazy as TL (pack) | |||
| 15 | 17 | ||
| 16 | import Data.String (IsString(..)) | 18 | import Data.String (IsString(..)) | 
| 17 | 19 | ||
| 18 | import Control.Monad (zipWithM_) | 20 | import Control.Monad (zipWithM_, join) | 
| 19 | import Data.Monoid ((<>)) | 21 | import Data.Monoid ((<>)) | 
| 20 | import Data.Function (on) | 22 | import Data.Function (on) | 
| 23 | import Data.Bifunctor | ||
| 21 | 24 | ||
| 22 | import Data.Sequence (Seq) | 25 | import Data.Sequence (Seq) | 
| 26 | import qualified Data.Sequence as Seq | ||
| 23 | 27 | ||
| 24 | instance Eq Block where | 28 | instance Eq Block where | 
| 25 | (==) = (==) `on` cotext | 29 | (==) = (==) `on` cotext | 
| @@ -30,10 +34,23 @@ instance IsString Line where | |||
| 30 | 34 | ||
| 31 | spec :: Spec | 35 | spec :: Spec | 
| 32 | spec = do | 36 | spec = do | 
| 33 | zipWithM_ example [1..] examples | 37 | describe "example texts for bbcode" $ | 
| 34 | where | 38 | zipWithM_ example [1..] examples | 
| 35 | example n (s, ts) = let str = "Example " <> show n | 39 | describe "cobbcode" $ prop "is inverse to bbcode" bbcodeInv | 
| 36 | in specify str $ bbcode s == (pOut <$> ts) | 40 | where | 
| 41 | example n (s, ts) = let str = show s | ||
| 42 | in specify str $ bbcode s == (pOut <$> ts) | ||
| 43 | |||
| 44 | bbcodeInv :: Printout -> Property | ||
| 45 | bbcodeInv (cobbcode -> Left _) = property True | ||
| 46 | bbcodeInv p@(cobbcode -> Right t) = either (const $ property True) property $ (==) <$> normalize (Right p) <*> normalize (bbcode t) | ||
| 47 | |||
| 48 | normalize = (!! 3) . iterate normalize' . first (const ()) | ||
| 49 | where | ||
| 50 | normalize' t = join' (bbcode <$> (join' $ cobbcode <$> t)) | ||
| 51 | join' :: Either a (Either b c) -> Either () c | ||
| 52 | join' (Right (Right a)) = Right a | ||
| 53 | join' _ = Left () | ||
| 37 | 54 | ||
| 38 | pOut :: Seq Block -> Printout | 55 | pOut :: Seq Block -> Printout | 
| 39 | pOut = fmap (pure . Cooked) | 56 | pOut = fmap (pure . Cooked) | 
| diff --git a/tp-bbcode/thermoprint-bbcode.cabal b/tp-bbcode/thermoprint-bbcode.cabal index 98681ca..3d47691 100644 --- a/tp-bbcode/thermoprint-bbcode.cabal +++ b/tp-bbcode/thermoprint-bbcode.cabal | |||
| @@ -18,6 +18,7 @@ cabal-version: >=1.10 | |||
| 18 | 18 | ||
| 19 | library | 19 | library | 
| 20 | exposed-modules: Thermoprint.Printout.BBCode | 20 | exposed-modules: Thermoprint.Printout.BBCode | 
| 21 | , Thermoprint.Printout.BBCode.Inverse | ||
| 21 | other-modules: Thermoprint.Printout.BBCode.Attribute | 22 | other-modules: Thermoprint.Printout.BBCode.Attribute | 
| 22 | extensions: OverloadedStrings | 23 | extensions: OverloadedStrings | 
| 23 | , OverloadedLists | 24 | , OverloadedLists | 
| @@ -28,6 +29,7 @@ library | |||
| 28 | , containers -any | 29 | , containers -any | 
| 29 | , text -any | 30 | , text -any | 
| 30 | , case-insensitive -any | 31 | , case-insensitive -any | 
| 32 | , bytestring >=0.10.6 && <1 | ||
| 31 | hs-source-dirs: src | 33 | hs-source-dirs: src | 
| 32 | default-language: Haskell2010 | 34 | default-language: Haskell2010 | 
| 33 | 35 | ||
| diff --git a/tp-bbcode/thermoprint-bbcode.nix b/tp-bbcode/thermoprint-bbcode.nix index d0b3d2c..7cec719 100644 --- a/tp-bbcode/thermoprint-bbcode.nix +++ b/tp-bbcode/thermoprint-bbcode.nix | |||
| @@ -1,5 +1,5 @@ | |||
| 1 | { mkDerivation, aeson, base, bbcode, case-insensitive, containers | 1 | { mkDerivation, aeson, base, bbcode, bytestring, case-insensitive | 
| 2 | , hspec, QuickCheck, quickcheck-instances, stdenv, text | 2 | , containers, hspec, QuickCheck, quickcheck-instances, stdenv, text | 
| 3 | , thermoprint-spec | 3 | , thermoprint-spec | 
| 4 | }: | 4 | }: | 
| 5 | mkDerivation { | 5 | mkDerivation { | 
| @@ -7,7 +7,8 @@ mkDerivation { | |||
| 7 | version = "1.0.0"; | 7 | version = "1.0.0"; | 
| 8 | src = ./.; | 8 | src = ./.; | 
| 9 | libraryHaskellDepends = [ | 9 | libraryHaskellDepends = [ | 
| 10 | base bbcode case-insensitive containers text thermoprint-spec | 10 | base bbcode bytestring case-insensitive containers text | 
| 11 | thermoprint-spec | ||
| 11 | ]; | 12 | ]; | 
| 12 | testHaskellDepends = [ | 13 | testHaskellDepends = [ | 
| 13 | aeson base containers hspec QuickCheck quickcheck-instances text | 14 | aeson base containers hspec QuickCheck quickcheck-instances text | 
