module Network.Haskoin.Transaction.Builder
( Coin(..)
, buildTx
, buildAddrTx
, SigInput(..)
, signTx
, signInput
, mergeTxs
, verifyStdTx
, verifyStdInput
, guessTxSize
, chooseCoins
, chooseCoinsSink
, chooseMSCoins
, chooseMSCoinsSink
, getFee
, getMSFee
) where
import Control.Arrow (first)
import Control.Monad (mzero, foldM, unless)
import Control.Monad.Identity (runIdentity)
import Control.DeepSeq (NFData, rnf)
import Data.Maybe (catMaybes, maybeToList, isJust, fromJust, fromMaybe)
import Data.List (find, nub)
import Data.Word (Word64)
import Data.Conduit (Sink, await, ($$))
import Data.Conduit.List (sourceList)
import Data.ByteString (ByteString)
import qualified Data.ByteString as BS (length, replicate, empty, null)
import Data.String.Conversions (cs)
import Data.Aeson
( Value (Object)
, FromJSON
, ToJSON
, (.=), (.:), (.:?)
, object
, parseJSON
, toJSON
)
import Network.Haskoin.Util
import Network.Haskoin.Crypto
import Network.Haskoin.Node.Types
import Network.Haskoin.Script
import Network.Haskoin.Transaction.Types
class Coin c where
coinValue :: c -> Word64
chooseCoins :: Coin c
=> Word64
-> Word64
-> Bool
-> [c]
-> Either String ([c], Word64)
chooseCoins target kbfee continue coins =
runIdentity $ sourceList coins $$ chooseCoinsSink target kbfee continue
chooseCoinsSink :: (Monad m, Coin c)
=> Word64
-> Word64
-> Bool
-> Sink c m (Either String ([c], Word64))
chooseCoinsSink target kbfee continue
| target > 0 =
maybeToEither err <$> greedyAddSink target (getFee kbfee) continue
| otherwise = return $ Left "chooseCoins: Target must be > 0"
where
err = "chooseCoins: No solution found"
chooseMSCoins :: Coin c
=> Word64
-> Word64
-> (Int, Int)
-> Bool
-> [c]
-> Either String ([c], Word64)
chooseMSCoins target kbfee ms continue coins =
runIdentity $ sourceList coins $$ chooseMSCoinsSink target kbfee ms continue
chooseMSCoinsSink :: (Monad m, Coin c)
=> Word64
-> Word64
-> (Int, Int)
-> Bool
-> Sink c m (Either String ([c], Word64))
chooseMSCoinsSink target kbfee ms continue
| target > 0 =
maybeToEither err <$> greedyAddSink target (getMSFee kbfee ms) continue
| otherwise = return $ Left "chooseMSCoins: Target must be > 0"
where
err = "chooseMSCoins: No solution found"
greedyAddSink :: (Monad m, Coin c)
=> Word64
-> (Int -> Word64)
-> Bool
-> Sink c m (Maybe ([c], Word64))
greedyAddSink target fee continue =
go [] 0 [] 0
where
goal c = target + fee c
go acc aTot ps pTot = await >>= \coinM -> case coinM of
Just coin -> do
let val = coinValue coin
if val + aTot >= (goal $ length acc + 1)
then if continue
then if pTot == 0 || val + aTot < pTot
then go [] 0 (coin:acc) (val + aTot)
else return $ Just (ps, pTot (goal $ length ps))
else return $
Just (coin:acc, val + aTot (goal $ length acc + 1))
else go (coin:acc) (val + aTot) ps pTot
Nothing ->
return $ if null ps
then Nothing
else Just (ps, pTot (goal $ length ps))
getFee :: Word64 -> Int -> Word64
getFee kbfee count =
kbfee*((len + 999) `div` 1000)
where
len = fromIntegral $ guessTxSize count [] 2 0
getMSFee :: Word64 -> (Int, Int) -> Int -> Word64
getMSFee kbfee ms count =
kbfee*((len + 999) `div` 1000)
where
len = fromIntegral $ guessTxSize 0 (replicate count ms) 2 0
guessTxSize :: Int
-> [(Int,Int)]
-> Int
-> Int
-> Int
guessTxSize pki msi pkout msout =
8 + inpLen + inp + outLen + out
where
inpLen = BS.length $ encode' $ VarInt $ fromIntegral $ (length msi) + pki
outLen = BS.length $ encode' $ VarInt $ fromIntegral $ pkout + msout
inp = pki*148 + (sum $ map guessMSSize msi)
out = pkout*34 +
msout*32
guessMSSize :: (Int,Int) -> Int
guessMSSize (m,n) =
40 + (BS.length $ encode' $ VarInt $ fromIntegral scp) + scp
where
rdm = BS.length $ encode' $ opPushData $ BS.replicate (n*34 + 3) 0
scp = rdm + m*73 + 1
buildAddrTx :: [OutPoint] -> [(ByteString, Word64)] -> Either String Tx
buildAddrTx xs ys =
buildTx xs =<< mapM f ys
where
f (s, v) = case base58ToAddr s of
Just a@(PubKeyAddress _) -> return (PayPKHash a,v)
Just a@(ScriptAddress _) -> return (PayScriptHash a,v)
_ -> Left $ "buildAddrTx: Invalid address " ++ cs s
buildTx :: [OutPoint] -> [(ScriptOutput, Word64)] -> Either String Tx
buildTx xs ys =
mapM fo ys >>= \os -> return $ Tx 1 (map fi xs) os 0
where
fi outPoint = TxIn outPoint BS.empty maxBound
fo (o, v)
| v <= 2100000000000000 = return $ TxOut v $ encodeOutputBS o
| otherwise =
Left $ "buildTx: Invalid amount " ++ show v
data SigInput = SigInput
{ sigDataOut :: !ScriptOutput
, sigDataOP :: !OutPoint
, sigDataSH :: !SigHash
, sigDataRedeem :: !(Maybe RedeemScript)
} deriving (Eq, Read, Show)
instance NFData SigInput where
rnf (SigInput o p h b) = rnf o `seq` rnf p `seq` rnf h `seq` rnf b
instance ToJSON SigInput where
toJSON (SigInput so op sh rdm) = object $
[ "pkscript" .= so
, "outpoint" .= op
, "sighash" .= sh
] ++ [ "redeem" .= r | r <- maybeToList rdm ]
instance FromJSON SigInput where
parseJSON (Object o) = do
so <- o .: "pkscript"
op <- o .: "outpoint"
sh <- o .: "sighash"
rdm <- o .:? "redeem"
return $ SigInput so op sh rdm
parseJSON _ = mzero
signTx :: Tx
-> [SigInput]
-> [PrvKey]
-> Either String Tx
signTx otx@(Tx _ ti _ _) sigis allKeys
| null ti = Left "signTx: Transaction has no inputs"
| otherwise = foldM go otx $ findSigInput sigis ti
where
go tx (sigi@(SigInput so _ _ rdmM), i) = do
keys <- sigKeys so rdmM allKeys
foldM (\t k -> signInput t i sigi k) tx keys
signInput :: Tx -> Int -> SigInput -> PrvKey -> Either String Tx
signInput tx i (SigInput so _ sh rdmM) key = do
let sig = TxSignature (signMsg msg key) sh
si <- buildInput tx i so rdmM sig $ derivePubKey key
return tx{ txIn = updateIndex i (txIn tx) (f si) }
where
f si x = x{ scriptInput = encodeInputBS si }
msg = txSigHash tx (encodeOutput $ fromMaybe so rdmM) i sh
findSigInput :: [SigInput] -> [TxIn] -> [(SigInput, Int)]
findSigInput si ti =
catMaybes $ map g $ zip (matchTemplate si ti f) [0..]
where
f s txin = sigDataOP s == prevOutput txin
g (Just s, i) = Just (s,i)
g (Nothing, _) = Nothing
sigKeys :: ScriptOutput -> (Maybe RedeemScript) -> [PrvKey]
-> Either String [PrvKey]
sigKeys so rdmM keys = do
case (so, rdmM) of
(PayPK p, Nothing) -> return $
map fst $ maybeToList $ find ((== p) . snd) zipKeys
(PayPKHash a, Nothing) -> return $
map fst $ maybeToList $ find ((== a) . pubKeyAddr . snd) zipKeys
(PayMulSig ps r, Nothing) -> return $
map fst $ take r $ filter ((`elem` ps) . snd) zipKeys
(PayScriptHash _, Just rdm) ->
sigKeys rdm Nothing keys
_ -> Left "sigKeys: Could not decode output script"
where
zipKeys = zip keys (map derivePubKey keys)
buildInput :: Tx -> Int -> ScriptOutput -> (Maybe RedeemScript)
-> TxSignature -> PubKey -> Either String ScriptInput
buildInput tx i so rdmM sig pub = case (so, rdmM) of
(PayPK _, Nothing) ->
return $ RegularInput $ SpendPK sig
(PayPKHash _, Nothing) ->
return $ RegularInput $ SpendPKHash sig pub
(PayMulSig msPubs r, Nothing) -> do
let mSigs = take r $ catMaybes $ matchTemplate allSigs msPubs f
return $ RegularInput $ SpendMulSig mSigs
(PayScriptHash _, Just rdm) -> do
inp <- buildInput tx i rdm Nothing sig pub
return $ ScriptHashInput (getRegularInput inp) rdm
_ -> Left "buildInput: Invalid output/redeem script combination"
where
scp = scriptInput $ txIn tx !! i
allSigs = nub $ sig : case decodeInputBS scp of
Right (ScriptHashInput (SpendMulSig xs) _) -> xs
Right (RegularInput (SpendMulSig xs)) -> xs
_ -> []
out = encodeOutput so
f (TxSignature x sh) p = verifySig (txSigHash tx out i sh) x p
mergeTxs :: [Tx] -> [(ScriptOutput, OutPoint)] -> Either String Tx
mergeTxs txs os
| null txs = error "Transaction list is empty"
| length (nub emptyTxs) /= 1 = Left "Transactions do not match"
| length txs == 1 = return $ head txs
| otherwise = foldM (mergeTxInput txs) (head emptyTxs) outs
where
zipOp = zip (matchTemplate os (txIn $ head txs) f) [0..]
outs = map (first $ fst . fromJust) $ filter (isJust . fst) zipOp
f (_,o) txin = o == prevOutput txin
emptyTxs = map (\tx -> foldl clearInput tx outs) txs
clearInput tx (_, i) = tx{ txIn =
updateIndex i (txIn tx) (\ti -> ti{ scriptInput = BS.empty }) }
mergeTxInput :: [Tx] -> Tx -> (ScriptOutput, Int) -> Either String Tx
mergeTxInput txs tx (so, i) = do
let ins = map (scriptInput . (!! i) . txIn) txs
sigRes <- mapM extractSigs $ filter (not . BS.null) ins
let rdm = snd $ head sigRes
unless (all (== rdm) $ map snd sigRes) $
Left "Redeem scripts do not match"
si <- encodeInputBS <$> go (nub $ concat $ map fst sigRes) so rdm
return tx{ txIn = updateIndex i (txIn tx) (\ti -> ti{ scriptInput = si }) }
where
go allSigs out rdmM = case out of
PayMulSig msPubs r ->
let sigs = take r $ catMaybes $ matchTemplate allSigs msPubs $ f out
in return $ RegularInput $ SpendMulSig sigs
PayScriptHash _ -> case rdmM of
Just rdm -> do
si <- go allSigs rdm Nothing
return $ ScriptHashInput (getRegularInput si) rdm
_ -> Left "Invalid output script type"
_ -> Left "Invalid output script type"
extractSigs si = case decodeInputBS si of
Right (RegularInput (SpendMulSig sigs)) -> Right (sigs, Nothing)
Right (ScriptHashInput (SpendMulSig sigs) rdm) -> Right (sigs, Just rdm)
_ -> Left "Invalid script input type"
f out (TxSignature x sh) p =
verifySig (txSigHash tx (encodeOutput out) i sh) x p
verifyStdTx :: Tx -> [(ScriptOutput, OutPoint)] -> Bool
verifyStdTx tx xs =
all go $ zip (matchTemplate xs (txIn tx) f) [0..]
where
f (_,o) txin = o == prevOutput txin
go (Just (so,_), i) = verifyStdInput tx i so
go _ = False
verifyStdInput :: Tx -> Int -> ScriptOutput -> Bool
verifyStdInput tx i so' =
go (scriptInput $ txIn tx !! i) so'
where
go inp so = case decodeInputBS inp of
Right (RegularInput (SpendPK (TxSignature sig sh))) ->
let pub = getOutputPubKey so
in verifySig (txSigHash tx out i sh) sig pub
Right (RegularInput (SpendPKHash (TxSignature sig sh) pub)) ->
let a = getOutputAddress so
in pubKeyAddr pub == a &&
verifySig (txSigHash tx out i sh) sig pub
Right (RegularInput (SpendMulSig sigs)) ->
let pubs = getOutputMulSigKeys so
r = getOutputMulSigRequired so
in countMulSig tx out i pubs sigs == r
Right (ScriptHashInput si rdm) ->
scriptAddr rdm == getOutputAddress so &&
go (encodeInputBS $ RegularInput si) rdm
_ -> False
where
out = encodeOutput so
countMulSig :: Tx -> Script -> Int -> [PubKey] -> [TxSignature] -> Int
countMulSig _ _ _ [] _ = 0
countMulSig _ _ _ _ [] = 0
countMulSig tx out i (pub:pubs) sigs@(TxSignature sig sh:rest)
| verifySig (txSigHash tx out i sh) sig pub =
1 + countMulSig tx out i pubs rest
| otherwise = countMulSig tx out i pubs sigs