selectively export only needed constructors

This commit is contained in:
Trolli Schmittlauch 2020-03-03 23:52:04 +01:00
parent 4a89ffe25a
commit 08932cf80a

View file

@ -9,12 +9,18 @@ Stability : experimental
Modernised EpiChord + k-choices load balancing Modernised EpiChord + k-choices load balancing
-} -}
module Hash2Pub.FediChord where module Hash2Pub.FediChord (
NodeID -- abstract, but newtype constructors cannot be hidden
, mkNodeID
, NodeState (..)
, CacheEntry
) where
import qualified Data.Map.Strict as Map import qualified Data.Map.Strict as Map
import qualified Data.String.UTF8 as U8S import qualified Data.String.UTF8 as U8S
import Network.Socket import Network.Socket
import Data.Time.Clock.System import Data.Time.Clock.System
import Control.Exception
-- define protocol constants -- define protocol constants
-- | static definition of ID length in bits -- | static definition of ID length in bits
@ -23,8 +29,16 @@ idBits = 256
-- |NodeIDs are Integers wrapped in a newtype, to be able to redefine -- |NodeIDs are Integers wrapped in a newtype, to be able to redefine
-- their instance behaviour -- their instance behaviour
--
-- for being able to check value bounds, the constructor should not be used directly
-- and new values are created via @mkNodeID@ (newtype constructors cannot be hidden)
newtype NodeID = NodeID { getNodeID :: Integer } deriving (Eq, Show, Enum) newtype NodeID = NodeID { getNodeID :: Integer } deriving (Eq, Show, Enum)
-- |smart data constructor for NodeID that throws a runtime exception for out-of-bounds values.
-- When needing a runtime-safe constructor with drawbacks, try @fromInteger@
mkNodeID :: Integer -> NodeID
mkNodeID i = assert (i >= getNodeID minBound && i <= getNodeID maxBound) $ NodeID i
-- |NodeIDs are bounded by the value range of an unsigned Integer of length 'idBits' -- |NodeIDs are bounded by the value range of an unsigned Integer of length 'idBits'
instance Bounded NodeID where instance Bounded NodeID where
minBound = NodeID 0 minBound = NodeID 0
@ -35,7 +49,8 @@ instance Num NodeID where
a + b = NodeID $ (getNodeID a + getNodeID b) `mod` (getNodeID maxBound + 1) a + b = NodeID $ (getNodeID a + getNodeID b) `mod` (getNodeID maxBound + 1)
a * b = NodeID $ (getNodeID a * getNodeID b) `mod` (getNodeID maxBound + 1) a * b = NodeID $ (getNodeID a * getNodeID b) `mod` (getNodeID maxBound + 1)
a - b = NodeID $ (getNodeID a - getNodeID b) `mod` (getNodeID maxBound + 1) a - b = NodeID $ (getNodeID a - getNodeID b) `mod` (getNodeID maxBound + 1)
-- Todo: decide whether throwing exceptions isn't better -- |safe constructor for NodeID values with the drawback, that out-of-bound values are wrapped around
-- with modulo to fit in the allowed value space. For runtime checking, look at @mkNodeID@.
fromInteger i = NodeID $ i `mod` (getNodeID maxBound + 1) fromInteger i = NodeID $ i `mod` (getNodeID maxBound + 1)
signum = NodeID . signum . getNodeID signum = NodeID . signum . getNodeID
abs = NodeID . abs . getNodeID -- ToDo: make sure that at creation time only IDs within the range are used abs = NodeID . abs . getNodeID -- ToDo: make sure that at creation time only IDs within the range are used