Skip to content

Commit

Permalink
Rename Semantics4 to Semantics
Browse files Browse the repository at this point in the history
  • Loading branch information
nau committed Aug 14, 2019
1 parent 940f668 commit fdf4f23
Show file tree
Hide file tree
Showing 13 changed files with 15 additions and 15 deletions.
2 changes: 1 addition & 1 deletion semantics-3.0/ActusContracts.hs
Expand Up @@ -16,7 +16,7 @@ import Data.Time.Clock.System
import Debug.Trace

import ACTUS
import Semantics4
import Semantics

zcb ied md notional discount = (emptyContractConfig ied)
{ maturityDate = Just md
Expand Down
2 changes: 1 addition & 1 deletion semantics-3.0/CrowdFunding.hs
@@ -1,6 +1,6 @@
module CrowdFunding where

import Semantics4
import Semantics

import Data.List (genericLength, genericSplitAt, inits, tails)

Expand Down
4 changes: 2 additions & 2 deletions semantics-3.0/DepositIncentive.hs
@@ -1,6 +1,6 @@
module DepositIncentive where

import Semantics4
import Semantics

payAll :: AccountId -> Payee -> Contract -> Contract
payAll acId payee cont =
Expand All @@ -27,7 +27,7 @@ depositAmt, incentiveAmt :: Value
depositAmt = Constant 100
incentiveAmt = Constant 20

depositAcc, incentiveAcc :: AccountId
depositAcc, incentiveAcc :: AccountId
depositAcc = AccountId 1 depositer
incentiveAcc = AccountId 1 incentiviser

Expand Down
2 changes: 1 addition & 1 deletion semantics-3.0/Escrow.hs
@@ -1,6 +1,6 @@
module Escrow where

import Semantics4
import Semantics

import Data.List (maximumBy, genericLength, inits, tails)
import Data.Ord (comparing)
Expand Down
2 changes: 1 addition & 1 deletion semantics-3.0/ExpCrowdFunding.hs
@@ -1,6 +1,6 @@
module ExpCrowdFunding where

import Semantics4
import Semantics

contract :: Contract
contract = crowdfunding 1000 100
Expand Down
2 changes: 1 addition & 1 deletion semantics-3.0/ExpEscrow.hs
@@ -1,6 +1,6 @@
module ExpEscrow where

import Semantics4
import Semantics

contract :: Contract
contract = When [Case (Deposit (AccountId 1 1) 1 (Constant 450))
Expand Down
2 changes: 1 addition & 1 deletion semantics-3.0/ExpRent.hs
@@ -1,6 +1,6 @@
module ExpRent where

import Semantics4
import Semantics

expanded =
When [
Expand Down
2 changes: 1 addition & 1 deletion semantics-3.0/Main.hs
Expand Up @@ -13,7 +13,7 @@ import Test.Tasty.HUnit
import Debug.Trace
import Data.Time

import Semantics4
import Semantics
import ZCBG2
import ActusContracts

Expand Down
2 changes: 1 addition & 1 deletion semantics-3.0/Rent.hs
@@ -1,6 +1,6 @@
module Rent where

import Semantics4
import Semantics

utility :: Contract
utility = mkDeposit $ payMonth 1 $ payMonth 2 $ payMonth 3 $ Refund
Expand Down
2 changes: 1 addition & 1 deletion semantics-3.0/Semantics4.hs → semantics-3.0/Semantics.hs
@@ -1,5 +1,5 @@
{-# LANGUAGE NamedFieldPuns #-}
module Semantics4 where
module Semantics where

import Data.List (foldl')
import Data.Map.Strict (Map)
Expand Down
4 changes: 2 additions & 2 deletions semantics-3.0/ZCBG.hs
@@ -1,6 +1,6 @@
module ZCBG where

import Semantics4
import Semantics
import Data.List (inits, tails)

splitEverywhere :: [a] -> [([a], a, [a])]
Expand All @@ -13,7 +13,7 @@ splitEverywhere xs =
(init (zip (inits xs) (tails xs)))

allActions :: [Action] -> Timeout -> Contract -> Contract -> Contract
allActions [] _ cont _ = cont
allActions [] _ cont _ = cont
allActions l timeout cont timeoutCont =
When [Case t $ allActions (b ++ a) timeout cont timeoutCont
| (b, t, a) <- splitEverywhere l]
Expand Down
2 changes: 1 addition & 1 deletion semantics-3.0/ZCBG2.hs
@@ -1,7 +1,7 @@

module ZCBG2 where

import Semantics4
import Semantics


zeroCouponBondGuaranteed :: Party -> Party -> Party -> Integer -> Integer -> Timeout
Expand Down
2 changes: 1 addition & 1 deletion semantics-3.0/marlowe.cabal
Expand Up @@ -23,9 +23,9 @@ executable marlowe
template-haskell
other-modules:
Semantics
Semantics1
Semantics2
Semantics3
Semantics4
ActusContracts
ACTUS
ZCBG
Expand Down

0 comments on commit fdf4f23

Please sign in to comment.