Skip to content

Commit

Permalink
Added Json Instances for TxHash and Word256. Added Tests for ToJson .…
Browse files Browse the repository at this point in the history
… FromJson = id
  • Loading branch information
sha49 authored and plaprade committed Jul 22, 2014
1 parent a4f6da8 commit e007554
Show file tree
Hide file tree
Showing 5 changed files with 75 additions and 17 deletions.
41 changes: 39 additions & 2 deletions Network/Haskoin/Crypto/BigWord.hs
Original file line number Diff line number Diff line change
Expand Up @@ -21,6 +21,8 @@ module Network.Haskoin.Crypto.BigWord
, inverseN
, quadraticResidue
, isIntegerValidKey
, encodeTxHashLE
, decodeTxHashLE
) where

import Data.Bits
Expand All @@ -45,11 +47,20 @@ import Data.Binary.Put
, putWord8
, putByteString
)
import Data.Aeson
( Value (String)
, FromJSON
, ToJSON
, parseJSON
, toJSON
, withText
)
import Control.DeepSeq (NFData, rnf)
import Control.Monad (unless, guard)
import Control.Applicative ((<$>))
import Data.Ratio (numerator, denominator)
import qualified Data.ByteString as BS (head, length)
import qualified Data.ByteString as BS (head, length, reverse)
import qualified Data.Text as T (pack, unpack)

import Network.Haskoin.Crypto.Curve
import Network.Haskoin.Crypto.NumberTheory
Expand Down Expand Up @@ -314,7 +325,23 @@ instance Binary (BigWord ModP) where

-- Section 2.3.7 http://www.secg.org/download/aid-780/sec1-v2.pdf
put r = put (fromIntegral r :: Word256)


instance ToJSON (BigWord Mod256Tx) where
toJSON = String . T.pack . encodeTxHashLE

instance FromJSON (BigWord Mod256Tx) where
parseJSON = withText "TxHash not a string: " $ \a -> do
let s = T.unpack a
maybe (fail $ "Not a TxHash: " ++ s) return $ decodeTxHashLE s

instance ToJSON (BigWord Mod256) where
toJSON = String . T.pack . bsToHex . encode'

instance FromJSON (BigWord Mod256) where
parseJSON = withText "Word256 not a string: " $ \a -> do
let s = T.unpack a
maybe (fail $ "Not a Word256: " ++ s) return $
hexToBS s >>= decodeToMaybe

-- curveP = 3 (mod 4), thus Lagrange solutions apply
-- http://en.wikipedia.org/wiki/Quadratic_residue
Expand All @@ -327,3 +354,13 @@ quadraticResidue x = guard (y^(2 :: Int) == x) >> [y, (-y)]
isIntegerValidKey :: Integer -> Bool
isIntegerValidKey i = i > 0 && i < curveN

-- | Encodes a transaction hash as little endian in HEX format.
-- This is mostly used for displaying transaction ids. Internally, these ids
-- are handled as big endian but are transformed to little endian when
-- displaying them.
encodeTxHashLE :: TxHash -> String
encodeTxHashLE = bsToHex . BS.reverse . encode'

-- | Decodes a little endian transaction hash in HEX format.
decodeTxHashLE :: String -> Maybe TxHash
decodeTxHashLE = (decodeToMaybe . BS.reverse =<<) . hexToBS
14 changes: 0 additions & 14 deletions Network/Haskoin/Crypto/Hash.hs
Original file line number Diff line number Diff line change
Expand Up @@ -29,8 +29,6 @@ module Network.Haskoin.Crypto.Hash
, txHash
, cbHash
, headerHash
, encodeTxHashLE
, decodeTxHashLE
) where

import Control.Monad (replicateM)
Expand Down Expand Up @@ -68,7 +66,6 @@ import qualified Data.ByteString as BS
, length
, replicate
, drop
, reverse
)

import Network.Haskoin.Util
Expand Down Expand Up @@ -199,17 +196,6 @@ encodeCompact i
| otherwise = (s1, c1)
c3 = fromIntegral $ c2 .|. ((toInteger s2) `shiftL` 24)

-- | Encodes a transaction hash as little endian in HEX format.
-- This is mostly used for displaying transaction ids. Internally, these ids
-- are handled as big endian but are transformed to little endian when
-- displaying them.
encodeTxHashLE :: TxHash -> String
encodeTxHashLE = bsToHex . BS.reverse . encode'

-- | Decodes a little endian transaction hash in HEX format.
decodeTxHashLE :: String -> Maybe TxHash
decodeTxHashLE = (decodeToMaybe . BS.reverse =<<) . hexToBS

-- | Computes the hash of a transaction.
txHash :: Tx -> TxHash
txHash = fromIntegral . doubleHash256 . encode'
Expand Down
1 change: 0 additions & 1 deletion Network/Haskoin/Script/Parser.hs
Original file line number Diff line number Diff line change
Expand Up @@ -47,7 +47,6 @@ import Data.Aeson
, toJSON
, withText
)

import Network.Haskoin.Util
import Network.Haskoin.Crypto.Keys
import Network.Haskoin.Crypto.Base58
Expand Down
4 changes: 4 additions & 0 deletions tests/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -39,6 +39,9 @@ import qualified Network.Haskoin.Transaction.Units (tests)
-- Stratum tests
import qualified Network.Haskoin.Stratum.Units (tests)

-- Json tests
import qualified Network.Haskoin.Json.Tests (tests)

main :: IO ()
main = defaultMain
( Network.Haskoin.Util.Tests.tests
Expand Down Expand Up @@ -66,5 +69,6 @@ main = defaultMain
++ Network.Haskoin.Transaction.Tests.tests
++ Network.Haskoin.Transaction.Units.tests
++ Network.Haskoin.Stratum.Units.tests
++ Network.Haskoin.Json.Tests.tests
)

32 changes: 32 additions & 0 deletions tests/Network/Haskoin/Json/Tests.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,32 @@
module Network.Haskoin.Json.Tests (tests) where

import Test.Framework (Test, testGroup)
import Test.Framework.Providers.QuickCheck2 (testProperty)

import Data.Aeson

import Network.Haskoin.Crypto
import Network.Haskoin.Script
import Network.Haskoin.Protocol
import Network.Haskoin.Transaction
import Network.Haskoin.Crypto.Arbitrary()
import Network.Haskoin.Script.Arbitrary()
import Network.Haskoin.Protocol.Arbitrary()
import Network.Haskoin.Transaction.Arbitrary()


tests :: [Test]
tests =
[ testGroup "Serialize & de-serialize haskoin types to JSON"
[ testProperty "Coin" (metaID :: Coin -> Bool)
, testProperty "ScriptOutput" (metaID :: ScriptOutput -> Bool)
, testProperty "OutPoint" (metaID :: OutPoint -> Bool)
, testProperty "Address" (metaID :: Address -> Bool)
, testProperty "Tx" (metaID :: Tx -> Bool)
, testProperty "TxHash" (metaID :: TxHash -> Bool)
, testProperty "Word256" (metaID :: Word256 -> Bool)
]
]

metaID :: (FromJSON a, ToJSON a, Eq a) => a -> Bool
metaID x = (decode . encode) [x] == Just [x]

0 comments on commit e007554

Please sign in to comment.