module System.Nix.Store.Remote.Types.ProtoVersion
( ProtoVersion(..)
, HasProtoVersion(..)
) where
import Data.Default.Class (Default(def))
import Data.Word (Word8, Word16)
import GHC.Generics (Generic)
data ProtoVersion = ProtoVersion
{ ProtoVersion -> Word16
protoVersion_major :: Word16
, ProtoVersion -> Word8
protoVersion_minor :: Word8
}
deriving (ProtoVersion -> ProtoVersion -> Bool
(ProtoVersion -> ProtoVersion -> Bool)
-> (ProtoVersion -> ProtoVersion -> Bool) -> Eq ProtoVersion
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ProtoVersion -> ProtoVersion -> Bool
== :: ProtoVersion -> ProtoVersion -> Bool
$c/= :: ProtoVersion -> ProtoVersion -> Bool
/= :: ProtoVersion -> ProtoVersion -> Bool
Eq, (forall x. ProtoVersion -> Rep ProtoVersion x)
-> (forall x. Rep ProtoVersion x -> ProtoVersion)
-> Generic ProtoVersion
forall x. Rep ProtoVersion x -> ProtoVersion
forall x. ProtoVersion -> Rep ProtoVersion x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ProtoVersion -> Rep ProtoVersion x
from :: forall x. ProtoVersion -> Rep ProtoVersion x
$cto :: forall x. Rep ProtoVersion x -> ProtoVersion
to :: forall x. Rep ProtoVersion x -> ProtoVersion
Generic, Eq ProtoVersion
Eq ProtoVersion =>
(ProtoVersion -> ProtoVersion -> Ordering)
-> (ProtoVersion -> ProtoVersion -> Bool)
-> (ProtoVersion -> ProtoVersion -> Bool)
-> (ProtoVersion -> ProtoVersion -> Bool)
-> (ProtoVersion -> ProtoVersion -> Bool)
-> (ProtoVersion -> ProtoVersion -> ProtoVersion)
-> (ProtoVersion -> ProtoVersion -> ProtoVersion)
-> Ord ProtoVersion
ProtoVersion -> ProtoVersion -> Bool
ProtoVersion -> ProtoVersion -> Ordering
ProtoVersion -> ProtoVersion -> ProtoVersion
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ProtoVersion -> ProtoVersion -> Ordering
compare :: ProtoVersion -> ProtoVersion -> Ordering
$c< :: ProtoVersion -> ProtoVersion -> Bool
< :: ProtoVersion -> ProtoVersion -> Bool
$c<= :: ProtoVersion -> ProtoVersion -> Bool
<= :: ProtoVersion -> ProtoVersion -> Bool
$c> :: ProtoVersion -> ProtoVersion -> Bool
> :: ProtoVersion -> ProtoVersion -> Bool
$c>= :: ProtoVersion -> ProtoVersion -> Bool
>= :: ProtoVersion -> ProtoVersion -> Bool
$cmax :: ProtoVersion -> ProtoVersion -> ProtoVersion
max :: ProtoVersion -> ProtoVersion -> ProtoVersion
$cmin :: ProtoVersion -> ProtoVersion -> ProtoVersion
min :: ProtoVersion -> ProtoVersion -> ProtoVersion
Ord, Int -> ProtoVersion -> ShowS
[ProtoVersion] -> ShowS
ProtoVersion -> String
(Int -> ProtoVersion -> ShowS)
-> (ProtoVersion -> String)
-> ([ProtoVersion] -> ShowS)
-> Show ProtoVersion
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ProtoVersion -> ShowS
showsPrec :: Int -> ProtoVersion -> ShowS
$cshow :: ProtoVersion -> String
show :: ProtoVersion -> String
$cshowList :: [ProtoVersion] -> ShowS
showList :: [ProtoVersion] -> ShowS
Show)
instance Default ProtoVersion where
def :: ProtoVersion
def = ProtoVersion
{ protoVersion_major :: Word16
protoVersion_major = Word16
1
, protoVersion_minor :: Word8
protoVersion_minor = Word8
24
}
class HasProtoVersion r where
hasProtoVersion :: r -> ProtoVersion
instance HasProtoVersion ProtoVersion where
hasProtoVersion :: ProtoVersion -> ProtoVersion
hasProtoVersion = ProtoVersion -> ProtoVersion
forall a. a -> a
id