{-# LANGUAGE OverloadedStrings #-}
module HUnit.FFC where

import GHC.Natural (minusNaturalMaybe)
import Data.Maybe (fromJust)
import Test.Tasty.HUnit
import Voting.Protocol
import Utils

hunit :: TestTree
hunit = testGroup "FFC"
 [ testGroup "inv"
	 [ testGroup "WeakParams"
		 [ testCase "groupGen" $
			reify weakFFC $ \(Proxy::Proxy c) ->
				inv (groupGen @c) @?=
					groupGen ^ E (fromJust $ groupOrder @c `minusNaturalMaybe` one)
		 ]
	 , testGroup "BeleniosParams"
		 [ testCase "groupGen" $
			reify beleniosFFC $ \(Proxy::Proxy c) ->
				inv (groupGen @c) @?=
					groupGen ^ E (fromJust $ groupOrder @c `minusNaturalMaybe` one)
		 ]
	 ]
 , testGroup "hash"
	 [ testGroup "WeakParams" $
		reify weakFFC $ \(Proxy::Proxy c) ->
		 [ testCase "[groupGen]" $
			hash "start" [groupGen @c] @?=
				fromNatural 62
		 , testCase "[groupGen, groupGen]" $
			hash "start" [groupGen @c, groupGen] @?=
				fromNatural 31
		 ]
	 , testGroup "BeleniosParams" $
		reify beleniosFFC $ \(Proxy::Proxy c) ->
		 [ testCase "[groupGen]" $
			hash "start" [groupGen @c] @?=
				fromNatural 75778590284190557660612328423573274641033882642784670156837892421285248292707
		 , testCase "[groupGen, groupGen]" $
			hash "start" [groupGen @c, groupGen] @?=
				fromNatural 28798937720387703653439047952832768487958170248947132321730024269734141660223
		 ]
	 ]
 ]