Skip to content

Commit

Permalink
updated setup for human.trace
Browse files Browse the repository at this point in the history
  • Loading branch information
smitdave committed Jan 31, 2024
1 parent 9d53da3 commit 8c3d4a1
Show file tree
Hide file tree
Showing 9 changed files with 123 additions and 60 deletions.
1 change: 0 additions & 1 deletion NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -357,7 +357,6 @@ export(get_inits_L)
export(get_inits_MYZ)
export(get_inits_X)
export(last_to_inits)
export(make_Hpar_trace)
export(make_Linits_basic)
export(make_Lpar_basic)
export(make_Lpar_trace)
Expand Down
36 changes: 14 additions & 22 deletions R/human-trace.R
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@
#' @return a [numeric] vector of length `nStrata`
#' @export
F_X.trace <- function(t, y, pars, i) {
with(pars$Xpar[[i]], scale*Kf(t))
with(pars$Xpar[[i]], pars$Hpar[[i]]$H*Kf(t))
}

#' @title Size of the human population
Expand Down Expand Up @@ -51,8 +51,15 @@ dXdt.trace <- function(t, y, pars, i) {
#' @return a [list] vector
#' @export
setup_Xpar.trace = function(Xname, pars, i, Xopts=list()){
pars$Xpar[[i]] = make_Xpar_trace(pars$nPatches, Xopts)
pars$Hpar[[i]] = make_Hpar_trace(pars$nPatches, Xopts)
nStrata= pars$nPatches

pars$Hpar[[i]]$nStrata = nStrata
pars$Hpar[[i]]$H = checkIt(pars$Hpar[[i]]$H, nStrata)
pars$BFpar$TimeSpent[[i]] = diag(1, nStrata)
pars = make_TaR(0, pars, i, 1)
pars$BFpar$searchWts[[i]][[1]] = checkIt(pars$BFpar$searchWts[[i]][[1]], nStrata)
pars$BFpar$residence[[i]] = checkIt(pars$BFpar$residence[[i]], nStrata)
pars$Xpar[[i]] = make_Xpar_trace(nStrata, Xopts)
return(pars)
}

Expand All @@ -67,39 +74,24 @@ setup_Xinits.trace = function(pars, i, Xopts=list()){
}

#' @title Make parameters for human null model
#' @param nPatches the number of patches in the model
#' @param nStrata the number of population strata in the model
#' @param Xopts a [list] that could overwrite defaults
#' @param kappa value
#' @param Kf a function
#' @return a [list]
#' @export
make_Xpar_trace = function(nPatches, Xopts=list(),
make_Xpar_trace = function(nStrata, Xopts=list(),
kappa = 0.1,
Kf = NULL){
with(Xopts,{
Xpar = list()
class(Xpar) <- "trace"

Xpar$scale = checkIt(kappa, nPatches)
if(is.null(Kf)) Kf = function(t){return(1)}
kappa = checkIt(kappa, nStrata)
if(is.null(Kf)) Kf = function(t){return(kappa)}
Xpar$Kf = Kf
return(Xpar)
})}

#' @title Make parameters for human null model
#' @param nPatches the number of patches in the model
#' @param Hopts a [list] that could overwrite defaults
#' @return a [list]
#' @export
make_Hpar_trace = function(nPatches, Hopts=list()){
with(Hopts,{
Hpar = list()
Hpar$wts_f = rep(1, nPatches)
Hpar$H = rep(1, nPatches)
Hpar$nStrata = nPatches
return(Hpar)
})}

#' @title Add indices for human population to parameter list
#' @description Implements [make_indices_X] for the trace model.
#' @inheritParams make_indices_X
Expand Down
21 changes: 10 additions & 11 deletions R/setup.R
Original file line number Diff line number Diff line change
Expand Up @@ -80,28 +80,27 @@ xde_setup = function(modelName = "unnamed",
pars$membership = membership
pars$calN = make_calN(pars$nPatches, pars$membership)

# Human Demography
pars = setup_Hpar_static(pars, 1, HPop)

# Blood Feeding
pars = setup_BloodFeeding(pars, 1, 1, BFopts, residence, searchB, F_circadian)
pars = make_TimeSpent(pars, 1, TimeSpent, TimeSpentOpts)

# Adult Mosquito Dynamics
EIPmod = setup_EIP(EIPname, EIPopts)
calK = make_calK(nPatches, calK, calKopts)
pars = setup_MYZpar(MYZname, pars, 1, MYZopts, EIPmod, calK)
pars = setup_MYZinits(pars, 1, MYZopts)

# Human Demography
pars = setup_Hpar_static(pars, 1, HPop)
# Blood Feeding
pars = setup_BloodFeeding(pars, 1, 1, BFopts, residence, searchB, F_circadian)
pars = make_TimeSpent(pars, 1, TimeSpent, TimeSpentOpts)
# Vertebrate Host Dynamics
pars = setup_Xpar(Xname, pars, 1, Xopts)
pars = setup_Xinits(pars, 1, Xopts)

# Aquatic Mosquito Dynamics
pars = setup_Lpar(Lname, pars, 1, Lopts)
pars = setup_Linits(pars, 1, Lopts)

# Egg Laying
pars = setup_EggLaying_static(pars, 1, searchQ)

# Vertebrate Host Dynamics
pars = setup_Xpar(Xname, pars, 1, Xopts)
pars = setup_Xinits(pars, 1, Xopts)

pars = make_indices(pars)

Expand Down
1 change: 0 additions & 1 deletion R/transmission.R
Original file line number Diff line number Diff line change
Expand Up @@ -160,7 +160,6 @@ F_EIR <- function(t, y, pars, i, s) {
#' @return [list]
#' @export
compute_kappa <- function(t, y, pars){

for(s in 1:pars$nVectors){
kappa <- F_kappa(t, y, pars, 1, s)

Expand Down
10 changes: 6 additions & 4 deletions _pkgdown.yml
Original file line number Diff line number Diff line change
Expand Up @@ -19,6 +19,12 @@ navbar:
href: articles/vc_lemenach.html
- text: Contributing
href: articles/Contributing.html
- text: Basic Concepts
menu:
- text: Heterogeneous Transmission
href: articles/heterogeneous_transmission.html
- text: Heterogeneous Biting
href: articles/heterogeneous_biting.html
- text: Adult Mosquito Dynamics
menu:
- text: Ross-Macdonald model
Expand Down Expand Up @@ -809,10 +815,6 @@ reference:
- compute_terms.human
- compute_terms.na
- compute_terms_steady
- compute_fqZ
- compute_fqZ_ix
- compute_fqM
- compute_fqM_ix
- compute_NI
- compute_NI_ix
- compute_vars_full
Expand Down
19 changes: 0 additions & 19 deletions man/make_Hpar_trace.Rd

This file was deleted.

4 changes: 2 additions & 2 deletions man/make_Xpar_trace.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

17 changes: 17 additions & 0 deletions vignettes/heterogeneous_biting.Rmd
Original file line number Diff line number Diff line change
@@ -0,0 +1,17 @@
---
title: "Heterogeneous Biting"
output: rmarkdown::html_vignette
vignette: >
%\VignetteIndexEntry{Heterogeneous Biting}
%\VignetteEngine{knitr::rmarkdown}
%\VignetteEncoding{UTF-8}
---

```{r, include = FALSE}
knitr::opts_chunk$set(
collapse = TRUE,
comment = "#>"
)
```

Heterogeneous blood feeding is a basic feature of malaria transmission. In `exDE,` heterogeneous blood feeding includes several distinct components: biting weights and heterogeneous biting; environmental heterogeneity; and time spent / time at risk.
74 changes: 74 additions & 0 deletions vignettes/heterogeneous_transmission.Rmd
Original file line number Diff line number Diff line change
@@ -0,0 +1,74 @@
---
title: "Heterogeneous Transmission"
output: rmarkdown::html_vignette
vignette: >
%\VignetteIndexEntry{Heterogeneous Transmission}
%\VignetteEngine{knitr::rmarkdown}
%\VignetteEncoding{UTF-8}
---

```{r, include = FALSE}
knitr::opts_chunk$set(
collapse = TRUE,
comment = "#>"
)
```

Blood feeding is an interaction among humans and mosquitoes. Parasite transmission is heterogeneous because mosquito populations are spatially heterogeneous and because human behaviors are heterogeneous. Heterogeneous blood feeding and transmission is an important aspect of malaria transmission dynamics and control, and it has been implemented in `exDE` through several related concepts and constructs.

+ **Mosquito populations** are heterogeneous over space and time. Spatial dynamics in `exDE` are organized around the concept of a *patch.* The adult mosquito populations in each *state* are assumed to be homogeneously distributed within each patch.

+ **Human population heterogeneity:** human populations are heterogeneous in several ways that affect malaria epidemiology and transmission, including age, the location of their primary residence, the type of house, mobility patterns and time spent, the use of bed nets and other personal protections, blood type, and nutrition. The design of `exDE` makes it possible to *sub-divide* the human population into an arbitrary number of homogenous strata.

+ **Blood Feeding Search Weights:** Mosquitoes fly around to find a blood meal.

+ **Time at Risk:** Humans spend time in different patches.


+ environmental heterogeneity

## Heterogeneous Biting

**Heterogeneous Biting** is defined throughout the `exDE` implementation and documentation as a difference in the relative biting rates for two strata that are otherwise identical. The implementation relies on two concepts:

+ **blood feeding search weights** or $\left\{\omega\right\}$

+ **relative biting rates** or $\left\{\xi\right\}$

### Blood Feeding Search Weights

A flexible implementation is handled through the blood feeding model, which includes the the concepts of *blood feeding search weights* and *availability*. The search weights, $\left\{\omega\right\}$, are a measure of how easy it is for mosquitoes to find and blood feed on a host. The total *availability* of humans for blood feeding is:

$$W = \sum_i \omega_i H_i.$$
Since mosquitoes could feed on alternative blood hosts, we let $B = W+O,$ where $O$ is the availability of other blood hosts. Using the fully defined blood feeding model, we compute the blood feeding rates $f$ as a functional response to the total availability of blood, $B$:

$$f = F_f(B).$$
and the human fraction is:

$$q = \frac W B.$$

Availability is used to compute the overall blood feeding rate for mosquitoes and the human fraction (human blood meals as a fraction of all blood meals). If we assign a biting weight to a stratum, then the fraction of bites received by that stratum is:

$$ \frac{\omega_i H_i}W.$$

### Relative Biting Rates

If we let $h$ denote the *average* force of infection (FoI) for a population with multiple strata, and $\xi_i$ the frailty term, then the FoI for the $i^{th}$ stratum is $$h_i = \xi_i h;$$

We let $H_i$ denote the size of the $i^{th}$ population, where $$H = \sum_i H_i.$$

The relative biting rates are constrained such that
$$\sum_i \xi_i \frac{H_i}H = 1$$
For example, if 20% of the population gets bitten at a rate that is twice as high as the population average, then the other 80% must get bitten (on average) at a rate that is 3/4 the population average, since:

$$ 2\;(0.2)+ 0.75\;(0.8)= 1$$



Relative biting rates are computed automatically from the blood feeding search weights, $\left\{\omega\right\},$ where

$$\xi_i = \omega_i \frac H W.$$

## Heterogeneous Mixing


0 comments on commit 8c3d4a1

Please sign in to comment.