~alcinnz/haskell-stylist

65464450d093c64adca7250abb8b738a4361cd35 — Adrian Cochrane 1 year, 2 days ago 1578769
Add support for chinese, with correction regarding handling negatives.
M src/Data/CSS/Preprocessor/Text/CounterStyle.hs => src/Data/CSS/Preprocessor/Text/CounterStyle.hs +63 -8
@@ 1,7 1,8 @@
{-# LANGUAGE OverloadedStrings #-}
module Data.CSS.Preprocessor.Text.CounterStyle(CounterStyle(..), CounterSystem(..),
    defaultCounter, decimalCounter, isValid, parseCounterStyle, CounterStore'(..),
    counterRender, counterRenderMarker, ranges', speakAs', parseCounter) where
    defaultCounter, decimalCounter, simpChineseInformal, cjkDecimal,
    isValid, parseCounterStyle, CounterStore'(..), parseCounter,
    counterRender, counterRenderMarker, ranges', speakAs') where
import Data.CSS.Syntax.Tokens
import Data.CSS.Syntax.StyleSheet



@@ 26,10 27,10 @@ data CounterStyle = CounterStyle {
    additiveSymbols :: [(Int, Text)],
    speakAs :: Maybe Text
}
data CounterSystem =
    Cyclic | Fixed Int | Symbolic | Alphabetic | Numeric | Additive
data CounterSystem = Cyclic | Fixed Int | Symbolic | Alphabetic | Numeric
        | Additive | Chinese { isSimplified :: Bool }

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


@@ 49,9 50,27 @@ decimalCounter = defaultCounter {
    symbols = ["0", "1", "2", "3", "4", "5", "6", "7", "8", "9"],
    fallback = Nothing
}
-- These are here mostly for testing...
cjkDecimal = defaultCounter {
    system = Numeric,
    ranges = Just [(0, maxBound)],
    symbols = ["〇", "一", "二", "三", "四", "五", "六", "七", "八", "九"],
    suffix = "、"
}
simpChineseInformal = defaultCounter {
    system = Chinese True,
    negativePrefix = "负",
    symbols = ["零", "一", "二", "三", "四", "五", "六", "七", "八", "九"],
    additiveSymbols = [(0, ""), (10, "十"), (100, "百"), (1000, "千")],
    suffix = "、",
    fallback = Just cjkDecimal
}

isValid :: CounterStyle -> Bool
isValid CounterStyle { system = Additive, additiveSymbols = [] } = False
isValid self@CounterStyle {
        system = Chinese _, symbols = syms, additiveSymbols = markers
    } = length syms == 10 && length markers >= 4 && ranges self == Nothing
isValid CounterStyle { symbols = [] } = False
isValid _ = True



@@ 68,6 87,8 @@ parseCounterProperty _ ("system", [Ident "alphabetic"]) self =
    self { system = Alphabetic }
parseCounterProperty _ ("system", [Ident "numeric"]) self =
    self { system = Numeric }
parseCounterProperty _ ("system", [Ident "-argo-chinese", Ident x]) self =
    self { system = Chinese (x == "simplified") }
-- Handled by caller so property overrides work correctly.
parseCounterProperty _ ("system", [Ident "extends", Ident _]) self = self



@@ 198,15 219,43 @@ counterRenderCore CounterStyle { system = Additive, additiveSymbols = syms } w
        reps = quot x weight
        x' = x - weight * reps
    inner [] _ = "\0" -- Run fallback counter!
-- Following https://w3c.github.io/csswg-drafts/css-counter-styles-3/#limited-chinese
-- 1. If the counter value is 0, the representation is the character for 0
-- specified for the given counter style. Skip the rest of this algorithm.
counterRenderCore CounterStyle { system = Chinese _, symbols = (sym:_) } 0 = sym
counterRenderCore CounterStyle {
        system = Chinese simplified, symbols = syms, additiveSymbols = markers
    } x = Txt.concat $ map renderDigit $ collapse0s $
        reverse $ enumerate $ decimalDigits x
  where
    -- Implements step 4.
    collapse0s ((i, 0):digits) = inner digits
      where
        inner ((_, 0):digits') = inner digits'
        -- Drop trailing 0s
        inner [] = []
        -- Collapse any remaining (consecutive?) zeroes into a single 0 digit.
        inner digits' = (i, 0):collapse0s digits'
    collapse0s (digit:digits) = digit:collapse0s digits
    collapse0s [] = []
    renderDigit (_, 0) = syms !! 0 -- Don't append digit marker for zero, step 2.
    -- 3. For the informal styles, if the counter value is between 10 and 19,
    -- remove the 10s digit (leave the digit marker).
    renderDigit (1,1) | simplified, [_, _] <- decimalDigits x = markers' !! 1
    -- Select characters per steps 2 & 5
    renderDigit (place, digit) = Txt.concat [syms !! digit, markers' !! place]
    markers' = map snd markers
decimalDigits :: Int -> [Int]
decimalDigits 0 = []
decimalDigits x = rem x 10:decimalDigits (quot x 10)
enumerate :: [a] -> [(Int, a)]
enumerate = zip $ enumFrom 0

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


@@ 214,6 263,11 @@ counterRender isMarker self x
        | not $ inRange x $ ranges' this = inner self' x'
        | counterRenderCore this x == fallbackSym = inner self' x'
    inner self' x'
        | x' < 0 = Txt.concat [
            negativePrefix self',
            inner self' { fallback = Nothing } $ -x',
            negativeSuffix self'
          ]
        | text == fallbackSym = Txt.pack $ show x' -- NOTE: Shouldn't happen
        | n < padLength self' =
            Txt.replicate (padLength self' - n) (padChar self') `Txt.append` text


@@ 236,6 290,7 @@ ranges' CounterStyle { system = Fixed _ } = infiniteRange
ranges' CounterStyle { system = Alphabetic } = [(1, maxBound)]
ranges' CounterStyle { system = Symbolic } = [(1, maxBound)]
ranges' CounterStyle { system = Additive } = [(0, maxBound)]
ranges' CounterStyle { system = Chinese _ } = [(-9999, 9999)]

speakAs' :: CounterStyle -> Text
speakAs' CounterStyle { speakAs = Just ret } = ret

M src/Data/CSS/Preprocessor/Text/counter-styles.css => src/Data/CSS/Preprocessor/Text/counter-styles.css +35 -0
@@ 1047,3 1047,38 @@
    additive-symbols: 1000 '\4D', 900 '\43\4D', 500 '\44', 400 '\43\44', 100 '\43', 90 '\58\43', 50 '\4C', 40 '\58\4C', 10 '\58', 9 '\49\58', 5 '\56', 4 '\49\56', 1 '\49';
    /* additive-symbols: 1000 'M', 900 'CM', 500 'D', 400 'CD', 100 'C', 90 'XC', 50 'L', 40 'XL', 10 'X', 9 'IX', 5 'V', 4 'IV', 1 'I'; */
}

/* Counters defined under https://w3c.github.io/csswg-drafts/css-counter-styles-3/#complex-predefined-counters
    Uses special CSS extensions. */
@counter-style simp-chinese-informal {
    system: -argo-chinese simplified;
    negative: 负;
    symbols: 零 一 二 三 四 五 六 七 八 九;
    additive-symbols: 0 "", 10 十, 100 百, 1000 千;
    suffix: "、";
    fallback: cjk-decimal;
}
@counter-style simp-chinese-formal {
    system: -argo-chinese formal;
    negative: 负;
    symbols: 零 壹 贰 叁 肆 伍 陆 柒 捌 玖;
    additive-symbols: 0 "", 10 拾, 100 佰, 1000 仟;
    suffix: "、";
    fallback: cjk-decimal;
}
@counter-style trad-chinese-informal {
    system: -argo-chinese simplified;
    negative: 負;
    symbols: 零 一 二 三 四 五 六 七 八 九;
    additive-symbols: 0 "", 10 十, 100 百, 1000 千;
    suffix: "、";
    fallback: cjk-decimal;
}
@counter-style trad-chinese-formal {
    system: -argo-chinese formal;
    negative: 負;
    symbols: 零 壹 貳 參 肆 伍 陸 柒 捌 玖;
    additive-symbols: 0 "", 10 拾, 100 佰, 1000 仟;
    suffix: "、";
    fallback: cjk-decimal;
}

M test/Test.hs => test/Test.hs +122 -0
@@ 587,6 587,128 @@ spec = do
            Ctr.counterRenderMarker counter 11 `shouldBe` "⚅⚄ "
            Ctr.counterRenderMarker counter 12 `shouldBe` "⚅⚅ "
            Ctr.counterRenderMarker counter 13 `shouldBe` "⚅⚅⚀ "
        it "Handles Chinese-specific numbering systems" $ do
            let counterRender = Ctr.counterRender False Ctr.simpChineseInformal
            counterRender 1 `shouldBe` "一"
            counterRender 2 `shouldBe` "二"
            counterRender 3 `shouldBe` "三"
            counterRender 4 `shouldBe` "四"
            counterRender 5 `shouldBe` "五"
            counterRender 6 `shouldBe` "六"
            counterRender 7 `shouldBe` "七"
            counterRender 8 `shouldBe` "八"
            counterRender 9 `shouldBe` "九"
            counterRender 10 `shouldBe` "十"
            counterRender 11 `shouldBe` "十一"
            counterRender 12 `shouldBe` "十二"
            counterRender 13 `shouldBe` "十三"
            counterRender 14 `shouldBe` "十四"
            counterRender 15 `shouldBe` "十五"
            counterRender 16 `shouldBe` "十六"
            counterRender 17 `shouldBe` "十七"
            counterRender 18 `shouldBe` "十八"
            counterRender 19 `shouldBe` "十九"
            counterRender 20 `shouldBe` "二十"
            counterRender 21 `shouldBe` "二十一"
            counterRender 22 `shouldBe` "二十二"
            counterRender 23 `shouldBe` "二十三"
            counterRender 24 `shouldBe` "二十四"
            counterRender 25 `shouldBe` "二十五"
            counterRender 26 `shouldBe` "二十六"
            counterRender 27 `shouldBe` "二十七"
            counterRender 28 `shouldBe` "二十八"
            counterRender 29 `shouldBe` "二十九"
            counterRender 30 `shouldBe` "三十"
            counterRender 31 `shouldBe` "三十一"
            counterRender 32 `shouldBe` "三十二"
            counterRender 33 `shouldBe` "三十三"
            counterRender 34 `shouldBe` "三十四"
            counterRender 35 `shouldBe` "三十五"
            counterRender 36 `shouldBe` "三十六"
            counterRender 37 `shouldBe` "三十七"
            counterRender 38 `shouldBe` "三十八"
            counterRender 39 `shouldBe` "三十九"
            counterRender 40 `shouldBe` "四十"
            counterRender 41 `shouldBe` "四十一"
            counterRender 42 `shouldBe` "四十二"
            counterRender 43 `shouldBe` "四十三"
            counterRender 44 `shouldBe` "四十四"
            counterRender 45 `shouldBe` "四十五"
            counterRender 46 `shouldBe` "四十六"
            counterRender 47 `shouldBe` "四十七"
            counterRender 48 `shouldBe` "四十八"
            counterRender 49 `shouldBe` "四十九"
            counterRender 50 `shouldBe` "五十"
            counterRender 51 `shouldBe` "五十一"
            counterRender 52 `shouldBe` "五十二"
            counterRender 53 `shouldBe` "五十三"
            counterRender 54 `shouldBe` "五十四"
            counterRender 55 `shouldBe` "五十五"
            counterRender 56 `shouldBe` "五十六"
            counterRender 57 `shouldBe` "五十七"
            counterRender 58 `shouldBe` "五十八"
            counterRender 59 `shouldBe` "五十九"
            counterRender 60 `shouldBe` "六十"
            counterRender 61 `shouldBe` "六十一"
            counterRender 62 `shouldBe` "六十二"
            counterRender 63 `shouldBe` "六十三"
            counterRender 64 `shouldBe` "六十四"
            counterRender 65 `shouldBe` "六十五"
            counterRender 66 `shouldBe` "六十六"
            counterRender 67 `shouldBe` "六十七"
            counterRender 68 `shouldBe` "六十八"
            counterRender 69 `shouldBe` "六十九"
            counterRender 70 `shouldBe` "七十"
            counterRender 71 `shouldBe` "七十一"
            counterRender 72 `shouldBe` "七十二"
            counterRender 73 `shouldBe` "七十三"
            counterRender 74 `shouldBe` "七十四"
            counterRender 75 `shouldBe` "七十五"
            counterRender 76 `shouldBe` "七十六"
            counterRender 77 `shouldBe` "七十七"
            counterRender 78 `shouldBe` "七十八"
            counterRender 79 `shouldBe` "七十九"
            counterRender 80 `shouldBe` "八十"
            counterRender 81 `shouldBe` "八十一"
            counterRender 82 `shouldBe` "八十二"
            counterRender 83 `shouldBe` "八十三"
            counterRender 84 `shouldBe` "八十四"
            counterRender 85 `shouldBe` "八十五"
            counterRender 86 `shouldBe` "八十六"
            counterRender 87 `shouldBe` "八十七"
            counterRender 88 `shouldBe` "八十八"
            counterRender 89 `shouldBe` "八十九"
            counterRender 90 `shouldBe` "九十"
            counterRender 91 `shouldBe` "九十一"
            counterRender 92 `shouldBe` "九十二"
            counterRender 93 `shouldBe` "九十三"
            counterRender 94 `shouldBe` "九十四"
            counterRender 95 `shouldBe` "九十五"
            counterRender 96 `shouldBe` "九十六"
            counterRender 97 `shouldBe` "九十七"
            counterRender 98 `shouldBe` "九十八"
            counterRender 99 `shouldBe` "九十九"
            counterRender 100 `shouldBe` "一百"
            counterRender 101 `shouldBe` "一百零一"
            counterRender 102 `shouldBe` "一百零二"
            counterRender 103 `shouldBe` "一百零三"
            counterRender 104 `shouldBe` "一百零四"
            counterRender 105 `shouldBe` "一百零五"
            counterRender 106 `shouldBe` "一百零六"
            counterRender 107 `shouldBe` "一百零七"
            counterRender 108 `shouldBe` "一百零八"
            counterRender 109 `shouldBe` "一百零九"
            counterRender 110 `shouldBe` "一百一十"
            counterRender 111 `shouldBe` "一百一十一"
            counterRender 112 `shouldBe` "一百一十二"
            counterRender 113 `shouldBe` "一百一十三"
            counterRender 114 `shouldBe` "一百一十四"
            counterRender 115 `shouldBe` "一百一十五"
            counterRender 116 `shouldBe` "一百一十六"
            counterRender 117 `shouldBe` "一百一十七"
            counterRender 118 `shouldBe` "一百一十八"
            counterRender 119 `shouldBe` "一百一十九"
            counterRender 120 `shouldBe` "一百二十"

styleIndex :: StyleIndex
styleIndex = new