~alcinnz/haskell-stylist

1578769433c856e9f9f8dbcd7c24191b733a7f7d — Adrian Cochrane 1 year, 2 days ago 4d14807
Minor corrections to counter rendering.
2 files changed, 44 insertions(+), 42 deletions(-)

M src/Data/CSS/Preprocessor/Text/CounterStyle.hs
M test/Test.hs
M src/Data/CSS/Preprocessor/Text/CounterStyle.hs => src/Data/CSS/Preprocessor/Text/CounterStyle.hs +11 -9
@@ 1,7 1,7 @@
{-# LANGUAGE OverloadedStrings #-}
module Data.CSS.Preprocessor.Text.CounterStyle(CounterStyle(..), CounterSystem(..),
    defaultCounter, decimalCounter, isValid, parseCounterStyle, CounterStore'(..),
    counterRender, ranges', speakAs', parseCounter) where
    counterRender, counterRenderMarker, ranges', speakAs', parseCounter) where
import Data.CSS.Syntax.Tokens
import Data.CSS.Syntax.StyleSheet



@@ 11,8 11,6 @@ import qualified Data.HashMap.Lazy as HM
import Data.HashMap.Lazy (HashMap)
import Data.Maybe (isJust, fromJust)

import Debug.Trace (traceShow)

-- NOTE: No support for image "symbols" yet.
data CounterStyle = CounterStyle {
    system :: CounterSystem,


@@ 201,11 199,15 @@ counterRenderCore CounterStyle { system = Additive, additiveSymbols = syms } w
        x' = x - weight * reps
    inner [] _ = "\0" -- Run fallback counter!

counterRender :: CounterStyle -> Int -> Text
counterRender self x
    | x < 0 = Txt.concat [prefix self, negativePrefix self, inner self $ -x,
                          negativeSuffix self, suffix self]
    | otherwise = Txt.concat [prefix self, inner self x, suffix self]
counterRenderMarker :: CounterStyle -> Int -> Text
counterRenderMarker = counterRender True
counterRender :: Bool -> CounterStyle -> Int -> Text
counterRender isMarker self x
    | isMarker && x < 0 = Txt.concat [prefix self, negativePrefix self,
                            inner self $ -x, negativeSuffix self, suffix self]
    | isMarker = Txt.concat [prefix self, inner self x, suffix self]
    | x<0 = Txt.concat [negativePrefix self,inner self $ -x,negativeSuffix self]
    | otherwise = inner self x
  where
    inner :: CounterStyle -> Int -> Text
    inner this@CounterStyle { fallback = Just self' } x'


@@ 258,5 260,5 @@ parseCounter _ (Function "symbols":Ident name:toks)
parseCounter store (Ident name:toks)
    | Just ret <- HM.lookup name store = Just (ret, toks)
parseCounter _ (String sym:toks) =
    Just (defaultCounter { system = Symbolic, symbols = [sym], suffix = " " }, toks)
    Just (defaultCounter {system = Cyclic, symbols = [sym], suffix = " "}, toks)
parseCounter _ _ = Nothing

M test/Test.hs => test/Test.hs +33 -33
@@ 529,64 529,64 @@ spec = do
            let counter = Ctr.defaultCounter {
                Ctr.system = Ctr.Cyclic, Ctr.symbols = ["!", "@", "#"]
              }
            Ctr.counterRender counter 2 `shouldBe` "@. "
            Ctr.counterRender counter 4 `shouldBe` "!. "
            Ctr.counterRenderMarker counter 2 `shouldBe` "@. "
            Ctr.counterRenderMarker counter 4 `shouldBe` "!. "
        it "Handles system: fixed" $ do
            let counter = Ctr.defaultCounter {
                Ctr.system = Ctr.Fixed 1, Ctr.symbols = ["◰", "◳", "◲", "◱"],
                Ctr.suffix = ": "
              }
            Ctr.counterRender counter 1 `shouldBe` "◰: "
            Ctr.counterRender counter 2 `shouldBe` "◳: "
            Ctr.counterRender counter 3 `shouldBe` "◲: "
            Ctr.counterRender counter 4 `shouldBe` "◱: "
            Ctr.counterRender counter 5 `shouldBe` "5: "
            Ctr.counterRender counter 6 `shouldBe` "6: "
            Ctr.counterRenderMarker counter 1 `shouldBe` "◰: "
            Ctr.counterRenderMarker counter 2 `shouldBe` "◳: "
            Ctr.counterRenderMarker counter 3 `shouldBe` "◲: "
            Ctr.counterRenderMarker counter 4 `shouldBe` "◱: "
            Ctr.counterRenderMarker counter 5 `shouldBe` "5: "
            Ctr.counterRenderMarker counter 6 `shouldBe` "6: "
        it "Handles system: symbolic" $ do
            let counter = Ctr.defaultCounter {
                Ctr.system = Ctr.Symbolic, Ctr.symbols = ["*", "⁑", "†", "‡"],
                Ctr.suffix = " "
            }
            Ctr.counterRender counter 1 `shouldBe` "* "
            Ctr.counterRender counter 2 `shouldBe` "⁑ "
            Ctr.counterRender counter 3 `shouldBe` "† "
            Ctr.counterRender counter 4 `shouldBe` "‡ "
            Ctr.counterRender counter 5 `shouldBe` "** "
            Ctr.counterRender counter 6 `shouldBe` "⁑⁑ "
            Ctr.counterRenderMarker counter 1 `shouldBe` "* "
            Ctr.counterRenderMarker counter 2 `shouldBe` "⁑ "
            Ctr.counterRenderMarker counter 3 `shouldBe` "† "
            Ctr.counterRenderMarker counter 4 `shouldBe` "‡ "
            Ctr.counterRenderMarker counter 5 `shouldBe` "** "
            Ctr.counterRenderMarker counter 6 `shouldBe` "⁑⁑ "
        it "Handles system: alphabetic" $ do
            let counter = Ctr.defaultCounter {
                Ctr.system = Ctr.Alphabetic, Ctr.symbols = ["◦", "•"],
                Ctr.suffix = " "
            }
            Ctr.counterRender counter 1 `shouldBe` "◦ "
            Ctr.counterRender counter 2 `shouldBe` "• "
            Ctr.counterRender counter 3 `shouldBe` "◦◦ "
            Ctr.counterRender counter 4 `shouldBe` "◦• "
            Ctr.counterRender counter 5 `shouldBe` "•◦ "
            Ctr.counterRender counter 6 `shouldBe` "•• "
            Ctr.counterRender counter 7 `shouldBe` "◦◦◦ "
            Ctr.counterRenderMarker counter 1 `shouldBe` "◦ "
            Ctr.counterRenderMarker counter 2 `shouldBe` "• "
            Ctr.counterRenderMarker counter 3 `shouldBe` "◦◦ "
            Ctr.counterRenderMarker counter 4 `shouldBe` "◦• "
            Ctr.counterRenderMarker counter 5 `shouldBe` "•◦ "
            Ctr.counterRenderMarker counter 6 `shouldBe` "•• "
            Ctr.counterRenderMarker counter 7 `shouldBe` "◦◦◦ "
        it "Handles system: numeric" $ do
            let counter = Ctr.defaultCounter {
                Ctr.system = Ctr.Numeric, Ctr.symbols = ["0", "1", "2"]
            }
            Ctr.counterRender counter 1 `shouldBe` "1. "
            Ctr.counterRender counter 2 `shouldBe` "2. "
            Ctr.counterRender counter 3 `shouldBe` "10. "
            Ctr.counterRender counter 4 `shouldBe` "11. "
            Ctr.counterRender counter 5 `shouldBe` "12. "
            Ctr.counterRender counter 6 `shouldBe` "20. "
            Ctr.counterRenderMarker counter 1 `shouldBe` "1. "
            Ctr.counterRenderMarker counter 2 `shouldBe` "2. "
            Ctr.counterRenderMarker counter 3 `shouldBe` "10. "
            Ctr.counterRenderMarker counter 4 `shouldBe` "11. "
            Ctr.counterRenderMarker counter 5 `shouldBe` "12. "
            Ctr.counterRenderMarker counter 6 `shouldBe` "20. "
        it "Handles system: additive" $ do
            let counter = Ctr.defaultCounter {
                Ctr.system = Ctr.Additive, Ctr.suffix = " ",
                Ctr.additiveSymbols = [(6, "⚅"), (5, "⚄"), (4, "⚃"),
                                        (3, "⚂"), (2, "⚁"), (1, "⚀")]
            }
            Ctr.counterRender counter 1 `shouldBe` "⚀ "
            Ctr.counterRender counter 2 `shouldBe` "⚁ "
            Ctr.counterRender counter 3 `shouldBe` "⚂ "
            Ctr.counterRender counter 11 `shouldBe` "⚅⚄ "
            Ctr.counterRender counter 12 `shouldBe` "⚅⚅ "
            Ctr.counterRender counter 13 `shouldBe` "⚅⚅⚀ "
            Ctr.counterRenderMarker counter 1 `shouldBe` "⚀ "
            Ctr.counterRenderMarker counter 2 `shouldBe` "⚁ "
            Ctr.counterRenderMarker counter 3 `shouldBe` "⚂ "
            Ctr.counterRenderMarker counter 11 `shouldBe` "⚅⚄ "
            Ctr.counterRenderMarker counter 12 `shouldBe` "⚅⚅ "
            Ctr.counterRenderMarker counter 13 `shouldBe` "⚅⚅⚀ "

styleIndex :: StyleIndex
styleIndex = new