{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE PatternSynonyms #-}
module Network.TLS.Types.Version (
Version (Version, SSL2, SSL3, TLS10, TLS11, TLS12, TLS13),
) where
import Codec.Serialise
import GHC.Generics
import Network.TLS.Imports
newtype Version = Version Word16 deriving (Version -> Version -> Bool
(Version -> Version -> Bool)
-> (Version -> Version -> Bool) -> Eq Version
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Version -> Version -> Bool
== :: Version -> Version -> Bool
$c/= :: Version -> Version -> Bool
/= :: Version -> Version -> Bool
Eq, Eq Version
Eq Version =>
(Version -> Version -> Ordering)
-> (Version -> Version -> Bool)
-> (Version -> Version -> Bool)
-> (Version -> Version -> Bool)
-> (Version -> Version -> Bool)
-> (Version -> Version -> Version)
-> (Version -> Version -> Version)
-> Ord Version
Version -> Version -> Bool
Version -> Version -> Ordering
Version -> Version -> Version
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 :: Version -> Version -> Ordering
compare :: Version -> Version -> Ordering
$c< :: Version -> Version -> Bool
< :: Version -> Version -> Bool
$c<= :: Version -> Version -> Bool
<= :: Version -> Version -> Bool
$c> :: Version -> Version -> Bool
> :: Version -> Version -> Bool
$c>= :: Version -> Version -> Bool
>= :: Version -> Version -> Bool
$cmax :: Version -> Version -> Version
max :: Version -> Version -> Version
$cmin :: Version -> Version -> Version
min :: Version -> Version -> Version
Ord, (forall x. Version -> Rep Version x)
-> (forall x. Rep Version x -> Version) -> Generic Version
forall x. Rep Version x -> Version
forall x. Version -> Rep Version x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Version -> Rep Version x
from :: forall x. Version -> Rep Version x
$cto :: forall x. Rep Version x -> Version
to :: forall x. Rep Version x -> Version
Generic)
pattern SSL2 :: Version
pattern $mSSL2 :: forall {r}. Version -> ((# #) -> r) -> ((# #) -> r) -> r
$bSSL2 :: Version
SSL2 = Version 0x0002
pattern SSL3 :: Version
pattern $mSSL3 :: forall {r}. Version -> ((# #) -> r) -> ((# #) -> r) -> r
$bSSL3 :: Version
SSL3 = Version 0x0300
pattern TLS10 :: Version
pattern $mTLS10 :: forall {r}. Version -> ((# #) -> r) -> ((# #) -> r) -> r
$bTLS10 :: Version
TLS10 = Version 0x0301
pattern TLS11 :: Version
pattern $mTLS11 :: forall {r}. Version -> ((# #) -> r) -> ((# #) -> r) -> r
$bTLS11 :: Version
TLS11 = Version 0x0302
pattern TLS12 :: Version
pattern $mTLS12 :: forall {r}. Version -> ((# #) -> r) -> ((# #) -> r) -> r
$bTLS12 :: Version
TLS12 = Version 0x0303
pattern TLS13 :: Version
pattern $mTLS13 :: forall {r}. Version -> ((# #) -> r) -> ((# #) -> r) -> r
$bTLS13 :: Version
TLS13 = Version 0x0304
instance Show Version where
show :: Version -> String
show Version
SSL2 = String
"SSL2"
show Version
SSL3 = String
"SSL3"
show Version
TLS10 = String
"TLS1.0"
show Version
TLS11 = String
"TLS1.1"
show Version
TLS12 = String
"TLS1.2"
show Version
TLS13 = String
"TLS1.3"
show (Version Word16
x) = String
"Version " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Word16 -> String
forall a. Show a => a -> String
show Word16
x
instance Serialise Version