Nomyx-Language-0.6.1: Language to express rules for Nomic

Safe HaskellNone

Language.Nomyx.Vote

Contents

Description

Voting system

Synopsis

Documentation

class (Eq (Alts a), Show (Alts a), Ord (Alts a), Typeable a) => Votable a whereSource

Associated Types

data Alts a Source

Methods

alts :: [Alts a]Source

quota :: Alts a -> Int -> Int -> IntSource

name :: a -> StringSource

exclusiveWinner :: a -> Maybe (Alts a, Alts a)Source

type VoteResult a = VoteStats a -> [Alts a]Source

data VoteStats a Source

Constructors

VoteStats 

voteWithSource

Arguments

:: Votable a 
=> VoteResult a

the function used to count the votes.

-> Assessor a

assessors: when and how to perform the vote assessment (several assessors can be chained).

-> a

toVote: the matter to be voted.

-> [Alts a]

the vote alternatives.

-> Nomex (Msg [Alts a])

return value: a message containing the result of the vote.

Perform a vote.

voteWith_ :: Votable a => VoteResult a -> Assessor a -> a -> Nomex (Msg [Alts a])Source

Performs a vote, all the possible alternatives are selected.

assessOnEveryVote :: Votable a => Assessor aSource

assess the vote on every new vote with the assess function, and as soon as the vote has an issue (positive of negative), sends a signal

assessOnTimeLimit :: Votable a => UTCTime -> Assessor aSource

assess the vote with the assess function when time is reached, and sends a signal with the issue (positive of negative)

assessOnTimeDelay :: Votable a => NominalDiffTime -> Assessor aSource

assess the vote with the assess function when time is elapsed, and sends a signal with the issue (positive of negative)

assessWhenEverybodyVoted :: Votable a => Assessor aSource

assess the vote only when every body voted. An error is generated if the assessing function returns Nothing.

cleanVote :: Votable a => VoteData a -> Nomex EventNumberSource

clean events and variables necessary for the vote

quorum :: Votable a => Int -> VoteStats a -> BoolSource

a quorum is the neccessary number of voters for the validity of the vote

withQuorum :: Votable a => VoteResult a -> Int -> VoteResult aSource

adds a quorum to an assessing function

unanimity :: Votable a => VoteStats a -> [Alts a]Source

assess the vote results according to a unanimity (everybody votes for)

majority :: Votable a => VoteStats a -> [Alts a]Source

assess the vote results according to an absolute majority (half voters plus one, no quorum is needed)

majorityWith :: Votable a => Int -> VoteStats a -> [Alts a]Source

assess the vote results according to a majority of x (in %)

numberVotes :: Votable a => Int -> VoteStats a -> [Alts a]Source

assess the vote results according to a necessary number of positive votes

firstXBest :: forall a. Votable a => Int -> VoteStats a -> [Alts a]Source

the winners are the x vote alternatives with the more votes

takeInGroups :: Int -> [[a]] -> [a]Source

firstBest :: Votable a => VoteStats a -> [Alts a]Source

the winner is the vote alternative with the more votes

sortWith :: Ord b => (a -> b) -> [a] -> [a]Source

voteQuota :: forall a. Votable a => Int -> VoteStats a -> [Alts a]Source

return the vote alternatives that are above threshold

exclusiveVoteQuota :: Votable a => Int -> VoteStats a -> (Alts a, Alts a) -> Maybe (Alts a)Source

in case of exclusive winner

nbVoters :: Votable a => VoteStats a -> IntSource

number of people that voted if the voting is finished, total number of people that should vote otherwise

counts :: (Eq a, Ord a) => [a] -> [(a, Int)]Source

onRuleProposed :: (RuleInfo -> Nomex (Msg [ForAgainst])) -> RuleSource

any new rule will be activate if the rule in parameter returns For

Referendum & elections