~alcinnz/haskell-stylist

fb3315b2c6c6efa0aeee25b732a6edf35df47e34 — Adrian Cochrane 1 year, 1 day ago 0073606
Test & fix rendering ethiopian numbers.
M src/Data/CSS/Preprocessor/Text/CounterStyle.hs => src/Data/CSS/Preprocessor/Text/CounterStyle.hs +15 -3
@@ 1,6 1,6 @@
{-# LANGUAGE OverloadedStrings #-}
module Data.CSS.Preprocessor.Text.CounterStyle(CounterStyle(..), CounterSystem(..),
    defaultCounter, decimalCounter, simpChineseInformal, cjkDecimal,
    defaultCounter, decimalCounter, simpChineseInformal, cjkDecimal, ethiopic,
    isValid, parseCounterStyle, CounterStore'(..), parseCounter,
    counterRender, counterRenderMarker, ranges', speakAs') where
import Data.CSS.Syntax.Tokens


@@ 30,7 30,8 @@ data CounterStyle = CounterStyle {
data CounterSystem = Cyclic | Fixed Int | Symbolic | Alphabetic | Numeric
        | Additive | Chinese { isSimplified :: Bool } | Ethiopic

defaultCounter, decimalCounter, simpChineseInformal, cjkDecimal :: CounterStyle
defaultCounter, decimalCounter :: CounterStyle
ethiopic, simpChineseInformal, cjkDecimal :: CounterStyle
defaultCounter = CounterStyle {
    system = Symbolic,
    negativePrefix = "-",


@@ 65,6 66,13 @@ simpChineseInformal = defaultCounter {
    suffix = "、",
    fallback = Just cjkDecimal
}
ethiopic = defaultCounter {
    system = Ethiopic,
    symbols = ["", "፩", "፪", "፫", "፬", "፭", "፮", "፯", "፰", "፱"],
    additiveSymbols = [(0, ""), (10, "፲"), (20, "፳"), (30, "፴"), (40, "፵"),
                       (50, "፶"), (60, "፷"), (70, "፸"), (80, "፹"), (90, "፺")],
    suffix = "/ "
}

isValid :: CounterStyle -> Bool
isValid CounterStyle { system = Additive, additiveSymbols = [] } = False


@@ 266,7 274,9 @@ counterRenderCore CounterStyle {

    renderPairs isBigEnd (group:groups) =
        renderPair isBigEnd group:renderPairs False groups
    renderPairs _ [] = []
    -- Handle step 4's exceptions.
    renderPair' :: Bool -> (Int, (Int, Int)) -> Text
    renderPair' _ (_,(0, 0)) = ""
    renderPair' True (_, (0,1)) = ""
    renderPair' _ (i, (0,1)) | odd i = ""


@@ 274,10 284,12 @@ counterRenderCore CounterStyle {
    renderPair' _ (_, (tens, units)) =
        (map snd tenSyms !! tens) `Txt.append` (unitSyms !! units)
    -- Step 6 & 7
    renderPair _ (i, (0,0)) = ""
    renderPair _ (i, (0,0)) | odd i = ""
    renderPair isBigEnd (0, group) = renderPair' isBigEnd (0, group)
    renderPair isBigEnd (i, group)
        | odd i = renderPair' isBigEnd (i, group) `Txt.append` "፻"
        | even i = renderPair' isBigEnd (i, group) `Txt.append` "፼"
    renderPair _ _ = "" -- Silence warnings, above case should not fallthrough.
decimalDigits :: Int -> [Int]
decimalDigits 0 = []
decimalDigits x = rem x 10:decimalDigits (quot x 10)

M src/Data/CSS/Preprocessor/Text/counter-styles.css => src/Data/CSS/Preprocessor/Text/counter-styles.css +7 -0
@@ 1082,3 1082,10 @@
    suffix: "、";
    fallback: cjk-decimal;
}

@counter-style ethiopic-numeric {
    system: -argo-ethiopic;
    symbols: "" ፩ ፪ ፫ ፬ ፭ ፮ ፯ ፰ ፱;
    additive-symbols: 0 "", 10 ፲, 20 ፳, 30 ፴, 40 ፵, 50 ፶, 60 ፷, 70 ፸, 80 ፹, 90 ፺;
    suffix: "/ ";
}

M test/Test.hs => test/Test.hs +4 -0
@@ 709,6 709,10 @@ spec = do
            counterRender 118 `shouldBe` "一百一十八"
            counterRender 119 `shouldBe` "一百一十九"
            counterRender 120 `shouldBe` "一百二十"
        it "Handles ethiopian numbering system" $ do
            Ctr.counterRender False Ctr.ethiopic 100 `shouldBe` "፻"
            Ctr.counterRender False Ctr.ethiopic 78010092 `shouldBe` "፸፰፻፩፼፺፪"
            Ctr.counterRender False Ctr.ethiopic 780100000092 `shouldBe` "፸፰፻፩፼፼፺፪"

styleIndex :: StyleIndex
styleIndex = new