Skip to content

Commit

Permalink
test case for assertKnown
Browse files Browse the repository at this point in the history
  • Loading branch information
jwaldmann committed Jun 24, 2013
1 parent 5895a8f commit 534ab80
Show file tree
Hide file tree
Showing 2 changed files with 53 additions and 0 deletions.
43 changes: 43 additions & 0 deletions CO4/Test/Assert.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,43 @@
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE NoMonomorphismRestriction #-}
{-# LANGUAGE ScopedTypeVariables #-}

-- module CO4.Test.WCB where
module Main where

import Language.Haskell.TH (runIO)
import qualified Satchmo.Core.SAT.Minisat
import qualified Satchmo.Core.Decode
import CO4
import CO4.Prelude
import CO4.Util (toBinary,fromBinary)

import qualified Data.Map as M
import Control.Monad ( void, forM )

import System.Environment (getArgs)
import System.IO

$( runIO $ configurable [ ImportPrelude
, DumpAll "/tmp/WCB"
, Cache
, Profile
]
$ compileFile "CO4/Test/Assert.standalone.hs" )


kList 0 a = known 0 2 []
kList i a = known 1 2 [ a , kList (i-1) a]

main = do
out <- solveAndTestBooleanP
( nat8 42 )
( booleanCache . profile )
( kList 5 uNat8 )
encConstraint
constraint
print out

10 changes: 10 additions & 0 deletions CO4/Test/Assert.standalone.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,10 @@
module CO4.Test.WCB_Matrix where

import CO4.Prelude
import CO4.Test.WCB_Nat8

constraint s xs = eqNat8 s ( summe xs)

summe xs = case assertKnown xs of
[] -> nat8 0
x:xs' -> plusNat8 x (summe xs')

0 comments on commit 534ab80

Please sign in to comment.