Build an ETH 1½ application in a day

FOAM

Topics

  1. Introduction
  2. Demo
  3. Outline of architecture
  4. Detailed walkthrough of the architecture components

Introduction

Kristoffer Josefsson

  • overview of the workshop
  • how to follow along
  • what is important and what isn't

Typical stack(?)

  • Define app logic in smart contracts
    • Depend on one or many services for APIs such as Infura, etherscan, etc to get events and lookups against ethereum state.
  • For every new integration
    • Find a service that allows you to connect your app
    • Hope that the API works and doesn't change
    • Write bindings..

We use the PHP stack

  • PureScript + Haskell
    • purity : no mutable state, managing effects
    • type systems : more than int ≠ bool

    • compiler-assistance : e.g. metaprogramming

  • Postgres
    • Batteries included
    • robust bindings in every language
    • can do everything (yes, also free-text search etc)

Architecture

Demo

Kristoffer Josefsson

Resources

Outline

Kristoffer Josefsson

chanterelle

a functional alternative to truffle

chanterelle

  • compiles and deploys contracts
  • generate types+bindings in PureScript
buy :: TransactionOptions MinorUnit 
    -> { _saleId :: UIntN S256 } 
    -> Web3 HexString
buy x0 r = uncurryFields r $ buy' x0
  where
    buy' :: TransactionOptions MinorUnit 
         -> (Tagged (SProxy "_saleId") (UIntN S256)) 
         -> Web3 HexString
    buy' y0 y1 = sendTx y0 ((tagged $ Tuple1 y1) :: BuyFn)

chanterelle

it "can buy signal tokens" \{ signalForSale } -> do
  let txOpts = defaultTransactionOptions # _from ?~ account2
                                         # _gas ?~ embed 8000000
      signal = unwrap signalForSale
      acc2BuyAction = SignalMarket.buy 
        (txOpts # _to ?~ signalMarket
                # _value ?~ convert (mkValue one :: Value Ether)) 
        { _saleId: signal.saleId }
      acc2BuyFilter = eventFilter (Proxy :: Proxy SignalMarket.SignalSold)
                        signalMarket
  SignalMarket.SignalSold purchase <- monitorUntil provider logger 
    acc2BuyAction acc2BuyFilter
  liftAff do
    purchase.tokenId `shouldEqual` signal.tokenId
    purchase.price `shouldEqual` originalPrice
  • generates test harness

Indexer

What does it do?

  1. Streams event logs from the Ethereum blockchain, either historical or current.
     
  2. Indexes data in a traditional database -- e.g. Postgres, Elasticsearch -- for application cache.
     
  3. Passes data downstream -- e.g. websockets, message channels, kafka.

Important Properties

  1. Should own the write access to its data stores.

  2. Should be deterministic -- running the indexer from blocks B1 to Bn should always produces the same result.


indexer

monitor :: IndexerM ()
monitor = do
  cfg <- ask
  let contracts = indexerCfgContracts cfg
      (window, _) = indexerMultiFilterOpts cfg
      signalMarketReceipt = contractsSignalMarket contracts
  (smSignalForSaleF, smSignalForSaleH) <- makeFilterHandlerPair 
    signalMarketReceipt SignalMarket.signalMarketSignalForSaleH
  (smSignalSoldF, smSignalSoldH) <- makeFilterHandlerPair 
    signalMarketReceipt SignalMarket.signalMarketSignalSoldH
  let filters  = ftTransferF
              :? smSignalForSaleF
              :? smSignalSoldF
              :? NilFilters
      handlers = ftTransferH
              :& smSignalForSaleH
              :& smSignalSoldH
              :& RNil
runWeb3 $ multiEventManyNoFilter' filters window handlers

indexer

signalMarketSignalSoldH
  :: ( MonadPG m
     , MonadThrow m )
  => Event Contract.SignalSold
  -> m ()
signalMarketSignalSoldH Event{eventEventID, eventData} = case eventData of
  Contract.SignalSold{..} -> do
    insert Sold.signalSoldTable $ Sold.SignalSold
      { Sold.saleID = signalSoldSaleId_ ^. _SaleID
      , Sold.tokenID = signalSoldTokenId_ ^. _TokenID
      , Sold.price = signalSoldPrice_ ^. _Value
      , Sold.soldFrom = signalSoldOwner_ ^. _EthAddress
      , Sold.soldTo = signalSoldNewOwner_ ^. _EthAddress }
    let updateSaleStatus a = a { ForSale.saleStatus = constant SSComplete }
        isActiveTokenID a = ForSale.saleID a 
          .== constant (signalSoldSaleId_ ^. _SaleID)
    _ :: ForSale.SignalForSale <- update ForSale.signalForSaleTable 
      updateSaleStatus isActiveTokenID
    pure ()

servant

defines API types

servant

type SignalMarketAPI = "signal_market"
  :> (   GetSignalMarketSignalForSale
    :<|> GetSignalMarketSignalSold
    :<|> GetSignalMarketHistory )

type GetSignalMarketSignalForSale = "for_sale"
  :> QueryParams "sale_id" SaleID
  :> QueryParams "token_id" TokenID
  :> QueryParam "sale_status" SaleStatus
  :> QueryParams "seller" EthAddress
  :> QueryParam "limit" Int
  :> QueryParam "offset" Int
  :> QueryParam "ordering" BlockNumberOrdering
  :> Get '[JSON] [WithMetadata SignalMarketSignalForSale.SignalForSale]

servant

getSignalMarketSignalForSaleH 
  :: [SaleID] -> [TokenID] -> Maybe SaleStatus -> [EthAddress]
  -> Maybe Int -> Maybe Int -> Maybe BlockNumberOrdering 
  -> AppHandler [WithMetadata ForSale.SignalForSale]
getSignalMarketSignalForSaleH {..} = do
  let withLimitAndOffset = maybe Cat.id withCursor 
    (Cursor <$> mlimit <*> moffset)
      saleIdFilter = case saleID of
        [] -> Cat.id
        xs -> O.keepWhen (\a -> fmap O.constant xs `O.in_` ForSale.saleID a)
      usingOrdering = withOrdering (fromMaybe DESC mord) 
        (RawChange.blockNumber . snd) (RawChange.logIndex . snd)
  as <- runDB $ \conn -> O.runQuery conn $
    withLimitAndOffset $ usingOrdering $ withMetadata ForSale.eventID $ 
      signalMarketSignalForSaleQ >>> saleIdFilter
  pure . flip map as $ \(t, rc) -> WithMetadata t rc

purescript-react

frontend application

purescript-react

renderSignal {..} =
  let (Signal s) = state.signal
  in classy R.div "Signal"
    [ renderBaseSignal addLink state.signal
    , case user of
     ...

      ]

purescript-react

    case user of
      UserGuest -> maybeHtml s.sale \{price} ->
        R.div_ [R.text $ "ON SALE FOR ", renderToken price]

type ConnectedState = { userAddress :: Address
                      , provider :: Provider
                      , contracts :: Contracts
                      }
data User =
    UserGuest
  | UserConnected ConnectedState

purescript-react

    case user of
      UserConnected con@{userAddress}
        | userAddress == s.owner -> case s.sale of
          Just {id, price} -> txOrElse state.tx $ React.fragment
            [ R.span_ [ R.text $ "ON SALE FOR "
                           , renderToken price, R.text " " ]
            , R.button
              { onClick: capture_ $ txSend (Tx.UnSell id) con
                (\newTxSt -> updateState _ {tx = Just newTxSt})
              , children: [ R.text "UnList" ]
              }
                 ]

Detailed architecture

Chanterelle

Ilya Ostrovskiy

Chanterelle

  • Build tool that imposes some (slightly opinionated, albeit consistent) structure between your smart contract code and the rest of your application's code.
  • Handles compiling your contract into EVM bytecode, and then converting the resulting ABI output into PureScript bindings that can craft transactions to interact with your blockchain code.
  • Allows you define how your contracts are deployed to the blockchain in PureScript. Think Truffle migrations, but type-safe.
  • Provides some convenient helpers for writing tests for your contracts in PureScript
  • Provides a fun, easy-to-use CLI to enable all of that.

chanterelle.json

{
    "name": "sample-nft-project",
    "version": "0.0.1",
    "source-dir": "dapp/contracts",
    "modules": [ "SimpleStorage"
               , "SignalMarket"
               , "FoamToken"
               , "SignalToken"
               ],
    "dependencies": [ "openzeppelin-solidity" ],
    "purescript-generator": {
        "output-path": "dapp/src",
        "module-prefix": "Contracts"
    },
    "solc-version": "0.5.11",
    "solc-evm-version": "byzantium"
}
    • go through chanterelle.json
      • allow different versions of solc etc
    • look at bindings and how types correspond from function calls
    • look at event types and how they can be used in tests assertWeb3 et al
    • do a deployment with cliquebait
    • the underlying architecture of chanterelle

purescript-react

Irakli Safareli

10 000 foot view

data Route
  = Signals
  | Signal SignalId
data Signal = Signal
  { id :: SignalId
  , stake :: Token FOAM
  , owner :: Address
  , geohash :: Geohash
  , radius :: Radius
  , sale :: Maybe
      { id :: SaleId
      , price :: Token ETHER 
      }
  }
data SignalActivity
  = ListedForSale
      { owner :: Address
      , saleId :: SaleId
      , price :: Token ETHER
      }
  | UnlistedFromSale
      { owner :: Address
      , saleId :: SaleId
      }
  | Sold
      { owner :: Address
      , saleId :: SaleId
      , buyer :: Address
      , price :: Token ETHER
      }
data SignalDetails = SignalDetails
  { signal :: Signal
  , activity :: Array SignalActivity
  }
data Event
  = SignalForSale SignalMarket.SignalForSale
  | SignalUnlisted SignalMarket.SignalUnlisted
  | SignalSold SignalMarket.SignalSold
  | TrackedToken SignalToken.TrackedToken

1 000 foot view

data Tx
  = UnSell SaleId
  | Sell SignalId (Token ETHER)
  | Buy SaleId (Token ETHER)
data Status
  = Submitting
  | SubmittingFailed Web3Error
  | MiningStart HexString
  | MiningFailed TransactionReceipt
  | MiningFinished HexString
data Web3Error
  = Rpc
    { code :: Int
    , message :: String
    }
  | RemoteError String
  | ParserError String
  | NullError
type Progress =
  { current :: Status
  , finished :: Array HexString 
  , total :: Int 
  }

100 foot view

data ProviderConnectivity
  = Connected
      { userAddress :: Address
      }
  | NotConnected
      { userAddress :: Maybe Address
      , currentNetwork :: NetworkId
      }
data ProviderState
  = NotInjected
  | Injected
      { loading :: Boolean
      }
  | Rejected
  | Enabled
      { connectivity :: ProviderConnectivity
      , provider :: Provider
      , contracts :: Contracts
      }
type ConnectedState =
  { userAddress :: Address
  , provider :: Provider
  , contracts :: Contracts
  }

data User
  = UserGuest
  | UserConnected ConnectedState

GraphQL

Charles Crain

Artwork Detail Page

Ex:

  • Intuitive and interactive interface for building queries
  • More flexibility for frontend devs

Why GraphQL?

  • Highly extensive with many out of the box tools that speed up development
  • Strongly typed, great with Haskell and Purescript 

Postgraphile

  • Define your data model as tables (often smart contract state and events)
  • BOOM! Rich GraphQL API and more time to build your DApp
  • Populate the data by indexing events