Public goods and altruism in group-structured populations

Public goods and altruism in group-structured populations preview image

1 collaborator

Ksteiner2020 Klaus Steiner (Author)

Tags

evolution of altruism 

Tagged by Klaus Steiner about 7 hours ago

Visible to everyone | Changeable by the author
Model was written in NetLogo 7.0.0 • Viewed 20 times • Downloaded 2 times • Run 0 times
Download the 'Public goods and altruism in group-structured populations' modelDownload this modelEmbed this model

Do you have questions or comments about this model? Ask them here! (You'll first need to log in.)


WHAT IS IT?

In a public goods game, participants can contribute something to a common pot, which is then divided equally among all members of the community, regardless of whether they have contributed anything or not.

This multi-agent simuation shows the dynamics of contributing cooperators (C, cyan dots) and free-riding defectors (D, yellow dots) in a group-structured population over many generations.

This is also a demo programm for the results discussed in my paper “Altruism pays off in group-structured populations through probable reciprocity” [1].

HOW IT WORKS

After the initial population has been set, the following steps are repeated for each generation:

1. Evaluation of indivual scores: The benefit values contributed by the C types to the group are added together and divided by the number of group members (C and D). This gives the score for the D types. The costs are then deducted from this score for each of the C types.

2. Selection: If the score is less than the specified threshold, the agent dies with probability subT-mort. In addition, there is a general mortality rate that affects all C and D equally.

3. Reproduction and mutation: Each survivor produces the same number of offspring that inherit the type (C or D) of its parent, but with a certain probability of mutating into the other type (mutation-rate).

4. Migration and elimination of the surplus: If the number of group members exceeds N-groupmembers, randomly selected surplus members are distributed to groups that are not full (fill-groups=all) or only to empty groups (fill-groups=empty). With fill-groups=none, they remain where they are. If all groups are full, the surplus members are eliminated. After that, migration % of randomly selected individuals move to another group. After that surplus group members are eliminated again by random.

HOW TO USE IT

Click SETUP or one of the examples to initialize a model. This sets proper parameters and creates the initial population. Then start simuation with GO as endless loop or stepwise clicking STEP.

Parameters for population ...

nr-groups ... Number of groups into which the total population is divided.

N-groupmembers ... Maximum number of members per group. Groups are always filled when the simulation starts.

startpopC_ ... Approximate frequency of C in the starting population.

Cost-C ... Costs for altruistic trait of C

Benefit ... Benefit for the group through one C

Threshold for selection

threshold ... Threshold value below which individuals with the probability ...

subT-mort ... will die

Parameters for mortality ...

mortality ... Additional general mortality of every individual, regardless of whether C or D.

Reproduction, mutation and migration

offspring ... Number of offspring for each survivor

muation-rate ... The probability that a child will get an other trait (C or D) than its parent.

fill-groups ... Defines how surplus offspring that do not have place in their own group are distributed to other groups: all: surplus offspring fill up non-full groups. empty: surplus offspring fill up only empty groups. none: surplus offspring die.

migration ... Percentage of individuals who are randomly placed in other groups (after fillgroups_ has applied).

Plots and outputs

Altruists (C) in the population ... This plot shows the trajectory beginning with the randomly set starting population, which is marked with surrounding orange dots in the plot. The x-axis [C] shows the frequency of C in the population, y-axis SD is the standard deviation of the frequencies of C in each group.

Population ... This black line is the total number of individuals, the yellow is the number of D (defectors) in each generation (iteration step). The red line shows the upper limit for the population size).

The text field indicates whether altruists can survive in the long term given the combination of selected costs, benefits and thresholds.

THINGS TO NOTICE AND TO TRY

Examples

The examples that can be selected using the buttons set the appropriate parameters for the scenarios described in [1].

standard ... This button sets the parameters used for my standard model in [1]. Costs, benefit and threshold are the same as in "selection only" but here we also have reproduction, mutation, migration and additional mortality.

selection only ... The "selection only" model for cost-benefit analysis within groups and global threshold for individual selection, but without reproduction, mutation and migration. Use button STEP rather than GO to run this model, because final state is usually reached after 2 steps ("generations").

Evolve #1 ... With this setup the model starts with a threshold so low (threshold=-5) that there is no selection pressure, so the all-D starting population will develop relatively pure C and D groups through mutation, inheritance and chance. After a while click increase threshold to suddenly increase the selection pressure (to threshold=3) und the altruists very quickly prevail.

Evolve #2 ... If the mortality for scores below the threshold is low, altruists have little chance in a starting population of egoists. However, if mortality increases, e.g. to subT-mort=75%, altruists can prevail in an initially purely egoistic population. BTW: The value must not be too high initially; at 100%, for example, an egoistic population dies out immediately in the standard model.

CREDITS AND REFERENCES

[1] This is a demo programm for results of my paper "Altruism pays off in group-structured populations through probable reciprocity"

ABOUT

Author: Klaus F. Steiner (2025)

E-Mail: ksteiner@vinckensteiner.com

WWW: https://www.vinckensteiner.com/ksteiner/

Comments and Questions

Please start the discussion about this model! (You'll first need to log in.)

Click to Run Model

;********************************************************************************************************
; groupsim_CD_fitness_demo
; by Klaus Steiner, 2024
; Email: ksteiner@vinckensteiner.com
; Web: https://www.vinckensteiner.com/ksteiner
;********************************************************************************************************
; change history:
;********************************************************************************************************

turtles-own [
  group        ;; group id
  typ          ;; defector "D" or cooperator "C"
  ;input         ;; input of turtle = benefit for group

  score-group
  score-pop

  isNew?       ;; internal use
  urahn        ;; id of the very first parent
]

globals [
  extinct-groups
  extinct-total
  extinct-delta
  groups-new      ;; list of group's birth-ticks
  c-list
  d-list
  fitness-list
  fit-C-grp-list fit-D-grp-list fit-C-pool-list fit-D-pool-list
  C_t C_gdead C_idead_ C_bdead
  D_t D_gdead D_idead_ D_bdead
  C_gdeadrate-list D_gdeadrate-list
  Pool_C_gdead Pool_D_gdead

  ; former elements
  verbose? time-wait overlap

  g-deviation g-deviation-old g-deviation-list ; for standard deviations of group's C:D ratio
  g-mean
  C-fit C-fit-old ;; [C] now (C-freq) and of former generation (C-freq-old)
  C-fit-0 g-deviation-0 ; [C] and SD of start population

  fit-D fit-C
]

;********************************************************************************************************

to setGrid
  if nr-groups = 2
  [
    ask patches with [ pxcor = 0 ]
    [ set pcolor 2 ]
  ]
  if nr-groups = 4
  [
    ask patches with [ pxcor = 0 or pycor = 0 ]
    [ set pcolor 2 ]
  ]
  if nr-groups = 9
  [
    ask patches with [ abs pxcor = round (max-pxcor / 3) or abs pycor = round (max-pycor / 3)  ]
    [ set pcolor 2 ]
  ]
  if nr-groups = 16
  [
    ask patches with [ pxcor = 0 or pycor = 0 or abs pxcor = round (max-pxcor / 2) or abs pycor = round (max-pycor / 2)  ]
    [ set pcolor 2 ]
  ]
end 

;********************************************************************************************************

to-report getx [ g ]
  let x0 0
  if nr-groups = 1
  [
    report x0 + 7 * random-xcor / 8
  ]
  if nr-groups = 4 or nr-groups = 2
  [
    ifelse g mod 2 = 1
    [set x0 -1 * max-pxcor * 1 / 2]
    [set x0 max-pxcor * 1 / 2]
    report x0 + random-xcor / 3
  ]
  if nr-groups = 9
  [
    if g mod 3 = 1
    [set x0 -1 * max-pxcor * 11 / 16]
    if g mod 3 = 0
    [set x0 max-pxcor * 11 / 16]
    report x0 + random-xcor / 4
  ]
  if nr-groups = 16
  [
    if g mod 4 = 1
    [set x0 -1 * max-pxcor * 9 / 12]
    if g mod 4 = 2
    [set x0 -1 * max-pxcor * 3 / 12]
    if g mod 4 = 3
    [set x0 max-pxcor * 3 / 12]
    if g mod 4 = 0
    [set x0 max-pxcor * 9 / 12]
    report x0 + random-xcor / 6
  ]
end 

;********************************************************************************************************

to-report gety [ g ]
  let y0 0
  if nr-groups = 1 or nr-groups = 2
  [
    report y0 + 7 * random-ycor / 8
  ]
  if nr-groups = 4
  [
    ifelse g <= 2
    [ set y0 -1 * max-pycor * 1 / 2 ]
    [ set y0 max-pycor * 1 / 2 ]
    report y0 + random-ycor / 3
  ]
  if nr-groups = 9
  [
    if g <= 3
    [ set y0 -1 * max-pycor * 11 / 16 ]
    if g > 6
    [ set y0 max-pycor * 11 / 16 ]
    report y0 + random-ycor / 4
  ]
  if nr-groups = 16
  [
    if g <= 4
    [ set y0 -1 * max-pycor * 9 / 12 ]
    if g >= 5 and g <= 8
    [ set y0 -1 * max-pycor * 3 / 12 ]
    if g >= 9 and g <= 12
    [ set y0 max-pycor * 3 / 12 ]
    if g >= 13
    [ set y0 max-pycor * 9 / 12 ]
    report y0 + random-ycor / 6
  ]
end 

;********************************************************************************************************

to-report setcolor [ typus ]
  ifelse typus = "C"
  [ report cyan ]
  [ report yellow ]
end 

;********************************************************************************************************

to-report  mutate [parenttrait]
  let newtrait parenttrait
  if random-float 1 < mutation-rate
  [
    ifelse newtrait = "C"
    [ set newtrait "D" ]
    [ set newtrait "C" ]
  ]
  report newtrait
end 


;********************************************************************************************************

to-report  getCase []
  let case ""
  if (Benefit <= Costs-C) [report "B<=K ... altruists are never supported."]

  if threshold <= fit-C [ set case word case "T<=-K ... No selection pressure for C and D, the development is purely random." ]
  if ((fit-C < threshold) and (threshold <= fit-C + Benefit) and (fit-C + Benefit <= fit-D)) or ((fit-C < threshold) and (threshold <= fit-D) and (fit-D <= fit-C + Benefit))
    [ set case word case "-K= fit-C + Benefit) or (fit-C + Benefit < threshold and fit-C + Benefit >= fit-D)
    [ set case word case "B-K < T ... both C and D are below the threshold value, the population will quickly die out if subT_mort=100%." ]
  report case
end 



;********************************************************************************************************

to setup
;********************************************************************************************************
  clear-all
  set verbose? false
  set time-wait 0

  set overlap true

  if verbose? [
    print ""
    print  "*** new SETUP *** "
  ]

  set fit-D 0  ;; basic fitness = fitness of D; always 0 in this model for simplification, since value is irrelevant
  set fit-C fit-D - Costs-C

  ;; print (fit-C + Benefit)
  clear-output
  output-print word "" getCase

  ask patches [ set pcolor 122]

  let g 0

  repeat nr-groups
  [
    set g g + 1
    crt N-groupmembers [
      setxy getx g gety g
      set shape "circle"
      ifelse nr-groups <= 4 and N-groupmembers <= 10
      [ set size 2 ]
      [ set size 1.5 ]
      set group g
      ifelse random 100 < startpop-C
      [
        set typ "C"
      ]
      [
        set typ "D"
      ]
      set color setcolor typ
      set isNew? false
      set urahn who
    ]
  ]


  set groups-new n-values nr-groups [-1]

  set extinct-total 0
  set extinct-delta 0
  set C_t 0
  set C_gdead 0
  set D_t 0
  set D_gdead 0
  set g-deviation-list []


  set g-mean -1
  set g-deviation -1
  set g-deviation-old -1
  set C-fit -1
  set C-fit-old -1

  group-statistics

  set C-fit-0 C-fit
  set g-deviation-0 g-deviation

  set C_gdeadrate-list []
  set D_gdeadrate-list []

  set fit-C-grp-list []
  set fit-D-grp-list []
  set fit-C-pool-list []
  set fit-D-pool-list []

  payoffs

  setGrid
  reset-ticks
end 


;********************************************************************************************************

to set-fitness-lists
  if count turtles with [typ = "C"] > 0
  [
    set fit-C-grp-list lput mean [score-group] of turtles with [typ = "C"] fit-C-grp-list
    set fit-C-pool-list lput mean [score-pop] of turtles with [typ = "C"] fit-C-pool-list
  ]

  if count turtles with [typ = "D"] > 0
  [
    set fit-D-grp-list lput mean [score-group] of turtles with [typ = "D"] fit-D-grp-list
    set fit-D-pool-list lput mean [score-pop] of turtles with [typ = "D"] fit-D-pool-list
  ]
end 

;; ********************************************************************************************************

to payoffs
;; calculates the payoffs (fitness) for unsplit population versus summed of groups for the traits
;; interaction against N-interacts opponents
;; ********************************************************************************************************
  ;;print "******* payoffs for current situation ********"

  ;; scores if pooled

  let C_pool 0
  let D_pool 0

  let nC count turtles with [ typ = "C" ]
  let nD count turtles with [ typ = "D" ]

  if nC + nD < 1 [ stop ]

  let benefit4each nC * Benefit / ( nC + nD)

  ask turtles [
    ifelse typ = "C"
    [
      set score-pop (fit-D - Costs-C) + benefit4each
      set C_pool C_pool + score-pop
    ]
    [
      set score-pop  fit-D + benefit4each
      set D_pool D_pool + score-pop
    ]
  ]

  ;; scores if grouped

  let g 0
  repeat nr-groups
  [
    set g g + 1
    set nC count turtles with [ typ = "C" and group = g ]
    set nD count turtles with [ typ = "D" and group = g ]

    if nC + nD > 0 [
      set benefit4each nC * Benefit / ( nC + nD)

      ask turtles with [ group = g ] [
        ifelse typ = "C"
        [
          set score-group (fit-D - Costs-C) + benefit4each
          set C_pool C_pool + score-pop
        ]
        [
          set score-group fit-D + benefit4each
          set D_pool D_pool + score-pop
        ]
      ]
    ]
  ]

  set-fitness-lists

  if time-wait > 0 or verbose?
  [
    let C_payoff_group "--"
    let C_payoff_pop "--"
    let D_payoff_group "--"
    let D_payoff_pop "--"

    if count turtles with [ typ = "C" ] > 0
    [
      set C_payoff_group precision mean [ score-group ] of turtles with [ typ = "C"] 3
      set C_payoff_pop precision mean [ score-pop ] of turtles with [ typ = "C"] 3
    ]
    if count turtles with [ typ = "D" ] > 0
    [
      set D_payoff_group precision mean [ score-group ] of turtles with [ typ = "D"] 3
      set D_payoff_pop precision mean [ score-pop ] of turtles with [ typ = "D"] 3
    ]
    type " *** Mean payoffs in groups C: " type C_payoff_group type " D: " type D_payoff_group type " ... in population C: " type C_payoff_pop type " D: " type D_payoff_pop print ""
  ]
end 


;********************************************************************************************************

to-report get-death-rate [ fitness ]
   ; death rate for group fitness level
  ifelse fitness < threshold
  [ report 1 - subT-mort / 100 ]
  [ report 1 ]
end 


;********************************************************************************************************

to selection
  ; performs selection due to individual fitness in groups
;********************************************************************************************************

  ;; basic mortality, same for C and D
  set C_bdead 0 ; basic dead
  set D_bdead 0

  ask turtles [
    if mortality > (random 100) [
      ifelse typ = "C"
      [ set C_bdead C_bdead + 1 ]
      [ set D_bdead D_bdead + 1 ]
      die
    ]
  ]


  ;; set fitness-last mean [ score-pop ] of turtles

  let g 0
  let Ccount count turtles with [ typ = "C" ]
  let Dcount count turtles with [ typ = "D" ]
  if Ccount + Dcount <= 0 [ stop ]

  set C_gdead 0
  set D_gdead 0

  ; calculate fictive mortality for whole genpool that is not split in groups
  if any? turtles with [ typ = "C"]
  [ set Pool_C_gdead Ccount * get-death-rate [ score-pop ] of one-of turtles with [ typ = "C"] ]
  if any? turtles with [ typ = "D"]
  [ set Pool_D_gdead Dcount * get-death-rate [ score-pop ] of one-of turtles with [ typ = "D"] ]

  ; let members die according to their fitness
  ask turtles with [ score-group < threshold ] [
    if random 100 < subT-mort
    [
      ifelse typ = "C"
        [ set C_gdead C_gdead + 1 ]
        [ set D_gdead D_gdead + 1 ]
      die
    ]
  ]


  if Ccount * Dcount > 0
  [
    set C_gdeadrate-list lput (C_gdead / Ccount) C_gdeadrate-list
    set D_gdeadrate-list lput (D_gdead / Dcount) D_gdeadrate-list
  ]

  if time-wait > 0 or verbose?
  [
    let Ccount1 count turtles with [ typ = "C" ]
    let Dcount1 count turtles with [ typ = "D" ]
    type "* Died C: " type C_gdead type " D: " type D_gdead type " # still alive C: " type Ccount1 type " D: " type Dcount1 print ""
    wait time-wait
  ]
end 

;********************************************************************************************************

to-report get-free-groups
  let g 0
  let llist []
  repeat nr-groups
  [
    set g g + 1
    let t count turtles with [ group = g ]
    if t < N-groupmembers
    [ set llist lput g llist ]
  ]
  report llist
end 

;********************************************************************************************************

to-report get-empty-groups
  let g 0
  let llist []
  repeat nr-groups
  [
    set g g + 1
    let t count turtles with [ group = g ]
    if t = 0
    [ set llist lput g llist ]
  ]
  report llist
end 



;********************************************************************************************************

to reproduce [ nchild ]
  ; Reproduction where each surviving subject produces "nchild" offsprings with isNew? = true.
;********************************************************************************************************
  if count turtles = 0 [ stop ]
  let g 0

  repeat nr-groups
  [
    set g g + 1
    let t count turtles with [ group = g and isNew? = false ]

    if t > 0
    [
      ask turtles with [ group = g and isNew? = false ]
      [
        let trait typ
        hatch nchild
        [
          set typ mutate trait
          set color setcolor typ
          set group g
          hide-turtle
          setxy getx g gety g
          set isNew? true
          set score-group -999
          set score-pop -999
        ]
      ]
    ]
  ]

  if not overlap
  [ ask turtles with [ isNew? = false]
    [ die ]
  ]

  if time-wait > 0 or verbose?
  [
    type "* Reproduction - "
    type "new offspring: " type count turtles with [isNew? = true]
    print ""
    ; wait time-wait
  ]
end 

;********************************************************************************************************

to disperse-wilson
;********************************************************************************************************

  ; merge populations
  ask turtles
  [ set group 0 ]

  ; kill surplus
  let d count turtles - (nr-groups * N-groupmembers)
  if d > 0
  [ ask n-of d turtles
    [ die ]
  ]

  ; split remaining population into groups
  let g 1
  ask turtles
  [
    set group g
    setxy getx g gety g
    show-turtle
    set isNew? false
    set g g + 1
    if g > nr-groups
    [ set g 1]
  ]

  if time-wait > 0 or verbose?  ; output current population and slow down simulation
  [
    type "* Dispersal - Wilson (population merged and splited into groups again) - "
    type "new population: " type count turtles
    if d >= 0
    [ type ", died as overpopulation: " type d ]
    print ""
    wait time-wait
  ]
end 


;********************************************************************************************************

to disperse [ mode ]
  ; Type of dispersal of offsprings. First they fill their group.
  ; If full, they spread to other groups, or die if all other groups are full, too.
;********************************************************************************************************
  let g 0

  ; offspring for own group ************************************
  repeat nr-groups
  [
    set g g + 1
    let t count turtles with [ group = g ]
    ;;show (word g ": " t)

    let missing N-groupmembers ;; for non-overlapping generations
    if overlap ;; for overlapping generations
    [ set missing N-groupmembers - count turtles with [ group = g and isNew? = false] ]

    if t > 0
    [
      ask turtles with [ group = g and isNew? = true ]
      [ set group -1 ]

      ask turtles with [ group = -1 and isNew? = true ]
      ; step is needed to select from offspring
      [
        ifelse missing > 0 ; oufspring can stay at home group
        [
          set group g
          setxy getx g gety g
          show-turtle
          set missing missing - 1
        ]
        [
          set group 0 ;; Group 0 for surplus
        ]
      ]
    ]
  ]

  let mustleave count turtles with [ group = 0 and isNew? = true ]
  let athome count turtles with [ isNew? = true ] - mustleave
  if time-wait > 0 or verbose?
  [
    type "* Dispersal - fill mode " type mode type ": "
    type athome  type " stay at home group, "
    ; wait time-wait
  ]

  ; dispersing offspring ************************************

  let dcount 0

  ifelse mode = "none"
  [
    ask turtles with [ group = 0 and isNew? = true ]
    [
      set dcount dcount + 1
      die
    ]

  ]
  [
    ifelse mode = "all"
    [
      ;; surplus offspring migrate to incomplete groups
      let free shuffle get-free-groups
      ;; show count turtles with [ group = 0 and isNew? = true ]
      ask turtles with [ group = 0 and isNew? = true ]
      [
        ifelse length free = 0
        [
          set dcount dcount + 1
          die
        ]
        [
          ; show free
          set g first free
          ; set color red
          set group g
          setxy getx g gety g
          show-turtle
          set isNew? false
          set free but-first free
          if length free = 0
          [ set free shuffle get-free-groups ]
        ]
      ]
    ]
    [
      ; only empty groups are filled with surplus offspring
      let free get-empty-groups
      ; show count turtles with [ group = 0 and isNew? = true ]
      ask turtles with [ group = 0 and isNew? = true ]
      [
        ifelse length free = 0
        [
          set dcount dcount + 1
          die
        ]
        [
          ; show free
          set g one-of free

          ; set color red
          set group g
          setxy getx g gety g
          show-turtle
          set isNew? false

          if count turtles with [ group = g ] = N-groupmembers
          [ set free remove g free ]

        ]
      ]
    ]
  ]

  ask turtles with [ isNew? = true ]
  [
    set isNew? false
  ]

  if time-wait > 0 or verbose?
  [
    type mustleave - dcount type " found a new group, and "  type dcount type " died"
    print ""
    wait time-wait
  ]
end 

;********************************************************************************************************

to migrate
  ; Random migration among groups.
  ; obsolete since 6.10.2023: Thus it is possible that groups are larger or smaller than N-groupmembers
;********************************************************************************************************
  if migration > 0
  [
    let p-mig round ( migration / 100 * count turtles )
    let gr 0
    ask n-of p-mig turtles
    [
      set gr random nr-groups + 1
      set group gr
      setxy getx gr gety gr
      ; set color red
    ]

    ;; 6.10.2023: added to avoid groups > N-groupmembers
    let g 0
    let nn 0
    repeat nr-groups
    [
      set g g + 1
      set nn count turtles with [ group = g ] - N-groupmembers
      if nn > 0
      [
        ask n-of nn turtles with [ group = g ]
        [ die ]
      ]
    ]


    if time-wait > 0 or verbose?
    [
      type "* Migration - "
      type p-mig type " have migrated" print ""
      wait time-wait
    ]
  ]
end 

;********************************************************************************************************

to group-check [ mode ]
  ; checks for empty groups, mode end: counts extincted groups of current tick
;********************************************************************************************************
  let g 0

  if mode = "new"
  [ set extinct-groups 0 ]

  repeat nr-groups
  [
    set g g + 1
    if count turtles with [ group = g ] = 0
    [
      set groups-new replace-item  (g - 1) groups-new ticks
    ]
  ]

  if mode = "end"
  [
    ;show  groups-new
    set extinct-groups 0
    foreach groups-new
    [
      x -> if x = ticks
      [ set extinct-groups extinct-groups + 1 ]
    ]
    ;show extinct-groups
    set extinct-total extinct-total + extinct-groups
    set extinct-delta extinct-delta + extinct-groups
  ]
end 

;********************************************************************************************************

to kill-singles
  ; kills subjects in groups of just one
;********************************************************************************************************
  let g 0
  repeat nr-groups
  [
    set g g + 1
    if count turtles with [ group = g ] = 1
    [
      ask turtles with [ group = g ]
      [ die ]
    ]
  ]
end 

;; ********************************************************************************************************

to-report standard-deviationN  [ dlist ]
;; ********************************************************************************************************
  ;; ist sdd-dev von Grundgesamtheit, nicht von Stichprobe wie die angeboten
  let mw mean dlist
  let summe 0
  foreach dlist [
    x -> set summe summe + ( x - mw ) ^ 2
  ]

  report sqrt ( summe / length dlist )
end 

;********************************************************************************************************

to group-statistics
;********************************************************************************************************

  set C_t count turtles with [ typ = "C" ]
  set D_t count turtles with [ typ = "D" ]


  set C-fit-old C-fit
  if any? turtles
  [ set C-fit C_t / count turtles ]

  let C-ratio-list []
  let g 1
  let empty 0
  repeat nr-groups
  [
    ifelse count turtles with [ group = g] > 0
    [
      let r count turtles with [ group = g and typ = "C"] / count turtles with [ group = g]
      set C-ratio-list lput r C-ratio-list
    ]
    [
      set empty empty + 1
    ]
    set g g + 1
  ]

  ;; print C-ratio-list

  if nr-groups - empty >= 1
  [
    set g-deviation-old g-deviation
    set g-deviation standard-deviationN C-ratio-list
    set g-mean mean C-ratio-list
    set g-deviation-list lput g-deviation g-deviation-list
  ]

  if time-wait > 0 or verbose?
  [
    print "******************************************************************"
    type "* Start population *** "
    type "C: " type C_t type " D: " type D_t type " Group Deviation: " type precision g-deviation 3 print ""
    wait time-wait
  ]
end 

;********************************************************************************************************

to go-n [ n ]
;********************************************************************************************************
  set c-list []
  set d-list []
  set fitness-list []
  set extinct-delta 0
  set g-deviation-list []
  set C_gdeadrate-list []
  set D_gdeadrate-list []
  set fit-C-grp-list []
  set fit-D-grp-list []
  set fit-C-pool-list []
  set fit-D-pool-list []
  let c 0

  type "0: C " type C_t type ", D " type D_t type ", [C] " type precision C-fit 3 type ", dev " print precision g-deviation 3

  repeat n
  [
    go
    set c c + 1
    set d-list lput count turtles with [ typ = "D"] d-list
    ifelse count turtles > 0
    [
      set fitness-list lput mean [ score-group ] of turtles fitness-list ;; ###
      set c-list lput ((count turtles with [ typ = "C"]) / (count turtles)) c-list
    ]
    [ stop ]

    if C_t + D_t > 0
    [
;      let c1 C_gdead / C_t
;      let d1 D_gdead / D_t
;      type c type ": C " type C_t type ", D " type D_t type ", C% " type precision (100 * C_t / ( C_t + D_t)) 3 type ", G-Dev " type precision g-deviation 3
;      type ", C_gdead " type precision (100 * c1) 3
;      type ", D_gdead " type precision (100 * d1) 3
;      type ", diff " type precision (100 * (d1 - c1)) 3
;      print ""

      type c
      type ": C " type C_t type ", D " type D_t type ", [C] " type precision C-fit 3 type ", dev " type precision g-deviation 3
      type ", rel-fit " type precision ( C-fit - C-fit-old ) 3
      type ", d-dev " type precision ( g-deviation - g-deviation-old ) 3
      type ", ext-Grps " type extinct-groups
      print ""

    ]
  ]
end 

;********************************************************************************************************

to go
;********************************************************************************************************

  if count turtles = 0
  [ stop ]

  ; get data of population at generation start
  ;group-statistics


  ; perform selection
  selection

  ; checks for empty groups
  group-check "new"

  ; reproduction
  reproduce offspring

  ; dispersal - emigration of offspring
  disperse fill-groups

  ; random migration among groups

;  let g 0
;  let li []
;  repeat nr-groups
;  [
;    if count turtles with [ group = g] > 0
;    [
;      let r count turtles with [ group = g and typ = "C"] / count turtles with [ group = g]
;      set li lput r li
;    ]
;    set g g + 1
;  ]
;  let d0 standard-deviation li

  migrate

;  set g 0
;  set li []
;  repeat nr-groups
;  [
;    if count turtles with [ group = g] > 0
;    [
;      let r count turtles with [ group = g and typ = "C"] / count turtles with [ group = g]
;      set li lput r li
;    ]
;    set g g + 1
;  ]
;  let d1 standard-deviation li
;  type precision d0 3 type " ... " type precision d1 3 type " ... " type precision (d0 - d1) 3 print ""

  ; eliminate singles in groups of one (new: 16.1.21)
  kill-singles

  ; checks for empty groups
  group-check "end"

  ; calc fitness for each agent
  payoffs


  ;get data of new population
  group-statistics


  ; debug
  if 1 = 2 and  C_t * D_t != 0
  [
    show ((D_gdead - Pool_D_gdead) / D_t - (C_gdead - Pool_C_gdead) / C_t)
    show (D_gdead + C_gdead - Pool_C_gdead - Pool_D_gdead) / (D_t + C_t)
    type D_gdead type " " type precision Pool_D_gdead 3 type " " type D_t print " #D"
    type C_gdead type " " type precision Pool_C_gdead 3 type " " type C_t print " #C"
    print " *** "
    stop
  ]

  tick
end 


;********************************************************************************************************

to getValues
; shows settings
;********************************************************************************************************
  print "*** VALUES ***"
  type "Nr-groups: " type Nr-groups type ", N-groupmembers: " type N-groupmembers type "; Costs-C: " type Costs-C  type ", Benefit: " type Benefit  type ", threshold: " type threshold type word " => CASE: " getCase print ""
  type "subT-mort: " type subT-mort type ", mortality: " type mortality type ", fill-groups: " type fill-groups type ", offspring: " type offspring type ", overlap: " type overlap type ", mutation-rate: " type mutation-rate  type ", migration: " type migration print ""
end 

There is only one version of this model, created about 10 hours ago by Klaus Steiner.

Attached files

File Type Description Last updated
Public goods and altruism in group-structured populations.png preview Preview for 'Public goods and altruism in group-structured populations' about 10 hours ago, by Klaus Steiner Download

This model does not have any ancestors.

This model does not have any descendants.