~alcinnz/fontconfig-pure

ref: c406e2016b6ae9b909501c05c5790693092447e3 fontconfig-pure/lib/Graphics/Text/Font/Choose/Range.hs -rw-r--r-- 987 bytes
c406e201 — Adrian Cochrane Properly handle ambiguity in empty char/lang sets. 7 months ago
                                                                                
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
{-# LANGUAGE DeriveGeneric #-}
module Graphics.Text.Font.Choose.Range(Range(..), iRange) where

import Data.MessagePack (MessagePack(..), Object(..))
import Test.QuickCheck (Arbitrary(..))
import GHC.Generics (Generic(..))
import Data.Hashable (Hashable(..))
import qualified Data.Vector as V
import qualified Data.IntMap as IM

-- | Matches a numeric range.
data Range = Range Double Double deriving (Eq, Read, Show, Ord, Generic)
-- | Matches an integral range.
iRange :: Int -> Int -> Range
iRange i j = toEnum i `Range` toEnum j

instance MessagePack Range where
    toObject (Range start end) = ObjectMap $ V.fromList [
        (ObjectInt 0, ObjectDouble start),
        (ObjectInt 1, ObjectDouble end)
      ]
    fromObject msg
        | Just msg' <- fromObject msg =
            Just (IM.findWithDefault 0 0 msg' `Range` IM.findWithDefault 0 1 msg')
        | otherwise = Nothing
instance Arbitrary Range where
    arbitrary = uncurry Range <$> arbitrary
instance Hashable Range