{-# LANGUAGE DeriveGeneric #-}
-- | A range between 2 values.
module Graphics.Text.Font.Choose.Range(Range(..), iRange, validRange) 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, bounded by 2 floating point numbers.
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 = do
(a, b) <- arbitrary
return $ Range a $ a + abs b + 1
instance Hashable Range
-- | Can FontConfig process this range?
validRange :: Range -> Bool
validRange (Range start end) = start < end