Skip to content

Commit

Permalink
Add stub cardano-wallet-jormungandr
Browse files Browse the repository at this point in the history
  • Loading branch information
Anviking committed May 8, 2019
1 parent 05e8a37 commit df0948e
Show file tree
Hide file tree
Showing 12 changed files with 383 additions and 0 deletions.
10 changes: 10 additions & 0 deletions .weeder.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -34,3 +34,13 @@
- name: Module not compiled
- module: Cardano.Launcher.Windows

- package:
- name: cardano-wallet-jormungandr
- section:
- name: test:unit
- message:
- name: Weeds exported
- module:
- name: Spec
- identifier: main

1 change: 1 addition & 0 deletions lib/jormungandr/LICENSE
1 change: 1 addition & 0 deletions lib/jormungandr/README.md
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
# Jörmungandr
81 changes: 81 additions & 0 deletions lib/jormungandr/cardano-wallet-jormungandr.cabal
Original file line number Diff line number Diff line change
@@ -0,0 +1,81 @@
name: cardano-wallet-jormungandr
version: 2019.5.8
synopsis: Wallet backend protocol-specific bits implemented using Jörmungandr
description: Please see README.md
homepage: https://github.com/input-output-hk/cardano-wallet
author: IOHK Engineering Team
maintainer: [email protected]
copyright: 2019 IOHK
license: MIT
license-file: LICENSE
category: Web
build-type: Simple
extra-source-files: README.md
cabal-version: >=1.10

flag development
description: Disable `-Werror`
default: False
manual: True

library
default-language:
Haskell2010
default-extensions:
NoImplicitPrelude
OverloadedStrings
ghc-options:
-Wall
-Wcompat
-fwarn-redundant-constraints
if (!flag(development))
ghc-options:
-Werror
build-depends:
base
, cardano-wallet-core
, fmt
-- , binary
-- , bytestring
-- , cardano-crypto
-- , cryptonite
-- , digest
, text
, text-class
hs-source-dirs:
src
exposed-modules:
Cardano.Environment
Cardano.Wallet.Binary.Jormungandr
Cardano.Wallet.Compatibility.Jormungandr
Cardano.Wallet.Transaction.Jormungandr

test-suite unit
default-language:
Haskell2010
default-extensions:
NoImplicitPrelude
OverloadedStrings
ghc-options:
-threaded -rtsopts
-Wall
-O2
if (!flag(development))
ghc-options:
-Werror
build-depends:
base
, bytestring
, cardano-wallet-core
, cardano-wallet-jormungandr
, memory
, hspec
type:
exitcode-stdio-1.0
hs-source-dirs:
test/unit
main-is:
Main.hs
other-modules:
Cardano.Wallet.Binary.JormungandrSpec
Spec
166 changes: 166 additions & 0 deletions lib/jormungandr/src/Cardano/Environment.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,166 @@
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE TypeApplications #-}

-- |
-- Copyright: © 2018-2019 IOHK
-- License: MIT
--
-- This module contains static configuration parameters. Rather than providing
-- and carrying around a configuration file through the application, we resolve
-- configuration data at runtime using the available environment.
--
-- This gives us a flexible and portable approach to software configuration, and
-- remove some pain from the development perspective. Prior to starting, the
-- wallet is expected to have a few configuration parameter available. One may
-- rely on a `.env` file to bundle configuration settings together for a given
-- target environment.

module Cardano.Environment
(
-- * Networking
Network(..)
, network
, ProtocolMagic(..)
, protocolMagic

-- * Internals
, ErrMissingOrInvalidEnvVar(..)
, unsafeLookupEnv
) where

import Prelude

import Control.Exception
( Exception (..), throwIO )
import Data.Int
( Int32 )
import Data.Text
( Text )
import Data.Text.Class
( FromText (..), TextDecodingError (..), ToText (..) )
import Fmt
( Buildable (..), nameF, padLeftF, pretty )
import GHC.Generics
( Generic )
import System.Environment
( getProgName, lookupEnv )
import System.IO.Unsafe
( unsafePerformIO )

import qualified Data.Text as T


-- | Fatal exception thrown when a required ENV var is missing upon start-up.
data ErrMissingOrInvalidEnvVar = ErrMissingOrInvalidEnvVar
{ name :: String
, command :: String
, additionalContext :: Maybe (String, TextDecodingError)
}

instance Show ErrMissingOrInvalidEnvVar where
show = displayException

-- | Produces a nice terminal output so that the error is very readable.
--
-- @
-- $ NETWORK=patate cardano-wallet-launcher
-- Starting...
-- cardano-wallet-launcher: Missing or invalid ENV var:
--
-- ENV[NETWORK] = patate
-- |
-- |
-- *--> patate is neither "mainnet", "testnet" nor "staging"
--
-- @
--
-- @
-- $ cardano-wallet-launcher
-- Starting...
-- cardano-wallet-launcher: Missing or invalid ENV var:
--
-- ENV[NETWORK] = ?
--
-- What about trying to provide a valid ENV var `NETWORK=value cardano-wallet-launcher` ?
-- @
instance Exception ErrMissingOrInvalidEnvVar where
displayException (ErrMissingOrInvalidEnvVar n cmd ctx) = pretty $ mempty
<> nameF "Missing or invalid ENV var"
( "\n ENV[" <> build n <> "] = " <> ctxF )
where
ctxF = case ctx of
Nothing -> "?"
<> "\n\nWhat about trying to provide a valid ENV var "
<> "`" <> build n <> "=value " <> build cmd <> "` ?"
Just (v, err) ->
let
pad = length n + (length v `div` 2) + 11
in
build v
<> "\n " <> padLeftF @Text pad ' ' "| "
<> "\n " <> padLeftF @Text pad ' ' "| "
<> "\n " <> padLeftF @Text pad ' ' "*--> "
<> build err

-- | Lookup the environment for a given variable
unsafeLookupEnv
:: FromText a
=> String
-> a
unsafeLookupEnv k = unsafePerformIO $ do
cmd <- getProgName
v <- lookupEnv k >>= \case
Just v -> return v
Nothing -> throwIO $ ErrMissingOrInvalidEnvVar
{ name = k
, command = cmd
, additionalContext = Nothing
}
case fromText (T.pack v) of
Right a -> return a
Left err -> throwIO $ ErrMissingOrInvalidEnvVar
{ name = k
, command = cmd
, additionalContext = Just (v, err)
}

{-------------------------------------------------------------------------------
Environment
-------------------------------------------------------------------------------}

-- | Available network options.
data Network = Mainnet | Testnet | Staging
deriving (Generic, Show, Eq, Enum)

instance FromText Network where
fromText = \case
"mainnet" -> Right Mainnet
"testnet" -> Right Testnet
"staging" -> Right Staging
s -> Left $ TextDecodingError $ T.unpack s
<> " is neither \"mainnet\", \"testnet\" nor \"staging\"."

instance ToText Network where
toText = \case
Mainnet -> "mainnet"
Testnet -> "testnet"
Staging -> "staging"

-- | Get the current target 'Network' from the Environment.
--
-- Throws a runtime exception is the ENV var isn't set or, is invalid.
network :: Network
network =
unsafeLookupEnv "NETWORK"
{-# NOINLINE network #-}

newtype ProtocolMagic = ProtocolMagic Int32
deriving (Generic, Show)

-- | Get the 'ProtocolMagic' corresponding to a given 'Network'.
protocolMagic :: Network -> ProtocolMagic
protocolMagic = \case
Mainnet -> ProtocolMagic 764824073
Staging -> ProtocolMagic 633343913
Testnet -> ProtocolMagic 1097911063
12 changes: 12 additions & 0 deletions lib/jormungandr/src/Cardano/Wallet/Binary/Jormungandr.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,12 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE RankNTypes #-}

-- |
-- Copyright: © 2018-2019 IOHK
-- License: MIT
--
-- The format is for the Shelley era as implemented by the Jörmungandr node.

module Cardano.Wallet.Binary.Jormungandr
(
) where
30 changes: 30 additions & 0 deletions lib/jormungandr/src/Cardano/Wallet/Compatibility/Jormungandr.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,30 @@
-- |
-- Copyright: © 2018-2019 IOHK
-- License: MIT
--
-- Contains various implementation decision that are specific to a particular
-- network / protocol. This allows us to easily select a particular backend
-- (Byron, Shelley-Rust, Shelley-Haskell) and isolate the bits that vary between
-- those backends.

module Cardano.Wallet.Compatibility.Jormungandr
( -- * Target
Jormungandr
) where

import Prelude

import Cardano.Wallet.Primitive.AddressDerivation
( KeyToAddress (..) )
import Cardano.Wallet.Primitive.Types
( TxId (..) )

-- | A type representing the Jormungandr as a network target. This has an
-- influence on binary serializer & network primitives. See also 'TxId'
data Jormungandr

instance TxId Jormungandr where
txId = undefined

instance KeyToAddress Jormungandr where
keyToAddress = undefined
19 changes: 19 additions & 0 deletions lib/jormungandr/src/Cardano/Wallet/Transaction/Jormungandr.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,19 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE RankNTypes #-}

module Cardano.Wallet.Transaction.Jormungandr
( newTransactionLayer
) where

import Prelude

import Cardano.Wallet.Transaction
( TransactionLayer (..) )


-- | Construct a 'TransactionLayer' compatible with Shelley and 'Jörmungandr'
newTransactionLayer :: TransactionLayer
newTransactionLayer = TransactionLayer
{ mkStdTx = error "TODO: See http-bridge as starting point"
, estimateSize = error "TODO: See http-bridge as starting point"
}
45 changes: 45 additions & 0 deletions lib/jormungandr/test/unit/Cardano/Wallet/Binary/JormungandrSpec.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,45 @@
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeApplications #-}

module Cardano.Wallet.Binary.JormungandrSpec
( spec
) where

import Prelude

import Cardano.Wallet.Binary.Jormungandr
()
import Data.ByteString
( ByteString )

import Cardano.Wallet.Primitive.Types
( BlockHeader (..), Hash (..), SlotId (..) )

import Data.ByteArray.Encoding
( Base (Base16), convertFromBase )
import Test.Hspec
( Spec, describe, shouldBe, xit )

{-# ANN spec ("HLint: ignore Use head" :: String) #-}
spec :: Spec
spec = do
describe "Decoding blocks" $ do
xit "should decode a genesis block" $ do
unsafeDeserialiseFromBytes decodeGenesisBlock genesisBlock
`shouldBe`
BlockHeader (SlotId 0 0) (Hash "?")
where
unsafeDeserialiseFromBytes = undefined
decodeGenesisBlock = error "TODO: import from Binary.Jormungandr"

genesisBlock :: ByteString
genesisBlock = either error id $ convertFromBase @ByteString Base16
"005200000000009f000000000000000000000000ffadebfecd59d9eaa12e903a\
\d58100f7c1e35899739c3d05d022835c069d2b4f000000000000000000000000\
\00000000000000000000000000000000000000000047000048000000005cc1c2\
\4900810200c200010108000000000000087001410f01840000000a01e030a694\
\b80dbba2d1b8a4b55652b03d96315c8414b054fa737445ac2d2a865c76002604\
\0001000000ff0005000006000000000000000000000000000000000000000000\
\0000000000002c020001833324c37869c122689a35917df53a4f2294a3a52f68\
\5e05f5f8e53b87e7ea452f000000000000000e"
16 changes: 16 additions & 0 deletions lib/jormungandr/test/unit/Main.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,16 @@
module Main where

import Prelude

import Cardano.Environment
( network )
import Test.Hspec.Runner
( hspecWith )

import qualified Spec
import qualified Test.Hspec.Runner as Hspec

main :: IO ()
main = do
network `seq` (return ())
hspecWith Hspec.defaultConfig Spec.spec
1 change: 1 addition & 0 deletions lib/jormungandr/test/unit/Spec.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
{-# OPTIONS_GHC -F -pgmF hspec-discover -optF --module-name=Spec #-}
Loading

0 comments on commit df0948e

Please sign in to comment.