Skip to content

Instantly share code, notes, and snippets.

@sirlensalot
Created April 29, 2016 16:32
Show Gist options
  • Save sirlensalot/3a9ebec377794f8035848e465f7a814c to your computer and use it in GitHub Desktop.
Save sirlensalot/3a9ebec377794f8035848e465f7a814c to your computer and use it in GitHub Desktop.
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE GADTs #-}
module Juno.DSL
where
import qualified Data.ByteString as BS
import Control.Monad.Identity
data SigNonce nonce ident cmd = SigNonce {
_nIdent :: ident
, _nNonce :: nonce
, _nCmd :: cmd
, _nDigest :: BS.ByteString --- == mac&sign OF ( Serialized (nonce,cmd) )
} deriving (Eq,Ord) -- nonce is main ord, can newtype a weaker form as necc.
data OuterT (m :: * -> *) a -- MonadTrans, etc
data Escrow unit time ident input (effects :: * -> *) = Escrow {
_eAmount :: unit
, _eExpiry :: time
, _eOriginator :: ident
, _ePredicate :: input -> Bool
, _eAction :: input -> effects ()
}
-- execEscrow :: Escrow unit time ident input effects -> OuterT effects ident
propose :: (Ord time) => Escrow unit time ident input effects -> time -> input -> Either String (effects ())
propose escrow nowsnap input | _eExpiry escrow <= nowsnap = Left "Expired"
| not $ _ePredicate escrow input = Left "Predicate Failure"
| otherwise = Right (_eAction escrow input)
createEscrow :: Escrow unit time ident input effects -> SigNonce nonce ident cmd -> OuterT Identity ident
createEscrow = undefined
data TransferArgs unit ident nonce cmd = TransferArgs {
_tAmount :: unit
, _tSource :: ident
, _tTarget :: ident
, _tNonce :: SigNonce nonce ident cmd
}
-- escrow :: Escrow unit time ident input effects -> SigNonce nonce ident ->
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment