{-# LANGUAGE GeneralizedNewtypeDeriving, TypeSynonymInstances #-} module Hranker.Rank ( highestRank , indexToRank , Rank , rankToIndex ) where import Control.Arrow (first) newtype Rank = Rank { getRank :: Int } deriving (Enum, Eq, Ord) instance Read Rank where -- Although this may look complicated, all it does is delegates to Read for Int and then converts the result readsPrec i = fmap (first Rank) . readsPrec i instance Show Rank where show = show . getRank -- | The highest possible rank. Ranks count upwards from this rank. highestRank :: Rank highestRank = Rank 1 -- | Convert a rank to a zero-based position in the list rankToIndex :: Rank -> Int rankToIndex r = getRank r - getRank highestRank -- | Inverse function of rankToIndex indexToRank :: Int -> Rank indexToRank = Rank . (+ getRank highestRank)