{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE OverloadedStrings #-}
module SLIP32
(
parse
, parseXPub
, parseXPrv
, parseText
, parseXPubText
, parseXPrvText
, renderXPub
, renderXPrv
, renderXPubText
, renderXPrvText
, XPub(..)
, Pub
, pub
, unPub
, XPrv(..)
, Prv
, prv
, unPrv
, Path
, path
, unPath
, Chain
, chain
, unChain
) where
import Control.Monad
import qualified Codec.Binary.Bech32 as Bech32
import qualified Data.Binary.Get as Bin
import qualified Data.ByteString as B
import qualified Data.ByteString.Builder as BB
import qualified Data.ByteString.Lazy as BL
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import Data.Word
data XPub = XPub !Path !Chain !Pub
deriving (Eq, Show)
data XPrv = XPrv !Path !Chain !Prv
deriving (Eq, Show)
data Path = Path !Word8 ![Word32]
deriving (Eq, Show)
unPath :: Path -> [Word32]
unPath (Path _ x) = x
path :: [Word32] -> Maybe Path
{-# INLINE path #-}
path x | l < 256 = Just (Path (fromIntegral l) x)
| otherwise = Nothing
where l = length x
newtype Chain = Chain B.ByteString
deriving (Eq, Show)
unChain :: Chain -> B.ByteString
{-# INLINE unChain #-}
unChain (Chain x) = x
chain :: B.ByteString -> Maybe Chain
{-# INLINE chain #-}
chain x | B.length x == 32 = Just (Chain x)
| otherwise = Nothing
newtype Prv = Prv B.ByteString
deriving (Eq, Show)
unPrv :: Prv -> B.ByteString
{-# INLINE unPrv #-}
unPrv (Prv x) = x
prv :: B.ByteString -> Maybe Prv
{-# INLINE prv #-}
prv x | B.length x == 33 && B.head x == 0 = Just (Prv x)
| otherwise = Nothing
newtype Pub = Pub B.ByteString
deriving (Eq, Show)
unPub :: Pub -> B.ByteString
{-# INLINE unPub #-}
unPub (Pub x) = x
pub :: B.ByteString -> Maybe Pub
{-# INLINE pub #-}
pub x | B.length x == 33 && (h == 2 || h == 3) = Just (Pub x)
| otherwise = Nothing
where h = B.head x
parseXPub :: B.ByteString -> Maybe XPub
{-# INLINE parseXPub #-}
parseXPub = parseXPubText <=< hush . T.decodeUtf8'
parseXPrv :: B.ByteString -> Maybe XPrv
{-# INLINE parseXPrv #-}
parseXPrv = parseXPrvText <=< hush . T.decodeUtf8'
parse :: B.ByteString -> Maybe (Either XPub XPrv)
{-# INLINE parse #-}
parse = parseText <=< hush . T.decodeUtf8'
parseXPubText :: T.Text -> Maybe XPub
{-# INLINE parseXPubText #-}
parseXPubText = either Just (\_ -> Nothing) <=< parseText
parseXPrvText :: T.Text -> Maybe XPrv
{-# INLINE parseXPrvText #-}
parseXPrvText = either (\_ -> Nothing) Just <=< parseText
parseText :: T.Text -> Maybe (Either XPub XPrv)
parseText = \t0 -> do
(hrp, dp) <- hush $ Bech32.decodeLenient t0
raw <- Bech32.dataPartToBytes dp
case Bin.runGetOrFail getRawSLIP32 (BL.fromStrict raw) of
Right (lo, _, out@(Left _)) | BL.null lo && hrp == hrpXPub -> Just out
Right (lo, _, out@(Right _)) | BL.null lo && hrp == hrpXPrv -> Just out
_ -> Nothing
getRawSLIP32 :: Bin.Get (Either XPub XPrv)
getRawSLIP32 = do
depth <- Bin.getWord8
pa <- Path depth <$> replicateM (fromIntegral depth) Bin.getWord32be
cc <- Chain <$> Bin.getByteString 32
kd <- Bin.getByteString 33
case pub kd of
Just k -> pure (Left (XPub pa cc k))
Nothing -> case prv kd of
Just k -> pure (Right (XPrv pa cc k))
Nothing -> fail "Bad key prefix"
renderXPub :: XPub -> B.ByteString
{-# INLINE renderXPub #-}
renderXPub = T.encodeUtf8 . renderXPubText
renderXPrv :: XPrv -> B.ByteString
{-# INLINE renderXPrv #-}
renderXPrv = T.encodeUtf8 . renderXPrvText
renderXPubText :: XPub -> T.Text
{-# INLINE renderXPubText #-}
renderXPubText = \(XPub p c (Pub k)) -> renderText hrpXPub p c (Key k)
renderXPrvText :: XPrv -> T.Text
{-# INLINE renderXPrvText #-}
renderXPrvText = \(XPrv p c (Prv k)) -> renderText hrpXPrv p c (Key k)
newtype Key = Key B.ByteString
renderText :: Bech32.HumanReadablePart -> Path -> Chain -> Key -> T.Text
renderText hrp (Path pl p) (Chain c) (Key k)
= Bech32.encodeLenient hrp $ Bech32.dataPartFromBytes
$ BL.toStrict $ BB.toLazyByteString
$ BB.word8 pl <>
foldMap BB.word32BE p <>
BB.byteString c <>
BB.byteString k
hrpXPub :: Bech32.HumanReadablePart
Right hrpXPub = Bech32.humanReadablePartFromText "xpub"
hrpXPrv :: Bech32.HumanReadablePart
Right hrpXPrv = Bech32.humanReadablePartFromText "xprv"
hush :: Either a b -> Maybe b
{-# INLINE hush #-}
hush = either (\_ -> Nothing) Just