hjugement-2.0.1.20190208: Majority Judgment.

Safe HaskellNone
LanguageHaskell2010

Majority.Merit

Contents

Synopsis

Type Choices

choices :: (Bounded choice, Enum choice, Eq choice, Hashable choice) => Choices choice Source #

Return a set of Choices by enumerating the alternatives of its type. Useful on sum types.

Type Grades

type Grades = Set Source #

How many grades should be used? A greater number of grades permits a finer distinction but demands a higher degree of expertise and discernment. The optimal number is the highest number of grades that constitutes a common language, that is, that allows Judges to make absolute judgments. Too little grades may lead too often to ties.

Note, however, that if the inputs or grades depend on the set of choices, i.e. if judges change their grades when choices are added or dropped, then the Arrow paradox cannot be avoided. To avoid this the scale of grades must be fixed and absolute so that more or fewer choices does not change the inputs or messages of other choices.

grades :: [grade] -> Grades (Ranked grade) Source #

Type Ranked

newtype Ranked a Source #

Helper type to rank data without a good Ord instance.

Constructors

Ranked (Integer, a) 
Instances
Functor Ranked Source # 
Instance details

Defined in Majority.Merit

Methods

fmap :: (a -> b) -> Ranked a -> Ranked b #

(<$) :: a -> Ranked b -> Ranked a #

Eq (Ranked a) Source # 
Instance details

Defined in Majority.Merit

Methods

(==) :: Ranked a -> Ranked a -> Bool #

(/=) :: Ranked a -> Ranked a -> Bool #

Ord (Ranked a) Source # 
Instance details

Defined in Majority.Merit

Methods

compare :: Ranked a -> Ranked a -> Ordering #

(<) :: Ranked a -> Ranked a -> Bool #

(<=) :: Ranked a -> Ranked a -> Bool #

(>) :: Ranked a -> Ranked a -> Bool #

(>=) :: Ranked a -> Ranked a -> Bool #

max :: Ranked a -> Ranked a -> Ranked a #

min :: Ranked a -> Ranked a -> Ranked a #

Show a => Show (Ranked a) Source # 
Instance details

Defined in Majority.Merit

Methods

showsPrec :: Int -> Ranked a -> ShowS #

show :: Ranked a -> String #

showList :: [Ranked a] -> ShowS #

zipRank :: [a] -> [Ranked a] Source #

zipRank xs returns a list with the items of xs wrapped so that they are compareable according to their position into xs.

rankKey :: [(k, a)] -> [(Ranked k, a)] Source #

unRank :: Ranked a -> a Source #

enum :: (Bounded a, Enum a, Ord a) => Set a Source #

Return the Set enumerating the alternatives of its type parameter. Useful on sum types.

Type Judges

type Judges = HashMap Source #

Map each judge to its default grade (usually the same for all judges but not necessarily).

For instance, when a judge gives no grade or has “no opinion”, this default grade could mean that the judge chooses “To Reject” the choice: the rationale being that a judge having “no opinion” concerning a choice has not even taken the time to evaluate it and thus has implicitly rejected it.

judges :: Eq judge => Hashable judge => [judge] -> grade -> Judges judge grade Source #

Type Opinions

type Opinions judge grade = HashMap judge (Distribution grade) Source #

Profile of opinions of some judges about a single choice.

opinions :: Eq judge => Hashable judge => Judges judge grade -> Opinions judge grade -> (Opinions judge grade, HashSet judge) Source #

(ok, ko) = opinions js os returns:

  • in ok the opinions of the judges js updated by those in os,
  • in ko the opinions of judges not in js.

Type Distribution

type Distribution grade = Map grade Share Source #

Usually, a judge gives a singleGrade to a given choice. However, when applying the Majority Judgment to a Tree of Sections, what a judge gives to a parent Section is composed by the grades he or she has given to the sub-Sections, and those can be different. In that case, each grade given to a sub-Section contributes to a Share of the parent Section which therefore is not necessarily a singleGrade, but more generally a Distribution of grades. And the sub-Sections can actually themselves have sub-Sections, hence not being given a grade, but a Distribution of grades too.

singleGrade :: grade -> Distribution grade Source #

Type Share

type Share = Rational Source #

Usually a judge attributes a singleGrade to a given choice, and then the Share of this grade is 1. However, when introducing vote colleges (giving more power to some judges), or when introducing Sections (decomposing a judgment into several sub-judgments), it becomes possible that only a percentage of grade is attributed by a judge to a given choice. This is what a Share is used for.

Type OpinionsByChoice

type OpinionsByChoice choice judge grade = HashMap choice (Opinions judge grade) Source #

Profile of opinions of some Judges about some choices.

opinionsByChoice :: Eq choice => Hashable choice => [(choice, Opinions judge grade)] -> OpinionsByChoice choice judge grade Source #

Type Merit

newtype Merit grade Source #

Profile of merit about a single choice.

Constructors

Merit 

Fields

Instances
(Ord grade, Show grade) => IsList (Merit grade) Source # 
Instance details

Defined in Majority.Merit

Associated Types

type Item (Merit grade) :: Type #

Methods

fromList :: [Item (Merit grade)] -> Merit grade #

fromListN :: Int -> [Item (Merit grade)] -> Merit grade #

toList :: Merit grade -> [Item (Merit grade)] #

Eq grade => Eq (Merit grade) Source # 
Instance details

Defined in Majority.Merit

Methods

(==) :: Merit grade -> Merit grade -> Bool #

(/=) :: Merit grade -> Merit grade -> Bool #

Ord grade => Ord (Merit grade) Source # 
Instance details

Defined in Majority.Value

Methods

compare :: Merit grade -> Merit grade -> Ordering #

(<) :: Merit grade -> Merit grade -> Bool #

(<=) :: Merit grade -> Merit grade -> Bool #

(>) :: Merit grade -> Merit grade -> Bool #

(>=) :: Merit grade -> Merit grade -> Bool #

max :: Merit grade -> Merit grade -> Merit grade #

min :: Merit grade -> Merit grade -> Merit grade #

Show grade => Show (Merit grade) Source # 
Instance details

Defined in Majority.Merit

Methods

showsPrec :: Int -> Merit grade -> ShowS #

show :: Merit grade -> String #

showList :: [Merit grade] -> ShowS #

Ord grade => Semigroup (Merit grade) Source # 
Instance details

Defined in Majority.Merit

Methods

(<>) :: Merit grade -> Merit grade -> Merit grade #

sconcat :: NonEmpty (Merit grade) -> Merit grade #

stimes :: Integral b => b -> Merit grade -> Merit grade #

type Item (Merit grade) Source # 
Instance details

Defined in Majority.Merit

type Item (Merit grade) = (grade, Share)

merit :: Ord grade => Foldable opinions => opinions (Distribution grade) -> Merit grade Source #

merit os returns the Merit given by opinions os

meritFromList :: Ord grade => Foldable opinions => Functor opinions => opinions grade -> Merit grade Source #

normalizeMerit :: Merit grade -> Merit grade Source #

'normalizeMerit m' multiply all Shares by their least common denominator to get integral Shares.

Type MeritByChoice

newtype MeritByChoice choice grade Source #

Profile of merit about some choices.

Constructors

MeritByChoice 

Fields

Instances
(Eq choice, Hashable choice, Show choice) => IsList (MeritByChoice choice grade) Source # 
Instance details

Defined in Majority.Merit

Associated Types

type Item (MeritByChoice choice grade) :: Type #

Methods

fromList :: [Item (MeritByChoice choice grade)] -> MeritByChoice choice grade #

fromListN :: Int -> [Item (MeritByChoice choice grade)] -> MeritByChoice choice grade #

toList :: MeritByChoice choice grade -> [Item (MeritByChoice choice grade)] #

(Eq choice, Eq grade) => Eq (MeritByChoice choice grade) Source # 
Instance details

Defined in Majority.Merit

Methods

(==) :: MeritByChoice choice grade -> MeritByChoice choice grade -> Bool #

(/=) :: MeritByChoice choice grade -> MeritByChoice choice grade -> Bool #

(Show choice, Show grade) => Show (MeritByChoice choice grade) Source # 
Instance details

Defined in Majority.Merit

Methods

showsPrec :: Int -> MeritByChoice choice grade -> ShowS #

show :: MeritByChoice choice grade -> String #

showList :: [MeritByChoice choice grade] -> ShowS #

(Eq choice, Hashable choice, Ord grade) => Semigroup (MeritByChoice choice grade) Source # 
Instance details

Defined in Majority.Merit

Methods

(<>) :: MeritByChoice choice grade -> MeritByChoice choice grade -> MeritByChoice choice grade #

sconcat :: NonEmpty (MeritByChoice choice grade) -> MeritByChoice choice grade #

stimes :: Integral b => b -> MeritByChoice choice grade -> MeritByChoice choice grade #

type Item (MeritByChoice choice grade) Source # 
Instance details

Defined in Majority.Merit

type Item (MeritByChoice choice grade) = (choice, Merit grade)

meritByChoice :: (Ord grade, Eq choice, Hashable choice) => OpinionsByChoice choice judge grade -> MeritByChoice choice grade Source #

meritByChoice gs cs os returns the Merits given to choices cs by opinions os from the Judges js on the Grades gs.