{-# LANGUAGE RecordWildCards #-}
module Data.Snowchecked.Encoding.Class ( IsFlake(..), Flakeish(..), goodFish ) where
import Data.Snowchecked.Internal.Import
data Flakeish = Flakeish
{ Flakeish -> Word256
fishNodeId :: Word256
, Flakeish -> Word256
fishCount :: Word256
, Flakeish -> Word256
fishTime :: Word256
, Flakeish -> Word256
fishCheck :: Word256
}
goodFish :: SnowcheckedConfig -> Flakeish -> Bool
goodFish :: SnowcheckedConfig -> Flakeish -> Bool
goodFish SnowcheckedConfig{Word8
confCheckBits :: SnowcheckedConfig -> Word8
confNodeBits :: SnowcheckedConfig -> Word8
confCountBits :: SnowcheckedConfig -> Word8
confTimeBits :: SnowcheckedConfig -> Word8
confCheckBits :: Word8
confNodeBits :: Word8
confCountBits :: Word8
confTimeBits :: Word8
..} Flakeish{Word256
fishCheck :: Word256
fishTime :: Word256
fishCount :: Word256
fishNodeId :: Word256
fishCheck :: Flakeish -> Word256
fishTime :: Flakeish -> Word256
fishCount :: Flakeish -> Word256
fishNodeId :: Flakeish -> Word256
..} =
Word256
checkInteger Word256 -> Word256 -> Bool
forall a. Eq a => a -> a -> Bool
== Word256 -> Word8 -> Word256
forall a bitCount.
(Num a, Bits a, Integral bitCount) =>
a -> bitCount -> a
cutBits (Word256
nodeInteger Word256 -> Word256 -> Word256
forall a. Num a => a -> a -> a
+ Word256
countInteger Word256 -> Word256 -> Word256
forall a. Num a => a -> a -> a
+ Word256
timeInteger) Word8
confCheckBits
where
checkInteger :: Word256
checkInteger = Word256 -> Word8 -> Word256
forall a bitCount.
(Num a, Bits a, Integral bitCount) =>
a -> bitCount -> a
cutBits Word256
fishCheck Word8
confCheckBits
nodeInteger :: Word256
nodeInteger = Word256 -> Word8 -> Word256
forall a bitCount.
(Num a, Bits a, Integral bitCount) =>
a -> bitCount -> a
cutBits Word256
fishNodeId Word8
confNodeBits
countInteger :: Word256
countInteger = Word256 -> Word8 -> Word256
forall a bitCount.
(Num a, Bits a, Integral bitCount) =>
a -> bitCount -> a
cutBits Word256
fishCount Word8
confCountBits
timeInteger :: Word256
timeInteger = Word256 -> Word8 -> Word256
forall a bitCount.
(Num a, Bits a, Integral bitCount) =>
a -> bitCount -> a
cutBits Word256
fishTime Word8
confTimeBits
{-# INLINEABLE goodFish #-}
class IsFlake a where
{-# MINIMAL fromFlake, (parseFish | parseFlake) #-}
fromFlake :: Flake -> a
parseFlake :: (MonadFail m) => SnowcheckedConfig -> a -> m Flake
parseFlake cfg :: SnowcheckedConfig
cfg@SnowcheckedConfig{Word8
confCheckBits :: Word8
confNodeBits :: Word8
confCountBits :: Word8
confTimeBits :: Word8
confCheckBits :: SnowcheckedConfig -> Word8
confNodeBits :: SnowcheckedConfig -> Word8
confCountBits :: SnowcheckedConfig -> Word8
confTimeBits :: SnowcheckedConfig -> Word8
..} a
a = SnowcheckedConfig -> a -> m Flakeish
forall a (m :: * -> *).
(IsFlake a, MonadFail m) =>
SnowcheckedConfig -> a -> m Flakeish
parseFish SnowcheckedConfig
cfg a
a m Flakeish -> (Flakeish -> m Flake) -> m Flake
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \fish :: Flakeish
fish@Flakeish{Word256
fishCheck :: Word256
fishTime :: Word256
fishCount :: Word256
fishNodeId :: Word256
fishCheck :: Flakeish -> Word256
fishTime :: Flakeish -> Word256
fishCount :: Flakeish -> Word256
fishNodeId :: Flakeish -> Word256
..} ->
if SnowcheckedConfig -> Flakeish -> Bool
goodFish SnowcheckedConfig
cfg Flakeish
fish then
Flake -> m Flake
forall (m :: * -> *) a. Monad m => a -> m a
return (Flake -> m Flake) -> Flake -> m Flake
forall a b. (a -> b) -> a -> b
$ Flake :: Word256 -> Word256 -> Word256 -> SnowcheckedConfig -> Flake
Flake
{ flakeTime :: Word256
flakeTime = Word256 -> Word8 -> Word256
forall a bitCount.
(Num a, Bits a, Integral bitCount) =>
a -> bitCount -> a
cutBits Word256
fishTime Word8
confTimeBits
, flakeCount :: Word256
flakeCount = Word256 -> Word8 -> Word256
forall a bitCount.
(Num a, Bits a, Integral bitCount) =>
a -> bitCount -> a
cutBits Word256
fishCount Word8
confCountBits
, flakeNodeId :: Word256
flakeNodeId = Word256 -> Word8 -> Word256
forall a bitCount.
(Num a, Bits a, Integral bitCount) =>
a -> bitCount -> a
cutBits Word256
fishNodeId Word8
confNodeBits
, flakeConfig :: SnowcheckedConfig
flakeConfig = SnowcheckedConfig
cfg
}
else
String -> m Flake
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Checksum is incorrect for Snowchecked flake"
parseFish :: (MonadFail m) => SnowcheckedConfig -> a -> m Flakeish
parseFish SnowcheckedConfig
cfg a
a = Flake -> Flakeish
toFlakeish (Flake -> Flakeish) -> m Flake -> m Flakeish
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SnowcheckedConfig -> a -> m Flake
forall a (m :: * -> *).
(IsFlake a, MonadFail m) =>
SnowcheckedConfig -> a -> m Flake
parseFlake SnowcheckedConfig
cfg a
a
where
toFlakeish :: Flake -> Flakeish
toFlakeish Flake{Word256
SnowcheckedConfig
flakeConfig :: SnowcheckedConfig
flakeNodeId :: Word256
flakeCount :: Word256
flakeTime :: Word256
flakeConfig :: Flake -> SnowcheckedConfig
flakeNodeId :: Flake -> Word256
flakeCount :: Flake -> Word256
flakeTime :: Flake -> Word256
..} = Flakeish :: Word256 -> Word256 -> Word256 -> Word256 -> Flakeish
Flakeish
{ fishTime :: Word256
fishTime = Word256
flakeTime
, fishCount :: Word256
fishCount = Word256
flakeCount
, fishNodeId :: Word256
fishNodeId = Word256
flakeNodeId
, fishCheck :: Word256
fishCheck = Word256
flakeTime Word256 -> Word256 -> Word256
forall a. Num a => a -> a -> a
+ Word256
flakeCount Word256 -> Word256 -> Word256
forall a. Num a => a -> a -> a
+ Word256
flakeNodeId
}