{-# LANGUAGE OverloadedStrings #-}
{-|
Module      : Haskoin.Transaction.Genesis
Copyright   : No rights reserved
License     : UNLICENSE
Maintainer  : jprupp@protonmail.ch
Stability   : experimental
Portability : POSIX

Code related to transactions parsing and serialization.
-}
module Haskoin.Transaction.Genesis
    ( genesisTx
    ) where

import           Data.String                (fromString)
import           Haskoin.Script.Standard
import           Haskoin.Transaction.Common
import           Haskoin.Util

-- | Transaction from Genesis block.
genesisTx :: Tx
genesisTx :: Tx
genesisTx =
    Word32 -> [TxIn] -> [TxOut] -> WitnessData -> Word32 -> Tx
Tx 1 [TxIn
txin] [TxOut
txout] [] Word32
locktime
  where
    txin :: TxIn
txin = OutPoint -> ByteString -> Word32 -> TxIn
TxIn OutPoint
outpoint ByteString
inputBS Word32
forall a. Bounded a => a
maxBound
    txout :: TxOut
txout = Word64 -> ByteString -> TxOut
TxOut 5000000000 (ScriptOutput -> ByteString
encodeOutputBS ScriptOutput
output)
    locktime :: Word32
locktime = 0
    outpoint :: OutPoint
outpoint = TxHash -> Word32 -> OutPoint
OutPoint TxHash
z Word32
forall a. Bounded a => a
maxBound
    Just inputBS :: ByteString
inputBS = Text -> Maybe ByteString
decodeHex (Text -> Maybe ByteString) -> Text -> Maybe ByteString
forall a b. (a -> b) -> a -> b
$ String -> Text
forall a. IsString a => String -> a
fromString (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$
        "04ffff001d0104455468652054696d65732030332f4a616e2f323030392043686" String -> String -> String
forall a. [a] -> [a] -> [a]
++
        "16e63656c6c6f72206f6e206272696e6b206f66207365636f6e64206261696c6f" String -> String -> String
forall a. [a] -> [a] -> [a]
++
        "757420666f722062616e6b73"
    output :: ScriptOutput
output = PubKeyI -> ScriptOutput
PayPK (PubKeyI -> ScriptOutput) -> PubKeyI -> ScriptOutput
forall a b. (a -> b) -> a -> b
$ String -> PubKeyI
forall a. IsString a => String -> a
fromString (String -> PubKeyI) -> String -> PubKeyI
forall a b. (a -> b) -> a -> b
$
        "04678afdb0fe5548271967f1a67130b7105cd6a828e03909a67962e0ea1f61deb" String -> String -> String
forall a. [a] -> [a] -> [a]
++
        "649f6bc3f4cef38c4f35504e51ec112de5c384df7ba0b8d578a4c702b6bf11d5f"
    z :: TxHash
z = "0000000000000000000000000000000000000000000000000000000000000000"