Skip to content

Commit

Permalink
Merge pull request #5 from f-o-a-m/json-instances
Browse files Browse the repository at this point in the history
Add Json Instances and make BigNumber consistent
  • Loading branch information
martyall committed May 9, 2018
2 parents 588ae1a + f4f19a2 commit 2192006
Show file tree
Hide file tree
Showing 7 changed files with 137 additions and 31 deletions.
9 changes: 5 additions & 4 deletions bower.json
Expand Up @@ -19,16 +19,17 @@
],
"dependencies": {
"purescript-prelude": "^3.3.0",
"purescript-console": "^3.0.0",
"purescript-modules": "^3.0.0",
"purescript-foreign": "^4.0.1",
"purescript-simple-json": "^3.0.0",
"purescript-sets": "^3.2.0",
"purescript-bytestrings": "^6.0.0",
"purescript-spec": "^2.0.0",
"purescript-debug": "^3.0.0"
"purescript-simple-json": "^3.0.0",
"purescript-argonaut": "^3.1.0"
},
"devDependencies": {
"purescript-psci-support": "^3.0.0"
"purescript-psci-support": "^3.0.0",
"purescript-spec": "^2.0.0",
"purescript-debug": "^3.0.0"
}
}
13 changes: 1 addition & 12 deletions src/Network/Ethereum/Core/BigNumber.js
Expand Up @@ -49,7 +49,7 @@ exports.fromStringAsImpl = function (just) {
} else {
result = new BigNumber(s, radix);
}
} catch (e) {
} catch (_) {
return nothing;
}
return just(result);
Expand Down Expand Up @@ -102,14 +102,3 @@ var isString = function (object) {
return typeof object === 'string' ||
(object && object.constructor && object.constructor.name === 'String');
};

exports.toBigNumber = function(number) {
if (isBigNumber(number))
return number;

if (isString(number) && (number.indexOf('0x') === 0 || number.indexOf('-0x') === 0)) {
return new BigNumber(number.replace('0x',''), 16);
}

return new BigNumber(number.toString(10), 10);
};
31 changes: 26 additions & 5 deletions src/Network/Ethereum/Core/BigNumber.purs
Expand Up @@ -12,12 +12,14 @@ module Network.Ethereum.Core.BigNumber

import Prelude

import Data.Foreign (Foreign)
import Data.Argonaut as A
import Data.Either (Either(..), either)
import Data.Foreign (ForeignError(..), readString, fail)
import Data.Foreign.Class (class Decode, class Encode, decode, encode)
import Data.Int (Radix, binary, decimal, hexadecimal, floor) as Int
import Data.Maybe (Maybe(..))
import Data.Module (class LeftModule, class RightModule)
import Simple.JSON (class ReadForeign)
import Simple.JSON (class ReadForeign, class WriteForeign)

--------------------------------------------------------------------------------
-- * BigNumber
Expand Down Expand Up @@ -119,13 +121,32 @@ unsafeToInt = Int.floor <<< toNumber
-- | Take the integer part of a big number
foreign import floorBigNumber :: BigNumber -> BigNumber

foreign import toBigNumber :: Foreign -> BigNumber
_encode :: BigNumber -> String
_encode = (append "0x") <<< toString Int.hexadecimal

_decode :: String -> Either String BigNumber
_decode str = case parseBigNumber Int.hexadecimal str of
Nothing -> Left $ "Failed to parse as BigNumber: " <> str
Just n -> Right n

instance decodeBigNumber :: Decode BigNumber where
decode = pure <<< toBigNumber
decode x = do
str <- readString x
either (fail <<< ForeignError) pure $ _decode str

instance readFBigNumber :: ReadForeign BigNumber where
readImpl = decode

instance writeFBigNumber :: WriteForeign BigNumber where
writeImpl = encode

instance encodeBigNumber :: Encode BigNumber where
encode = encode <<< (append "0x") <<< toString Int.hexadecimal
encode = encode <<< _encode

instance decodeJsonBigNumber :: A.DecodeJson BigNumber where
decodeJson json = do
str <- A.decodeJson json
_decode str

instance encodeJsonBigNumber :: A.EncodeJson BigNumber where
encodeJson = A.encodeJson <<< _encode
30 changes: 25 additions & 5 deletions src/Network/Ethereum/Core/HexString.purs
Expand Up @@ -28,8 +28,11 @@ module Network.Ethereum.Core.HexString

import Prelude

import Data.Argonaut as A
import Data.Array (uncons, unsafeIndex, replicate)
import Data.ByteString (ByteString, toString, fromString) as BS
import Data.Either (Either(..), either)
import Data.Foreign (ForeignError(..), fail)
import Data.Foreign.Class (class Decode, class Encode, decode, encode)
import Data.Int (even)
import Data.Maybe (Maybe(..), fromJust, isJust)
Expand All @@ -40,7 +43,7 @@ import Data.String as S
import Network.Ethereum.Core.BigNumber (BigNumber, toString, hexadecimal)
import Node.Encoding (Encoding(Hex, UTF8, ASCII))
import Partial.Unsafe (unsafePartial)
import Simple.JSON (class ReadForeign)
import Simple.JSON (class ReadForeign, class WriteForeign)

--------------------------------------------------------------------------------
-- * Signed Values
Expand Down Expand Up @@ -87,18 +90,35 @@ derive newtype instance hexStringOrd :: Ord HexString
derive newtype instance semigpStringEq :: Semigroup HexString
derive newtype instance monoidStringEq :: Monoid HexString

_encode :: HexString -> String
_encode = append "0x" <<< unHex

_decode :: String -> Either String HexString
_decode str = case mkHexString str of
Just res -> Right res
Nothing -> Left $ "Failed to parse as HexString: " <> str

instance decodeHexString :: Decode HexString where
decode s = do
str <- decode s
case stripPrefix (Pattern "0x") str of
Nothing -> pure <<< HexString $ str
Just res -> pure <<< HexString $ res
either (fail <<< ForeignError) pure $ _decode str

instance readFHexString :: ReadForeign HexString where
readImpl = decode

instance writeFHexString :: WriteForeign HexString where
writeImpl = encode

instance encodeHexString :: Encode HexString where
encode = encode <<< append "0x" <<< unHex
encode = encode <<< _encode

instance decodeJsonHexString :: A.DecodeJson HexString where
decodeJson json = do
str <- A.decodeJson json
_decode str

instance encodeJsonHexString :: A.EncodeJson HexString where
encodeJson = A.encodeJson <<< _encode

unHex :: HexString -> String
unHex (HexString hx) = hx
Expand Down
31 changes: 29 additions & 2 deletions src/Network/Ethereum/Core/Signatures.purs
Expand Up @@ -21,15 +21,19 @@ module Network.Ethereum.Core.Signatures

import Prelude

import Data.Argonaut as A
import Data.ByteString as BS
import Data.Either (Either(..), either)
import Data.Function.Uncurried (Fn2, Fn3, runFn2, runFn3)
import Data.Maybe (Maybe(..), fromJust)
import Data.Foreign.Class (class Decode, class Encode)
import Data.Foreign (ForeignError(..), fail)
import Data.Foreign.Class (class Decode, class Encode, decode, encode)
import Data.Generic.Rep (class Generic)
import Data.Generic.Rep.Show (genericShow)
import Network.Ethereum.Core.HexString (HexString, dropHex, hexLength, toByteString, fromByteString)
import Network.Ethereum.Core.Keccak256 (keccak256)
import Partial.Unsafe (unsafePartial)
import Simple.JSON (class ReadForeign, class WriteForeign)

-- | Opaque PrivateKey type
newtype PrivateKey = PrivateKey BS.ByteString
Expand Down Expand Up @@ -98,9 +102,32 @@ newtype Address = Address HexString
derive newtype instance addressShow :: Show Address
derive newtype instance addressEq :: Eq Address
derive newtype instance addressOrd :: Ord Address
derive newtype instance decodeAddress :: Decode Address
derive newtype instance encodeAddress :: Encode Address

_decode :: HexString -> Either String Address
_decode hx = case mkAddress hx of
Nothing -> Left $ "Address must be 20 bytes long: " <> show hx
Just res -> Right res

instance decodeAddress :: Decode Address where
decode a = do
hxString <- decode a
either (fail <<< ForeignError) pure $ _decode hxString

instance decodeJsonAddress :: A.DecodeJson Address where
decodeJson json = do
hxString <- A.decodeJson json
_decode hxString

instance encodeJsonAddress :: A.EncodeJson Address where
encodeJson = A.encodeJson <<< unAddress

instance readFAddress :: ReadForeign Address where
readImpl = decode

instance writeFAddress :: WriteForeign Address where
writeImpl = encode

unAddress :: Address -> HexString
unAddress (Address a) = a

Expand Down
25 changes: 23 additions & 2 deletions test/Spec/BigNumber.purs
Expand Up @@ -2,10 +2,19 @@ module CoreSpec.BigNumber (bigNumberSpec) where


import Prelude
import Data.Maybe (Maybe(Just))

import Control.Monad.Except (runExcept)
import Data.Argonaut as A
import Data.Either (Either(..), fromRight)
import Data.Foreign (toForeign)
import Data.Foreign.Class (decode, encode)
import Data.Maybe (Maybe(Just), fromJust)
import Network.Ethereum.Core.BigNumber (BigNumber, decimal, embed, hexadecimal, parseBigNumber)
import Partial.Unsafe (unsafePartial)
import Simple.JSON (readImpl)
import Test.Spec (Spec, describe, it)
import Test.Spec.Assertions (shouldEqual)
import Network.Ethereum.Core.BigNumber (BigNumber, decimal, embed, hexadecimal, parseBigNumber)


bigNumberSpec :: forall r . Spec r Unit
bigNumberSpec = describe "BigNumber-spec" do
Expand Down Expand Up @@ -47,3 +56,15 @@ bigNumberSpec = describe "BigNumber-spec" do
((parseBigNumber decimal "21") >>= \x -> pure $ x - zero) `shouldEqual` parseBigNumber hexadecimal "0x15"
(Just $ one `mul` one) `shouldEqual` parseBigNumber decimal "1"
(Just $ one * embed (-7)) `shouldEqual` parseBigNumber hexadecimal "-0x7"

it "can handle deserialization" do
let bnString = "f43"
d1 = unsafePartial $ fromRight $ runExcept $ readImpl (toForeign bnString)
d2 = unsafePartial $ fromRight $ runExcept $ decode (toForeign bnString)
d3 = unsafePartial $ fromRight $ A.decodeJson (A.fromString bnString)
d4 = unsafePartial $ fromJust $ parseBigNumber hexadecimal bnString
d4 `shouldEqual` d1
d4 `shouldEqual` d2
d4 `shouldEqual` d3
runExcept (decode (encode d1)) `shouldEqual` Right d4
(A.decodeJson (A.encodeJson d1)) `shouldEqual` Right d4
29 changes: 28 additions & 1 deletion test/Spec/Hex.purs
Expand Up @@ -2,11 +2,17 @@ module CoreSpec.Hex (hexSpec) where

import Prelude

import Control.Monad.Except (runExcept)
import Data.Argonaut as A
import Data.ByteString as BS
import Data.Either (Either(..), fromRight)
import Data.Foreign (toForeign)
import Data.Foreign.Class (encode, decode)
import Data.Maybe (Maybe(Just), fromJust)
import Network.Ethereum.Core.HexString (mkHexString, toByteString, toUtf8, toAscii, fromUtf8, fromAscii)
import Network.Ethereum.Core.HexString (HexString, mkHexString, toByteString, toUtf8, toAscii, fromUtf8, fromAscii)
import Node.Encoding (Encoding(Hex))
import Partial.Unsafe (unsafePartial)
import Simple.JSON (readImpl)
import Test.Spec (Spec, describe, it)
import Test.Spec.Assertions (shouldEqual)

Expand Down Expand Up @@ -46,3 +52,24 @@ hexSpec = describe "hex-spec" do
it "can convert asci to hex" do
fromAscii "myString" `shouldEqual` unsafePartial (fromJust <<< mkHexString) "6d79537472696e67"
fromAscii "myString\00" `shouldEqual` unsafePartial (fromJust <<< mkHexString) "6d79537472696e6700"

describe "json tests" do

it "can convert hex strings to and from json" do

let hx = (unsafePartial (fromJust <<< mkHexString) "0x6d79537472696e67")
hxJson = A.fromString "0x6d79537472696e67"
(A.encodeJson <$> (A.decodeJson hxJson :: Either String HexString)) `shouldEqual` Right hxJson
A.decodeJson (A.encodeJson hx) `shouldEqual` Right hx

it "can handle deserialization" do
let hxString = "0f43"
d1 = unsafePartial $ fromRight $ runExcept $ readImpl (toForeign hxString)
d2 = unsafePartial $ fromRight $ runExcept $ decode (toForeign hxString)
d3 = unsafePartial $ fromRight $ A.decodeJson (A.fromString hxString)
d4 = unsafePartial $ fromJust $ mkHexString hxString
d4 `shouldEqual` d1
d4 `shouldEqual` d2
d4 `shouldEqual` d3
runExcept (decode (encode d1)) `shouldEqual` Right d4
(A.decodeJson (A.encodeJson d1)) `shouldEqual` Right d4

0 comments on commit 2192006

Please sign in to comment.