module Ssb.Types.Key where import Data.ByteString import Data.Text.Encoding (decodeUtf8) import qualified Data.Text as T import qualified Data.ByteString.Base64 as B64 import qualified Crypto.Sign.Ed25519 as Ed newtype PublicKey = Ed25519PublicKey { ed25519Key :: Ed.PublicKey } deriving (Eq, Ord) instance Show PublicKey where show = T.unpack . decodeUtf8 . formatPublicKey -- | Decodes a SSB Ed25519 public key, which is base64 encoded. parseEd25519PublicKey :: ByteString -> Maybe PublicKey parseEd25519PublicKey b = Ed25519PublicKey <$> maybeEd25519PublicKey where decodedPublicKey = B64.decode b maybeEd25519PublicKey = either (const Nothing) (Just . Ed.PublicKey) decodedPublicKey -- | Formats a SSB public key as a base64 encoded string. formatPublicKey :: PublicKey -> ByteString formatPublicKey (Ed25519PublicKey { ed25519Key = k }) = B64.encode (Ed.unPublicKey k)