diff --git a/.gitignore b/.gitignore new file mode 100644 index 00000000..85fc56ac --- /dev/null +++ b/.gitignore @@ -0,0 +1,14 @@ +html/ +src/build/* +src/equilibrium.obj +src/gmacs.cpp +src/gmacs.exe +src/gmacs.htp +src/gmacs.obj +src/moltIncrement.cpp +src/multinomial.obj +src/nloglike.obj +src/robust_multi.obj +src/spr.obj +src/tailcompression.obj +.Rproj.user diff --git a/CHANGES.md b/CHANGES.md new file mode 100644 index 00000000..265a9200 --- /dev/null +++ b/CHANGES.md @@ -0,0 +1,54 @@ +# Gmacs Changes +## List of changes to Gmacs since pilot version (V1.0): + +1. Generic functions at end of code, now exported to Cstar. +2. Selectivity functions exported to Cstar. +3. Cstar selectivity functions used in code (more options available). +4. When number of classes in data and model are same, class link matrix not required. Automatically generated instead. +5. When number of classes in the data and the model differ by an integer factor, class link matrix is automatically generated. +6. When number of classes in the data is not a multiple of number of classes in the model, read in class_link matrix. +7. Names of fleets and surveys now printed correctly to echoinput file: (bug fix). +8. Functionality improved for writeR: Fleet and survey names now exported to R and used for plots. +9. All references in model are now to size-classes rather than length classes. +10. Gmacs R Functions now wrapped in simple 'gmplot_all' function, can be used with any model. +11. Fleet control section of data file is now extended to include surveys, catch units and multipliers, all entered in the one matrix. This is to prepare for future options where a fishing fleet might also have a 'survey' such as a CPUE index, and where a survey might have some catch. +12. Data file now expects extra dimensions to be specified, such as number of shell and maturity types. +13. Initial numbers can now be specified by estimating early recruitments. Initial numbers options input via control file. NOTE: Currently the lognin_parms have to be entered and have phase set to -ve so as not to be estimated. Later: Make reading these lines conditional. +14. Retention function can now be selected from among multiple options. This includes a logistic function. Currently borrowed from cstar::selex functions. +15. Growth functions can now be selected from among multiple options. This includes a linear growth relationship with a gamma distribution about each size class. +16. Internal calculations have been modified so that multiple copies of selectivity, retention, or size-transition matrix patterns are not created nor stored as before. This make the code mode efficient. NOTE: Will do the same for selectivity, but waiting until further selectivity updates are made [to selex_fleet and selex_survey] + +* Cstar functions for selectivity (and some others) have now been written in Template style code. +* Many updates to Gmacs R functions: Can now be used for any Gmacs model. + +--- + +## Priority changes for Gmacs: Development of a complete example for BBRKC. + +1. A 20 size class model requires several changes from the basic structure presented in January: + * Change to available selectivity functions, beyond 'parameter-per-class'. DONE + * Change to initial numbers estimation from 'parameter-per-class' option to early-recruitment build-up option. DONE + * Change to available retention functions, beyond 'parameter-per-class'. MODIFY FROM SELECTIVITY + * Change to growth estimation from 'parameter-per-class' to parametric approach. +2. Change population dynamics calculations to include more dimensions: + * Set-up dimensions of N matrix via input numbers of sex, shell, maturity. DONE + * Read in data for each dimension as necessary: DONE + * Make sure predicted and observed vales have the same generalized structure and complete calculations. + * Change pop dynamics equations to loop over different dimensions: +3. Remove penalty E3 in the final estimation phase. + +4. Include molting probability (inc. time-varying) into the calculation of the growth transition matrix. + * Might be able to cheat at start by using growth transition matrix from Jie. + +5. Create output file with estimated parameters, starting values, final estimates, bounds, phases, as well as asymptotic standard errors. + * Automatically highlight cases where parameters are on or close to the bounds in the input. + +6. Update R plots for Gmacs Assessment Report + * Add confidence intervals to plots of data points which are considered uncertain. + - DONE for Recruitment estimates + - Others with SD functions? + +7. Check weightings and likelihoods are working correctly with more generalised model. + +8. See NPRB model for 'biological parameters' set up, which uses a counter to allow for differing numbers of parms. + This could replace the current 'theta' block of parameters. \ No newline at end of file diff --git a/README.md b/README.md index 9ef88b68..ac96dbcb 100644 --- a/README.md +++ b/README.md @@ -1,36 +1,25 @@ -# Gmacs Version 1.0 # +# Gmacs -This is the pilot release of Gmacs. Currently posted source files are compilable using ADMB 11.1 and have been tested using the BBRKC model available in the examples folder. This release will remain active until the current 'under development' version is released. **Updated February 2014, by Athol Whitten** +Gmacs is currently under development. A simple working release version of Gmacs is available via `Tag V1.0` and has been tested using the BBRKC model available in the examples folder. The next major release of Gmacs is planned for September 2014. -## Generalized Modeling for Alaskan Crab Stocks ## +## Table of contents +- [About Gmacs](#about-gmacs) +- [Gmacs R Package](#r-package-for-gmacs) +- [Development](#development) -This repository holds source code, instructions, examples, and associated scripts for **Gmacs** (Generalized Modeling for Alaskan Crab Stocks), a generic size-based stock assessment model. +## About Gmacs +**Gmacs** is a generalized size-structured stock assessment modelling framework. The framework is designed with similar flexibility to that provided by age-structured stock assessment modelling frameworks like Stock Synthesis and CASAL. Gmacs can fit to a wide-variety of data for single sex or sex-specific population dynamics and fishery models: data can include survey and fishery indices of abundance and fishery- and survey-based size-composition data. -## Modeling structure and format ## +### Data Requirements +Data must be supplied via the `model.dat` file in a *flat format* to enable easy indexing and simple preparation. Each record for catch, abundance, length-structure etc. should be held in an individual row, with information relating to year, fleet, sex and more. -Gmacs implements a size-structured modelling framework with flexibility similar to that provided by other general stock assessment modelling frameworks. Some effort has been made to maintain consistency with data and control file formats familiar to users of Stock Synthesis. +Model specifcations are controlled through the `model.ctl` file. Information read from files is printed to a separate file called `echoinput.rep` allowing users to check and debug their input. For more information see the [Gmacs Wiki](https://github.com/seacode/gmacs/wiki). -### Input file structure +## R Package for Gmacs +An R package, called `gmr` is under development in support of Gmacs. The package provides functions for creating plots from Gmacs output files. A full pilot version is intended for release in September 2014, timed to coincide with the next stable release of Gmacs. Current development versions of the package can be downloaded from Github directly through R, see https://github.com/seacode/gmr for more details. -Data are supplied via the `model.dat` file in a *flat format* to enable easy indexing and simple preparation using spreadsheet software. Each record for catch, abundance, length-structure etc. should be held in an individual row, with information relating to year, fleet, sex and more: +## Simulation Mode +A simulation-estimation procedure can be performed with Gmacs, by using the `gmacs -sim` flag. For example, try `gmacs -sim 123`, where 123 is a random number seed. -#### Catch data structure - - * Year, Season, Fleet, Sex, Observation - -#### Survey data structure - - * Year, Season, Survey, Observation, Error - -#### Length frequency data structure - - * Year, Season, Fleet/Survey, Sex, Maturity, Shell Condition, No. Samples, Data - -Gmacs allows for the inclusion of an optional growth data file `growth.dat` to specify a fixed growth transtion matrix or year-specific growth transtion matrices. The program also reads a `starter.gm` file for specifying the overall model run conditions, and a control file `model.ctl` for specifications relating to parameter estimation. Finally, a `forecast.gm` file is read to specify the calculation of relevant reference points. This file will allow users to specify model projection options in later versions of Gmacs. - -During the read-in procedure, helpful messages are printed to screen and the information read in is printed to a separate file called `echoinput.gm` allowing users to check and debug their data and control files. - -A general user-guide to the program is under development and will be made available with future releases. - -## Development ## -This software is under development and is not yet intended for general use. If you would like to contribute to the project, please contact [Athol Whitten](mailto:whittena@uw.edu). +## Development +This software is under development and is not yet intended for general use. If you would like to contribute to the project, please see the [Developers Guide](https://github.com/seacode/gmacs/wiki/5.-Developers). \ No newline at end of file diff --git a/Rsrc/DESCRIPTION b/Rsrc/DESCRIPTION new file mode 100644 index 00000000..26864c23 --- /dev/null +++ b/Rsrc/DESCRIPTION @@ -0,0 +1,19 @@ +Package: gmr +Title: Plotting and analysis tools for the Gmacs stock assessment framework +Description: gmr is a set of tools for analysing data and outputs from Gmacs + stock assessment models. The package streamlines the process of taking + text-based ADMB output files and creating visual plots of both input data + and fitted model results. +Authors@R: c(person("Whitten", "Athol", email = "athol.whitten@gmail.com", role + = c("aut","cre")), person("Ianelli", "Jim", email = "jim.ianelli@noaa.gov", + role = c("aut","cre")), person("Martell", "Steve", role = "aut")) +URL: https://github.com/seacode/gmr +Version: 0.2 +Depends: + R (>= 3.0.0), + ggplot2 (>= 0.9.3.1) +Imports: + gdata (>= 2.13.3), + reshape2 (>= 1.2.2), + shiny (>= 0.10.2.2), +License: MIT diff --git a/Rsrc/NAMESPACE b/Rsrc/NAMESPACE new file mode 100644 index 00000000..fdd18533 --- /dev/null +++ b/Rsrc/NAMESPACE @@ -0,0 +1,31 @@ +# Generated by roxygen2 (4.0.2): do not edit by hand + +export(get_cpue) +export(get_recruitment) +export(get_selectivity) +export(get_sizecomp) +export(get_ssb) +export(plot_catch) +export(plot_cpue) +export(plot_cpue_res) +export(plot_datarange) +export(plot_growth) +export(plot_growth_inc) +export(plot_multiple) +export(plot_naturalmortality) +export(plot_recruitment) +export(plot_selectivity) +export(plot_sizecomp) +export(plot_sizecomp_res) +export(plot_sizetransition) +export(plot_ssb) +export(read_admb) +export(read_fit) +export(read_psv) +export(read_rep) +export(set_ggtheme) +export(shiny_gmacs) +import(gdata) +import(ggplot2) +import(reshape2) +import(shiny) diff --git a/Rsrc/R/get-cpue.R b/Rsrc/R/get-cpue.R new file mode 100644 index 00000000..069960fa --- /dev/null +++ b/Rsrc/R/get-cpue.R @@ -0,0 +1,16 @@ +#' Plot cpue or other indices +#' +#' @param replist List object created by read_admb function +#' @return dataframe of observed and predicted indices and residuals +#' @export +get_cpue <- function(replist){ + A <- replist + df <- as.data.frame(A$dSurveyData) + colnames(df) <- c("year","seas","fleet","sex","cpue","cv","units") + sd <- sqrt(log(1+df$cv^2)) + df$lb <- exp(log(df$cpue)-1.96*sd) + df$ub <- exp(log(df$cpue)+1.96*sd) + df$pred <- na.exclude(as.vector(t(A$pre_cpue))) + df$resd <- na.exclude(as.vector(t(A$res_cpue))) + return(df) +} \ No newline at end of file diff --git a/Rsrc/R/get-recruitment.R b/Rsrc/R/get-recruitment.R new file mode 100644 index 00000000..35a66733 --- /dev/null +++ b/Rsrc/R/get-recruitment.R @@ -0,0 +1,20 @@ +#' Plot predicted recruitment and approximate asymptotic error-bars +#' +#' +#' @param replist List object created by read_admb function +#' @return Dataframe of recruitment +#' @export +get_recruitment <- function(replist){ + A <- replist + if(is.null(A$fit$logDetHess)) { + stop("Appears that the Hessian was not positive definite\n + thus estimates of recruitment do not exist.\n + See this in replist$fit.") + } + dfpar <- data.frame(par=A$fit$names,log_rec=A$fit$est,log_sd=A$fit$std) + df <- subset(dfpar,par=="sd_log_recruits")[,-1] + df$year <- A$mod_yrs + df$lb <- exp(df$log_rec - 1.96*df$log_sd) + df$ub <- exp(df$log_rec + 1.96*df$log_sd) + return(df) +} diff --git a/Rsrc/R/get-ssb.R b/Rsrc/R/get-ssb.R new file mode 100644 index 00000000..112265d7 --- /dev/null +++ b/Rsrc/R/get-ssb.R @@ -0,0 +1,16 @@ +#' Plot predicted spawning stock biomass (ssb) +#' +#' Spawning biomass may be defined as all males or some combination of males and females +#' +#' @param replist List object created by read_admb function +#' @return Dataframe of spawning biomass +#' @export +get_ssb <- function(replist){ + A <- replist + dfpar <- data.frame(par=A$fit$names,log_mmb=A$fit$est,log_sd=A$fit$std) + df <- subset(dfpar,par=="sd_log_mmb")[,-1] + df$year <- A$mod_yrs + df$lb <- exp(df$log_mmb - 1.96*df$log_sd) + df$ub <- exp(df$log_mmb + 1.96*df$log_sd) + return(df) +} diff --git a/Rsrc/R/gmr.R b/Rsrc/R/gmr.R new file mode 100644 index 00000000..64561d39 --- /dev/null +++ b/Rsrc/R/gmr.R @@ -0,0 +1,13 @@ +#' gmr: R code for Gmacs +#' +#' gmr is a set of tools for analysing data and outputs +#' related to Gmacs stock assessment models. +#' +#' +#' @name gmr +#' @docType package +#' @import ggplot2 +#' @import shiny +#' @import reshape2 +#' @import gdata +NULL diff --git a/Rsrc/R/plot-catch.R b/Rsrc/R/plot-catch.R new file mode 100644 index 00000000..145b832b --- /dev/null +++ b/Rsrc/R/plot-catch.R @@ -0,0 +1,42 @@ +#' Plot observed and predicted catch values +#' +#' @param replist List object created by read_admb function +#' @param plot_res plot residuals only (default=F) +#' @return Plot of catch history (observed) and predicted values +#' @export +plot_catch <- function(replist, plot_res=FALSE) +{ + A <- replist + df <- as.data.frame(A$dCatchData) + colnames(df)<- c("year","seas","fleet","sex","obs","cv","type","units","mult","effort") + df$residuals <- na.omit(as.vector(t(A$res_catch))) + + #Loop over retained and discarded catch. + type = unique(df$type) + ldf = list() + for(i in type) + { + ldf[[i]] <- subset(df,type %in% i) + } + if (plot_res) + { + # Residuals + p <- ggplot(df,aes(x=factor(year),y=residuals,fill=factor(sex))) + p <- p + geom_bar(stat = "identity", position="dodge") + p <- p + scale_x_discrete(breaks=pretty(df$year)) + p <- p + labs(x="Year",y="Residuals ln(kt)",fill="Sex") + p <- p + facet_wrap(~fleet~type,scales="free") + } + else + { + p <- ggplot(df,aes(x=factor(year),y=obs,fill=factor(sex))) + p <- p + geom_bar(stat = "identity") + p <- p + scale_x_discrete(breaks=pretty(df$year)) + p <- p + labs(x="Year",y="Catch (kt)",fill="Sex") + p <- p + facet_wrap(~fleet,scales="free") + } + # This line applies the plotting over all unique types... + pCatch <- lapply(ldf,FUN = function(x,p){p %+% x},p=p) + pCatch <- p + ggtheme + return(pCatch) +} diff --git a/Rsrc/R/plot-cpue.R b/Rsrc/R/plot-cpue.R new file mode 100644 index 00000000..2437df31 --- /dev/null +++ b/Rsrc/R/plot-cpue.R @@ -0,0 +1,32 @@ +#' Plot cpue or other indices +#' +#' @param replist List object created by read_admb function +#' @return Plot of all observed and predicted incices +#' @export +plot_cpue <- function(replist){ + df <- get_cpue(replist) + p <- ggplot(df,aes(year,cpue)) +# p <- p + geom_point(aes(col=sex)) + p <- p + geom_pointrange(aes(year,cpue,ymax=ub,ymin=lb,col=sex)) + p <- p + labs(x="Year",y="CPUE",col="Sex") + pCPUE <- p + facet_wrap(~fleet+sex,scales="free") +# Fitted CPUE + pCPUEfit <- pCPUE + geom_line(data=df,aes(year,pred)) + return(pCPUEfit) +} + +#' Plot residuals of cpue or other indices +#' +#' @param replist List object created by read_admb function +#' @return Plot of fit indices residuals +#' @export +plot_cpue_res <- function(replist){ +# CPUE residuals + df <- get_cpue(replist) + p <- ggplot(df,aes(factor(year),resd)) + p <- p + geom_bar(aes(fill=factor(sex)),stat = "identity", position="dodge") + p <- p + scale_x_discrete(breaks=pretty(df$year)) + p <- p + labs(x="Year",y="CPUE Residuals",fill="Sex") + pCPUEres <- p + facet_wrap(~fleet,scales="free_x") + return(pCPUEres) +} \ No newline at end of file diff --git a/Rsrc/R/plot-datarange.R b/Rsrc/R/plot-datarange.R new file mode 100644 index 00000000..e388cef3 --- /dev/null +++ b/Rsrc/R/plot-datarange.R @@ -0,0 +1,126 @@ +#' Plot data range by fleet and year +#' +#' @param replist List object created by read_admb function +#' @return Plot of data range +#' @export +plot_datarange <-function(replist) +{ + #repfile <- paste(deparse(substitute(replist)),".rep",sep="") + repfile <- replist$run_name + print(repfile) + narepfile <- strsplit(scan(repfile,what="character",flush=TRUE,blank.lines.skip=FALSE,quiet=TRUE)[1:4],':') + + startyr <- replist$mod_yrs[1] + endyr <- replist$mod_yrs[length(replist$mod_yrs)] + nfleets <- length(narepfile[[2]]) + length(narepfile[[4]]) + nfishfleets <- length(narepfile[[2]]) + fleetnames <- c(narepfile[[2]], narepfile[[4]]) + + df <- as.data.frame(replist$dCatchData) + colnames(df)<- c("year","seas","fleet","sex","obs","cv","type","units","mult","effort","discard_mort") + + retainedcatch <- df[df$type==1,] + discards <- df[df$type==2,] + cpue <- as.data.frame(replist$dSurveyData) + colnames(cpue)<- c("year","seas","fleet","sex","obs","cv","units") + size <- as.data.frame(replist$d3_SizeComps) + colnames(size)<- c("year","seas","fleet","sex","type","shell","maturity","Nsamp",as.character(replist$mid_points)) + + typetable <- matrix(c("retainedcatch", "Retained_Catch", + "discards", "Discards", + "cpue", "Abundance indices", + "size", "Size compositions"),ncol=2,byrow=TRUE) + + typenames <- typetable[,1] + typelabels <- typetable[,2] + + # loop over types to make a database of years with comp data + ntypes <- 0 + # replace typetable object with empty table + typetable <- NULL + # now loop over typenames looking for presence of this data type + for(itype in 1:length(typenames)){ + dat <- get(typenames[itype]) + typename <- typenames[itype] + if(!is.null(dat) && !is.na(dat) && nrow(dat)>0){ + ntypes <- ntypes+1 + for(ifleet in 1:nfleets){ + allyrs <- NULL + # identify years from different data types + #if(typename=="catch" & ifleet<=nfishfleets) allyrs <- dat$Yr[dat[,ifleet]>0] + if(typename %in% c("retainedcatch","discards") & ifleet<=nfishfleets) + { + allyrs <- dat$year[dat$fleet==ifleet] + } + + if(typename %in% "cpue") allyrs <- dat$year[dat$fleet==ifleet] + if(typename %in% "size") allyrs <- dat$year[dat$fleet==ifleet] + # expand table of years with data + if(!is.null(allyrs) & length(allyrs)>0){ + yrs <- sort(unique(floor(allyrs))) + typetable <- rbind(typetable, + data.frame(yr=yrs,fleet=ifleet, + itype=ntypes,typename=typename, + stringsAsFactors=FALSE)) + } + } + } + } + + ntypes <- max(typetable$itype) + fleets <- sort(unique(typetable$fleet)) + + plotdata <- function() + { + margins=c(5.1,2.1,4.1,8.1) + par(mar=margins) # multi-panel plot + xlim <- c(-1,1)+range(typetable$yr,na.rm=TRUE) + yval <- 0 + # count number of unique combinations of fleet and data type + ymax <- sum(as.data.frame(table(typetable$fleet,typetable$itype))$Freq>0) + plot(0,xlim=xlim,ylim=c(0,ymax+ntypes+.5),axes=FALSE,xaxs='i',yaxs='i', + type="n",xlab="Year",ylab="",main="Data by type and year",cex.main=1.5) + xticks <- 5*round(xlim[1]:xlim[2]/5) + abline(v=xticks,col='grey',lty=3) + axistable <- data.frame(fleet=rep(NA,ymax),yval=NA) + itick <- 1 + for(itype in rev(unique(typetable$itype))){ + typename <- unique(typetable$typename[typetable$itype==itype]) + #fleets <- sort(unique(typetable2$fleet[typetable2$itype==itype])) + for(ifleet in rev(fleets)){ + yrs <- typetable$yr[typetable$fleet==ifleet & typetable$itype==itype] + if(length(yrs)>0){ + yval <- yval+1 + x <- min(yrs):max(yrs) + n <- length(x) + y <- rep(yval,n) + y[!x%in%yrs] <- NA + # identify solo points (no data from adjacent years) + solo <- rep(FALSE,n) + if(n==1) solo <- 1 + if(n==2 & yrs[2]!=yrs[1]+1) solo <- rep(TRUE,2) + if(n>=3){ + for(i in 2:(n-1)) if(is.na(y[i-1]) & is.na(y[i+1])) solo[i] <- TRUE + if(is.na(y[2])) solo[1] <- TRUE + if(is.na(y[n-1])) solo[n] <- TRUE + } + # add points and lines + points(x[solo], y[solo], pch=16, cex=2,col=rainbow(nfleets)[ifleet]) + lines(x, y, lwd=12,col=rainbow(nfleets)[ifleet]) + axistable[itick,] <- c(ifleet,yval) + itick <- itick+1 + } + } + + yval <- yval+1 + if(itype!=1) abline(h=yval,col='grey',lty=3) + text(mean(xlim),yval-.3,typelabels[typenames==typename],font=2) + } + + axis(4,at=axistable$yval,labels=fleetnames[axistable$fleet],las=1) + box() + axis(1,at=xticks) + } + pdatarange <- plotdata() + return(pdatarange) +} diff --git a/Rsrc/R/plot-growth-inc.R b/Rsrc/R/plot-growth-inc.R new file mode 100644 index 00000000..dcd05673 --- /dev/null +++ b/Rsrc/R/plot-growth-inc.R @@ -0,0 +1,14 @@ +#' Plot growth from arbitrary start age +#' +#' @param replist List object created by read_admb function +#' @return Plot growth increment for given pre-molt size, including model predictions and data +#' @export +plot_growth_inc <- function(replist){ + A <- replist + df <- data.frame(sex=as.factor(A$iMoltIncSex),obs=A$pMoltInc, pred=A$dMoltInc,size=A$dPreMoltSize) + p <- ggplot(df) + p <- p + geom_line(aes(x=size,y=obs, colour=sex)) + p <- p + geom_point(aes(x=size,y=pred, colour=sex)) + p <- p + labs(x="Pre-molt size",y="Molting increment") + return(p) +} diff --git a/Rsrc/R/plot-growth.R b/Rsrc/R/plot-growth.R new file mode 100644 index 00000000..068378eb --- /dev/null +++ b/Rsrc/R/plot-growth.R @@ -0,0 +1,34 @@ +#' Plot growth from arbitrary start age +#' +#' @param replist List object created by read_admb function +#' @return Plot natural mortality over time and size +#' @export +plot_growth <- function(replist){ + A <- replist + df <- data.frame(A$mean_size) + nclass<-length(df[1,]) + colnames(df) <- 1:nclass + nrow <- dim(df)[1] + # Always saves for both sexes??? + df$sex <- c(rep(1,length=nrow/2),rep(2,length=nrow/2)) + mdf <- melt(df,id=c("sex")) + + p <- ggplot(mdf,aes(x=as.factor(variable),y=value)) + p <- p + geom_line(aes(as.numeric(variable),value),stat="identity") + p <- p + labs(x="Time (years)",y="Mean size (mm)") + p <- p + facet_wrap(~sex,scale="free") +ggtheme + + #nyr <- nclass + #df<- data.frame(A$growth_matrix) + #df$sex <- c(rep(1,length=nrow/2),rep(2,length=nrow/2)) + #df$time <- 1:nyr + #mdf <- melt(df,id=c("sex","time")) + #p2 <- ggplot(mdf,aes(x=time,y=as.double(variable),z=value)) + #p2 <- p2 + geom_tile(aes(fill = value)) + #p2 <- p2 + stat_contour(geom="polygon", aes(fill=(value))) + #p2 <- p2 + labs(x="time",y="size bin",fill="Density") + #p2 <- p2 + facet_wrap(~sex,scale="free") +# +# plot_multiple(p2,p) + return(p) +} diff --git a/Rsrc/R/plot-naturalmortality.R b/Rsrc/R/plot-naturalmortality.R new file mode 100644 index 00000000..f9444515 --- /dev/null +++ b/Rsrc/R/plot-naturalmortality.R @@ -0,0 +1,24 @@ +#' Plot natural mortality +#' +#' @param replist List object created by read_admb function +#' @return Plot natural mortality over time and size +#' @export +plot_naturalmortality <- function(replist){ + A <- replist + df <- data.frame(A$M) + colnames(df) <- A$mid_points + nrow <- dim(A$M)[1] + # Always saves for both sexes??? + df$sex <- c(rep(1,length=nrow/2),rep(2,length=nrow/2)) + df$Year <- A$mod_yrs + mdf <- melt(df,id=c("sex","Year")) + + p <- ggplot(mdf,aes(x=Year,y=as.double(variable),z=value)) + p <- p + geom_tile(aes(fill = value)) + p <- p + stat_contour(geom="polygon", aes(fill=(value))) + p <- p + labs(x="Year",y="size bin",fill="M") + p <- p + facet_wrap(~sex,scale="free") + p2 <- ggplot(mdf,aes(x=Year,y=value)) + p2 <- p2 + geom_line() + ggtheme + labs(y="Natural mortality") + plot_multiple(p2,p) +} diff --git a/Rsrc/R/plot-recruitment.R b/Rsrc/R/plot-recruitment.R new file mode 100644 index 00000000..137dcd1d --- /dev/null +++ b/Rsrc/R/plot-recruitment.R @@ -0,0 +1,41 @@ +#' Plot predicted recruitment and approximate asymptotic error-bars +#' +#' +#' @param replist List object created by read_admb function +#' @return Plot of predicted recruitment +#' @export +plot_recruitment <- function(replist){ + A <- replist + df <- get_recruitment(replist) + p <- ggplot(df,aes(x=factor(year),y=exp(log_rec))) + p <- p + geom_bar(stat = "identity", alpha=0.4) + p <- p + geom_pointrange(aes(factor(year),exp(log_rec),ymax=ub,ymin=lb)) + p <- p + labs(x="Year",y="Recruitment") + pRecruitment <- p + ggtheme + return(pRecruitment) +} + +#' Plot predicted recruitment across model runs +#' +#' +#' @param data A list of multiple objects created by read_admb function +#' @param modnames A vector of model names included in \code{data} +#' @return Plot of predicted recruitment compared across models +#' @author Cole Monnahan Kelli Johnson +#' @export +plot_models_recruitment <- function(data, modnames=NULL ){ + if (is.null(modnames)) + modnames = paste("Model ",1:length(data)) + if (length(data)!=length(modnames)) + stop("Holy moly, unequal object lengths") + + recs <- lapply(data, get_recruitment) + df <- do.call("rbind", Map(cbind, recs, modname = modnames)) + + p <- ggplot(df,aes(x=factor(year),y=exp(log_rec), group=modname, colour=modname)) + p <- p + geom_line(stat = "identity", alpha=0.4) + p <- p + geom_pointrange(aes(factor(year),exp(log_rec),ymax=ub,ymin=lb)) + p <- p + labs(x="Year", y="Recruitment") + pRecruitment <- p + ggtheme + return(pRecruitment) +} \ No newline at end of file diff --git a/Rsrc/R/plot-selectivity.R b/Rsrc/R/plot-selectivity.R new file mode 100644 index 00000000..daf70710 --- /dev/null +++ b/Rsrc/R/plot-selectivity.R @@ -0,0 +1,68 @@ +#' Get selectivity +#' +#' @param replist List object created by read_admb function +#' @param type =1 Capture, =2 Retained, =3 Discarded selectivity +#' @return List of selectivities +#' @export +get_selectivity <- function(replist,type=1){ + A <- replist + df <- as.data.frame(cbind(A$slx_capture)) + colnames(df) <- c("year", "sex", "fleet", as.character(A$mid_points)) + mdf <- melt(df,id=1:3) + #fleet <- unique(mdf$fleet) + #sex <- unique(mdf$sex) + #i <- 1 + #sdf <- list() + #for(k in fleet) + #{ + #for(h in sex) + #{ + #tmpdf <- subset(mdf,fleet %in% k & sex %in% h) + #if(dim(tmpdf)[1]!=0) + #{ + #sdf[[i]] <- cbind(tmpdf) + #i <- i+1 + #print(i) + #} + #} + #} + return(mdf) +} + +#' Plot selectivity +#' +#' @param replist List object created by read_admb function +#' @return Plot of selectivity +#' @export +plot_selectivity <- function(replist){ + A <- replist + sdf <- get_selectivity(replist) + + p <- ggplot(data=sdf,x=mid_points) + p <- p + geom_line(aes(as.numeric(variable),value),stat="identity") + # p <- p + geom_line(aes(as.numeric(variable),pred),col="red") + p <- p + labs(y="Selectivity",x="size bin") + p <- p + facet_wrap(~fleet+sex) + ggtheme + #p <- p + facet_wrap(~fleet) + ggtheme + print(p) + + pSelectivity <- lapply(sdf,FUN = function(x,p){p %+% x},p=p) + #n <- length(M) + #mdf <- NULL + #for(i in 1:n) + #{ + #df <- data.frame(Model=names(M)[i],logSel=M[[i]]$log_sel) + #colnames(df)<-c("Model","Gear","Sex","Year",M[[i]]$age) +# + #mdf <- rbind(mdf,melt(df,id=c("Model","Gear","Sex","Year"))) + #} +# + #p <- ggplot(mdf,aes(x=Year,y=as.double(variable),z=exp(value)/max(exp(value)))) + #p <- p + stat_contour(aes(colour = ..level..)) + #p <- p + labs(x="Year",y="Age",colour="Selectivity") + ## p <- p + stat_contour(geom="polygon", aes(fill=exp(value))) + #p <- p + facet_wrap(~Model+Gear+Sex,scale="free") + #print(p + .THEME) + + return(pSelectivity) +} diff --git a/Rsrc/R/plot-sizecomp.R b/Rsrc/R/plot-sizecomp.R new file mode 100644 index 00000000..60707631 --- /dev/null +++ b/Rsrc/R/plot-sizecomp.R @@ -0,0 +1,115 @@ +#' Get observed and predicted size composition values +#' +#' TODO: Insert more information here. +#' +#' @param replist List object created by read_admb function +#' @return List of observed and predicted size composition values +#' @export +get_sizecomp <- function(replist){ + A <- replist + df <- as.data.frame(cbind(A$d3_SizeComps[,1:8],A$d3_obs_size_comps)) + pf <- as.data.frame(cbind(A$d3_SizeComps[,1:8],A$d3_pre_size_comps)) + rf <- as.data.frame(cbind(A$d3_SizeComps[,1:8],A$d3_res_size_comps)) + colnames(df) <- tolower(c("Year", "Seas", "Fleet", "Sex", "Type", "Shell", + "Maturity", "Nsamp", as.character(A$mid_points))) + colnames(rf) <- colnames(pf) <- colnames(df) + mdf <- melt(df,id=1:8) + mpf <- melt(pf,id=1:8) + mrf <- melt(rf,id=1:8) + + fleet <- unique(mdf$fleet) + sex <- unique(mdf$sex) + type <- unique(mdf$type) + shell <- unique(mdf$shell) + + i <- 1 + + sdf <- list() + + for(k in fleet) + { + for(h in sex) + { + for(t in type) + { + for(s in shell) + { + tmpdf <- subset(mdf,fleet %in% k & sex %in% h & type %in% t & shell %in% s) + tmppf <- subset(mpf,fleet %in% k & sex %in% h & type %in% t & shell %in% s) + tmprf <- subset(mrf,fleet %in% k & sex %in% h & type %in% t & shell %in% s) + if(dim(tmpdf)[1]!=0) + { + sdf[[i]] <- cbind(tmpdf,pred=tmppf$value,resid=tmprf$value) + i <- i+1 + } + } + } + } + } + return(sdf) +} + +#' Plot observed and predicted size composition +#' +#' TODO: Insert more information here. +#' +#' @param replist List object created by read_admb function +#' @return Plot of observed and predicted size composition +#' @export +plot_sizecomp <- function(replist,which_plots="all"){ + A <- replist + sdf <- get_sizecomp(replist) + + p <- ggplot(data=sdf[[1]]) + p <- p + geom_bar(aes(variable,value),stat="identity") + p <- p + geom_line(aes(as.numeric(variable),pred),col="red") + p <- p + scale_x_discrete(breaks=pretty(A$mid_points)) + p <- p + labs(x="Size (mm)",y="proportion ") + p <- p + facet_wrap(~year) + ggtheme + + if (which_plots=="all") + pSizeComps <- lapply(sdf,FUN = function(x,p){p %+% x},p=p) + else + { + if (!is.numeric(which_plots)) + { + print("Error, need numeric argument for which_plots=") + stop() + } + pSizeComps <- lapply(sdf,FUN = function(x,p){p %+% x},p=p)[which_plots] + } + return(pSizeComps) +} + +#' Plot size composition residuals +#' +#' TODO: Insert more information here. +#' +#' @param replist List object created by read_admb function +#' @return Bubble plot of size composition residuals +#' @export +plot_sizecomp_res <- function(replist,which_plots="all"){ + A <- replist + sdf <- get_sizecomp(replist) + + p <- ggplot(data=sdf[[1]]) + p <- p + geom_point(aes(x=factor(year),variable,col=factor(sign(resid)),size=abs(resid)) + ,alpha=0.6) + p <- p + scale_size_area(max_size=10) + p <- p + labs(x="Year",y="Length",col="Sign",size="Residual") + p <- p + scale_x_discrete(breaks=pretty(A$mod_yrs)) + p <- p + scale_y_discrete(breaks=pretty(A$mid_points)) + p <- p + ggtheme + if (which_plots=="all") + pSizeComps <- lapply(sdf,FUN = function(x,p){p %+% x},p=p) + else + { + if (!is.numeric(which_plots)) + { + print("Error, need numeric argument for which_plots=") + stop() + } + pSizeComps <- lapply(sdf,FUN = function(x,p){p %+% x},p=p)[which_plots] + } + return(pSizeComps) +} diff --git a/Rsrc/R/plot-sizetransition.R b/Rsrc/R/plot-sizetransition.R new file mode 100644 index 00000000..bf155738 --- /dev/null +++ b/Rsrc/R/plot-sizetransition.R @@ -0,0 +1,41 @@ +#' Plot size transition +#' +#' @param replist List object created by read_admb function +#' @return Plot of size transition matrix +#' @export +plot_sizetransition <- function(replist){ + A <- replist + df <- data.frame(stm = A$size_transition_M,stm_f = A$size_transition_F) + colnames(df) <- A$mid_points + nrow <- dim(A$size_transition_M)[2] + df$sex <- c(rep(1,length=nrow),rep(2,length=nrow)) + df$col <- A$mid_points + mdf <- melt(df,id=c("sex","col")) + + p <- ggplot(mdf) + p <- p + geom_point(aes(variable,col,size=value),alpha=0.4,col="red") + p <- p + scale_size_area(max_size=10) + p <- p + labs(x="Post-molt carapace width",y="Pre-molt carapace width",size="Probability") + p <- p + facet_wrap(~sex) + pSizeTransition <- p + return(pSizeTransition) +} + +# THis routine includs the molting probability +plot_growthtransition <- function(replist){ + A <- replist + df <- data.frame(stm = A$size_transition %*% A$P) + colnames(df) <- A$mid_points + nrow <- dim(A$size_transition)[2] + df$sex <- c(rep(1,length=nrow),rep(2,length=nrow)) + df$col <- A$mid_points + mdf <- melt(df,id=c("sex","col")) + + p <- ggplot(mdf) + p <- p + geom_point(aes(variable,col,size=value),alpha=0.4,col="red") + p <- p + scale_size_area(max_size=10) + p <- p + labs(x="Post-molt carapace width",y="Pre-molt carapace width",size="Probability") + p <- p + facet_wrap(~sex) + pGrowthTransition <- p + return(pGrowthTransition) +} diff --git a/Rsrc/R/plot-ssb.R b/Rsrc/R/plot-ssb.R new file mode 100644 index 00000000..1a1989d2 --- /dev/null +++ b/Rsrc/R/plot-ssb.R @@ -0,0 +1,26 @@ +#' Plot predicted spawning stock biomass (ssb) +#' +#' Spawning biomass may be defined as all males or some combination of males and females +#' +#' @param replist List object created by read_admb function +#' @return Plot of predicted mature male biomass +#' @export +plot_ssb <- function(replist){ + + df <- get_ssb(replist) + #A <- replist +# + #dfpar <- data.frame(par=A$fit$names,log_mmb=A$fit$est,log_sd=A$fit$std) + #df <- subset(dfpar,par=="sd_log_mmb")[,-1] + #df$year <- A$mod_yrs + #df$lb <- exp(df$log_mmb - 1.96*df$log_sd) + #df$ub <- exp(df$log_mmb + 1.96*df$log_sd) +# + p <- ggplot(df) + p <- p + geom_line(aes(x=year,y=exp(log_mmb))) + p <- p + geom_ribbon(aes(x=year,ymax=ub,ymin=lb),alpha=0.3) + p <- p + labs(x="Year",y="Spawning biomass") + + pSSB <- p + ggtheme + return(pSSB) +} diff --git a/Rsrc/R/plot_multiple.R b/Rsrc/R/plot_multiple.R new file mode 100644 index 00000000..7b4ee377 --- /dev/null +++ b/Rsrc/R/plot_multiple.R @@ -0,0 +1,48 @@ +#' Plot multiple figures on a page +#' +#' From http://www.cookbook-r.com/Graphs/Multiple_graphs_on_one_page_(ggplot2)/ +#' +#' ggplot objects can be passed in ..., or to plotlist (as a list of ggplot objects) +#' +#' If the layout is something like matrix(c(1,2,3,3), nrow=2, byrow=TRUE), +#' then plot 1 will go in the upper left, 2 will go in the upper right, and +#' 3 will go all the way across the bottom. +#' +#' @param plotlist ggplot objects +#' @param file does nothing (yet) +#' @param cols Number of columns in layout +#' @param layout A matrix specifying the layout. If present, 'cols' is ignored. +#' @return page with figures +#' @export +plot_multiple <- function(..., plotlist=NULL, file, cols=1, layout=NULL) { + require(grid) + # Make a list from the ... arguments and plotlist + plots <- c(list(...), plotlist) + numPlots = length(plots) + # If layout is NULL, then use 'cols' to determine layout + if (is.null(layout)) { + # Make the panel + # ncol: Number of columns of plots + # nrow: Number of rows needed, calculated from # of cols + layout <- matrix(seq(1, cols * ceiling(numPlots/cols)), + ncol = cols, nrow = ceiling(numPlots/cols)) + } + + if (numPlots==1) { + print(plots[[1]]) + + } else { + # Set up the page + grid.newpage() + pushViewport(viewport(layout = grid.layout(nrow(layout), ncol(layout)))) + + # Make each plot, in the correct location + for (i in 1:numPlots) { + # Get the i,j matrix positions of the regions that contain this subplot + matchidx <- as.data.frame(which(layout == i, arr.ind = TRUE)) + + print(plots[[i]], vp = viewport(layout.pos.row = matchidx$row, + layout.pos.col = matchidx$col)) + } + } +} diff --git a/Rsrc/R/read-admb.R b/Rsrc/R/read-admb.R new file mode 100644 index 00000000..ca188196 --- /dev/null +++ b/Rsrc/R/read-admb.R @@ -0,0 +1,135 @@ +#' Read ADMB output files +#' +#' Read ADMB output files .rep, .par, and .cor and return an R object of type 'list' +#' +#' @author Steve Martell, Anders Nielsen, Athol Whitten +#' @param repfile ADMB output files to be read (no extension needed) +#' @return object of type 'list' with ADMB outputs as list elements +#' @export +read_admb <- function(repfile){ + ret <- read_fit(repfile) + fn <- paste(repfile, '.rep', sep='') + + A <- read_rep(fn) + A$fit <- ret + A$run_name <- fn + + pfn <- paste(repfile, '.psv', sep='') + if(file.exists(pfn)) + A$post.samp <- read_psv(pfn) + + return(A) +} + +#' +#' Read ADMB .par, .std, and .cor file and return an R object of type 'list' of estimates and correlations +#' +#' @author Steve Martell, Anders Nielsen, Athol Whitten +#' @param repfile name of ADMB output file to be read (no extension needed) +#' @return object of type 'list' with ADMB outputs therein +#' @export +read_fit <- function(repfile){ + ret <- list() + parfile <- as.numeric(scan(paste(repfile,'.par', sep=''), what='', n=16, quiet=TRUE)[c(6,11,16)]) + ret$nopar <- as.integer(parfile[1]) + ret$nlogl <- parfile[2] + ret$maxgrad <- parfile[3] + file <- paste(repfile,'.cor', sep='') + if(file.exists(file)) + { + lin <- readLines(file) + ret$npar <- length(lin)-2 + ret$logDetHess <- as.numeric(strsplit(lin[1], '=')[[1]][2]) + sublin <- lapply(strsplit(lin[1:ret$npar+2], ' '),function(x)x[x!='']) + ret$names <- unlist(lapply(sublin,function(x)x[2])) + ret$est <- as.numeric(unlist(lapply(sublin,function(x)x[3]))) + ret$std <- as.numeric(unlist(lapply(sublin,function(x)x[4]))) + ret$cor <- matrix(NA, ret$npar, ret$npar) + corvec <- unlist(sapply(1:length(sublin), function(i)sublin[[i]][5:(4+i)])) + ret$cor[upper.tri(ret$cor, diag=TRUE)] <- as.numeric(corvec) + ret$cor[lower.tri(ret$cor)] <- t(ret$cor)[lower.tri(ret$cor)] + ret$cov <- ret$cor*(ret$std%o%ret$std) + } + return(ret) +} + +#' Read ADMB .rep file +#' +#' Read ADMB .rep file and return an R object of type 'list' +#' +#' @author Steve Martell +#' @param repfile name of ADMB output file to be read (no extension needed) +#' @return object of type 'list' with ADMB outputs therein +#' @export +read_rep <- function(fn) { + + options(warn=-1) #Suppress the NA message in the coercion to double + + repfile <- scan(fn,what="character",flush=TRUE,blank.lines.skip=FALSE,quiet=TRUE) + idx <- sapply(as.double(repfile),is.na) + vnam <- repfile[idx] #list names + # cat(vnam) + nv <- length(vnam) #number of objects + A <- list() + ir <- 0 + for(i in 1:nv) + { + ir <- match(vnam[i],repfile) + if(i!=nv) irr=match(vnam[i+1],repfile) else irr=length(repfile)+1 #next row + dum=NA + if(irr-ir==2) dum=as.double(scan(fn,skip=ir,nlines=1,quiet=TRUE,what="")) + if(irr-ir>2) + { + # ncols <- 0 + # irows <- ir:irr-1 + # for(j in irows) + # { + # tmp=as.double(scan(fn,skip=j,nlines=1,quiet=TRUE,what="")) + # if(length(tmp)>ncols) ncols <- length(tmp) + # #print(paste(1:ncols)) + # } + # cname <- paste(1:ncols) + # dum=as.matrix(read.table(fn,skip=ir,nrow=irr-ir-1,fill=TRUE,col.names=cname)) + # cat("\n ir ",ir," irr ",irr) + dum=as.matrix(read.table(fn,skip=ir,nrow=irr-ir-1,fill=TRUE,row.names = NULL)) + } + + + if(is.numeric(dum))#Logical test to ensure dealing with numbers + { + A[[vnam[i]]]=dum + } + } + options(warn=0) + + return(A) +} + +#' Read ADMB .psv file +#' +#' Read ADMB .psv file and return an R object of type 'list' +#' +#' @author Steve Martell +#' @param repfile name of ADMB output file to be read (no extension needed) +#' @return object of type 'list' with ADMB outputs therein +#' @export +read_psv <- function(fn, nsamples=10000) +{ + #This function reads the binary output from ADMB + #-mcsave command line option. + #fn = paste(repfile,'.psv',sep='') + filen <- file(fn, "rb") + nopar <- readBin(filen, what = integer(), n = 1) + mcmc <- readBin(filen, what = numeric(), n = nopar * nsamples) + mcmc <- matrix(mcmc, byrow = TRUE, ncol = nopar) + close(filen) + return(mcmc) +} + +# A simple function for creating transparent colors +# Author: Nathan Stephens (hacks package) +colr <- function(col.pal=1,a=1) +{ + col.rgb<-col2rgb(col.pal)/255 + rgb(t(col.rgb),alpha=a) +} diff --git a/Rsrc/R/set-ggtheme.R b/Rsrc/R/set-ggtheme.R new file mode 100644 index 00000000..c60a02f4 --- /dev/null +++ b/Rsrc/R/set-ggtheme.R @@ -0,0 +1,18 @@ +#' Set plotting theme for ggplot2 via gmr +#' +#' Gives user control over plot theme by running ggplot2 functions +#' that do the same. This allows a user to set the theme without +#' independently loading the ggplot2 package. +#' +#' @param name of desired theme +#' @return Sets ggplot2 theme for current working session +#' @export +set_ggtheme <- function(theme){ + switch(theme, + bw = ggtheme <<- theme_bw(), + gray = ggtheme <<- theme_gray(), + classic = ggtheme <<- theme_classic(), + minimal = ggtheme <<- theme_minimal() + ) + message("The ggplot theme has been set to ", theme, " for this working session") +} \ No newline at end of file diff --git a/Rsrc/R/shiny_gmacs.R b/Rsrc/R/shiny_gmacs.R new file mode 100644 index 00000000..4e75d022 --- /dev/null +++ b/Rsrc/R/shiny_gmacs.R @@ -0,0 +1,51 @@ +#' Plot Gmacs on shiny app +#' +#' @param replist List object created by read_admb function +#' @export +shiny_gmacs <- function(gmrep) { + shinyApp( ui = pageWithSidebar( + # Application title + headerPanel("Gmacs Model Outputs"), + sidebarPanel( + selectInput('plotType',"Select variable to plot", + c( "Spawning Biomass", + "Fit to Index Data", + "Retained Catch", + "Retained Catch Residuals", + "Growth Transition", + "Growth curve", + "Natural Mortality", + "Size Composition" + ), + selected="Mature Male Biomass")), + # Show plot + mainPanel( plotOutput("distPlot") ) ), +server = function(input, output) { output$distPlot <- renderPlot( + if(input$plotType == "Spawning Biomass") + plot_ssb(gmrep) + else if(input$plotType == "Recruitment") + plot_recruitment(gmrep) + else if(input$plotType == "Growth Transition") + plot_sizetransition(gmrep) + else if(input$plotType == "Growth curve") + plot_growth(gmrep) + else if(input$plotType == "Natural Mortality") + plot_naturalmortality(gmrep) + else if(input$plotType == "Retained Catch") + plot_catch(gmrep) + else if(input$plotType == "Retained Catch Residuals") + plot_catch(gmrep,plot_res=T) + #else if(input$plotType == "Discarded Catch") + #print(pCatch[[2]] + .THEME) + else if(input$plotType == "Fit to Index Data") + plot_cpue(gmrep) + #plot_sizecomp(gmrep,which_plots=c(1)) + #plot_sizecomp(gmrep,which_plots=c(11)) + #plot_sizecomp_res(gmrep) + #plot_selectivity(gmrep) + else if(input$plotType == "Size Composition") + plot_sizecomp(gmrep,which_plots=c(1)) + ) + } + ) +} \ No newline at end of file diff --git a/Rsrc/README.md b/Rsrc/README.md new file mode 100644 index 00000000..654be263 --- /dev/null +++ b/Rsrc/README.md @@ -0,0 +1,33 @@ +# gmr +### R code for Gmacs + +The `gmr` R package is under development in support of the [Gmacs](https://github.com/seacode/gmacs) stock assessment modeling framework. More information about the package can be found on the [Gmacs Wiki](https://github.com/seacode/gmacs/wiki), under the [R Package](https://github.com/seacode/gmacs/wiki/4.-R-Package) section. + +The most recent release of the `gmr` package can be downloaded and installed from Github through R: +```S +install.packages("devtools") +install.packages("shiny") +devtools::install_github("seacode/gmacs",subdir="/Rsrc",ref="develop") +``` + + +Once the `gmr` package is installed, it can be loaded in the regular manner: + +```S +library(gmr) +```` + +To install previous release versions of `gmr`, use, for example: + +```S +devtools::install_github("seacode/gmacs/Rsrc", ref = "V1.0") +```` + +To install current development versions of `gmr`, use: + +```S +devtools::install_github("seacode/gmacs/Rsrc", ref = "develop") +``` + +### Useage note +> The R code available in this package comes with no warranty or guarantee of accuracy. It merely represents an ongoing attempt to integrate output plotting with statistical and diagnostical analsyses for Gmacs. It is absolutely necessary that prior to use with a new application, the user checks the output manually to verify that there are no plotting or statistical bugs which could incorrectly represent the output files being analyzed. diff --git a/Rsrc/build_gmr.sh b/Rsrc/build_gmr.sh new file mode 100755 index 00000000..396c5a40 --- /dev/null +++ b/Rsrc/build_gmr.sh @@ -0,0 +1,3 @@ +R CMD BATCH roxygenize.R +R CMD build gmr +R CMD INSTALL gmr_*.tar.gz diff --git a/Rsrc/gmacs.R b/Rsrc/gmacs.R new file mode 100644 index 00000000..97de54ab --- /dev/null +++ b/Rsrc/gmacs.R @@ -0,0 +1,58 @@ +#========================================================================================================= +# +# gmr Script for Gmacs: Example for BBRKC Demonstration Model +# Authors: Athol Whitten, Jim Ianelli +# Info: https://github.com/seacode/gmr +# +#========================================================================================================= + +# Load gmr package for Gmacs: +library(gmr) + +# Set working directory to that containing Gmacs model results: +# setwd("c:/seacode/gmacs/examples/demo") +# setwd("~/_mymods/seacode/gmacs/examples/demo") +# setwd("~/_mymods/seacode/gmacs/examples/bbrkc") +setwd("/Users/stevenmartell1/Documents/CURRENT PROJECTS/GMACS/examples/bbrkc") +# setwd("c:/Users/Crab2015/gmacs/examples/bbrkc") +# Set theme for ggplot2 (works for themes classic, minimal, gray, bw): +set_ggtheme('bw') + +# Read report file and create gmacs report object (a list): +gmrep <- read_admb('gmacs') + +# Get plots of interest: +plot_catch(gmrep) +plot_growth(gmrep) +plot_catch(gmrep,plot_res=T) +names(gmrep$fit) +plot_growth_inc(gmrep) +plot_cpue(gmrep) + +plot_sizecomp(gmrep,which_plots=c(1)) +plot_sizecomp(gmrep) +plot_sizecomp_res(gmrep, which_plots=c(1)) + + +plot_sizecomp(gmrep,which_plots=c(1)) +plot_sizecomp(gmrep,which_plots=c(2)) +plot_sizecomp(gmrep,which_plots=c(5)) + + +plot_sizecomp(gmrep,which_plots=c(7)) +plot_sizecomp(gmrep,which_plots=c(8)) + + + +plot_sizecomp_res(gmrep) +plot_sizetransition(gmrep) + +plot_selectivity(gmrep) +plot_recruitment(gmrep) +plot_datarange(gmrep) +plot_ssb(gmrep) +plot_naturalmortality(gmrep) + +shiny_gmacs(gmrep) + +#========================================================================================================= diff --git a/Rsrc/man/DESCRIPTION b/Rsrc/man/DESCRIPTION new file mode 100644 index 00000000..b8bc23a9 --- /dev/null +++ b/Rsrc/man/DESCRIPTION @@ -0,0 +1,17 @@ +Package: gmr +Title: Plotting and analysis tools for the Gmacs stock assessment framework +Description: gmr is a set of tools for analysing data and outputs from Gmacs + stock assessment models. The package streamlines the process of taking + text-based ADMB output files and creating visual plots of both input data + and fitted model results. +Authors@R: c(person("Whitten", "Athol", email = "athol.whitten@gmail.com", role + = c("aut","cre")), person("Ianelli", "Jim", email = "jim.ianelli@noaa.gov", + role = c("aut","cre")), person("Martell", "Steve", role = "aut")) +URL: https://github.com/seacode/gmr +Version: 0.2 +Depends: + R (>= 3.0.0), + ggplot2 (>= 0.9.3.1) +Imports: + reshape2 (>= 1.2.2), +License: MIT diff --git a/Rsrc/man/README.md b/Rsrc/man/README.md new file mode 100644 index 00000000..4a3d622c --- /dev/null +++ b/Rsrc/man/README.md @@ -0,0 +1,31 @@ +# gmr +### R code for Gmacs + +The `gmr` R package is under development in support of the [Gmacs](https://github.com/seacode/gmacs) stock assessment modeling framework. More information about the package can be found on the [Gmacs Wiki](https://github.com/seacode/gmacs/wiki), under the [R Package](https://github.com/seacode/gmacs/wiki/4.-R-Package) section. + +The most recent release of the `gmr` package can be downloaded and installed from Github through R: +```S +install.packages("devtools") +devtools::install_github("seacode/gmr") +``` + +Once the `gmr` package is installed, it can be loaded in the regular manner: + +```S +library(gmr) +```` + +To install previous release versions of `gmr`, use, for example: + +```S +devtools::install_github("seacode/gmr", ref = "V1.0") +```` + +To install current development versions of `gmr`, use: + +```S +devtools::install_github("seacode/gmr", ref = "develop") +``` + +### Useage note +> The R code available in this package comes with no warranty or guarantee of accuracy. It merely represents an ongoing attempt to integrate output plotting with statistical and diagnostical analsyses for Gmacs. It is absolutely necessary that prior to use with a new application, the user checks the output manually to verify that there are no plotting or statistical bugs which could incorrectly represent the output files being analyzed. diff --git a/Rsrc/man/get_selectivity.Rd b/Rsrc/man/get_selectivity.Rd new file mode 100644 index 00000000..0ac97e19 --- /dev/null +++ b/Rsrc/man/get_selectivity.Rd @@ -0,0 +1,19 @@ +% Generated by roxygen2 (4.0.2): do not edit by hand +\name{get_selectivity} +\alias{get_selectivity} +\title{Get selectivity} +\usage{ +get_selectivity(replist, type = 1) +} +\arguments{ +\item{replist}{List object created by read_admb function} + +\item{type}{=1 Capture, =2 Retained, =3 Discarded selectivity} +} +\value{ +List of selectivities +} +\description{ +Get selectivity +} + diff --git a/Rsrc/man/get_sizecomp.Rd b/Rsrc/man/get_sizecomp.Rd new file mode 100644 index 00000000..0562098c --- /dev/null +++ b/Rsrc/man/get_sizecomp.Rd @@ -0,0 +1,17 @@ +% Generated by roxygen2 (4.0.2): do not edit by hand +\name{get_sizecomp} +\alias{get_sizecomp} +\title{Get observed and predicted size composition values} +\usage{ +get_sizecomp(replist) +} +\arguments{ +\item{replist}{List object created by read_admb function} +} +\value{ +List of observed and predicted size composition values +} +\description{ +TODO: Insert more information here. +} + diff --git a/Rsrc/man/gmacs.R b/Rsrc/man/gmacs.R new file mode 100644 index 00000000..80ef80dc --- /dev/null +++ b/Rsrc/man/gmacs.R @@ -0,0 +1,42 @@ +#========================================================================================================= +# +# gmr Script for Gmacs: Example for BBRKC Demonstration Model +# Authors: Athol Whitten, Jim Ianelli +# Info: https://github.com/seacode/gmr +# +#========================================================================================================= + +# Load gmr package for Gmacs: +# library(gmr) + +# Set working directory to that containing Gmacs model results: +# setwd("c:/seacode/gmacs/examples/demo") +# setwd("~/_mymods/seacode/gmacs/examples/demo") + +# Set theme for ggplot2 (works for themes classic, minimal, gray, bw): +set_ggtheme('bw') + +# Read report file and create gmacs report object (a list): +gmrep <- read_admb('gmacs') + +# Get plots of interest: +plot_catch(gmrep) +plot_catch(gmrep,plot_res=T) + +plot_sizecomp(gmrep,which_plots=c(1)) +plot_sizecomp(gmrep) +plot_sizecomp_res(gmrep, which_plots=c(1)) + +plot_sizecomp(gmrep,which_plots=c(11)) +plot_sizecomp_res(gmrep) +plot_sizetransition(gmrep) + +plot_selectivity(gmrep) +plot_recruitment(gmrep) +plot_ssb(gmrep) +plot_naturalmortality(gmrep) +plot_naturalmortality(gmrep) + +shiny_gmacs(gmrep) + +#========================================================================================================= diff --git a/Rsrc/man/gmr.Rd b/Rsrc/man/gmr.Rd new file mode 100644 index 00000000..e7a1448f --- /dev/null +++ b/Rsrc/man/gmr.Rd @@ -0,0 +1,11 @@ +% Generated by roxygen2 (4.0.2): do not edit by hand +\docType{package} +\name{gmr} +\alias{gmr} +\alias{gmr-package} +\title{gmr: R code for Gmacs} +\description{ +gmr is a set of tools for analysing data and outputs +related to Gmacs stock assessment models. +} + diff --git a/Rsrc/man/gmr.Rproj b/Rsrc/man/gmr.Rproj new file mode 100644 index 00000000..9f964990 --- /dev/null +++ b/Rsrc/man/gmr.Rproj @@ -0,0 +1,18 @@ +Version: 1.0 + +RestoreWorkspace: Default +SaveWorkspace: Default +AlwaysSaveHistory: Default + +EnableCodeIndexing: Yes +UseSpacesForTab: Yes +NumSpacesForTab: 2 +Encoding: UTF-8 + +RnwWeave: knitr +LaTeX: pdfLaTeX + +BuildType: Package +PackageUseDevtools: Yes +PackageInstallArgs: --no-multiarch --with-keep.source +PackageRoxygenize: rd,collate,namespace diff --git a/Rsrc/man/plot_catch.Rd b/Rsrc/man/plot_catch.Rd new file mode 100644 index 00000000..0792bcc6 --- /dev/null +++ b/Rsrc/man/plot_catch.Rd @@ -0,0 +1,19 @@ +% Generated by roxygen2 (4.0.2): do not edit by hand +\name{plot_catch} +\alias{plot_catch} +\title{Plot observed and predicted catch values} +\usage{ +plot_catch(replist, plot_res = FALSE) +} +\arguments{ +\item{replist}{List object created by read_admb function} + +\item{plot_res}{plot residuals only (default=F)} +} +\value{ +Plot of catch history (observed) and predicted values +} +\description{ +Plot observed and predicted catch values +} + diff --git a/Rsrc/man/plot_cpue.Rd b/Rsrc/man/plot_cpue.Rd new file mode 100644 index 00000000..34401ad3 --- /dev/null +++ b/Rsrc/man/plot_cpue.Rd @@ -0,0 +1,17 @@ +% Generated by roxygen2 (4.0.2): do not edit by hand +\name{plot_cpue} +\alias{plot_cpue} +\title{Plot cpue or other indices} +\usage{ +plot_cpue(replist) +} +\arguments{ +\item{replist}{List object created by read_admb function} +} +\value{ +Plot of observed and predicted incices +} +\description{ +Plot cpue or other indices +} + diff --git a/Rsrc/man/plot_cpue_res.Rd b/Rsrc/man/plot_cpue_res.Rd new file mode 100644 index 00000000..fc8a2f83 --- /dev/null +++ b/Rsrc/man/plot_cpue_res.Rd @@ -0,0 +1,17 @@ +% Generated by roxygen2 (4.0.2): do not edit by hand +\name{plot_cpue_res} +\alias{plot_cpue_res} +\title{Plot residuals of cpue or other indices} +\usage{ +plot_cpue_res(replist) +} +\arguments{ +\item{replist}{List object created by read_admb function} +} +\value{ +Plot of fit indices residuals +} +\description{ +Plot residuals of cpue or other indices +} + diff --git a/Rsrc/man/plot_multiple.Rd b/Rsrc/man/plot_multiple.Rd new file mode 100644 index 00000000..7fdd824e --- /dev/null +++ b/Rsrc/man/plot_multiple.Rd @@ -0,0 +1,30 @@ +% Generated by roxygen2 (4.0.2): do not edit by hand +\name{plot_multiple} +\alias{plot_multiple} +\title{Plot multiple figures on a page} +\usage{ +plot_multiple(..., plotlist = NULL, file, cols = 1, layout = NULL) +} +\arguments{ +\item{plotlist}{ggplot objects} + +\item{file}{does nothing (yet)} + +\item{cols}{Number of columns in layout} + +\item{layout}{A matrix specifying the layout. If present, 'cols' is ignored.} +} +\value{ +page with figures +} +\description{ +From http://www.cookbook-r.com/Graphs/Multiple_graphs_on_one_page_(ggplot2)/ +} +\details{ +ggplot objects can be passed in ..., or to plotlist (as a list of ggplot objects) + +If the layout is something like matrix(c(1,2,3,3), nrow=2, byrow=TRUE), +then plot 1 will go in the upper left, 2 will go in the upper right, and +3 will go all the way across the bottom. +} + diff --git a/Rsrc/man/plot_naturalmortality.Rd b/Rsrc/man/plot_naturalmortality.Rd new file mode 100644 index 00000000..5587ff21 --- /dev/null +++ b/Rsrc/man/plot_naturalmortality.Rd @@ -0,0 +1,17 @@ +% Generated by roxygen2 (4.0.2): do not edit by hand +\name{plot_naturalmortality} +\alias{plot_naturalmortality} +\title{Plot natural mortality} +\usage{ +plot_naturalmortality(replist) +} +\arguments{ +\item{replist}{List object created by read_admb function} +} +\value{ +Plot natural mortality over time and size +} +\description{ +Plot natural mortality +} + diff --git a/Rsrc/man/plot_recruitment.Rd b/Rsrc/man/plot_recruitment.Rd new file mode 100644 index 00000000..a5fcc9c5 --- /dev/null +++ b/Rsrc/man/plot_recruitment.Rd @@ -0,0 +1,17 @@ +% Generated by roxygen2 (4.0.2): do not edit by hand +\name{plot_recruitment} +\alias{plot_recruitment} +\title{Plot predicted recruitment and approximate asymptotic error-bars} +\usage{ +plot_recruitment(replist) +} +\arguments{ +\item{replist}{List object created by read_admb function} +} +\value{ +Plot of predicted recruitment +} +\description{ +Plot predicted recruitment and approximate asymptotic error-bars +} + diff --git a/Rsrc/man/plot_selectivity.Rd b/Rsrc/man/plot_selectivity.Rd new file mode 100644 index 00000000..a905e07b --- /dev/null +++ b/Rsrc/man/plot_selectivity.Rd @@ -0,0 +1,17 @@ +% Generated by roxygen2 (4.0.2): do not edit by hand +\name{plot_selectivity} +\alias{plot_selectivity} +\title{Plot selectivity} +\usage{ +plot_selectivity(replist) +} +\arguments{ +\item{replist}{List object created by read_admb function} +} +\value{ +Plot of selectivity +} +\description{ +Plot selectivity +} + diff --git a/Rsrc/man/plot_sizecomp.Rd b/Rsrc/man/plot_sizecomp.Rd new file mode 100644 index 00000000..57e76110 --- /dev/null +++ b/Rsrc/man/plot_sizecomp.Rd @@ -0,0 +1,17 @@ +% Generated by roxygen2 (4.0.2): do not edit by hand +\name{plot_sizecomp} +\alias{plot_sizecomp} +\title{Plot observed and predicted size composition} +\usage{ +plot_sizecomp(replist, which_plots = "all") +} +\arguments{ +\item{replist}{List object created by read_admb function} +} +\value{ +Plot of observed and predicted size composition +} +\description{ +TODO: Insert more information here. +} + diff --git a/Rsrc/man/plot_sizecomp_res.Rd b/Rsrc/man/plot_sizecomp_res.Rd new file mode 100644 index 00000000..ce23e306 --- /dev/null +++ b/Rsrc/man/plot_sizecomp_res.Rd @@ -0,0 +1,17 @@ +% Generated by roxygen2 (4.0.2): do not edit by hand +\name{plot_sizecomp_res} +\alias{plot_sizecomp_res} +\title{Plot size composition residuals} +\usage{ +plot_sizecomp_res(replist, which_plots = "all") +} +\arguments{ +\item{replist}{List object created by read_admb function} +} +\value{ +Bubble plot of size composition residuals +} +\description{ +TODO: Insert more information here. +} + diff --git a/Rsrc/man/plot_sizetransition.Rd b/Rsrc/man/plot_sizetransition.Rd new file mode 100644 index 00000000..728ce64e --- /dev/null +++ b/Rsrc/man/plot_sizetransition.Rd @@ -0,0 +1,17 @@ +% Generated by roxygen2 (4.0.2): do not edit by hand +\name{plot_sizetransition} +\alias{plot_sizetransition} +\title{Plot size transition} +\usage{ +plot_sizetransition(replist) +} +\arguments{ +\item{replist}{List object created by read_admb function} +} +\value{ +Plot of size transition matrix +} +\description{ +Plot size transition +} + diff --git a/Rsrc/man/read_admb.Rd b/Rsrc/man/read_admb.Rd new file mode 100644 index 00000000..0e2d3a01 --- /dev/null +++ b/Rsrc/man/read_admb.Rd @@ -0,0 +1,20 @@ +% Generated by roxygen2 (4.0.2): do not edit by hand +\name{read_admb} +\alias{read_admb} +\title{Read ADMB output files} +\usage{ +read_admb(repfile) +} +\arguments{ +\item{repfile}{ADMB output files to be read (no extension needed)} +} +\value{ +object of type 'list' with ADMB outputs as list elements +} +\description{ +Read ADMB output files .rep, .par, and .cor and return an R object of type 'list' +} +\author{ +Steve Martell, Anders Nielsen, Athol Whitten +} + diff --git a/Rsrc/man/read_fit.Rd b/Rsrc/man/read_fit.Rd new file mode 100644 index 00000000..5ad302c2 --- /dev/null +++ b/Rsrc/man/read_fit.Rd @@ -0,0 +1,20 @@ +% Generated by roxygen2 (4.0.2): do not edit by hand +\name{read_fit} +\alias{read_fit} +\title{Read ADMB .par, .std, and .cor file and return an R object of type 'list' of estimates and correlations} +\usage{ +read_fit(repfile) +} +\arguments{ +\item{repfile}{name of ADMB output file to be read (no extension needed)} +} +\value{ +object of type 'list' with ADMB outputs therein +} +\description{ +Read ADMB .par, .std, and .cor file and return an R object of type 'list' of estimates and correlations +} +\author{ +Steve Martell, Anders Nielsen, Athol Whitten +} + diff --git a/Rsrc/man/read_psv.Rd b/Rsrc/man/read_psv.Rd new file mode 100644 index 00000000..a18cdf9c --- /dev/null +++ b/Rsrc/man/read_psv.Rd @@ -0,0 +1,20 @@ +% Generated by roxygen2 (4.0.2): do not edit by hand +\name{read_psv} +\alias{read_psv} +\title{Read ADMB .psv file} +\usage{ +read_psv(fn, nsamples = 10000) +} +\arguments{ +\item{repfile}{name of ADMB output file to be read (no extension needed)} +} +\value{ +object of type 'list' with ADMB outputs therein +} +\description{ +Read ADMB .psv file and return an R object of type 'list' +} +\author{ +Steve Martell +} + diff --git a/Rsrc/man/read_rep.Rd b/Rsrc/man/read_rep.Rd new file mode 100644 index 00000000..96bcdbf5 --- /dev/null +++ b/Rsrc/man/read_rep.Rd @@ -0,0 +1,20 @@ +% Generated by roxygen2 (4.0.2): do not edit by hand +\name{read_rep} +\alias{read_rep} +\title{Read ADMB .rep file} +\usage{ +read_rep(fn) +} +\arguments{ +\item{repfile}{name of ADMB output file to be read (no extension needed)} +} +\value{ +object of type 'list' with ADMB outputs therein +} +\description{ +Read ADMB .rep file and return an R object of type 'list' +} +\author{ +Steve Martell +} + diff --git a/Rsrc/man/set_ggtheme.Rd b/Rsrc/man/set_ggtheme.Rd new file mode 100644 index 00000000..efdfb74c --- /dev/null +++ b/Rsrc/man/set_ggtheme.Rd @@ -0,0 +1,19 @@ +% Generated by roxygen2 (4.0.2): do not edit by hand +\name{set_ggtheme} +\alias{set_ggtheme} +\title{Set plotting theme for ggplot2 via gmr} +\usage{ +set_ggtheme(theme) +} +\arguments{ +\item{name}{of desired theme} +} +\value{ +Sets ggplot2 theme for current working session +} +\description{ +Gives user control over plot theme by running ggplot2 functions +that do the same. This allows a user to set the theme without +independently loading the ggplot2 package. +} + diff --git a/Rsrc/man/shiny_gmacs.Rd b/Rsrc/man/shiny_gmacs.Rd new file mode 100644 index 00000000..c320b0e9 --- /dev/null +++ b/Rsrc/man/shiny_gmacs.Rd @@ -0,0 +1,14 @@ +% Generated by roxygen2 (4.0.2): do not edit by hand +\name{shiny_gmacs} +\alias{shiny_gmacs} +\title{Plot Gmacs on shiny app} +\usage{ +shiny_gmacs(gmrep) +} +\arguments{ +\item{replist}{List object created by read_admb function} +} +\description{ +Plot Gmacs on shiny app +} + diff --git a/Rsrc/roxygenize.R b/Rsrc/roxygenize.R new file mode 100644 index 00000000..3bb8dfc2 --- /dev/null +++ b/Rsrc/roxygenize.R @@ -0,0 +1,2 @@ +library(roxygen2) +roxygen2::roxygenize("R/") diff --git a/docs/api/DoxMainPage.dox b/docs/api/DoxMainPage.dox new file mode 100644 index 00000000..fd227f8e --- /dev/null +++ b/docs/api/DoxMainPage.dox @@ -0,0 +1,35 @@ +/** + * @mainpage GMACS + * + * \a GMACS is a size-structured assessment model for use with crustacean species that + * undergo a molting process. + * + * You can find more information in the following sections: + * - \subpage p_about + * - \subpage p_install + * + * \tableofcontents + * + * + */ + + //-----------------------------------------------------------------------------------// + // ABOUT PAGE + //-----------------------------------------------------------------------------------// + /** + \page p_about About + I'll tell you more about it when I have time to tell you about it. +*/ + //-----------------------------------------------------------------------------------// + // INSTALL PAGE + //-----------------------------------------------------------------------------------// + /** + * \page p_install Install instructions + * + * There are two options for installing Gmacs: + * -# clone the githup repository + * -# download the source code + * + * + */ + diff --git a/docs/api/Doxyfile b/docs/api/Doxyfile new file mode 100644 index 00000000..8e26c3a4 --- /dev/null +++ b/docs/api/Doxyfile @@ -0,0 +1,304 @@ +# Doxyfile 1.8.4 + +#--------------------------------------------------------------------------- +# Project related configuration options +#--------------------------------------------------------------------------- +DOXYFILE_ENCODING = UTF-8 +PROJECT_NAME = "GMACS" +PROJECT_NUMBER = 0.1 +PROJECT_BRIEF = "Length structured assessment model for crustaceans" +PROJECT_LOGO = +OUTPUT_DIRECTORY = html +CREATE_SUBDIRS = YES +OUTPUT_LANGUAGE = English +BRIEF_MEMBER_DESC = YES +REPEAT_BRIEF = YES +ABBREVIATE_BRIEF = +ALWAYS_DETAILED_SEC = NO +INLINE_INHERITED_MEMB = NO +FULL_PATH_NAMES = YES +STRIP_FROM_PATH = +STRIP_FROM_INC_PATH = +SHORT_NAMES = NO +JAVADOC_AUTOBRIEF = NO +QT_AUTOBRIEF = NO +MULTILINE_CPP_IS_BRIEF = NO +INHERIT_DOCS = YES +SEPARATE_MEMBER_PAGES = NO +TAB_SIZE = 4 +ALIASES = +TCL_SUBST = +OPTIMIZE_OUTPUT_FOR_C = NO +OPTIMIZE_OUTPUT_JAVA = NO +OPTIMIZE_FOR_FORTRAN = NO +OPTIMIZE_OUTPUT_VHDL = NO +EXTENSION_MAPPING = .tpl=.cpp +MARKDOWN_SUPPORT = YES +AUTOLINK_SUPPORT = YES +BUILTIN_STL_SUPPORT = NO +CPP_CLI_SUPPORT = NO +SIP_SUPPORT = NO +IDL_PROPERTY_SUPPORT = YES +DISTRIBUTE_GROUP_DOC = NO +SUBGROUPING = YES +INLINE_GROUPED_CLASSES = NO +INLINE_SIMPLE_STRUCTS = NO +TYPEDEF_HIDES_STRUCT = NO +LOOKUP_CACHE_SIZE = 0 +#--------------------------------------------------------------------------- +# Build related configuration options +#--------------------------------------------------------------------------- +EXTRACT_ALL = NO +EXTRACT_PRIVATE = NO +EXTRACT_PACKAGE = NO +EXTRACT_STATIC = NO +EXTRACT_LOCAL_CLASSES = YES +EXTRACT_LOCAL_METHODS = NO +EXTRACT_ANON_NSPACES = NO +HIDE_UNDOC_MEMBERS = NO +HIDE_UNDOC_CLASSES = NO +HIDE_FRIEND_COMPOUNDS = NO +HIDE_IN_BODY_DOCS = NO +INTERNAL_DOCS = NO +CASE_SENSE_NAMES = NO +HIDE_SCOPE_NAMES = NO +SHOW_INCLUDE_FILES = YES +FORCE_LOCAL_INCLUDES = NO +INLINE_INFO = YES +SORT_MEMBER_DOCS = YES +SORT_BRIEF_DOCS = NO +SORT_MEMBERS_CTORS_1ST = NO +SORT_GROUP_NAMES = NO +SORT_BY_SCOPE_NAME = NO +STRICT_PROTO_MATCHING = NO +GENERATE_TODOLIST = YES +GENERATE_TESTLIST = YES +GENERATE_BUGLIST = YES +GENERATE_DEPRECATEDLIST= YES +ENABLED_SECTIONS = +MAX_INITIALIZER_LINES = 30 +SHOW_USED_FILES = YES +SHOW_FILES = YES +SHOW_NAMESPACES = YES +FILE_VERSION_FILTER = +LAYOUT_FILE = +CITE_BIB_FILES = +#--------------------------------------------------------------------------- +# configuration options related to warning and progress messages +#--------------------------------------------------------------------------- +QUIET = YES +WARNINGS = YES +WARN_IF_UNDOCUMENTED = YES +WARN_IF_DOC_ERROR = YES +WARN_NO_PARAMDOC = NO +WARN_FORMAT = "$file:$line: $text" +WARN_LOGFILE = +#--------------------------------------------------------------------------- +# configuration options related to the input files +#--------------------------------------------------------------------------- +INPUT = ../../src/gmacs.tpl ../../src/ ../../src/lib ../../src/include DoxMainPage.dox +INPUT_ENCODING = UTF-8 +FILE_PATTERNS = *.tpl *.cpp *.h *.hpp +RECURSIVE = YES +EXCLUDE = +EXCLUDE_SYMLINKS = NO +EXCLUDE_PATTERNS = +EXCLUDE_SYMBOLS = +EXAMPLE_PATH = +EXAMPLE_PATTERNS = +EXAMPLE_RECURSIVE = NO +IMAGE_PATH = +INPUT_FILTER = +FILTER_PATTERNS = *.tpl=tpl2dox +FILTER_SOURCE_FILES = NO +FILTER_SOURCE_PATTERNS = +USE_MDFILE_AS_MAINPAGE = +#--------------------------------------------------------------------------- +# configuration options related to source browsing +#--------------------------------------------------------------------------- +SOURCE_BROWSER = YES +INLINE_SOURCES = NO +STRIP_CODE_COMMENTS = YES +REFERENCED_BY_RELATION = NO +REFERENCES_RELATION = NO +REFERENCES_LINK_SOURCE = YES +USE_HTAGS = NO +VERBATIM_HEADERS = YES +#--------------------------------------------------------------------------- +# configuration options related to the alphabetical class index +#--------------------------------------------------------------------------- +ALPHABETICAL_INDEX = YES +COLS_IN_ALPHA_INDEX = 5 +IGNORE_PREFIX = +#--------------------------------------------------------------------------- +# configuration options related to the HTML output +#--------------------------------------------------------------------------- +GENERATE_HTML = YES +HTML_OUTPUT = html +HTML_FILE_EXTENSION = .html +HTML_HEADER = +HTML_FOOTER = +HTML_STYLESHEET = +HTML_EXTRA_STYLESHEET = +HTML_EXTRA_FILES = +HTML_COLORSTYLE_HUE = 220 +HTML_COLORSTYLE_SAT = 100 +HTML_COLORSTYLE_GAMMA = 80 +HTML_TIMESTAMP = YES +HTML_DYNAMIC_SECTIONS = NO +HTML_INDEX_NUM_ENTRIES = 100 +GENERATE_DOCSET = NO +DOCSET_FEEDNAME = "Doxygen generated docs" +DOCSET_BUNDLE_ID = org.doxygen.Project +DOCSET_PUBLISHER_ID = org.doxygen.Publisher +DOCSET_PUBLISHER_NAME = Publisher +GENERATE_HTMLHELP = NO +CHM_FILE = +HHC_LOCATION = +GENERATE_CHI = NO +CHM_INDEX_ENCODING = +BINARY_TOC = NO +TOC_EXPAND = NO +GENERATE_QHP = NO +QCH_FILE = +QHP_NAMESPACE = org.doxygen.Project +QHP_VIRTUAL_FOLDER = doc +QHP_CUST_FILTER_NAME = +QHP_CUST_FILTER_ATTRS = +QHP_SECT_FILTER_ATTRS = +QHG_LOCATION = +GENERATE_ECLIPSEHELP = NO +ECLIPSE_DOC_ID = org.doxygen.Project +DISABLE_INDEX = NO +GENERATE_TREEVIEW = YES +ENUM_VALUES_PER_LINE = 4 +TREEVIEW_WIDTH = 250 +EXT_LINKS_IN_WINDOW = NO +FORMULA_FONTSIZE = 12 +FORMULA_TRANSPARENT = YES +USE_MATHJAX = YES +MATHJAX_FORMAT = HTML-CSS +MATHJAX_RELPATH = http://cdn.mathjax.org/mathjax/latest +MATHJAX_EXTENSIONS = +MATHJAX_CODEFILE = +SEARCHENGINE = YES +SERVER_BASED_SEARCH = NO +EXTERNAL_SEARCH = NO +SEARCHENGINE_URL = +SEARCHDATA_FILE = searchdata.xml +EXTERNAL_SEARCH_ID = +EXTRA_SEARCH_MAPPINGS = +#--------------------------------------------------------------------------- +# configuration options related to the LaTeX output +#--------------------------------------------------------------------------- +GENERATE_LATEX = NO +LATEX_OUTPUT = latex +LATEX_CMD_NAME = latex +MAKEINDEX_CMD_NAME = makeindex +COMPACT_LATEX = NO +PAPER_TYPE = a4 +EXTRA_PACKAGES = +LATEX_HEADER = +LATEX_FOOTER = +LATEX_EXTRA_FILES = +PDF_HYPERLINKS = YES +USE_PDFLATEX = YES +LATEX_BATCHMODE = NO +LATEX_HIDE_INDICES = NO +LATEX_SOURCE_CODE = NO +LATEX_BIB_STYLE = plain +#--------------------------------------------------------------------------- +# configuration options related to the RTF output +#--------------------------------------------------------------------------- +GENERATE_RTF = NO +RTF_OUTPUT = rtf +COMPACT_RTF = NO +RTF_HYPERLINKS = NO +RTF_STYLESHEET_FILE = +RTF_EXTENSIONS_FILE = +#--------------------------------------------------------------------------- +# configuration options related to the man page output +#--------------------------------------------------------------------------- +GENERATE_MAN = NO +MAN_OUTPUT = man +MAN_EXTENSION = .3 +MAN_LINKS = NO +#--------------------------------------------------------------------------- +# configuration options related to the XML output +#--------------------------------------------------------------------------- +GENERATE_XML = NO +XML_OUTPUT = xml +XML_SCHEMA = +XML_DTD = +XML_PROGRAMLISTING = YES +#--------------------------------------------------------------------------- +# configuration options related to the DOCBOOK output +#--------------------------------------------------------------------------- +GENERATE_DOCBOOK = NO +DOCBOOK_OUTPUT = docbook +#--------------------------------------------------------------------------- +# configuration options for the AutoGen Definitions output +#--------------------------------------------------------------------------- +GENERATE_AUTOGEN_DEF = NO +#--------------------------------------------------------------------------- +# configuration options related to the Perl module output +#--------------------------------------------------------------------------- +GENERATE_PERLMOD = NO +PERLMOD_LATEX = NO +PERLMOD_PRETTY = YES +PERLMOD_MAKEVAR_PREFIX = +#--------------------------------------------------------------------------- +# Configuration options related to the preprocessor +#--------------------------------------------------------------------------- +ENABLE_PREPROCESSING = YES +MACRO_EXPANSION = NO +EXPAND_ONLY_PREDEF = NO +SEARCH_INCLUDES = YES +INCLUDE_PATH = +INCLUDE_FILE_PATTERNS = +PREDEFINED = +EXPAND_AS_DEFINED = +SKIP_FUNCTION_MACROS = YES +#--------------------------------------------------------------------------- +# Configuration::additions related to external references +#--------------------------------------------------------------------------- +TAGFILES = +GENERATE_TAGFILE = +ALLEXTERNALS = NO +EXTERNAL_GROUPS = YES +EXTERNAL_PAGES = YES +PERL_PATH = /usr/bin/perl +#--------------------------------------------------------------------------- +# Configuration options related to the dot tool +#--------------------------------------------------------------------------- +CLASS_DIAGRAMS = YES +MSCGEN_PATH = +HIDE_UNDOC_RELATIONS = YES +HAVE_DOT = NO +DOT_NUM_THREADS = 0 +DOT_FONTNAME = Helvetica +DOT_FONTSIZE = 10 +DOT_FONTPATH = +CLASS_GRAPH = YES +COLLABORATION_GRAPH = YES +GROUP_GRAPHS = YES +UML_LOOK = NO +UML_LIMIT_NUM_FIELDS = 10 +TEMPLATE_RELATIONS = NO +INCLUDE_GRAPH = YES +INCLUDED_BY_GRAPH = YES +CALL_GRAPH = NO +CALLER_GRAPH = NO +GRAPHICAL_HIERARCHY = YES +DIRECTORY_GRAPH = YES +DOT_IMAGE_FORMAT = png +INTERACTIVE_SVG = NO +DOT_PATH = +DOTFILE_DIRS = +MSCFILE_DIRS = +DOT_GRAPH_MAX_NODES = 50 +MAX_DOT_GRAPH_DEPTH = 0 +DOT_TRANSPARENT = NO +DOT_MULTI_TARGETS = NO +GENERATE_LEGEND = YES +DOT_CLEANUP = YES diff --git a/docs/api/Makefile b/docs/api/Makefile new file mode 100644 index 00000000..0c89402d --- /dev/null +++ b/docs/api/Makefile @@ -0,0 +1,14 @@ +.PHONY: default clean + + +default: Doxyfile + doxygen Doxyfile + @cd html; git add . + @cd html; git ci -ma"Updates to API" + @cd html; git push origin gh-pages + + +clean: + #rm -rf html + + \ No newline at end of file diff --git a/docs/bbrkc/bbrkc.Rmd b/docs/bbrkc/bbrkc.Rmd new file mode 100644 index 00000000..5d1f4487 --- /dev/null +++ b/docs/bbrkc/bbrkc.Rmd @@ -0,0 +1,136 @@ +--- +title: "Gmacs Example Stock Assessment" +author: "Athol R. Whitten, James N. Ianelli, André E. Punt" +date: "September 2014" +output: + pdf_document: + highlight: zenburn + toc: yes + html_document: + theme: flatly + toc: yes + word_document: default +bibliography: bbrkc.bib +--- + +## Introduction +Gmacs is a generalized size-structured stock assessment modeling framework [more here on Gmacs]. Crab stocks of Alaska are managed by the North Pacific Fisheries Management Council [NPFMC](http://npfmc.org). Some stocks are assessed with integrated size-structured assessment models of the form described by @Punt2012. Currenlty, each stock is assessed using a stock-specific assessment model. The Gmacs project aims to provide software that will allow each stock to be assessed inside a single modelling framework. + +Gmacs is used here to develop an assessment model for the Bristol Bay Red King Crab (BBRKC) stock. This analysis serves as a test-case for the development of Gmacs: the example assessment is intended to match closely with a model scenario presented to the Spring 2014 BSAI Crab Plan Team Meeting by @Zheng2014. + +Together, the Gmacs-BBRKC model and this report serve as the first example of what should follow for other crab stocks: that is, direct model comparisons to (1) test the efficacy of Gmacs, and (2) determine whether Gmacs can be used in practice to closely match the outputs of existing ADFG stock assessment models. + +## Summary of analytical approach +Information here on the model, the history, and specifications (current and old). + +### ADFG-BBRKC + +### Gmacs-BBRK +How Gmacs deals with retention and selectivity: this is an important part to add, as there. + +## Comparison of Data and Model Specifications + +### ADFG +### Survey Data + +### Catch Data + +### Weight and Fecundity +For the length-weight relationships, Jie's data file `rk7513s1.dat` has information on the weight-at-length parameters for BBRKC. He suggests we use the 'new' parameters listed (see line 339 onwards): these parameters were estimated by NMFS. + +Fecundity-at-length is a little more complicated: This information was provided by Jie: + +From Jie: Fecundity-at-length depends on clutch fullness, which changes from year to year. Right now, we do not use fecundity in the management, so no fecundity is used in the model. The “fecundity” used in Andre's simplified model looks like the male mean weight by length with the “old" parameters”. If GMACS needs fecundity, maybe just input mean weight by length of mature females, or mature males (please use “new” parameters). As to the maturity by length, right now, it is 0 for lengths less than 90 mm and 1 for lengths 90 or larger for females and 0 for lengths less than 120mm and 1 for lengths greater than 119 mm for males. In the future, I plan to estimate maturity by length for females over time to improve estimation of growth. + +### Gmacs +The data and model specifications used in the Gmacs-BBRKC model are very similar to those used in the '4nb' scenario developed by @Zheng2014, herein referred to as the ADFG-BBRKC model. + + + +Parameterization of the Bristol Bay red king crab + +### Population Dynamics +Comparison tables of two different model approaches could be done by + +Life History Trait | Parameter | ADFG Value | Gmacs Value | Comments +------------------ | --------- | ---------- | ----------- | -------- +Natural Mortality | M | Fixed | Fixed | M is fixed in both models + + +### Fishery Dynamics +Specification | Parameter | ADFG Value | Gmacs Value | Comments +------------------ | --------- | ---------- | ----------- | -------- +No. Fleets | | 5 | 5 | + +There are five separate fishing fleets accounted for in the ADFG model: + +## Comparison of Model Results +The results of the ADFG-BBRKC model are compared here to the results of the Gmacs-BBRKC model. + +### Gmacs Results +We need to be able to produce a table of the comparative likelihoods (by component) of the alternative models. For best practice, just try and do what we do with SS models for SESSF stocks anyway. See the pink link report, and enter a section for each of those, and see if we can emulate a report of that type. + +In what follows, we demonstrate the use of the `gmr` package to process the output of the Gmacs-BBRKC model and produce plots that can be used in assessment reports. + +```{r, echo=FALSE} +# Load gmr package for Gmacs: +library(gmr) + +# Set working directory to that containing Gmacs model results: +setwd("c:/seacode/gmacs/examples/demo/") + +# Set theme for ggplot2 (works for themes classic, minimal, gray, bw): +set_ggtheme('bw') + +# Read report file and create gmacs report object (a list): +gmrep <- read_admb('gmacs') + +# Set working directory to that containing Gmacs model results: +setwd("c:/seacode/gmacs/examples/demo") + +# Set theme for ggplot2 (works for themes classic, minimal, gray, bw): +set_ggtheme('bw') + +# Read report file and create gmacs report object (a list): +gmrep <- read_admb('gmacs') + +# Get plots of interest: +plot_catch(gmrep) +plot_catch(gmrep,plot_res=T) + +# plot_sizecomp(gmrep,which_plots=c(1)) +# plot_sizecomp_res(gmrep) +# +# plot_sizecomp(gmrep,which_plots=c(11)) +# plot_sizecomp_res(gmrep) +# plot_sizetransition(gmrep) +# +# plot_selectivity(gmrep) +# plot_recruitment(gmrep) +# plot_mmb(gmrep) +``` + +## Comparison of Assessment Processes +### File Description + + * The `*.tpl` file is working, it builds and the `*.exe` file runs successfully. + * The main `*.dat` file is read in as expected (comments within). + * There is a second data file `rksize13s.dat` with sample sizes for + various rows of size-comp data. See lines 81-87 of `*.tpl`. + * Input sample sizes appear to be capped to the constant numbers entered in + the main data file under 'number of samples' or 'sample sizes' (variously). + * There is a third data file `tc7513s.dat` specifically for data from the + tanner crab fishery (with red crab bycatch). + * There is a standard control file `*.ctl` with internal comments. + * There is an excel spreadsheet which can be used to read in the model + output files and display related plots (it's a bit clunky). + + * There are two batch files in the model directory: `clean.bat` and `scratch.bat`. + The 'clean' batch file deletes files related to a single model run. The + 'scratch' batch file deletes all files relating to the model build and + leaves only source and data files. + +## Discussion +This discussion will focus on the challenges in developing a Gmacs version of the BBRKC model: those met, and those yet to be met. + +## References diff --git a/docs/bbrkc/bbrkc.html b/docs/bbrkc/bbrkc.html new file mode 100644 index 00000000..6b4bdf4a --- /dev/null +++ b/docs/bbrkc/bbrkc.html @@ -0,0 +1,239 @@ + + + + + + + + + + + + + + +Gmacs Example Stock Assessment + + + + + + + + + + + + + + + + + + + + +
+ + + + +
+ +
+ +
+

Introduction

+

Gmacs is a generalized size-structured stock assessment modeling framework [more here on Gmacs]. Crab stocks of Alaska are managed by the North Pacific Fisheries Management Council NPFMC. Some stocks are assessed with integrated size-structured assessment models of the form described by Punt, Huang, and Maunder (2012). Currenlty, each stock is assessed using a stock-specific assessment model. The Gmacs project aims to provide software that will allow each stock to be assessed inside a single modelling framework.

+

Gmacs is used here to develop an assessment model for the Bristol Bay Red King Crab (BBRKC) stock. This analysis serves as a test-case for the development of Gmacs: the example assessment is intended to match closely with a model scenario presented to the Spring 2014 BSAI Crab Plan Team Meeting by Zheng and Siddeek (2014).

+

Together, the Gmacs-BBRKC model and this report serve as the first example of what should follow for other crab stocks: that is, direct model comparisons to (1) test the efficacy of Gmacs, and (2) determine whether Gmacs can be used in practice to closely match the outputs of existing ADFG stock assessment models.

+
+
+

Summary of analytical approach

+

Information here on the model, the history, and specifications (current and old).

+
+

ADFG-BBRKC

+
+
+

Gmacs-BBRK

+

How Gmacs deals with retention and selectivity: this is an important part to add, as there.

+
+
+
+

Comparison of Data and Model Specifications

+
+

ADFG

+
+
+

Survey Data

+
+
+

Catch Data

+
+
+

Weight and Fecundity

+

For the length-weight relationships, Jie’s data file rk7513s1.dat has information on the weight-at-length parameters for BBRKC. He suggests we use the ‘new’ parameters listed (see line 339 onwards): these parameters were estimated by NMFS.

+

Fecundity-at-length is a little more complicated: This information was provided by Jie:

+

From Jie: Fecundity-at-length depends on clutch fullness, which changes from year to year. Right now, we do not use fecundity in the management, so no fecundity is used in the model. The “fecundity” used in Andre’s simplified model looks like the male mean weight by length with the “old” parameters”. If GMACS needs fecundity, maybe just input mean weight by length of mature females, or mature males (please use “new” parameters). As to the maturity by length, right now, it is 0 for lengths less than 90 mm and 1 for lengths 90 or larger for females and 0 for lengths less than 120mm and 1 for lengths greater than 119 mm for males. In the future, I plan to estimate maturity by length for females over time to improve estimation of growth.

+
+
+

Gmacs

+

The data and model specifications used in the Gmacs-BBRKC model are very similar to those used in the ‘4nb’ scenario developed by Zheng and Siddeek (2014), herein referred to as the ADFG-BBRKC model.

+ + +

Parameterization of the Bristol Bay red king crab

+
+
+

Population Dynamics

+

The table below currently just uses basic markdown table formatting. There is an option for Rmd to use something like this:

+

The above is the output of an R data.frame. This could be useful for reproducing model results or inputs from Gmacs i/o files.

+ + + + + + + + + + + + + + + + + + + +
Life History TraitParameterADFG ValueGmacs ValueComments
Natural MortalityMFixedFixedM is fixed in both models
+
+
+

Fishery Dynamics

+ + + + + + + + + + + + + + + + + + +
SpecificationParameterADFG ValueGmacs ValueComments
No. Fleets55
+

There are five separate fishing fleets accounted for in the ADFG model:

+
+
+
+

Comparison of Model Results

+

The results of the ADFG-BBRKC model are compared here to the results of the Gmacs-BBRKC model.

+
+

Gmacs Results

+

We need to be able to produce a table of the comparative likelihoods (by component) of the alternative models. For best practice, just try and do what we do with SS models for SESSF stocks anyway. See the pink link report, and enter a section for each of those, and see if we can emulate a report of that type.

+

In what follows, we demonstrate the use of the gmr package to process the output of the Gmacs-BBRKC model and produce plots that can be used in assessment reports.

+
## Loading required package: ggplot2
+## The ggplot theme has been set to bw for this working session
+## The ggplot theme has been set to bw for this working session
+

plot of chunk unnamed-chunk-1plot of chunk unnamed-chunk-1

+
+
+
+

Comparison of Assessment Processes

+
+

File Description

+
    +
  • The *.tpl file is working, it builds and the *.exe file runs successfully.
  • +
  • The main *.dat file is read in as expected (comments within).
  • +
  • There is a second data file rksize13s.dat with sample sizes for various rows of size-comp data. See lines 81-87 of *.tpl.
  • +
  • Input sample sizes appear to be capped to the constant numbers entered in the main data file under ‘number of samples’ or ‘sample sizes’ (variously).
  • +
  • There is a third data file tc7513s.dat specifically for data from the tanner crab fishery (with red crab bycatch).
  • +
  • There is a standard control file *.ctl with internal comments.
  • +
  • There is an excel spreadsheet which can be used to read in the model output files and display related plots (it’s a bit clunky).

  • +
  • There are two batch files in the model directory: clean.bat and scratch.bat. The ‘clean’ batch file deletes files related to a single model run. The ‘scratch’ batch file deletes all files relating to the model build and leaves only source and data files.

  • +
+
+
+
+

Discussion

+

This discussion will focus on the challenges in developing a Gmacs version of the BBRKC model: those met, and those yet to be met.

+
+

References

+

Punt, Andre E, Tzuchuan Huang, and Mark N Maunder. 2012. “Review of Integrated Size-Structured Models for Stock Assessment of Hard-to-Age Crustacean and Mollusc Species.” ICES Journal of Marine Science 70 (1): 16–33. doi:10.1093/icesjms/fss185. http://icesjms.oxfordjournals.org/cgi/doi/10.1093/icesjms/fss185.

+

Zheng, J, and MSM Siddeek. 2014. “Bristol Bay Red King Crab Stock Assessment in Spring 2014.” Notes. Alaska Department of Fish & Game.

+
+
+ + +
+ + + + + + + + diff --git a/docs/bbrkc/bbrkc.pdf b/docs/bbrkc/bbrkc.pdf new file mode 100644 index 00000000..946488e9 Binary files /dev/null and b/docs/bbrkc/bbrkc.pdf differ diff --git a/docs/developer/DataStructures.tex b/docs/developer/DataStructures.tex new file mode 100644 index 00000000..54375b3e --- /dev/null +++ b/docs/developer/DataStructures.tex @@ -0,0 +1,165 @@ +%!TEX root = ModelDescription.tex +\section{Data structures} +The following is a list of the input data structures used in data file for Gmacs. + +\begin{table}[!tbh] + \caption{Input data structures}\label{Tab:inputDataStructures} + \begin{tabular}{lcll} + \hline + Variable & Symbol & Type & Description \\ + \hline + styr & $t$ & int & Start year \\ + endyr & $t$ & int & End year \\ + tstep & NA & double & time step \\ + ndata & & int & number of data groups \\ + nsex & $s$ & int & number of sexes \\ + nshell & $v$ & int & number of shell conditions\\ + nmature & $m$ & int & number of maturity states \\ + nclass & $l$ & int & number of size classes in the model\\ + % ndclass & $l$ & int & number of size classes in the data\\ + ncol & & int & number of columns in N-matrix \\ + + % Not used anywhere in the code. + % psex & & ivector(1,nsex)& starting col pos for sex-specific N\\ + % pshell && ivector(1,npshell)& starting col pos for shell-specific N\\ + % pmature &&ivector(1,npmature)&starting col pos for mature-specific N\\ + % pall&&ivector(1,npmature)& col position for all blocks of N\\ + + class\_link & & matrix(1,nclass,1,2)&links between model and data size-classes.\\ + \hline + \end{tabular} +\end{table} + + +\paragraph{Indexes} +For consistency the following indexes are used to describe the various model dimensions: + +\begin{description} + \item [g] index for group (sex, shell condition, maturity state), + \item [h] index for sex, + \item [i] index for year, + \item [j] index for season or month, + \item [k] index for fleet, + \item [l] index for length class, + \item [m] index for maturity state, + \item [n] index for shell condition, +\end{description} + + +\subsection{Recruitment} % (fold) +\label{sub:recruitment} +The numbers-at-size in the first year are initialized using an initial mean recruitment $\dot{R}$, natural mortality, the size transition matrix, and a vector of deviations for each size class that represents recruitment variability prior to the initial start year of the model. Assuming steady state conditions, the model assumes that at any time the population consists of a vector of individuals in each size category. At each time step, these individuals experience natural mortality and grow into the next size category and is represented by the matrix $\boldsymbol{A}$. If the number of individuals in a given size class is represented by $\boldsymbol{v}=(v_1,v_2,\ldots,v_n)$, then after growing and surviving to the next time step is given by $\boldsymbol{A}\boldsymbol{v}$. This does not include new recruits into the population. Let $\boldsymbol{r}= (r_1, r_2, \ldots, r_n)$ be the vector of new recruits at each size class. Then the population next year is equal to $\boldsymbol{A}\boldsymbol{v} + \boldsymbol{r}$. Recruitment in this contexts is defined as the number of new individuals entering the popuation in a specific size class. In a simple age-structured model this would be the total number of age-0 recruits, and in the next year these individuals would all enter the age-1 class. In a size-based model, not all individuals will leave a given size class (i.e., there is a probability of not molting and remaining in the same size class). Moreover, individuals will growth to multiple size categories in one-time step due to individual variation in molt increments or molt frequency. + +Let $\boldsymbol{x}=(x_1,x_2,\ldots,x_n)$ be the equilibrium population when the recruitment vector is $\boldsymbol{r}$. The requirement that the population is at equilibrium is equivalent to the matrix equation +\begin{equation}\label{eq1} + \bs{x} = \bs{A}\bs{x} + \bs{r} +\end{equation} +and the equilibrium solution for $\bs{x}$ is given by +\begin{equation}\label{eq2} + \bs{x} =-(\bs{A}-\mathbf{I})^{-1}(\bs{r}) +\end{equation} +where $\mathbf{I}$ is the $n \times n$ identity matrix. + +Given an initial value of $\dot{R}$, the distribution of new recriuts is represented by a gamma distribution \eqref{T4.4}, where the estimated parameters $R_\alpha$ and $R_\beta$ represent the mean size at recruitment and the coefficient of variation in size. At equilibrium, the total number of recruits in each size class is given by +\begin{equation}\label{eq3} + \bs{r} = p(\bs{r})\dot{R}, +\end{equation} +and departures from equilibrium conditions are represented by +\begin{equation}\label{eq4} + \bs{r} = p(\bs{r})\dot{R}\exp(\bs{\nu}), +\end{equation} +where $\bs{\nu}=(\nu_1,\nu_2,\ldots,\nu_n)$ is a vector of estimated deviations with the additional constraint $\sum_i\nu_i = 0$. + +Annual recruitment to each size class is an estimated vector of deviates $\bs{\xi}=(\xi_{i=2},\xi_{i=3},\ldots,\xi_{i=I})$ around an average recruitment value $\bar{R}$ +\begin{equation} + \bs{r}_i = p(\bs{r})\bar{R}\xi_i +\end{equation} +where it is assumed that the size-distribution of new recruits is time-invariant and the additional constraint $\sum_i \xi_i = 0$. +% subsection recruitment (end) + + +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% +\begin{table} + \centering +\caption{Statistical catch-at-length model used in Gmacs} +\label{tab:statistical_catch_length_model} +\tableEq + \begin{align} + \hline \nonumber \\ + &\mbox{Estimated parameters} \nonumber\\ + \Theta&= + (M_0,\ln(\dot{R}),\ln(\bar{R}),R_\alpha,R_\beta, + \alpha_h, \beta_h,b_h, \bs{\nu},\bs{\xi})\label{T4.1}\\ + \sigma^2&=\rho /\vartheta^2, \quad + \tau^2=(1-\rho)/\vartheta^2\label{T4.2}\\[1ex] + %\vartheta^2=\sigma^2+\tau^2, \quad + %\rho=\frac{\sigma^2}{\sigma^2+\tau^2}\label{T4.3}\\[1ex] + %% + %% + &\mbox{Unobserved states} \nonumber\\ + &\boldsymbol{N},\boldsymbol{Z} \label{T4.3}\\ + %% + %% + &\mbox{Recruitment size distribution} \nonumber\\ + \alpha &= R_\alpha /R_\beta \nonumber \\ + p(\boldsymbol{r}) &= \int_{x_l-0.5\Delta x}^{x_l+0.5\Delta x} + \frac{x_l^{(\alpha-1)}e^{x_l/R_\beta}}{\Gamma(\alpha)x_l^\alpha}dx + \label{T4.4}\\ + %% + %% + &\mbox{Molt increment \& size transition} \nonumber\\ + a_{h,l} &= \alpha_h + \beta_h l \label{T4.5} \\ + p({l},{l'})_h &= \int_{l-0.5\Delta l}^{l+0.5\Delta l} + \frac{ l^{(a_{h,l}-1)} e^{l/b_h} } + { \Gamma(a_{h,l}) l^{a_{h,l}} } dl \label{T4.6} \\ + % &\mbox{Initial states} \nonumber\\ + % %v_a=\left[1+e^{-(\hat{a}-a)/\hat{\gamma}}\right]^{-1}\label{T4.7}\\ + % N_{t,a}&=\bar{R}e^{\omega_{t-a}} \exp(-M_t)^{(a-1)};\quad t=1; 2\leq a\leq A \label{T4.4}\\ + % N_{t,a}&=\bar{R}e^{\omega_{t}} ;\quad 1\leq t\leq T; a=1 \label{T4.5}\\ + % v_{k,a}&=f(\gamma_k) \label{T4.6}\\ + % M_t &= M_{t-1} \exp(\varphi_t), \quad t>1 \label{T4.6b}\\ + % F_{k,t}&=\exp(\digamma_{k,t}) \label{T4.7}\\[1ex] + % %% + % %% + % &\mbox{State dynamics (t$>$1)} \nonumber\\ + % B_t&=\sum_a N_{t,a}f_a \label{T4.8}\\ + % Z_{t,a}&=M_t+\sum_k F_{k,t} v_{k,t,a}\label{T4.9}\\ + % \hat{C}_{k,t}&=\sum _ a\frac {N_{{t,a}}w_{{a}}F_{k,t} v_{{k,t,a}} + % \left( 1-{e^{-Z_{t,a}}} \right) }{Z_{t,a}}^{\eta_t} \label{T4.10}\\ + % %F_{t_{i+1}}= \ F_{t_{i}} -\frac{\hat{C}_t-C_t}{\hat{C}_t'} \label{T4.12}\\ + % N_{t,a}&=\begin{cases} + % %\dfrac{s_oE_{t-1}}{1+\beta E_{t-1}} \exp(\omega_t-0.5\tau^2) &a=1\\ \\ + % N_{t-1,a-1} \exp(-Z_{t-1,a-1}) &a>1\\ + % N_{t-1,a} \exp(-Z_{t-1,a}) & a=A + % \end{cases}\label{T4.11}\\[1ex] + % %% + % %% + % &\mbox{Recruitment models} \nonumber\\ + % R_t &= \frac{s_oB_{t-k}}{1+\beta B_{t-k}}e^{\delta_{t}-0.5\tau^2} \quad \mbox{Beverton-Holt} \label{T4.12}\\ + % R_t &= s_oB_{t-k}e^{-\beta B_{t-k}+\delta_t-0.5\tau^2} \quad \mbox{Ricker} \label{T4.13}\\ + %% \mbox{Residuals \& predicted observations} \nonumber\\ + %% \epsilon_t=\ln\left(\frac{I_t}{B_t}\right)-\frac{1}{n}\sum_{t \in I_t}\ln\left(\frac{I_t}{B_t}\right)\label{T4.15}\\ + %% \hat{A}_{t,a}=\dfrac{N_{t,a}\dfrac{F_tv_a}{Z_{t,a}}\left(1-e^{-Z_{t,a}}\right)} + %% {\sum_a N_{t,a}\dfrac{F_tv_a}{Z_{t,a}}\left(1-e^{-Z_{t,a}}\right)}\label{T4.16}\\ + \hline \hline \nonumber + \end{align} + + \normalEq +\end{table} +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% + +\subsection{Size transition matrix} % (fold) +\label{sub:size_transition_matrix} + +A parametric approach based on molt increments for calculating the elements of the size transition matrix is based on \eqref{T4.5} and \eqref{T4.6}. Molt increments are assumed to be a linear function of carapace width, or size-interval $l$. Growth is assumed to be sex-specific and is index by $h$. The probability of growing from interval $l$ to $l'$ is based on the gamma distribution \eqref{T4.6} where the expected increased in length is a function of the molt increment at length $l$ \eqref{T4.5} and the shape parameter $b_h$. + +In short, 3 estimated parameters ($\alpha_h, \beta_h$, and $b_h$) are required to describe growth increments and the size-transition matrix. Ideally, independent molt-increment data, by sex, should be included in the model to provide additional information to estimate $\alpha_h$ and $\beta_h$. Absent this information, clear modes in the size-composition data must be discernable in order to reasonably resolve confounding among the three growth parameters. + +% subsection size_transition_matrix (end) + +\subsection{Shell condition} % (fold) +\label{sub:shell_condition} +Many of the crab composition data sets are categorized by shell condition (e.g., new shell, old shell). Fitting to these data requires predicted values for new shell and old shell by size class. This is critical for species that have a terminal molt, and the proportion of old shell would accumulate over time, but less so under higher fishing mortality rates. +% subsection shell_condition (end) diff --git a/docs/developer/ModelDescription.pdf b/docs/developer/ModelDescription.pdf new file mode 100644 index 00000000..16a6e578 Binary files /dev/null and b/docs/developer/ModelDescription.pdf differ diff --git a/docs/developer/ModelDescription.tex b/docs/developer/ModelDescription.tex new file mode 100644 index 00000000..02da3b4c --- /dev/null +++ b/docs/developer/ModelDescription.tex @@ -0,0 +1,116 @@ +\documentclass[12pt,letterpaper]{article} + + + + +% Use utf-8 encoding for foreign characters +\usepackage[utf8]{inputenc} + +% Setup for fullpage use +\usepackage{fullpage} +\usepackage{lscape} + +% Uncomment some of the following if you use the features +% +% Running Headers and footers +\usepackage{fancyhdr} + +% Multipart figures +%\usepackage{subfigure} + +% Multicols +\usepackage{multicol} +\setlength{\columnseprule}{0.5pt} +\setlength{\columnsep}{15pt} + +% More symbols +\usepackage{amsmath} +\usepackage{amssymb} +\usepackage{latexsym} + +% Surround parts of graphics with box +\usepackage{boxedminipage} + +% Longtables +\usepackage{longtable} + +% Package for including code in the document +\usepackage{listings} +\usepackage{alltt} + +% If you want to generate a toc for each chapter (use with book) +% \usepackage{minitoc} + +% This is now the recommended way for checking for PDFLaTeX: +\usepackage{ifpdf} + +% Natbib +\usepackage[round]{natbib} + +%% -math- +\def\bs#1{\boldsymbol{#1}} + +\newcounter{saveEq} + \def\putEq{\setcounter{saveEq}{\value{equation}}} + \def\getEq{\setcounter{equation}{\value{saveEq}}} + \def\tableEq{ % equations in tables + \putEq \setcounter{equation}{0} + \renewcommand{\theequation}{T\arabic{table}.\arabic{equation}} + \vspace{-5mm} + } + \def\normalEq{ % renew normal equations + \getEq + \renewcommand{\theequation}{\arabic{section}.\arabic{equation}}} + + \def\puthrule{ %thick rule lines for equation tables + \hrule \hrule \hrule \hrule \hrule} + +% Hyperref +% \usepackage{url} +\usepackage[colorlinks,bookmarks,citecolor=magenta,linkcolor=blue]{hyperref} +% \usepackage{hyperref} + +%\newif\ifpdf +%\ifx\pdfoutput\undefined +%\pdffalse % we are not running PDFLaTeX +%\else +%\pdfoutput=1 % we are running PDFLaTeX +%\pdftrue +%\fi + +\ifpdf +\usepackage[pdftex]{graphicx} +\else +\usepackage{graphicx} +\fi + + +\usepackage{tikz-uml} + + +\title{GMACS DOCUMENTATION} +\author{Steve Martell, Dave Fournier, Athol Whitten, Jim Ianelli} + + +\begin{document} +\maketitle + \input{DataStructures} + + +% TO do class diagrams +% \begin{tikzpicture} + % \umlclass[x=0,y=0]{myclass}{}{} + % \umlclass[x=2,y=-2]{B}{}{a} +% \end{tikzpicture} +% +% \begin{tikzpicture} +% \begin{umlcomponent}{Some name} +% \umlbasiccomponent[x=2]{A} +% \umlprovidedinterface{A} +% \umlrequiredinterface[interface=C]{A} +% \pgfnodealias{newname}{A-west-interface} %<- Adding another name +% \end{umlcomponent} +% \draw[blue,ultra thick] (newname) -- (0,-1); %<- using new name +% \end{tikzpicture} +% +\end{document} \ No newline at end of file diff --git a/docs/manuscript/GLBAM.pdf b/docs/manuscript/GLBAM.pdf new file mode 100644 index 00000000..ff733abb Binary files /dev/null and b/docs/manuscript/GLBAM.pdf differ diff --git a/docs/manuscript/GLBAM.tex b/docs/manuscript/GLBAM.tex new file mode 100644 index 00000000..f97777b5 --- /dev/null +++ b/docs/manuscript/GLBAM.tex @@ -0,0 +1,562 @@ +\documentclass[12pt,letterpaper]{article} + +% Use utf-8 encoding for foreign characters +\usepackage[utf8]{inputenc} + +% Setup for fullpage use +\usepackage{fullpage} +\usepackage{lscape} + +% Uncomment some of the following if you use the features +% +% Running Headers and footers +\usepackage{fancyhdr} + +% Multipart figures +%\usepackage{subfigure} + +% Multicols +\usepackage{multicol} +\setlength{\columnseprule}{0.5pt} +\setlength{\columnsep}{15pt} + +% More symbols +\usepackage{amsmath} +\usepackage{amssymb} +\usepackage{latexsym} +\usepackage{bm} + +% Surround parts of graphics with box +\usepackage{boxedminipage} + +% Longtables +\usepackage{longtable} + +% Package for including code in the document +\usepackage{listings} +\usepackage{alltt} + +% If you want to generate a toc for each chapter (use with book) +% \usepackage{minitoc} + +% This is now the recommended way for checking for PDFLaTeX: +\usepackage{ifpdf} + +% Natbib +\usepackage[round]{natbib} + + +%% -math- +\def\bs#1{\boldsymbol{#1}} + +\newcounter{saveEq} + \def\putEq{\setcounter{saveEq}{\value{equation}}} + \def\getEq{\setcounter{equation}{\value{saveEq}}} + \def\tableEq{ % equations in tables + \putEq \setcounter{equation}{0} + \renewcommand{\theequation}{T\arabic{table}.\arabic{equation}} + \vspace{-5mm} + } + \def\normalEq{ % renew normal equations + \getEq + \renewcommand{\theequation}{\arabic{section}.\arabic{equation}}} + + \def\puthrule{ %thick rule lines for equation tables + \hrule \hrule \hrule \hrule \hrule} + +% Hyperref +% \usepackage{url} +\usepackage[colorlinks,bookmarks,citecolor=magenta,linkcolor=blue]{hyperref} +% \usepackage{hyperref} + +%\newif\ifpdf +%\ifx\pdfoutput\undefined +%\pdffalse % we are not running PDFLaTeX +%\else +%\pdfoutput=1 % we are running PDFLaTeX +%\pdftrue +%\fi + +\ifpdf +\usepackage[pdftex]{graphicx} +\else +\usepackage{graphicx} +\fi + + +\usepackage{tikz-uml} + + +\title{A generalized size-structured assessment model for Crustaceans} +\author{Athol Whitten, Andre Punt, Dave Fournier, James Ianelli, John Levitt, and Steve Martell} + +% Andre should probably be on here too, check with others. +% I understand the problem with using the name Gmacs, and thus the relationship with Alaskan Crab stocks, +% but it's probably too late to change. Thus Gmacs is now written as a name, not an acronym. +% We must use 'size' instead of 'length' for all descriptions, as some species are measured via widths, not lengths. + + +% my macros +\newcommand{\fspr}{$F_{\textnormal{SPR}}$} +\newcommand{\bspr}{$B_{\textnormal{SPR\%}}$} + +\newcommand{\fmsy}{$F_{\textnormal{MSY}}$} +\newcommand{\bmsy}{$B_{\textnormal{MSY}}$} + +\begin{document} + \maketitle + + \begin{abstract} + Gmacs is a statistical size-structured stock assessment modelling framework for molting crustacean species. The framework makes use of a wide variety of data, including both fishery- and survey-based size-composition data, and fishery-dependent and -independent indices of abundance. Gmacs has initially been designed for application to the king crab stocks of Alaska. Models of these stocks serve as a testing ground for the first versions of the modeling framework. Gmacs is coded using AD Model Builder, so inherits its capability to efficiently estimate hundreds of parameters. In this paper we describe details of the underlying population dynamics and statistical framework. The description is based upon modelling for crustaceans that undergo molting and with each subsequent molt increase in size. + + \end{abstract} + + + \section*{Introduction} % (fold) + \label{sec:introduction} + + Statistical catch age models have several advantages over simple production type models in that age and size composition data can be used to better inform structural features such as recruitment variability, and total mortality rates. There are a number of generic age-structured models in use today, but there are very few generic size-based, or staged-based models that are used in stock assessment. In this paper we describe a generalized statistical catch-at-size model that is well suited for animals that cannot be aged, and where only precise length measurements are available. The description is based on a crustaceans that undergo molting and with each subsequent molt increase in length. + + % section introduction (end) + + \section*{Methods} % (fold) + \label{sec:methods} + The analytical details of the generalized model is summarized using tables of equations (e.g., Table \ref{tab:equilibrium_model}). These tables serve two purposes: (1) to clearly provide the logical order in which calculations proceed, and (2) organization of a relatively large integrated model into a series of sub-models that represent specific components such as population dynamics, observation models, reference point calculations, fisheries dynamics, and the objective function. We first start with a description of the population dynamics under steady-state (equilibrium) conditions. + + For model notation, vectors and matrixes are given in bold using lower and upper case notation, respectively. Model notation and a description of symbols are provided in Table \ref{tab:notation}. + + +\begin{table} + \centering + \caption{Mathematical notation, symbols and descriptions.} + \label{tab:notation} + \begin{tabular}{cl} + \hline + Symbol & Description \\ + \hline + \multicolumn{2}{l}{\underline{Index}}\\ + $g$ & group \\ + $h$ & sex \\ + $i$ & year \\ + $j$ & time step (years) \\ + $k$ & gear or fleet \\ + $l$ & index for length class \\ + $m$ & index for maturity state \\ + $o$ & index for shell condition. \\ + \multicolumn{2}{l}{\underline{Leading Model Parameters}}\\ + $M$ & Instantaneous natural mortality rate\\ + $\bar{R}$ & Average recruitment\\ + $\ddot{R}$ & Initial recruitment\\ + $\alpha_r$ & Mode of size-at-recruitment\\ + $\beta_r $ & Shape parameter for size-at-recruitment\\ + $R_0$ & Unfished average recruitment\\ + $\kappa$ & Recruitment compensation ratio\\ + \multicolumn{2}{l}{\underline{Size schedule information}}\\ + $w_{h,l}$ & Mean weight-at-length $l$ \\ + $m_{h,l}$ & Average proportion mature-at-length $l$ \\ + \multicolumn{2}{l}{\underline{Per recruit incidence functions}} \\ + $\phi_B$ & Spawning biomass per recruit \\ + $\phi_{Q_k}$& Yield per recruit for fishery $k$\\ + $\phi_{Y_k}$& Retained catch per recruit for fishery $k$ \\ + $\phi_{D_k}$& Discarded catch per recruit for fishery $k$ \\ + \multicolumn{2}{l}{\underline{Selectivity parameters}} \\ + $a_{h,k,l}$ & Length at 50\% selectivity in length interval $l$\\ + $\sigma_{s_{h,k}}$ & Standard deviation in length-at-selectivity\\ + $r_{h,k,l}$ & Length at 50\% retention\\ + $\sigma_{y_{h,k}}$ & Standard deviation in length-at-retention\\ + $\xi_{h,k}$ & Discard mortality rate for gear $k$ and sex $h$\\ + \hline + \end{tabular} +\end{table} + + + \subsection*{Equilibrium considerations} % (fold) + \label{sub:equilibrium_considerations} + Parameters for the population sub model are represented by the vector $\Theta$ (\ref{T1.1} in Table \ref{tab:equilibrium_model}), which consists of the natural mortality rate, average-recruitment, initial recruitment in the first year, parameters that describe the size-distribution of new recruits, and stock-recruitment parameters (see Table \ref{tab:notation} for notation). Constraints for these model parameters are defined in \eqref{T1.2}. Assuming the molt increments are linear, growth following each molt is a parametric function with the parameters defined in $\Phi$. + + The model is based on a set of user defined size categories. We assume at any time the population consists of a vector where each component of the vector consists of a number of individuals in some size category. The size category intervals and mid points of those intervals are defined by \eqref{T1.3}. Average molt increments from size category $l$ to the next is assumed to be sex-specific, and is defined by a linear function \eqref{T1.4}. The probability of transitioning from size category $l$ to $l'$ assumed that variation in molt increments follows a Gamma distribution \eqref{T1.5}, and the size-transition matrix for each sex $h$ is denoted as $\pmb{G}_h$. + + The size distribution of new recruits is assumed to follow a gamma distribution \eqref{T1.7} with the parameters $\alpha_r$ and $\beta_r$. The gamma distribution is scaled such that $\alpha_r$ is the mode of the distribution and could potentially be obtained from empirical size composition data. The vector of new recruits at each time step \eqref{T1.8} assumes a 50:50 sex ratio. + + For unfished conditions that are subject only to sex-specific natural mortality $M_h$ rates, we assume that each year members of the population grow and experience mortality. The basic assumption is that this process is a linear function of the numbers in each size category, where the categories are separated by sex to accommodate differential growth and survival rates. Survival and growth at each time step in unfished conditions is based on \eqref{T1.10}, where $(\pmb{I}_n)_{l,l'}$ is the identity matrix and $M_h$ is a scaler. It's also possible to accommodate size-specific natural mortality rates in \eqref{T1.10} where $M_h$ represents a vector of length-specific natural mortality rates. + + + +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% +\begin{table} + \centering +\caption{Mathematical equations and notation for a steady-state length based model.} +\label{tab:equilibrium_model} +\tableEq + \begin{align} + \hline \nonumber \\ + &\mbox{\underline{model parameters}} \nonumber\\ + &\Theta = (M_h,\bar{R},\ddot{R},\alpha_r,\beta_r,R_0,\kappa) \label{T1.1}\\ + &M_h > 0 , \bar{R} > 0, \ddot{R}>0, \alpha_r > 0, \beta_r > 0, R_0>0,\kappa > 1.0 \label{T1.2}\\ + &\Phi = (\alpha_h,\beta_h,\varphi_h) \label{T1.3}\\ + %% + %% + &\mbox{\underline{length-schedule information}} \nonumber \\ + %vector of length intervals + &\vec{l},\vec{x} \quad \mbox{vector of length intervals and midpoints, respectively} \nonumber\\ + % Growth increment + &a_{h,l} = (\alpha_h + \beta_h l)/\varphi_h \label{T1.4} \\ + %Size transition matrix + &p({l},{l'})_h =\pmb{G}_h= \int_{l}^{l+\Delta l} + \frac{ l^{(a_{h,l}-1)} \exp(l/\varphi_h) } + { \Gamma(a_{h,l}) l^{(a_{h,l})} } dl \label{T1.5} \\ + %% + %% + &\mbox{\underline{recruitment size-distribution}} \nonumber \\ + & \alpha = \alpha_r / \beta_r \\ + % Size distribution of new recruits + &p[\bm{r}] = \int_{x_l-0.5\Delta x}^{x_l+0.5\Delta x} + \frac{x^{(\alpha-1)}\exp(- x / \beta_r)}{\Gamma(\alpha)\beta_r^\alpha}dx + \label{T1.7}\\ + &\pmb{r}_h = 0.5 p[\bm{r}] \ddot{R} \label{T1.8}\\ + %% + %% + &\mbox{\underline{growth and survival}} \nonumber \\ + % &\pmb{U}_h = \exp(-M_h) (\pmb{I}_n)_{l,l'} \label{T1.9} \\ + %unfished + &\pmb{A}_h = \pmb{G}_h [\exp(-M_h) (\pmb{I}_n)_{l,l'}]\label{T1.10}\\ + % &\pmb{F}_h = \exp(-M_h - \pmb{f}_{h,l}) (\pmb{I}_n)_{l,l'} \label{T1.11}\\ + %fished + &\pmb{B}_h = \pmb{G}_h [\exp(-M_h - \pmb{f}_{h,l}) (\pmb{I}_n)_{l,l'}] \label{T1.12}\\ + %% + %% + &\mbox{\underline{survivorship to length}} \nonumber \\ + & \bm{u}_h = -(\bm{A}_h - (\bm{I}_n)_{l,l'})^{-1} (p[\bm{r}]) \label{T1.13a}\\ + & \bm{v}_h = -(\bm{B}_h - (\bm{I}_n)_{l,l'})^{-1} (p[\bm{r}]) \label{T1.13b}\\ + %% + %% + &\mbox{\underline{steady-state conditions}}\nonumber \\ + % & \pmb{v}_h = -(\pmb{A}_h-(\pmb{I}_n)_{l,l'})^{-1} (\pmb{r}_h)\label{T1.13}\\ + & B_0 = R_0 \sum_h \lambda_h \sum_l \pmb{u}_{h,l} w_{h,l} m_{h,l} \label{T1.14}\\ + % & \pmb{n}_h = -(\pmb{B}_h-(\pmb{I}_n)_{l,l'})^{-1} (\pmb{r}_h)\label{T1.15}\\ + & \tilde{B} = \tilde{R}\sum_h \lambda_h \sum_l \pmb{v}_{h,l} w_{h,l} m_{h,l} \label{T1.16}\\ + %% + %% + &\mbox{\underline{stock-recruitment parameters}}\nonumber\\ + &s_o = \kappa R_0 / B_0 \label{T1.17}\\ + &\beta = (\kappa -1)/B_0 \label{T1.18}\\ + &\tilde{R} = \frac{s_o \tilde{\phi}_B -1}{\beta \tilde{\phi}_B} \label{T1.19}\\ + %% + %% + \hline \hline \nonumber + \end{align} +\normalEq +\end{table} +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% + + Assuming a non-zero steady-state fishing mortality rate vector $\pmb{f}$, the equilibrium growth and survival process is represented by \eqref{T1.12}. The vector $\bm{f}_h$ represents all mortality associated with fishing, including mortality associated with discards in directed and non-directed fisheries. + + Assuming unit recruitment, then the growth and survivorship in unfished and fished conditions is given by the solutions to the matrix equations \eqref{T1.13a} and \eqref{T1.13b}, respectively. The vectors $\bm{u}_h$ and $\bm{v}_h$ represent the unique equilibrium solution for the numbers per recruit in each size category. The total unfished numbers in each size category is defined as $R_0 \bm{u}_h$. + + The unfished spawning stock biomass is defined as the equilibrium unfished recruitment multiplied by the sum of products of survivorship per recruit, weight-at-length, and proportion mature-at-length \eqref{T1.14}. The definition of spawning biomass may include only the females, or only males, or some combination thereof. To accommodate various definitions of spawning biomass the parameter $\lambda_h$, with the additional constraint $\sum_h \lambda_h = 1$, assigns the relative contribution of each sex to the spawning biomass. For example, if $\lambda = 1$ then the definition of spawning biomass is determined by a single sex. If $\lambda = 0.5$, the spawning biomass consists of an equal sex ratio. + + Under steady-state conditions where the fishing mortality rate is non zero, \eqref{T1.16} defines the equilibrium spawning biomass based on the survivorship of a fished population. In this case the equilibrium recruitment $\tilde{R}$ must be defined based on a few additional assumptions; the first of which being the form of the stock-recruitment relationship. Assuming recruitment follows the familiar asymptotic function, or Beverton-Holt relationship: + \begin{equation} \label{eq:BevertonHolt} + \tilde{R} = \frac{s_o \tilde{B}}{1 + \beta \tilde{B}}, + \end{equation} + where $\tilde{B}$ is the equilibrium spawning biomass, $s_o$ is the slope at the origin, and $s_o/\beta$ is the asymptote of the function. The parameters of this model can be derived from the unfished recruitment $R_0$ and the recruitment compensation ratio $\kappa$. The slope at the origin, or $s_o$, is defined as \eqref{T1.17} with the additional constraint that $\kappa > 1$ for an extant population. Substituting \eqref{T1.17} into the Beverton-Holt model \eqref{eq:BevertonHolt}, and solving for $\beta$ yields \eqref{T1.18}. For a given level of survivorship, the equilibrium recruitment is defined by \eqref{T1.19}, where $\tilde{\phi}_B$ is defined by \eqref{T3.1}. + + Given \eqref{T1.13b} is defined as the vector of individuals per recruit in a fished population, the relative reproductive potential per individual recruit is defined as the sum of products of weight-at-length, maturity-at-length and survivorship-to-length: + \[ + \tilde{\phi}_B = \sum_h \lambda_h \sum_l \bm{v}_{h,l} w_{h,l} m_{h,l} + \] + The total equilibrium spawning biomass is defined as $\tilde{B} = \tilde{R} \phi$. Substituting this expression into \eqref{eq:BevertonHolt} and solving for $\tilde{R}$ results in \eqref{T1.19}. + + + + + + % Given initial estimates of the unfished recruitment $R_0$ and the recruitment compensation parameter $\kappa$ we can then derive the stock recruitment parameters from the following Beverton-Holt recruitment model + % where $B_e$ is the equilibrium spawning biomass, $s_o$ is the maximum survival rate $R_e/B_e$ as $B_e$ tends towards 0, $\beta$ is a density dependent survival rate parameter, and $R_e$ is the equilibrium number of recruits of all size classes ($R_e = \sum_l r_l$). The maximum survival rate at the origin of the stock-recruitment curve is a multiple of the recruits per unit of spawning biomass at unfished conditions. This results in \eqref{T1.17}, with the additional constraint that $\kappa > 1$. Equation \ref{T1.18} is derived by solving the above equation for $\beta$, substituting \eqref{T1.17} for $s_o$ and simplifying. If we further assume unit recruitment (i.e., $\ddot{R} = 1$ in eq. \ref{T1.8}), the reproductive potential per recruit can be calculated as: + % where $\pmb{y}_h$ is the unique equilibrium solution corresponding to the unit recruitment. This is calculated as + % \[ + % \pmb{y}_h = -(\pmb{F}_h - (\pmb{I}_n)_{l,l'})^{-1} p(\pmb{r}) + % \] + % The equilibrium recruitment given steady-state conditions with fishing mortality greater than 0 is defined by \eqref{T1.19}. + + The equilibrium model defined in Table \ref{tab:equilibrium_model} is a very concise system of equations from which fisheries reference points are easily derived. The minimum amount of information that is necessary to derive SPR-based reference points is an estimate of the natural mortality rate, fisheries selectivity, the size-transition matrix (or growth based on molt increment information). These data alone are sufficient enough to calculate $F_{\rm{SPR}}$, and the only additional requirement for $B_{\rm{SPR}}$ is to have an estimate of unfished recruitment or a specified average recruitment. + + % subsection equilibrium_considerations (end) + + + \subsection*{SPR-based reference points} % (fold) + \label{sub:spr_based_reference_points} + Reference points based on the Spawning Potential Ratio (SPR) are frequently used as proxies to determine Maximum Sustainable Yield (MSY). The spawning potential ratio is defined as the ratio of reproductive output in fished conditions relative to unfished conditions. In the notation used in Table \ref{tab:incidence_fucntions} the SPR is defined as + \begin{equation} + SPR = \tilde{\phi}_B/\phi_B + \end{equation} + Fishing mortality rates that results in SPR values of 0.3-0.4 are often desirable for approximating maximum sustainable yield \citep{clark2002f}. To calculate \fspr\ an iterative solution is required to determine the instantaneous fishing mortality rate that is required to achieve the desired SPR level. For a single fishery this is relatively simple; the fishing mortality rate-at-length vector is the product of selectivity-at-length and fishing effort. A simple bisection algorithm can then be used to iteratively solve for the value of \fspr\ that results in the target SPR. In cases where there is one or more fisheries involved, and the selectivities differ among fisheries, the target \fspr\ will depend on the relative differences in selectivities among gears. Moreover, the allocation of total fishing mortality to each gear has to be specified \textit{a priori}. The solution to this problem must be negotiated as part of the management process as there are an infinite number of allocation combinations that would result in achieving \fspr. Given a vector of predefined fishing mortality rate ratios, \fspr\ can then be numerically determined using the same algorithm as the single fishery example. + + The expected spawning biomass level when fishing at \fspr\ is referred to as \bspr. To calculate \bspr\ we first evaluate \eqref{T1.12} using \fspr\ and then calculate the steady state biomass using \eqref{T1.16}. An alternative way to calculate the SPR-based reference points is to use per recruit quantities, or incidence functions (Table \ref{tab:incidence_fucntions}). For example, the SPR is the ratio of spawning biomass per recruit in fished and unfished populations, or \eqref{T2.3}. For each incidence function the primary difference between the fished and unfished states is the equilibrium numbers at length. In Table \ref{tab:incidence_fucntions} we used $\phi$ and $\tilde{\phi}$ to represent fished and unfished states. \bspr\ is given by \eqref{T2.4} and the total catch at \fspr\ is given by \eqref{T2.5}. Other quantities such as the equilibrium retained catch, or discards, when fishing at \fspr\ or any other rate can easily be computed using survivorship-at-length schedules and the equilibrium recruitment (Table \ref{tab:incidence_fucntions}). + + \begin{table} + \centering + \caption{Incidence functions for equilibrium calculations based on unfished and fished conditions, and SPR-based reference points.} + \label{tab:incidence_fucntions} + \tableEq + \begin{align} + \hline \nonumber + &\mbox{\underline{Incidence functions}} \nonumber \\ + &\mbox{\underline{unfished}} &\mbox{\underline{fished}}\nonumber \\ + %% Biomass Per Recruit + &\phi_B = \sum_h \lambda_h \sum_l u_{h,l} w_{h,l} m_{h,l}, \qquad + &\tilde{\phi}_B = \sum_h \lambda_h \sum_l v_{h,l} w_{h,l} m_{h,l} \label{T3.1}\\ + %% + %% Yield Per Recruit + &\phi_{Q_k} = 0, \qquad + &\tilde{\phi}_{Q_k} = \sum_h \sum_l \frac{v_{h,l} w_{h,l} s_{h,k,l} (1-\exp(-Z_{h,l}))}{Z_{h,l}} \\ + %% + %% Retained catch per recruit + &\phi_{Y_k} = 0, \qquad + &\tilde{\phi}_{Y_k} = \sum_h \sum_l \frac{v_{h,l} w_{h,l} y_{h,k,l} (1-\exp(-Z_{h,l}))}{Z_{h,l}} \\ + %% Discarded catch per recruit + &\phi_{D_k} = 0, \qquad + &\tilde{\phi}_{D_k} = \sum_h \sum_l \frac{v_{h,l} w_{h,l} d_{h,k,l} (1-\exp(-Z_{h,l}))}{Z_{h,l}} \\ + %% + %% + &\mbox{\underline{SPR-based reference points}} \nonumber \\ + & SPR = \tilde{\phi}_B/ \phi_B \label{T2.3}\\ + & B_{\textnormal{SPR\%}} = \tilde{R} \tilde{\phi}_B \bigr\rvert _{F=F_{\textnormal{SPR}}} \label{T2.4}\\[1ex] + & C_{\textnormal{SPR\%}} = \tilde{R} \tilde{\phi}_Q \bigr\rvert _{F=F_{\textnormal{SPR}}} \label{T2.5}\\[1ex] + \hline \hline \nonumber + \end{align} + \normalEq + \end{table} + + % subsection spr_based_reference_points (end) + + \subsection*{Fishing mortality} % (fold) + \label{sub:fishing_mortality} + + Many invertebrate fisheries impose a minimum size limits and prohibit the retention of females as a conservation tool. The probability dying due to fishing comes in two forms, an individual is captured and retained, or the same individual is discarded and dies prematurely due to handling effects. The retained portion of the catch is generally a measurable quantity; however, the discard mortality component cannot be directly measured in situ. To account for mortality associated with both retention and discarding we use the following joint probability to model vulnerability due to fishing mortality by gear $k$ at length category $l$ (ignoring sex for clarity) + \begin{equation}\label{eq:selectivity} + \nu_{k,l} = s_{k,l} [y_{k,l} + (1-y_{k,l})\xi_{k}], + \end{equation} + where $s_{k,l}$ is the probability of catching an animal of length $l$ (or selectivity), $y_{k,l}$ is the probability of retaining an individual in fishery $k$, and $\xi_{k}$ is the discard mortality rate for fishery $k$. Both parametric functions and non-parametric can be used to parameterize selectivity and retention functions. In this application we use a simple logistic function to represent selectivity \eqref{T4.3}, and retention \eqref{T4.4} The discard mortality rate $\xi_k$ in \eqref{eq:selectivity} and \eqref{T4.5} assumes the rate is size-independent. However, alternative size-based functions or other covariates such as temperature could be accommodated, but the estimates would have to be obtained independently as its not possible to quantify the discard mortality rate in situ. + + \begin{table} + \centering + \caption{Size-based selectivity, retention and fishing mortality.} + \label{tab:fishing_mortality} + \tableEq + \begin{align} + \hline \nonumber + &\mbox{\underline{Parameters}} \nonumber \\ + & \bm{\bar{f}}_k,\bm{\Psi}_{k,i}, a_{h,k},\sigma_{s_{h,k}},r_{h,k},\sigma_{y_{h,k}} \label{T4.1}\\ + & \sum_i \bm\Psi_{k,i} = 0 \label{T4.2}\\ + %% + %% + &\mbox{\underline{Selectivity \& retention}} \nonumber \\ + &s_{h,k,l} = (1 + \exp(-(l-a_{h,k} )/ \sigma_{s_{h,k}}))^{-1}\label{T4.3}\\ + &y_{h,k,l} = (1 + \exp(-(r_{h,k} - l) / \sigma_{y_{h,k}}))^{-1}\label{T4.4}\\ + &\nu_{h,k,l} = s_{h,k,l} [y_{h,k,l} + (1-y_{h,k,l})\xi_{h,k}]\label{T4.5}\\[1ex] + %% + %% + &\mbox{\underline{Fishing mortality}} \nonumber \\ + & \bm{F}_{k,i} = \exp(\bm{\bar{f}_k + \bm{\Psi_{k,i}}}) \label{T4.6}\\ + &\bm{f}_{h,i,l} = \sum_k \bm{F}_{k,i} \nu_{h,k,l} \label{T4.7}\\ + %% + %% + &\mbox{\underline{Penalized negative loglikelihoods}} \nonumber\\ + &\ell_{F_k} = 0.5 \ln(2 \pi) + \ln(\sigma_{F_k}) + + 0.5 (\bar{F}_k - \hat{F})^2 / \sigma_{F_k}^2 \label{T4.8}\\ + \hline \hline \nonumber + \end{align} + \normalEq + \end{table} + In cases where only one sex is allowed to be retained (i.e., male only fisheries) the retention probability $y_{h,k,l} = 0$ for all size-classes. In this case, it is not necessary to estimate parameters for a sex-specific retention curve, as all females for example, would be discarded. + + To improve numerical stability during early phases of the parameter estimation scheme, a penalized likelihood component \eqref{T4.8} is used to constrain the average fishing mortality $\bar{F}_k$ to some user defined value of $\hat{F}_k$, where the weight associated with this penalty is defined by $\sigma_{F_k}$. During the last phase of estimation, the value of $\sigma_{F_k}$ is arbitrarily set to a large value (e.g., 2.0) to ensure its is not influencing the overall estimate of the mean fishing mortality rate. + + % subsection fishing_mortality (end) + + \subsection*{Natural mortality} % (fold) + \label{sub:natural_mortality} + Natural mortality is assumed to be sex-specific, size-independent, and may or may not be constant over time. In the case of time-varying natural mortality, the model assumes that changes in $M_{h,i}$ is a random walk process + \[M_{h,i+1} = M_{h,i} e^{\delta_{i}}\] + where $\delta_i$ is assumed to be normal with a known variance $\sigma^2_M$. There is an additional constraint where $\sum_i \delta_i = 0$ to ensure that the scale of $M_h$ remains estimable. The model further assumes that deviations in natural mortality rate are independent of sex. Key parameters for parameterizing natural mortality are defined in \eqref{T5.1}. Note that $\sigma_{M_h}$ is not estimable and must either be fixed or use an informative prior. + + The parameter vector $\bm{\delta}_i$ with all elements set equal to 0 is equivalent to time-invariant $M$. To implement time-varying changes in natural mortality rates, $\bm{\delta}$ is treated as an estimated vector of parameters; one parameter for each year in the model, or a fixed number of nodes and the series is interpolated using a bicubic spline. The number of nodes and the placement of the nodes is specified \emph{a priori}. + + Two alternative methods are used to constrain the natural mortality rate deviations: (1) the first is using a penalized likelihood, and (2) using cubic spline interpolation with a fixed number of nodes. There are two options for penalizing the likelihood \eqref{T5.3} for deviations in natural mortality: (a) allow for deviations around a mean, and (b) allow for drift in natural mortality rate using a likelihood penalizes the first differences in $\delta_i$. + + \begin{table} + \centering + \caption{Model and constraints for natural mortality} + \label{tab:natural_mortality} + \tableEq + \begin{align} + \hline \nonumber + &\mbox{Parameters} \nonumber \\ + & M_h, \bm{\delta}_i, \sigma_{M_h} \label{T5.1} \\[1ex] + &\mbox{Natural mortality} \nonumber \\ + & M_{h,i} = + \begin{cases} + M_h, &i=1\\ + M_{h,i-1} \exp(\delta_i) &i>1 + \end{cases} \label{T5.2} \\[1ex] + %% + %% + &\mbox{Penalized negative log-likelihood} \nonumber \\ + &\ell_{M_h} = + \begin{cases} + 0.5 \ln(2 \pi) + \ln(\sigma_{M_h}) + + 0.5 \sigma_{M_h}^{-2} \sum_{i=1}^{N} \delta_{i}^2, & \mbox{or} \\[1ex] + %% + 0.5 \ln(2 \pi) + \ln(\sigma_{M_h}) + + 0.5 \sigma_{M_h}^{-2}\sum_{i=1}^{N-1}(\delta_{i+1} - \delta{i})^{2} \\ + \end{cases}\label{T5.3}\\[1ex] + %% + \hline \hline \nonumber + \end{align} + \normalEq + \end{table} + + % subsection natural_mortality (end) + + \subsection*{Initial conditions} % (fold) + \label{sub:initial_conditions} + Initialization of the numbers-at-length, annual recruitment, can either be done assuming steady-state conditions using the equations laid out in Table \ref{tab:equilibrium_model}, or treated as unknown parameters to be estimated by fitting the model to data. The latter method requires size-composition data in the initial years in order to estimate the initial numbers-at-length. Table \ref{tab:initial_numbers} summarizes the proceeding steps required to initialize the number-at-length for the initial conditions. + + Estimated parameters at this stage include the natural mortality rate, the initial recruits, parameters for the size distribution of new recruits, and a vector of deviates $\bm{\upsilon}$, which are constrained to sum to zero, that represent historical variation in recruitment and or mortality \eqref{T6.1}. The initial numbers-at-length can be found by solving the same matrix equation outlined in Table \ref{tab:equilibrium_model}; however, in this case the total number of recruits is used, rather than assuming unit recruitment. This first proceeds by calculating the growth transition matrix \eqref{T6.4}, the distribution of new recruits \eqref{T6.6}, and assume a 50:50 sex ratio \eqref{T6.7} for the new recruits in each size class. The transition and survival from length class $l$ to $l'$ is assumed to involve only natural mortality $M_h$ in \eqref{T6.8}. Note that $(\bm{I}_n)_{l,l'}$ is the identity matrix. The initial numbers at length, for each sex, is given by \eqref{T6.9}, which is just the equilibrium vector of numbers-at-length multiplied by a vector of deviates $\bm{\upsilon}$. + + \begin{table} + \centering + \caption{ Initialize population model $\{i=1\}$ } + \label{tab:initial_numbers} + \tableEq + \begin{align} + \hline \nonumber + &\mbox{ Parameters } \\ + &\Theta = (M_h,\ddot{R},\alpha_r,\beta_r, \bm{\upsilon}) + ,\quad\mbox{where} \sum_l \bm{\upsilon}_l = 0 \label{T6.1} \\ + &\Phi = (\alpha_h,\beta_h,\varphi_h)\\[1ex] + %% + %% + &\mbox{Growth transition}\nonumber \\ + % Growth increment + &a_{h,l} = (\alpha_h + \beta_h l)/\varphi_h \label{T6.3} \\ + %Size transition matrix + &\pmb{G}_h= \int_{l}^{l+\Delta l} + \frac{ l^{(a_{h,l}-1)} \exp(l/\varphi_h) } + { \Gamma(a_{h,l}) l^{(a_{h,l})} } dl \label{T6.4} \\[1ex] + %% + &\mbox{Recruitment vector} \nonumber \\ + & \alpha = \alpha_r / \beta_r \label{T6.5} \\ + % Size distribution of new recruits + &p(\boldsymbol{r}) = \int_{x_l-0.5\Delta x}^{x_l+0.5\Delta x} + \frac{x^{(\alpha-1)}\exp(x / \beta_r)}{\Gamma(\alpha)x^\alpha}dx + \label{T6.6}\\ + &\pmb{r}_h = 0.5 p(\boldsymbol{r}) \ddot{R} \label{T6.7}\\[1ex] + %% + &\mbox{Growth and survival} \nonumber \\ + %unfished + &\pmb{A}_h = \pmb{G}_h [\exp(-M_h) (\pmb{I}_n)_{l,l'}]\label{T6.8}\\[1ex] + %% Initial numbers-at-length + &\mbox{Initial numbers-at-length $i=1$} \nonumber \\ + &\bm{n}_{h,i} = [-(\bm{A}_h - (\bm{I}_n)_{l,l'})^{-1} (\bm{r}_h)] e^{\bm{\upsilon}} \label{T6.9}\\[1ex] + \hline \hline \nonumber + \end{align} + \normalEq + \end{table} + + It is also possible to assume unfished equilibrium conditions for this model, where $\ddot{R}$ is replace with $R_0$ in \eqref{T6.7}, and the vector of deviates $\bm{\upsilon} = 0$. In this case, the size-structured model, with any number of size-classes, is initialized with just seven parameters assuming sex-independent growth and survival, and just 11 parameters with sex-dependent growth and survival. + + % subsection initial_conditions (end) + + \subsection*{Population dynamics} % (fold) + \label{sub:population_dynamics} + Updating the numbers ($\bm{n}_{h,i}$) in each size-class at each time step is the product of size-specific growth and survival ($\bm{A}_h$) times the numbers-at-length plus new recruitment ($\bm{r}_{h,i}$): + \begin{equation}\label{eq:update_numbers_at_length} + \bm{n}_{h,i+1} = \bm{n}_{h,i} \bm{A}_h + \bm{r}_{h,i} + \end{equation} + + \begin{table} + \centering + \caption{ Population dynamics. } + \label{tab:population_dynamics} + \tableEq + \begin{align} + \hline \nonumber + &\mbox{ Parameters } \\ + &\Theta = \\ + \hline \hline \nonumber + \end{align} + \normalEq + \end{table} + + % subsection population_dynamics (end) + \subsection*{Model fitting} % (fold) + \label{sub:Model fitting} + \subsubsection*{Data components} + \label{subsub:Data components} + \subsubsection*{Prior distributions} + \label{subsub:Prior distributions} + As noted in reference to \eqref{T5.3} some penalties are relaxed at the final stages of estimation to provide stability. There are other prior assumptions in the model. Namely the prior for the stock-recruit relationship (in specification of $\sigma_{R}$) + +\begin{table} + \centering + \caption{Likelihoods and prior distributions} + \label{tab:likelihoods} + \tableEq + \begin{align} + \hline \nonumber + &\mbox{Negative log-likehoods} \nonumber \\ + &\mbox{Indices} \nonumber \\ + & l_i = \bm{\delta}_i, \sigma_{M_h} \label{T5.1} \\[1ex] + &\mbox{Size compositions} \nonumber \\ + & M_{h,i} =0.5 \sigma_{M_h}^{-2} \sum_{i=1}^{N} \delta_{i}^2, + \begin{cases} + M_h, &i=1\\ + M_{h,i-1} \exp(\delta_i) &i>1 + \end{cases} \label{T5.2} \\[1ex] + %% + %% + &\mbox{(negative log) Priors (ignoring constants)} \nonumber \\ + &\ell_{M_h} = + \begin{cases} + \ln(\sigma_{M_h}) + + 0.5 \sigma_{M_h}^{-2} \sum_{i=1}^{N} \delta_{i}^2, & \mbox{or} \\[1ex] + %% + 0.5 \ln(2 \pi) + \ln(\sigma_{M_h}) + + 0.5 \sigma_{M_h}^{-2}\sum_{i=1}^{N-1}(\delta_{i+1} - \delta{i})^{2} \\ + \end{cases}\label{T5.3}\\[1ex] + %% + \hline \hline \nonumber + \end{align} + \normalEq + \end{table} + +% subsection Model fitting (end) + +% subsection population_dynamics (end) + + % section methods (end) + + %\input{Methods} + + +% +% + \subsection*{Application to Bristol Bay red king crab} % (fold) + The data set used for this application was set to be the same as that used for the 2013 assessment [ref?] + + + \section*{Results} % (fold) + Data + + \section*{Discussion} % (fold) + + + + \bibliographystyle{apalike} + \bibliography{$HOME/Documents/ARTICLES/Articles-1} + +\end{document} diff --git a/docs/manuscript/Methods.tex b/docs/manuscript/Methods.tex new file mode 100644 index 00000000..c7d3115c --- /dev/null +++ b/docs/manuscript/Methods.tex @@ -0,0 +1,165 @@ +%!TEX root = GLBAM.tex +\section*{Model description} +The following is a list of the input data structures used in data file for Gmacs. + +\begin{table}[!tbh] + \caption{Input data structures}\label{Tab:inputDataStructures} + \begin{tabular}{lcll} + \hline + Variable & Symbol & Type & Description \\ + \hline + styr & $t$ & int & Start year \\ + endyr & $t$ & int & End year \\ + tstep & NA & double & time step \\ + ndata & & int & number of data groups \\ + nsex & $s$ & int & number of sexes \\ + nshell & $v$ & int & number of shell conditions\\ + nmature & $m$ & int & number of maturity states \\ + nclass & $l$ & int & number of size classes in the model\\ + % ndclass & $l$ & int & number of size classes in the data\\ + ncol & & int & number of columns in N-matrix \\ + + % Not used anywhere in the code. + % psex & & ivector(1,nsex)& starting col pos for sex-specific N\\ + % pshell && ivector(1,npshell)& starting col pos for shell-specific N\\ + % pmature &&ivector(1,npmature)&starting col pos for mature-specific N\\ + % pall&&ivector(1,npmature)& col position for all blocks of N\\ + + class\_link & & matrix(1,nclass,1,2)&links between model and data size-classes.\\ + \hline + \end{tabular} +\end{table} + + +\paragraph{Indexes} +For consistency the following indexes are used to describe the various model dimensions: + +\begin{description} + \item [g] index for group (sex, shell condition, maturity state), + \item [h] index for sex, + \item [i] index for year, + \item [j] index for season or month, + \item [k] index for fleet, + \item [l] index for length class, + \item [m] index for maturity state, + \item [n] index for shell condition, +\end{description} + + +\subsection{Recruitment} % (fold) +\label{sub:recruitment} +The numbers-at-size in the first year are initialized using an initial mean recruitment $\dot{R}$, natural mortality, the size transition matrix, and a vector of deviations for each size class that represents recruitment variability prior to the initial start year of the model. Assuming steady state conditions, the model assumes that at any time the population consists of a vector of individuals in each size category. At each time step, these individuals experience natural mortality and grow into the next size category and is represented by the matrix $\boldsymbol{A}$. If the number of individuals in a given size class is represented by $\boldsymbol{v}=(v_1,v_2,\ldots,v_n)$, then after growing and surviving to the next time step is given by $\boldsymbol{A}\boldsymbol{v}$. This does not include new recruits into the population. Let $\boldsymbol{r}= (r_1, r_2, \ldots, r_n)$ be the vector of new recruits at each size class. Then the population next year is equal to $\boldsymbol{A}\boldsymbol{v} + \boldsymbol{r}$. Recruitment in this contexts is defined as the number of new individuals entering the popuation in a specific size class. In a simple age-structured model this would be the total number of age-0 recruits, and in the next year these individuals would all enter the age-1 class. In a size-based model, not all individuals will leave a given size class (i.e., there is a probability of not molting and remaining in the same size class). Moreover, individuals will growth to multiple size categories in one-time step due to individual variation in molt increments or molt frequency. + +Let $\boldsymbol{x}=(x_1,x_2,\ldots,x_n)$ be the equilibrium population when the recruitment vector is $\boldsymbol{r}$. The requirement that the population is at equilibrium is equivalent to the matrix equation +\begin{equation}\label{eq1} + \bs{x} = \bs{A}\bs{x} + \bs{r} +\end{equation} +and the equilibrium solution for $\bs{x}$ is given by +\begin{equation}\label{eq2} + \bs{x} =-(\bs{A}-\mathbf{I})^{-1}(\bs{r}) +\end{equation} +where $\mathbf{I}$ is the $n \times n$ identity matrix. + +Given an initial value of $\dot{R}$, the distribution of new recriuts is represented by a gamma distribution \eqref{T4.4}, where the estimated parameters $R_\alpha$ and $R_\beta$ represent the mean size at recruitment and the coefficient of variation in size. At equilibrium, the total number of recruits in each size class is given by +\begin{equation}\label{eq3} + \bs{r} = p(\bs{r})\dot{R}, +\end{equation} +and departures from equilibrium conditions are represented by +\begin{equation}\label{eq4} + \bs{r} = p(\bs{r})\dot{R}\exp(\bs{\nu}), +\end{equation} +where $\bs{\nu}=(\nu_1,\nu_2,\ldots,\nu_n)$ is a vector of estimated deviations with the additional constraint $\sum_i\nu_i = 0$. + +Annual recruitment to each size class is an estimated vector of deviates $\bs{\xi}=(\xi_{i=2},\xi_{i=3},\ldots,\xi_{i=I})$ around an average recruitment value $\bar{R}$ +\begin{equation} + \bs{r}_i = p(\bs{r})\bar{R}\xi_i +\end{equation} +where it is assumed that the size-distribution of new recruits is time-invariant and the additional constraint $\sum_i \xi_i = 0$. +% subsection recruitment (end) + + +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% +\begin{table} + \centering +\caption{Statistical catch-at-length model used in Gmacs} +\label{tab:statistical_catch_length_model} +\tableEq + \begin{align} + \hline \nonumber \\ + &\mbox{Estimated parameters} \nonumber\\ + \Theta&= + (M_0,\ln(\dot{R}),\ln(\bar{R}),R_\alpha,R_\beta, + \alpha_h, \beta_h,b_h, \bs{\nu},\bs{\xi})\label{T4.1}\\ + \sigma^2&=\rho /\vartheta^2, \quad + \tau^2=(1-\rho)/\vartheta^2\label{T4.2}\\[1ex] + %\vartheta^2=\sigma^2+\tau^2, \quad + %\rho=\frac{\sigma^2}{\sigma^2+\tau^2}\label{T4.3}\\[1ex] + %% + %% + &\mbox{Unobserved states} \nonumber\\ + &\boldsymbol{N},\boldsymbol{Z} \label{T4.3}\\ + %% + %% + &\mbox{Recruitment size distribution} \nonumber\\ + \alpha &= R_\alpha /R_\beta \nonumber \\ + p(\boldsymbol{r}) &= \int_{x_l-0.5\Delta x}^{x_l+0.5\Delta x} + \frac{x_l^{(\alpha-1)}e^{x_l/R_\beta}}{\Gamma(\alpha)x_l^\alpha}dx + \label{T4.4}\\ + %% + %% + &\mbox{Molt increment \& size transition} \nonumber\\ + a_{h,l} &= \alpha_h + \beta_h l \label{T4.5} \\ + p({l},{l'})_h &= \int_{l-0.5\Delta l}^{l+0.5\Delta l} + \frac{ l^{(a_{h,l}-1)} e^{l/b_h} } + { \Gamma(a_{h,l}) l^{a_{h,l}} } dl \label{T4.6} \\ + % &\mbox{Initial states} \nonumber\\ + % %v_a=\left[1+e^{-(\hat{a}-a)/\hat{\gamma}}\right]^{-1}\label{T4.7}\\ + % N_{t,a}&=\bar{R}e^{\omega_{t-a}} \exp(-M_t)^{(a-1)};\quad t=1; 2\leq a\leq A \label{T4.4}\\ + % N_{t,a}&=\bar{R}e^{\omega_{t}} ;\quad 1\leq t\leq T; a=1 \label{T4.5}\\ + % v_{k,a}&=f(\gamma_k) \label{T4.6}\\ + % M_t &= M_{t-1} \exp(\varphi_t), \quad t>1 \label{T4.6b}\\ + % F_{k,t}&=\exp(\digamma_{k,t}) \label{T4.7}\\[1ex] + % %% + % %% + % &\mbox{State dynamics (t$>$1)} \nonumber\\ + % B_t&=\sum_a N_{t,a}f_a \label{T4.8}\\ + % Z_{t,a}&=M_t+\sum_k F_{k,t} v_{k,t,a}\label{T4.9}\\ + % \hat{C}_{k,t}&=\sum _ a\frac {N_{{t,a}}w_{{a}}F_{k,t} v_{{k,t,a}} + % \left( 1-{e^{-Z_{t,a}}} \right) }{Z_{t,a}}^{\eta_t} \label{T4.10}\\ + % %F_{t_{i+1}}= \ F_{t_{i}} -\frac{\hat{C}_t-C_t}{\hat{C}_t'} \label{T4.12}\\ + % N_{t,a}&=\begin{cases} + % %\dfrac{s_oE_{t-1}}{1+\beta E_{t-1}} \exp(\omega_t-0.5\tau^2) &a=1\\ \\ + % N_{t-1,a-1} \exp(-Z_{t-1,a-1}) &a>1\\ + % N_{t-1,a} \exp(-Z_{t-1,a}) & a=A + % \end{cases}\label{T4.11}\\[1ex] + % %% + % %% + % &\mbox{Recruitment models} \nonumber\\ + % R_t &= \frac{s_oB_{t-k}}{1+\beta B_{t-k}}e^{\delta_{t}-0.5\tau^2} \quad \mbox{Beverton-Holt} \label{T4.12}\\ + % R_t &= s_oB_{t-k}e^{-\beta B_{t-k}+\delta_t-0.5\tau^2} \quad \mbox{Ricker} \label{T4.13}\\ + %% \mbox{Residuals \& predicted observations} \nonumber\\ + %% \epsilon_t=\ln\left(\frac{I_t}{B_t}\right)-\frac{1}{n}\sum_{t \in I_t}\ln\left(\frac{I_t}{B_t}\right)\label{T4.15}\\ + %% \hat{A}_{t,a}=\dfrac{N_{t,a}\dfrac{F_tv_a}{Z_{t,a}}\left(1-e^{-Z_{t,a}}\right)} + %% {\sum_a N_{t,a}\dfrac{F_tv_a}{Z_{t,a}}\left(1-e^{-Z_{t,a}}\right)}\label{T4.16}\\ + \hline \hline \nonumber + \end{align} + + \normalEq +\end{table} +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% + +\subsection{Size transition matrix} % (fold) +\label{sub:size_transition_matrix} + +A parametric approach based on molt increments for calculating the elements of the size transition matrix is based on \eqref{T4.5} and \eqref{T4.6}. Molt increments are assumed to be a linear function of carapace width, or size-interval $l$. Growth is assumed to be sex-specific and is index by $h$. The probability of growing from interval $l$ to $l'$ is based on the gamma distribution \eqref{T4.6} where the expected increased in length is a function of the molt increment at length $l$ \eqref{T4.5} and the shape parameter $b_h$. + +In short, 3 estimated parameters ($\alpha_h, \beta_h$, and $b_h$) are required to describe growth increments and the size-transition matrix. Ideally, independent molt-increment data, by sex, should be included in the model to provide additional information to estimate $\alpha_h$ and $\beta_h$. Absent this information, clear modes in the size-composition data must be discernable in order to reasonably resolve confounding among the three growth parameters. + +% subsection size_transition_matrix (end) + +\subsection{Shell condition} % (fold) +\label{sub:shell_condition} +Many of the crab composition data sets are categorized by shell condition (e.g., new shell, old shell). Fitting to these data requires predicted values for new shell and old shell by size class. This is critical for species that have a terminal molt, and the proportion of old shell would accumulate over time, but less so under higher fishing mortality rates. +% subsection shell_condition (end) diff --git a/docs/manuscript/gmacsNRC.aux b/docs/manuscript/gmacsNRC.aux new file mode 100644 index 00000000..4ad9ce0b --- /dev/null +++ b/docs/manuscript/gmacsNRC.aux @@ -0,0 +1,3 @@ +\relax +\newlabel{gmacsNRC.start.page}{{}{1}} +\providecommand \NRC@tabwd {\@gobbletwo } diff --git a/docs/manuscript/gmacsNRC.fdb_latexmk b/docs/manuscript/gmacsNRC.fdb_latexmk new file mode 100644 index 00000000..1c55abb6 --- /dev/null +++ b/docs/manuscript/gmacsNRC.fdb_latexmk @@ -0,0 +1,16 @@ +# Fdb version 3 +["pdflatex"] 1416695466 "gmacsNRC.tex" "gmacsNRC.pdf" "gmacsNRC" 1416695466 + "/Users/stevenmartell1/Library/texmf/tex/latex/nrc/nrc2.cls" 1409083934 66000 c4e1cd04011310aa8f9f1a56e6cf89f9 "" + "/usr/local/texlive/2013/texmf-dist/tex/latex/base/article.cls" 1254151887 20571 b8bd218bf2e18b4f5817ee643cd9c515 "" + "/usr/local/texlive/2013/texmf-dist/tex/latex/base/fleqn.clo" 1254151887 3707 0625824d900a022b4f4ba15964210720 "" + "/usr/local/texlive/2013/texmf-dist/tex/latex/base/leqno.clo" 1254151887 1822 b0fdfbe75052d748d44447974b60ed4f "" + "/usr/local/texlive/2013/texmf-dist/tex/latex/base/size10.clo" 1254151887 9042 248dfba326a1b8733d6bb8e0a3ac1e49 "" + "/usr/local/texlive/2013/texmf-dist/tex/latex/psnfss/ot1phv.fd" 1137110629 1684 0ac4554419e828cf2c810306539da167 "" + "/usr/local/texlive/2013/texmf-dist/tex/latex/psnfss/ot1ptm.fd" 1137110629 961 15056f4a61917ceed3a44e4ac11fcc52 "" + "/usr/local/texlive/2013/texmf-dist/tex/latex/tools/multicol.sty" 1312409015 26766 56c30c5bea3083b5a0d6fc2ce0063096 "" + "gmacsNRC.aux" 1416695466 88 7c05dba9315226d7f78f1462f780c296 "" + "gmacsNRC.tex" 1409083716 7300 6d6e7312c46e3930cd4d8498bf5df6ac "" + (generated) + "gmacsNRC.log" + "gmacsNRC.aux" + "gmacsNRC.pdf" diff --git a/docs/manuscript/gmacsNRC.log b/docs/manuscript/gmacsNRC.log new file mode 100644 index 00000000..3ce36760 --- /dev/null +++ b/docs/manuscript/gmacsNRC.log @@ -0,0 +1,142 @@ +This is pdfTeX, Version 3.1415926-2.5-1.40.14 (TeX Live 2013) (format=pdflatex 2014.6.14) 22 NOV 2014 13:31 +entering extended mode + restricted \write18 enabled. + %&-line parsing enabled. +**gmacsNRC.tex -recorder +(./gmacsNRC.tex +LaTeX2e <2011/06/27> +Babel <3.9k> and hyphenation patterns for 78 languages loaded. +(/Users/stevenmartell1/Library/texmf/tex/latex/nrc/nrc2.cls +Document Class: nrc2 2013/02/02 v2.01a NRC 2-column journal class +(/usr/local/texlive/2013/texmf-dist/tex/latex/base/article.cls +Document Class: article 2007/10/19 v1.4h Standard LaTeX document class +(/usr/local/texlive/2013/texmf-dist/tex/latex/base/leqno.clo +File: leqno.clo 1998/08/17 v1.1c Standard LaTeX option (left equation numbers) +) +(/usr/local/texlive/2013/texmf-dist/tex/latex/base/fleqn.clo +File: fleqn.clo 1998/08/17 v1.1c Standard LaTeX option (flush left equations) +\mathindent=\dimen102 +) +(/usr/local/texlive/2013/texmf-dist/tex/latex/base/size10.clo +File: size10.clo 2007/10/19 v1.4h Standard LaTeX file (size option) +) +\c@part=\count79 +\c@section=\count80 +\c@subsection=\count81 +\c@subsubsection=\count82 +\c@paragraph=\count83 +\c@subparagraph=\count84 +\c@figure=\count85 +\c@table=\count86 +\abovecaptionskip=\skip41 +\belowcaptionskip=\skip42 +\bibindent=\dimen103 +) + +Class nrc2 Warning: GUTenberg Babel french style detected -- +(nrc2) some corruption of NRC-defined format may occur. + +(/usr/local/texlive/2013/texmf-dist/tex/latex/tools/multicol.sty +Package: multicol 2011/06/27 v1.7a multicolumn formatting (FMi) +\c@tracingmulticols=\count87 +\mult@box=\box26 +\multicol@leftmargin=\dimen104 +\c@unbalance=\count88 +\c@collectmore=\count89 +\doublecol@number=\count90 +\multicoltolerance=\count91 +\multicolpretolerance=\count92 +\full@width=\dimen105 +\page@free=\dimen106 +\premulticols=\dimen107 +\postmulticols=\dimen108 +\multicolsep=\skip43 +\multicolbaselineskip=\skip44 +\partial@page=\box27 +\last@line=\box28 +\mult@rightbox=\box29 +\mult@grightbox=\box30 +\mult@gfirstbox=\box31 +\mult@firstbox=\box32 +\@tempa=\box33 +\@tempa=\box34 +\@tempa=\box35 +\@tempa=\box36 +\@tempa=\box37 +\@tempa=\box38 +\@tempa=\box39 +\@tempa=\box40 +\@tempa=\box41 +\@tempa=\box42 +\@tempa=\box43 +\@tempa=\box44 +\@tempa=\box45 +\@tempa=\box46 +\@tempa=\box47 +\@tempa=\box48 +\@tempa=\box49 +\c@columnbadness=\count93 +\c@finalcolumnbadness=\count94 +\last@try=\dimen109 +\multicolovershoot=\dimen110 +\multicolundershoot=\dimen111 +\mult@nat@firstbox=\box50 +\colbreak@box=\box51 +\multicol@sort@counter=\count95 +) +\NRC@columnwidth=\dimen112 +\NRC@leftbox=\box52 +\NRC@rightbox=\box53 +\@tempboxb=\box54 +\NRC@theIDbox=\box55 +\NRC@abstract@toks=\toks14 +\NRC@resume@toks=\toks15 +\NRC@topcaptcounter=\count96 +\captionwidth=\dimen113 +) + +Class nrc2 Warning: Journal "" not recognised on input line 133. + + +Class nrc2 Warning: Journal code not recognised on input line 134. + +(./gmacsNRC.aux) +\openout1 = `gmacsNRC.aux'. + +LaTeX Font Info: Checking defaults for OML/cmm/m/it on input line 160. +LaTeX Font Info: ... okay on input line 160. +LaTeX Font Info: Checking defaults for T1/cmr/m/n on input line 160. +LaTeX Font Info: ... okay on input line 160. +LaTeX Font Info: Checking defaults for OT1/cmr/m/n on input line 160. +LaTeX Font Info: ... okay on input line 160. +LaTeX Font Info: Checking defaults for OMS/cmsy/m/n on input line 160. +LaTeX Font Info: ... okay on input line 160. +LaTeX Font Info: Checking defaults for OMX/cmex/m/n on input line 160. +LaTeX Font Info: ... okay on input line 160. +LaTeX Font Info: Checking defaults for U/cmr/m/n on input line 160. +LaTeX Font Info: ... okay on input line 160. +LaTeX Font Info: Try loading font information for OT1+ptm on input line 160. + + (/usr/local/texlive/2013/texmf-dist/tex/latex/psnfss/ot1ptm.fd +File: ot1ptm.fd 2001/06/04 font definitions for OT1/ptm. +) +LaTeX Font Info: Try loading font information for OT1+phv on input line 160. + + (/usr/local/texlive/2013/texmf-dist/tex/latex/psnfss/ot1phv.fd +File: ot1phv.fd 2001/06/04 scalable font definitions for OT1/phv. +)) +! Emergency stop. +<*> gmacsNRC.tex -recorder + +*** (job aborted, no legal \end found) + + +Here is how much of TeX's memory you used: + 846 strings out of 493308 + 11480 string characters out of 6137816 + 64153 words of memory out of 5000000 + 4370 multiletter control sequences out of 15000+600000 + 4753 words of font info for 16 fonts, out of 8000000 for 9000 + 957 hyphenation exceptions out of 8191 + 29i,0n,26p,201b,107s stack positions out of 5000i,500n,10000p,200000b,80000s +! ==> Fatal error occurred, no output PDF file produced! diff --git a/docs/manuscript/gmacsNRC.tex b/docs/manuscript/gmacsNRC.tex new file mode 100644 index 00000000..52d06c28 --- /dev/null +++ b/docs/manuscript/gmacsNRC.tex @@ -0,0 +1,217 @@ +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% +%% +%% Typeset by , Research Press, NRC +%% Date: +%% NRC, +%% +%%%%%%%%%%%%%% +%% +%% 1. See original preamble material (at bottom of file) for +%% details on source of current .tex file: conversion +%% from word-processing program or author-generated TeX +%% code. +%% +%% 2. This template includes most options and packages used by +%% all the NRC journals. UNcomment those packages and options +%% which are REQUIRED. +%% +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% + + +%% 1. Class file (nrc1 or nrc2) + options (see userguide, pp.1-2; p.9): +\documentclass[ + %% french, %% use with \usepackage[french]{babel} + %% leqno, %% only for nrc1 (default is right eqno) + %% reqno, %% only for nrc2 (default is left eqno) + %% nonumbib, %% biblio entries without nos. +% + %% breakaddress, %% linebreak btwn author(s) + address(es) + %% twocolid, %% IDbox spans 2 cols + %% twocolid*, %% 2-col IDbox + %% preprint, %% removes identifying nos. from headers/footers + %% proof, %% `Proof/Epreuve' in footer + %% pagnf, %% `Pagination not final/Pagination non finale' + %% trimmarks, %% add trimmarks + %% finalverso, %% final blank verso NOT included in pagerange +]{nrc2} %% choose one: nrc1 or nrc2 + +%% NOTE: authors may use the following options, which should be +%% DELETED once the file comes in-house: +%% +%% usecmfonts type1rest genTeX + + +%% 2. Frequently used packages -- see pp.2-3 of userguide: +%% a. graphics-related: +%% \usepackage{graphicx} %% color not usually needed +%% \usepackage[figuresright]{rotating} %% for landscape tables + +%% b. math-related: +%% \usepackage{amsmath} %% math macros in wide use +%% \usepackage{amssymb} %% additional math symbols +%% \usepackage{dcolumn} %% decimal alignment for tables +%% \usepackage{bm} %% `bold math' via \bm command + +%% c. for website addresses: +%% \usepackage{url} %% inserts linebreaks automatically +%% \NRCurl{url} + +%% d. biblio-related: +%% \usepackage{cite} %% enhances options for \cite commands + +%% e. for English-language papers: +%% \usepackage[french,english]{babel} + +%% f. for French-language papers: +%% \usepackage[english,french]{babel} %% remember to add french as a + %% CLASS option, above +%% g. for ragged-right tables: +%% \usepackage{array} +%% \newcommand{\PreserveBackslash}[1]{\let\temp=\\#1\let\\=\temp} +%% \let\PBS=\PreserveBackslash + +%% h. for left curly brace to span several lines of equations: +%% \usepackage{cases} +%% \expandafter\let\csname numc@left\expandafter\endcsname\csname +%% z@\endcsname + + +%% 3. Resetting float parameters: +%% a. in nrc1: +%% \renewcommand{\topfraction}{.95} +%% \renewcommand{\textfraction}{.05} +%% \renewcommand{\floatpagefraction}{.95} + +%% b. in nrc2: +%% \renewcommand{\topfraction}{.95} +%% \renewcommand{\floatpagefraction}{.95} +%% \renewcommand{\dbltopfraction}{.95} +%% \renewcommand{\textfraction}{.05} +%% \renewcommand{\dblfloatpagefraction}{.95} + + +%% 4. Resetting journal-specific parameters: +%% a. eqn nos. with section nos.: +%% \numberby {equation}{section} +%% \setcounter{equation}{0} + +%% b. in-line citations to use ( ) instead of default [ ]: +%% \renewcommand{\citeleft}{(} +%% \renewcommand{\citeright}{)} + +%% c. for JEES (to expand inter-line spacing; see p.12 of guide): +%% \easebaselines + + +%% 5. Miscellaneous macros to always have available: +%% a. shorthands: +\let\p=\phantom +\let\mc=\multicolumn + +%% b. struts for vertical spacing above/below rules in tables: +%%%%%%%%%%%%%%%%%% beginning of Claudio Beccari's code: +%% Spacing commands for {tabular} (from TTN 2,3:10 -- Claudio +%% Beccari): +%% Usage: a. use \T to put space below a line +%% (e.g., at top of a `cell' of text) +%% b. use \B to put space above a line +%% (e.g., at bottom of a `cell' of text) +\newcommand\T{\rule{0pt}{2.6ex}} % = `top' strut +\newcommand\B{\rule[-1.2ex]{0pt}{0pt}} % = `bottom' strut +%%%%%%%%%%%%%%%%%% end of Claudio's code + +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% end of class and package +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% options, additional macros + + +%% Journal-specific information for opening page -- pp.9-11 of guide: +%% a. numbers: +\setcounter{page}{1} %% replace 1 with starting page no. +\volyear{XX}{2001} %% volume, year of journal +\journal{} %% jrnl. abbrev. (see App.A of guide) +\journalcode{} %% jrnl. acro (see App.A of guide) +\filenumber{} %% NRC file number +%% \filenumber*{} %% prefixes \filenumber to all page nos. + %% NOTE: COMMENT OUT class options + %% pagnf + %% proof + %% once no longer needed + + +%% b. dates: +\received{} %% insert date, no period +\revreceived{} %% +\accepted{} %% +\revaccepted{} %% +%% \IDdates{} %% . Use for `Revised ...' etc. +%% \webpub{} %% insert date +%% \commdate{} %% + + +%% c. miscellaneous: +%% \assoced{} %% insert name of Associate ed. +%% \corred{} %% insert name of Corresponding ed. +%% \dedication{} %% insert text as neede +%% \abbreviations{} %% insert as needed + + +\begin{document} + +%% Reversed titlebar -- see p.11 of userguide: +%% \specialtitle{} %% for black stripe + text + regular title +%% \specialtitle*{} %% black stripe + text only + + + + +%% Title, Author(s), Address(es) -- see p.4 of userguide for +%% various options to save time and keyboarding, esp. where +%% authors share same address(s). + +\title{} + +%% Author 1: +\author[J.L. Humar]{John Larry Humar} %% opt. arg. ONLY if IDbox + %% name is diff. from + %% titleblock name +\address{} %% address of 1st author + + +%% Author 2: +\author{M.A. Rahgozar} +\address{} + +%% Author 3: +\author{Fred Murray} +\address{} + + +\shortauthor{Humar, Rahgozar, and Murray} %% for headers + +%%%%%%%% +%% This line goes here in nrc1. +%% \maketitle +%%%%%%%% + + +%% Abstract/Resume area -- see pp.5,12 of userguide: +\begin{abstract} + Abstract text +%% \keywords{} +%% \translation +\end{abstract} + +\begin{resume} + Texte du resume +%% \motscles{} +%% \Traduit %% or \traduit +\end{resume} + +%%%%%%%% +%% This line goes here in nrc2. +%% \maketitle +%%%%%%%% + +%%%%%%%%%%%%%%%%%%%%%% END OF TEMPLATE %%%%%%%%%%%%%%%%%%%%%% \ No newline at end of file diff --git a/examples/bbrkc/Makefile b/examples/bbrkc/Makefile new file mode 100644 index 00000000..e415900a --- /dev/null +++ b/examples/bbrkc/Makefile @@ -0,0 +1,23 @@ +EXEC = gmacs +ifeq ($(OPT),TRUE) + DIST = ../../src/build/release/ +else + DIST = ../../src/build/debug/ +endif +ARGS = -nox -iprint 50 + +all: run + +$(EXEC): $(DIST)$(EXEC).tpl + ln -sf $(DIST)$(EXEC) $@ + +$(DIST)$(EXEC).tpl: + $(MAKE) --directory=../../src + +run: $(EXEC) + ./$(EXEC) $(ARGS) + +clean: + rm -f $(EXEC) + rm -f admodel.* + rm -f $(EXEC) $(EXEC).[brces]* $(EXEC).*[0123456789] *.rpt *.log variance diff --git a/examples/bbrkc/bbrkc.ctl b/examples/bbrkc/bbrkc.ctl index 7a1f2f00..b104497c 100644 --- a/examples/bbrkc/bbrkc.ctl +++ b/examples/bbrkc/bbrkc.ctl @@ -1,175 +1,145 @@ -# Gmacs Control File Version 1.02 -# General parameter specifications *(only two for now): -#======================================================================================================== -# Init Lower Upper Phase Prior Pmean Psd Cov. Dev. Dsd Dmin Dmax Block - 9.76518 -10 40 1 0 0 0 0 0 0 0 0 0 #R0 - 0.18 0 1 -1 0 0.18 1000 0 0 0 0 0 0 #M -#======================================================================================================== +# Model 1, fixed multinomial sample sizes +# —————————————————————————————————————————————————————————————————————————————————————— # +# Controls for leading parameter vector theta +# LEGEND FOR PRIOR: +# 0 -> uniform +# 1 -> normal +# 2 -> lognormal +# 3 -> beta +# 4 -> gamma +# —————————————————————————————————————————————————————————————————————————————————————— # +# ntheta + 7 +# —————————————————————————————————————————————————————————————————————————————————————— # +# ival lb ub phz prior p1 p2 # parameter # +# —————————————————————————————————————————————————————————————————————————————————————— # + 0.18 0.01 1 -2 2 0.18 0.04 # M + 7.0 -10 20 -1 1 3.0 5.0 # logR0 + 7.0 -10 20 1 1 3.0 5.0 # logR1 + 7.0 -10 20 1 1 3.0 5.0 # logRbar + 72.5 55 100 -4 1 72.5 7.25 # Recruitment Expected Value + 0.40 0.1 5 -3 0 0.1 5 # Recruitment scale (variance component) + -0.51 -10 0.75 -4 0 -10 0.75 # ln(sigma_R) +## ———————————————————————————————————————————————————————————————————————————————————— ## -6 # Lag to recruitment -3 # SR_Act +## ———————————————————————————————————————————————————————————————————————————————————— ## +## GROWTH PARAM CONTROLS ## +## nGrwth +## ## +## Two lines for each parameter if split sex, one line if not ## +## ———————————————————————————————————————————————————————————————————————————————————— ## +# ival lb ub phz prior p1 p2 # parameter # +# —————————————————————————————————————————————————————————————————————————————————————— # + 17.5 10.0 30.0 3 0 0.0 20.0 # alpha males or combined + 17.5 10.0 30.0 3 0 0.0 20.0 # alpha + 0.10 0.0 0.5 3 0 0.0 10.0 # beta males or combined + 0.10 0.0 0.5 3 0 0.0 10.0 # beta + 6.0 1.0 30.0 3 0 0.0 3.0 # gscale males or combined + 6.0 1.0 30.0 3 0 0.0 3.0 # gscale + 115. 65.0 165.0 2 0 0.0 3.0 # molt_mu males or combined + 159. 65.0 165.0 -2 0 0.0 3.0 # molt_mu + 0.2 0.0 1.0 3 0 0.0 3.0 # molt_cv males or combined + 0.01 0.0 1.0 -3 0 0.0 3.0 # molt_cv +# ———————————————————————————————————————————————————————————————————————————————————— ## -# Time-varying natural mortality blocks -# 68 69 70 71 72 73 74 75 76 77 78 79 80 81 82 83 84 85 86 87 88 89 90 91 92 93 94 95 96 97 98 99 00 01 02 03 04 05 06 07 08 09 10 - 1 1 1 1 1 1 1 1 3 3 3 3 2 2 2 2 2 3 3 3 3 3 3 3 3 3 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 +## ———————————————————————————————————————————————————————————————————————————————————— ## +## SELECTIVITY CONTROLS ## +## -Each gear must have a selectivity and a retention selectivity ## +## LEGEND sel_type:1=coefficients,2=logistic,3=logistic95 ## +## Index: use +ve for selectivity, -ve for retention +## sex dep: 0 for sex-independent, 1 for sex-dependent. +## ———————————————————————————————————————————————————————————————————————————————————— ## +## ivector for number of year blocks or nodes ## +## Gear-1 Gear-2 Gear-3 Gear-4 + 1 1 1 1 #Selectivity blocks + 1 1 1 1 #Retention blocks + 1 0 0 0 #male retention flag (0 -> no, 1 -> yes) + 0 0 0 0 #female retention flag (0 -> no, 1 -> yes) +## ———————————————————————————————————————————————————————————————————————————————————— ## +## sel sel sel sex size year phz start end ## +## Index type mu sd dep nodes nodes mirror lam1 lam2 lam3 | block block ## +## ———————————————————————————————————————————————————————————————————————————————————— ## +## Selectivity P(capture of all sizes) + 1 3 95 140 1 1 1 -2 12.5 12.5 12.5 1975 2014 + 2 3 110 150 0 1 1 -2 12.5 12.5 12.5 1975 2014 + 3 2 90 10 1 1 1 -2 12.5 12.5 12.5 1975 2014 + 4 2 70 10 1 1 1 -2 12.5 12.5 12.5 1975 2014 +## ———————————————————————————————————————————————————————————————————————————————————— ## +## Retained + -1 2 135 2 0 1 1 -2 12.5 12.5 12.5 1975 2014 + -2 2 95 10 0 1 1 -2 12.5 12.5 12.5 1975 2014 + -3 2 90 10 0 1 1 -2 12.5 12.5 12.5 1975 2014 + -4 2 90 10 0 1 1 -2 12.5 12.5 12.5 1975 2014 +## ———————————————————————————————————————————————————————————————————————————————————— ## -# Specifications for Madd parameters -# Init, Lower, Upper, Phase -0.5 0 1 2 -0.585 0 1 2 -0.0001 0 1 2 +## ———————————————————————————————————————————————————————————————————————————————————— ## +## PRIORS FOR CATCHABILITY +## TYPE: 0 = UNINFORMATIVE, 1 - NORMAL (log-space), 2 = time-varying (nyi) +## ———————————————————————————————————————————————————————————————————————————————————— ## +## SURVEYS/INDICES ONLY +## NMFS BSFRF +## TYPE Mean_q SD_q + 1 0.896 0.13 + 0 0.00 0.00 +## ———————————————————————————————————————————————————————————————————————————————————— ## -# Time-varying fishery selectivity blocks -# 68 69 70 71 72 73 74 75 76 77 78 79 80 81 82 83 84 85 86 87 88 89 90 91 92 93 94 95 96 97 98 99 00 01 02 03 04 05 06 07 08 09 10 - 1 1 1 1 1 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 - 3 3 3 3 3 3 3 3 3 3 3 3 3 3 3 3 3 3 3 3 3 3 3 3 3 3 3 3 3 3 3 3 3 3 3 3 3 3 3 3 3 3 3 - 4 4 4 4 4 4 4 4 4 4 4 4 4 4 4 4 4 4 4 4 4 4 4 4 4 4 4 4 4 4 4 4 4 4 4 4 4 4 4 4 4 4 4 +## ———————————————————————————————————————————————————————————————————————————————————— ## +## PENALTIES FOR AVERAGE FISHING MORTALITY RATE FOR EACH GEAR +## ———————————————————————————————————————————————————————————————————————————————————— ## +## Trap Trawl NMFS BSFRF +## Mean_F STD_PHZ1 STD_PHZ2 PHZ + 0.10 0.10 1.10 1 #TRAP + 0.05 0.10 1.10 1 #Trawl + 0.00 2.00 2.00 -1 #NMFS trawl survey (0 catch) + 0.00 2.00 2.00 -1 #BSFRF (0) +## ———————————————————————————————————————————————————————————————————————————————————— ## -# Time-varying survey selectivity blocks -# 68 69 70 71 72 73 74 75 76 77 78 79 80 81 82 83 84 85 86 87 88 89 90 91 92 93 94 95 96 97 98 99 00 01 02 03 04 05 06 07 08 09 10 11 - 5 5 6 6 6 7 7 7 7 7 7 7 7 7 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 8 - 9 9 9 9 9 9 9 9 9 9 9 9 9 9 9 9 9 9 9 9 9 9 9 9 9 9 9 9 9 9 9 9 9 9 9 9 9 9 9 9 9 9 9 9 - -# Selectivity types -1 2 0 -2 2 0 -3 2 0 -4 2 0 -5 2 0 -6 2 0 -7 2 0 -8 2 0 -9 2 0 +## ———————————————————————————————————————————————————————————————————————————————————— ## +## OPTIONS FOR SIZE COMPOSTION DATA (COLUMN FOR EACH MATRIX) +## LIKELIHOOD OPTIONS: +## -1) multinomial with estimated/fixed sample size +## -2) robust_multi. Robust approximation to multinomial +## -3) logistic normal (NIY) +## -4) multivariate-t (NIY) +## AUTOTAIL COMPRESSION: +## - pmin is the cumulative proportion used in tail compression. +## ———————————————————————————————————————————————————————————————————————————————————— ## + 2 2 2 2 2 2 2 2 2 # Type of likelihood. + 0 0 0 0 0 0 0 0 0 # Auto tail compression (pmin) +-4 -4 -4 -4 -4 -4 -4 -4 -4 # Phz for estimating effective sample size (if appl.) +## ———————————————————————————————————————————————————————————————————————————————————— ## -# Specifications for Selectivity (Fishing Fleets) parameters -# Init, Lower, Upper, Phase -# Block 1:00 1968-72 for Fleet 2 -46.0517019 -100 1000 -1 -7.93719501 -100 1000 2 --0.617569645 -100 1000 2 --0.981484548 -100 1000 2 --4.5951199 -100 1000 -1 -# Block 2:00 1973+ for Fleet 2 -46.0517019 -100 1000 -1 -2.743604047 -100 1000 2 -0.967349593 -100 1000 2 --1.965728316 -100 1000 2 --4.5951199 -100 1000 -1 -# Block 3:00 1968+ for Fleet 3 -3.171179741 -100 1000 1 -2.699082027 -100 1000 3 -0.957124967 -100 1000 3 --1.472148417 -100 1000 3 --4.5951199 -100 1000 -1 -# Block 4:00 1968+ for Fleet 4 -4.5951199 -100 1000 -1 -3.712349783 -100 1000 3 -2.884812932 -100 1000 3 -1.895795309 -100 1000 3 -0.980092568 -100 1000 3 -# Specifications for Selectivity (Surveys) parameters -# Init, Lower, Upper, Phase -# Block 5:00 1968-69 for Survey 1 -1.951350344 -1000 1000 2 -1.378166653 -1000 1000 2 -0.567513036 -1000 1000 2 --0.698241465 -1000 1000 2 --0.83158641 -1000 1000 2 -# Block 6:00 1970-72 for Survey 1 -2.521822408 -1000 1000 2 -2.034452369 -1000 1000 2 -1.303003082 -1000 1000 2 --0.328685749 -1000 1000 2 --1.28138964 -1000 1000 2 -# Block 7:00 1973-81 for Survey 1 -1.018708293 -1000 1000 2 -0.778642437 -1000 1000 2 --0.054054721 -1000 1000 2 --0.745344082 -1000 1000 2 --0.046671702 -1000 1000 2 -# Block 8:00 1982+ for Survey 1 -1.230433954 -1000 1000 3 -1.059279433 -1000 1000 3 -0.03830702 -1000 1000 3 --0.945483854 -1000 1000 3 -0.154878154 -1000 1000 3 -# Block 9:00 1968+ for Survey 2 -100 -1000 1000 -1 -100 -1000 1000 -1 -1.0986123 -1000 1000 -1 --100 -1000 1000 -1 --100 -1000 1000 -1 +## ———————————————————————————————————————————————————————————————————————————————————— ## +## TIME VARYING NATURAL MORTALIIY RATES ## +## ———————————————————————————————————————————————————————————————————————————————————— ## +## TYPE: +## 0 = constant natural mortality +## 1 = Random walk (deviates constrained by variance in M) +## 2 = Cubic Spline (deviates constrained by nodes & node-placement) +## 3 = Blocked changes (deviates constrained by variance AT specific knots) + 3 +## Phase of estimation + 3 +## STDEV in m_dev for Random walk + 0.60 +## Number of nodes for cubic spline or number of step-changes for option 3 + 2 +## Year position of the knots (vector must be equal to the number of nodes) + 1980 1985 -# Time-varying fishery retention -# 68 69 70 71 72 73 74 75 76 77 78 79 80 81 82 83 84 85 86 87 88 89 90 91 92 93 94 95 96 97 98 99 00 01 02 03 04 05 06 07 08 09 10 - 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 - -# Specifications for the retained probability (one parm per size-class, per fleet) -# Init, Lower, Upper, Phase -0 -100 100 4 -12.2 -100 100 4 -5.5 -100 100 4 --0.1 -100 100 4 --6.7 -100 100 4 - -# Time-varying Q -# 68 69 70 71 72 73 74 75 76 77 78 79 80 81 82 83 84 85 86 87 88 89 90 91 92 93 94 95 96 97 98 99 00 01 02 03 04 05 06 07 08 09 10 11 - 1 1 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 - 3 3 3 3 3 3 3 3 3 3 3 3 3 3 3 3 3 3 3 3 3 3 3 3 3 3 3 3 3 3 3 3 3 3 3 3 3 3 3 3 3 3 3 3 - -# Number of survey fleets which are in a sub-area of the main survey -0 # Number of cases - -# Specifications for survey Q parameters -# Init, Lower, Upper, Phase, Prior, Pmean, Psd --2.6e-8 -50 1 4 1 0 -100 --0.10981487 -50 1 -1 1 0.896 0.03 - 0.0 -50 1 -1 1 0 -100 - -# Specifications for the initial numbers parameters -# Init, Lower, Upper, Phase -0.8133 -10 10 2 -1.1774 -10 10 2 -0.1239 -10 10 2 --0.84 -10 10 2 --1.02 -10 10 2 - -# Specifications for the growth transition probabilities -# Init, Lower, Upper, Phase -10 -20 50 5 -0.4 -20 50 5 -1.2 -20 50 5 -0.8 -20 50 5 - -# Objective Fn weights -# (1) Priors -# Devs -0.00001 100.000 100.000 -# Rec_devs -1.0000 -# Parameters -0.0001 0.0001 0.0001 -# Survey Q -1.000 1.000 1.000 -# Prior on M -1.000 -# 2nd Derviative prior -1.000 - -# Objective Fn weights -# (2) Data -# Catch: PotDisc, PotRet, Trawl, Tanner - 10.00 100.00 10.00 10.00 -# LF: PotDisc, PotRet, Trawl, Tanner - 0.100 1.000 0.100 0.100 -# Effort: PotRet, Trawl, Tanner - 0.000 0.000 10.000 -# Survey: NMFS, BSFRF - 1.000 1.000 -# Survey-LF: NMFS, BSFRF - 1.00 1.00 - -#EOF -999 +## ———————————————————————————————————————————————————————————————————————————————————— ## +## OTHER CONTROLS +## ———————————————————————————————————————————————————————————————————————————————————— ## + 3 # Estimated rec_dev phase + 0 # VERBOSE FLAG (0 = off, 1 = on, 2 = objective func) + 0 # INITIALIZE MODEL AT UNFISHED RECRUITS (0=FALSE, 1=TRUE) + 1984 # First year for average recruitment for Bspr calculation. + 2014 # Last year for average recruitment for Bspr calculation. + 0.35 # Target SPR ratio for Bmsy proxy. + 1 # Gear index for SPR calculations (i.e., directed fishery). + 1 # Lambda (proportion of mature male biomass for SPR reference points.) + 1 # Use empirical molt increment data (0=FALSE, 1=TRUE) +## EOF +9999 diff --git a/examples/bbrkc/bbrkc.dat b/examples/bbrkc/bbrkc.dat index 527da368..a43b6f13 100644 --- a/examples/bbrkc/bbrkc.dat +++ b/examples/bbrkc/bbrkc.dat @@ -1,382 +1,641 @@ -# Gmacs Main Data File Version 1.02 -# Fisheries: -1 Discard, 0 Pot Fishery, 1 Trawl by-catch, 2 Tanner by-catch -# Surveys: 1 NMFS Trawl Survey, 2 BSFRF Index +#======================================================================================================== +#======================================================================================================== +# Gmacs Main Data File Version 1.1: BBRKC Example +# GEAR_INDEX DESCRIPTION +# 1 : Pot fishery retained catch. +# 1 : Pot fishery with discarded catch. +# 2 : Trawl bycatch +# 3 : Trawl survey -1968 # Start year -2010 # End year -1 # Time-step (years) -2 # Number of sexes -4 # Number of fishing fleets -2 # Number of surveys -5 # Number of size-classes in the model -20 # Number of size-classes in the data - -# Fishery names (delimited with ":" no spaces in names?) -Discard:Pot:Trawl:Tanner - -# Survey names (delimited with ":" no spaces in names?) -NMFS_Trawl:BSRF - -# Links between data size classes and model size classes -1 4 -5 8 -9 12 -13 16 -17 20 - -1 1 1 1 # Catch units (per fishery) # 1= biomass (tons); 2=numbers -1000 1000 1000 1000 # Catch multipliers -2 2 # Survey units -1000 1000 # Survey multipliers -98 # Number of lines of catch data to read -45 # Number of lines of survey data to read -0.5 # Time between survey and fishery - -#Fleet specifications: (1) catch retain, (2) catch discard, or (3) bycatch (either retained or discarded) - 2 1 - 1 1 - 3 2 - 3 3 - -# Catch data -# Year, Season, Fleet, Sex, Catch Obs. -1990 1 1 1 2.007217356 -1991 1 1 1 1.499104609 -1992 1 1 1 1.325487342 -1993 1 1 1 2.547012128 -1996 1 1 1 0.595119119 -1997 1 1 1 0.713863332 -1998 1 1 1 3.584581435 -1999 1 1 1 1.406309082 -2000 1 1 1 1.235999509 -2001 1 1 1 1.190035241 -2002 1 1 1 1.509166271 -2003 1 1 1 3.043101099 -2004 1 1 1 0.708887472 -2005 1 1 1 5.447537937 -2006 1 1 1 2.099719769 -2007 1 1 1 3.302423531 -2008 1 1 1 4.444923701 -2009 1 1 1 3.52682827 -2010 1 1 1 3.255224085 -1968 1 2 1 16.4 -1969 1 2 1 11.243 -1970 1 2 1 9.772 -1971 1 2 1 8.655 -1972 1 2 1 12.004 -1973 1 2 1 12.311 -1974 1 2 1 19.388 -1975 1 2 1 23.281 -1976 1 2 1 28.994 -1977 1 2 1 31.737 -1978 1 2 1 39.743 -1979 1 2 1 48.91 -1980 1 2 1 58.944 -1981 1 2 1 15.237 -1982 1 2 1 1.361 -1984 1 2 1 1.897 -1985 1 2 1 1.894 -1986 1 2 1 5.168 -1987 1 2 1 5.574 -1988 1 2 1 3.351 -1989 1 2 1 4.656 -1990 1 2 1 9.273 -1991 1 2 1 7.885 -1992 1 2 1 3.709 -1993 1 2 1 6.66 -1994 1 2 1 0.042 -1995 1 2 1 0.036 -1996 1 2 1 3.862 -1997 1 2 1 4.042 -1998 1 2 1 6.779 -1999 1 2 1 5.378 -2000 1 2 1 3.738 -2001 1 2 1 3.866 -2002 1 2 1 4.385 -2003 1 2 1 7.135 -2004 1 2 1 7.007 -2005 1 2 1 8.4 -2006 1 2 1 7.143 -2007 1 2 1 9.304 -2008 1 2 1 9.216 -2009 1 2 1 7.272 -2010 1 2 1 6.762 -1976 1 3 1 0.887 -1977 1 3 1 1.416 -1978 1 3 1 1.655 -1979 1 3 1 1.92 -1980 1 3 1 1.131 -1981 1 3 1 0.22 -1982 1 3 1 0.448 -1983 1 3 1 0.404 -1984 1 3 1 1.122 -1985 1 3 1 0.444 -1986 1 3 1 0.254 -1987 1 3 1 0.186 -1988 1 3 1 0.778 -1989 1 3 1 0.237 -1990 1 3 1 0.306 -1991 1 3 1 0.322 -1992 1 3 1 0.498 -1994 1 3 1 0.145 -1995 1 3 1 0.126 -1996 1 3 1 0.135 -1997 1 3 1 0.114 -1998 1 3 1 0.235 -1999 1 3 1 0.256 -2000 1 3 1 0.141 -2001 1 3 1 0.225 -2002 1 3 1 0.176 -2003 1 3 1 0.208 -2004 1 3 1 0.137 -2005 1 3 1 0.213 -2006 1 3 1 0.124 -2007 1 3 1 0.204 -2008 1 3 1 0.238 -2009 1 3 1 0.152 -2010 1 3 1 0.122 -1991 1 4 1 0.471018 -1992 1 4 1 0.153993 -1993 1 4 1 0.0384672 - -# Survey data (adundance indices) -# Year, Season, Survey, Sex, Obs, CV -1968 1 1 1 49.98149876 0.2 -1969 1 1 1 45.98887874 0.2 -1970 1 1 1 28.49876378 0.2 -1972 1 1 1 31.9873901 0.16 -1973 1 1 1 97.60202588 0.12 -1974 1 1 1 139.3897878 0.14 -1975 1 1 1 161.1481537 0.18 -1976 1 1 1 184.6369643 0.19 -1977 1 1 1 225.4820798 0.14 -1978 1 1 1 224.8711283 0.15 -1979 1 1 1 171.0281627 0.12 -1980 1 1 1 162.0059434 0.22 -1981 1 1 1 72.66277842 0.1 -1982 1 1 1 70.88060418 0.26 -1983 1 1 1 20.14109128 0.22 -1984 1 1 1 49.63677179 0.64 -1985 1 1 1 19.23154467 0.16 -1986 1 1 1 28.55626343 0.19 -1987 1 1 1 47.49625561 0.21 -1988 1 1 1 32.5984591 0.21 -1989 1 1 1 34.8781941 0.21 -1990 1 1 1 36.87053274 0.21 -1991 1 1 1 48.16707092 0.46 -1992 1 1 1 20.35986715 0.17 -1993 1 1 1 28.19321585 0.17 -1994 1 1 1 16.5712593 0.17 -1995 1 1 1 24.30238816 0.22 -1996 1 1 1 29.95415974 0.2 -1997 1 1 1 38.63195226 0.26 -1998 1 1 1 48.89559812 0.18 -1999 1 1 1 37.04373311 0.16 -2000 1 1 1 43.31580773 0.17 -2001 1 1 1 29.71449131 0.18 -2002 1 1 1 48.87947295 0.2 -2003 1 1 1 60.65781218 0.16 -2004 1 1 1 57.54862346 0.16 -2005 1 1 1 70.93678171 0.17 -2006 1 1 1 63.47205131 0.13 -2007 1 1 1 56.99998406 0.14 -2008 1 1 1 62.17678984 0.2 -2009 1 1 1 49.32716453 0.32 -2010 1 1 1 45.19262181 0.15 -2011 1 1 1 38.9328442 0.133 -2007 1 2 1 22.331 0.0634 -2008 1 2 1 19.747 0.0765 - -# Discard mortalities per fishery -1.0 # Pot discards -1.0 # Landed catches -1.0 # Trawl bycatch -1.0 # Tanner fishery - -# Fishery retention values (highgrading rate) -# 68 69 70 71 72 73 74 75 76 77 78 79 80 81 82 83 84 85 86 87 88 89 90 91 92 93 94 95 96 97 98 99 00 01 02 03 04 2005 2006 2007 2008 2009 2010 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.2785 0.0440 0.0197 0.019875 0 0 - -# Fishery timing (as fraction of year) -# 1968 1969 1970 1971 1972 1973 1974 1975 1976 1977 1978 1979 1980 1981 1982 1983 1984 1985 1986 1987 1988 1989 1990 1991 1992 1993 1994 1995 1996 1997 1998 1999 2000 2001 2002 2003 2004 2005 2006 2007 2008 2009 2010 - 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 - 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 - 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 - -# Effort (by fishery) -# 1968 1969 1970 1971 1972 1973 1974 1975 1976 1977 1978 1979 1980 1981 1982 1983 1984 1985 1986 1987 1988 1989 1990 1991 1992 1993 1994 1995 1996 1997 1998 1999 2000 2001 2002 2003 2004 2005 2006 2007 2008 2009 2010 - 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 0.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 0.0 0.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 - 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 - 20.0 20.0 20.0 20.0 20.0 20.0 20.0 20.0 20.0 120.031 88.489 110.989 267.154 87.951 102.987 16.239 52.598 0.000 0.000 32.750 53.203 108.519 109.371 152.541 154.976 159.922 1.042 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 2.0 2.0 2.0 1.5 0.0 - #1.0001 1.0001 1.0001 1.0001 1.0001 1.0001 1.0001 1.0001 1.0001 1.0001 1.0001 1.0001 1.0001 1.0001 1.0001 0.0001 1.0001 1.0001 1.0001 1.0001 1.0001 1.0001 1.0001 1.0001 1.0001 1.0001 0.0001 0.0001 1.0001 1.0001 1.0001 1.0001 1.0001 1.0001 1.0001 1.0001 1.0001 1.0001 1.0001 1.0001 1.0001 1.0001 1.0001 -#1.0001 1.0001 1.0001 1.0001 1.0001 1.0001 1.0001 1.0001 1.0001 1.0001 1.0001 1.0001 1.0001 1.0001 1.0001 1.0001 1.0001 1.0001 1.0001 1.0001 1.0001 1.0001 1.0001 1.0001 1.0001 1.0001 1.0001 1.0001 1.0001 1.0001 1.0001 1.0001 1.0001 1.0001 1.0001 1.0001 1.0001 1.0001 1.0001 1.0001 1.0001 1.0001 1.0001 -#0.074963188 0.074963188 0.074963188 0.074963188 0.074963188 0.074963188 0.074963188 0.074963188 0.074963188 0.449395163 0.33132843 0.415549516 1.0001 0.32931461 0.385596755 0.060885165 0.196982697 0.0001 0.0001 0.12268847 0.199247308 0.406303912 0.409493084 0.571085274 0.580199867 0.598713534 0.004000372 0.0001 0.0001 0.0001 0.0001 0.0001 0.0001 0.0001 0.0001 0.0001 0.0001 0.0001 0.007586319 0.007586319 0.007586319 0.005714739 0.0001 - -# Use effort to compute F (by fishery) -0 1900 1900 1900 1900 -0 1900 1900 1900 1900 -0 1900 1900 1900 1900 - -96 # Number of length frequency lines to read - -# Length frequency data for fishing fleets -# Year, Season, Fleet, Sex, Maturity, Shell Cond, Nsamp, DataVec -1990 1 1 1 3 3 79.0167 1.9 0 1.9 13.8 7.9 21.7 11.9 65 86.6 131.8 210.7 261.8 320.9 419.4 147.6 15.8 0 0 0 0 -1991 1 1 1 3 3 66.8289 4.8 14.7 28.6 31.1 35.2 57.3 47.4 91.6 90.7 100.6 93.2 163.5 230.6 313.1 136.5 14.7 0 0 0 0 -1992 1 1 1 3 3 106.004 0 2.1 2.8 25.6 51.2 126.6 200.4 263.5 272.8 283.6 272.1 288.4 256.4 186.1 67.6 6.5 0 0 0 0 -1993 1 1 1 3 3 123.566 5.1 12.1 15.3 13.4 16.7 32.8 83.9 153.5 209.1 290.3 358.6 415 408 458.3 200.8 14.8 0 0 0 0 -1996 1 1 1 3 3 27.3596 0 0 0 7.8 31.2 49.4 44.1 18.2 28.6 41.6 36.4 59.7 88.4 119.5 62.4 7.8 0 0 0 0 -1997 1 1 1 3 3 41.837 0 0.2 0.5 0.6 1.4 17.9 50.3 99.2 115.4 118.7 93.8 91.2 116 129.6 68.3 6.9 0 0 0 0 -1998 1 1 1 3 3 145.91 0.6 1.6 2.5 14 22.2 31.7 33 55.5 124.1 307.8 444.9 654.3 649.5 574.6 226.6 30.8 0 0 0 0 -1999 1 1 1 3 3 42.3887 0 0 0 7.9 7.9 2.7 7 7.9 13.2 26.4 58.1 116.2 195.3 299.1 173.3 7 0 0 0 0 -2000 1 1 1 3 3 64.0244 0.4 7.1 26.7 67.3 85.4 80.2 82.9 80.9 74.1 77.7 99.2 147.5 208.5 216.5 124.7 13.5 0 0 0 0 -2001 1 1 1 3 3 74.6446 2.6 9.3 15.1 18.7 25.2 49 92.2 140.6 163.8 194.2 201.2 229.1 214.1 183.1 78.1 7.3 0 0 0 0 -2002 1 1 1 3 3 70.2126 1.8 9.3 9.2 13.9 9.9 15.9 20.3 51.2 96.2 174.4 235.6 260.4 250.7 241.6 122.6 14.2 0 0 0 0 -2003 1 1 1 3 3 163.003 28.7 42.2 51.8 112.4 195.7 236.1 255.3 237.5 227.6 212.4 232.2 339.7 468.7 605.6 276.9 22.7 0 0 0 0 -2004 1 1 1 3 3 70.7643 0.6 11.4 27.2 62.1 78.5 74.4 94.7 167.4 213 223.5 169.6 130.6 107.7 105.9 62.2 10.4 0 0 0 0 -2005 1 1 1 3 3 174.35 0.8 3 5.5 10.9 28.9 83.6 129.9 158.5 172 249.4 362.4 521.6 523.8 525.3 276.6 99.5 93.3 132.2 130.7 284.4 -2006 1 1 1 3 3 82.9476 0.6 2.3 7.9 27.1 56.2 68 66.3 62.5 81.6 138.2 167.6 206.4 248.4 318.2 230 51.3 18.9 15.4 13.5 23.8 -2007 1 1 1 3 3 165.5 4.5 15 24.5 35.2 61.7 131.9 236.8 306.1 334 308.5 294.8 355.5 464.6 594.3 344.1 45.5 11.4 10.2 8 13.2 -2008 1 1 1 3 3 174.097 0.5 1.3 4.6 17.6 40.9 53.5 60.4 81 167.1 306.1 480.5 679 752.7 695.8 372.3 37.6 5.2 6.8 6.9 17 -2009 1 1 1 3 3 127.322 1.1 2.9 5 8.7 11.3 20.2 49.3 111.2 174.7 195.2 220.9 326.7 501.1 668.3 402.9 41.4 5.9 4.5 6.1 12 -2010 1 1 1 3 3 113.304 1.74 2.79 6.06 13.45 20.97 29.34 36.51 53.66 84.11 133.44 237.13 373.85 497.19 584.72 332.74 33.87 4.11 4.53 3.97 10.31 -1968 1 2 1 3 3 200 0 0 0 0 0 0 0 0 0 0 0 27.314811 174.814789 344.166616 480.740669 682.870269 710.18508 753.888777 617.314723 1693.518267 -1969 1 2 1 3 3 192.553 0 0 0 0 0 0 0 0 0 0 0.559896 105.719924 270.341589 431.763631 500.71198 625.676705 578.486 535.253118 384.039314 755.674844 -1970 1 2 1 3 3 173.152 0 0 0 0 0 0 0 0 0 0 21.779477 176.655758 411.759244 642.30941 682.750258 522.623691 437.803083 289.53094 184.899114 396.131025 -1971 1 2 1 3 3 174.969 0 0 0 0 0 0 0 0 0 0 0 0 19.798348 361.588785 785.672669 851.986633 668.925868 482.901366 297.487458 337.403874 -1972 1 2 1 3 3 200 0 0 0 0 0 0 0 0 0 0 0 0 41.185815 610.943438 1015.91058 1033.087008 869.54966 618.137223 383.89625 435.348027 -1973 1 2 1 3 3 200 0 0 0 0 0 0 0 0 0 0 0 0.452059 36.164704 513.086738 916.775246 862.980249 759.458784 613.89585 377.017039 440.75733 -1974 1 2 1 3 3 200 0 0 0 0 0 0 0 0 0 0 0 0 90.7 945.4 1716.3 1735.5 1408.3 912.7 542.2 543.7 -1975 1 2 1 3 3 200 0 0 0 0 0 0 0 0 0 0 0 0 62.1 648 1504.8 1958.4 1855.8 1280 750 686.1 -1976 1 2 1 3 3 200 0 0 0 0 0 0 0 0 0 0 0 0 17.2 307.7 1503.1 2456.1 2331.2 1733.8 1135.8 1118.5 -1977 1 2 1 3 3 200 0 0 0 0 0 0 0 0 0 0 0 0 19.8 225.7 1621.2 2864.9 2612.2 1883.6 1219.9 1285.8 -1978 1 2 1 3 3 200 0 0 0 0 0 0 0 0 0 0 0 0 17.1 308 2125.4 3816.5 3540.1 2466.6 1423.7 1048.2 -1979 1 2 1 3 3 200 0 0 0 0 0 0 0 0 0 0 0 0 21.1 200.6 1256.2 2771.5 3357.7 3368 2616.1 3217.4 -1980 1 2 1 3 3 200 0 0 0 0 0 0 0 0 0 0 0 0 16.3 288 1915.9 3691.1 4064.2 3734.6 2926.1 4209.2 -1981 1 2 1 3 3 200 0 0 0 0 0 0 0 0 0 0 0 0 3.3 119.2 617.86 925.15 908.24 841.01 681.38 1211.8 -1982 1 2 1 3 3 24.8728 0 0 0 0 0 0 0 0 0 0 0 0 0 29.42 139.36 151.58 90.17 45.28 27.47 57.73 -1984 1 2 1 3 3 36.4993 0 0 0 0 0 0 0 0 0 0 0 0.2 1.8 51.9 246.9 248.9 140 67.2 25.5 11.5 -1985 1 2 1 3 3 36.6005 0 0 0 0 0 0 0 0 0 0 0 0.4 3.5 62.9 228.4 246.6 151.1 68.5 24.4 10.3 -1986 1 2 1 3 3 96.5285 0 0 0 0 0 0 0 0 0 0 0 0 3.4 111.4 548.6 690.6 437.6 205.3 73.9 28.8 -1987 1 2 1 3 3 97.5767 0 0 0 0 0 0 0 0 0 0 0 0 2.8 60.3 402.2 646.2 535.3 301.5 120 54.1 -1988 1 2 1 3 3 56.8248 0 0 0 0 0 0 0 0 0 0 0 0 0 25 160 327.1 305.4 231.9 127.7 58.9 -1989 1 2 1 3 3 77.4582 0 0 0 0 0 0 0 0 0 0 0 0 0.8 31.5 204 372.1 368.9 321.5 201.6 184.4 -1990 1 2 1 3 3 143.896 0 0 0 0 0 0 0 0 0 0 0 0.902738 0 45.738726 277.541787 563.810042 534.220296 540.740071 447.958664 718.980676 -1991 1 2 1 3 3 122.329 0 0 0 0 0 0 0 0 0 0 0.101144 0.303432 1.314873 37.625593 225.652416 439.268688 476.186273 462.734112 381.110849 636.499621 -1992 1 2 1 3 3 55.5453 0 0 0 0 0 0 0 0 0 0 0.3028 0.201867 0.605599 11.50639 77.113003 159.070802 202.068366 211.051425 197.627303 348.623445 -1993 1 2 1 3 3 104.347 0 0 0 0 0 0 0 0 0 0 0 0 3.185309 31.299117 213.277152 406.057628 394.632112 362.294213 302.11963 556.80584 -1984 1 2 1 3 3 58.1302 0 0 0 0 0 0 0 0 0 0 0 0.703805 0.703805 16.325292 98.516792 177.894069 204.774446 223.914959 211.248458 330.313374 -1997 1 2 1 3 3 61.4989 0 0 0 0 0 0 0 0 0 0 0 0.509459 0.424549 18.518342 120.200401 198.776988 214.407396 227.319689 212.45347 345.056705 -1998 1 2 1 3 3 102.88 0 0 0 0 0 0 0 0 0 0.7 0.832339 0.416169 1.8034 50.356481 265.654715 357.07323 333.351582 320.450335 311.849503 595.260773 -1999 1 2 1 3 3 88.3882 0 0 0 0 0 0 0 0 0 0 0.108827 0 0.108827 28.186226 252.478931 495.054594 440.641031 312.225023 184.679632 209.056908 -2000 1 2 1 3 3 58.4891 0 0 0 0 0 0 0 0 0 0.090297 0 0.180595 0.36119 14.086409 118.470313 247.505433 268.635047 231.883967 158.652699 232.335454 -2001 1 2 1 3 3 59.1565 0 0 0 0 0 0 0 0 0 0.3 0.3 0.3 1.602 23.226 107.619 216.238 255.482 251.277 193.814 236.561 -2002 1 2 1 3 3 68.246 0 0 0 0 0 0 0 0 0 0.372 0.093 0 0.28 22.361 160.257 279.704 284.269 249.796 198.085 289.208 -2003 1 2 1 3 3 115.409 0 0 0 0 0 0 0 0 0 0.46444 0.15484 0.61936 2.167759 61.006934 367.590002 582.35299 469.784358 375.796518 249.447133 400.880588 -2004 1 2 1 3 3 104.448 0 0 0 0 0 0 0 0 0 0 0.113383 0 0.453533 14.513065 116.784821 295.703703 386.637127 447.864121 370.876845 638.915018 -2005 1 2 1 3 3 127.013 0 0 0 0 0 0 0 0 0 0.099141 0.198282 0.297423 2.280243 41.540082 237.442711 426.40547 458.824579 492.631663 418.969895 683.973806 -2006 1 2 1 3 3 113.874 0 0 0 0 0 0 0 0 0 0 0.274796 0.274796 0.961786 25.143837 183.014155 471.962178 545.744912 467.428044 339.373095 442.696401 -2007 1 2 1 3 3 145.018 0 0 0 0 0 0 0 0 0 0 0 0.563595 0.845392 20.993905 274.752448 578.248229 609.950434 582.334291 464.402086 622.20862 -2008 1 2 1 3 3 140.868 0 0 0 0 0 0 0 0 0 0 0 0.210341 0.631022 30.709732 228.640268 446.342823 496.193553 548.568371 497.876278 814.859612 -2009 1 2 1 3 3 117.371 0 0 0 0 0 0 0 0 0 0 0 0 0.536559 27.632781 294.168389 565.398886 502.487361 405.50435 276.864366 480.354309 -2010 1 2 1 3 3 110.797 0 0 0 0 0 0 0 0 0 0 0.119678 0.119678 0.718066 21.901011 237.679829 540.703659 539.267527 448.432185 275.737324 345.270044 -1976 1 3 1 3 3 13.7035 0 0 0 0 0 4.9998 3.34602 1.65378 8.30736 3.34602 9.9996 14.9994 16.65318 24.96054 38.30616 33.30636 28.30656 34.96014 24.96054 49.95954 -1977 1 3 1 3 3 34.5267 2.83572 0.70893 0.70893 0.70893 2.04802 2.75695 6.22283 7.64069 24.97009 38.20345 47.18323 78.45492 85.38668 98.54127 81.9208 83.25989 79.08508 49.94018 25.67902 34.73757 -1978 1 3 1 3 3 25.5734 0 0 0 0 0 0 0 1.61625 0.7758 1.61625 9.63285 17.7141 33.03615 56.3748 80.48925 74.8647 51.52605 63.6156 43.4448 121.542 -1979 1 3 1 3 3 24.1428 13.10436 0.95706 1.8405 0.95706 1.8405 5.59512 2.79756 1.8405 0.95706 4.63806 3.75462 8.39268 16.78536 40.93272 42.84684 52.12296 66.11076 63.3132 59.55858 136.78596 -1980 1 3 1 3 3 28.4183 60.60303 23.62491 10.95648 15.40755 16.20646 18.60319 31.27162 30.01619 43.3694 42.79875 48.16286 44.96722 41.99984 43.02701 35.72269 26.36403 23.62491 16.20646 14.95103 30.24445 -1981 1 3 1 3 3 5.53576 6.99802 0.74788 1.20195 1.76286 2.99152 4.67425 7.45209 9.32179 10.31006 13.46184 11.59214 12.8208 7.66577 8.92114 6.43711 5.66252 2.99152 1.70944 1.36221 2.32377 -1982 1 3 1 3 3 22.7809 55.05654 21.04872 19.39938 25.60404 27.96024 34.79322 32.12286 31.65162 31.49454 37.3065 33.45804 37.62066 31.8087 25.60404 17.12172 12.01662 6.59736 4.08408 2.98452 7.77546 -1983 1 3 1 3 3 14.7289 11.38368 10.54592 16.55808 16.95232 15.32608 15.72032 18.57856 21.9296 23.30944 23.21088 22.52096 21.53536 20.15552 20.40192 18.28288 13.94624 10.05312 6.35712 4.73088 8.8704 -1984 1 3 1 3 3 37.4557 42.75612 18.22392 17.17254 23.24718 31.5414 39.95244 46.61118 47.54574 50.34942 55.60632 59.69502 69.62472 69.39108 65.76966 55.25586 41.4711 30.84048 19.8594 12.73338 17.05572 -1985 1 3 1 3 3 10.6742 1.40097 0.38458 0.93398 1.62073 2.747 4.50508 7.03232 10.87812 9.80679 12.25162 14.77886 17.47092 23.15721 23.67914 24.25601 23.15721 17.52586 12.49885 8.21353 15.87766 -1986 1 3 1 3 3 5.45255 2.21427 0.44604 1.2744 1.68858 2.53287 3.17007 3.77541 4.18959 3.90285 5.03388 6.26049 8.47476 11.77227 12.29796 12.79179 11.24658 9.62172 6.30828 5.20911 6.38793 -1987 1 3 1 3 3 4 0.21165 0.2988 0.6972 0.9462 1.43175 2.1165 2.87595 3.64785 4.12095 4.34505 5.86395 6.2997 6.76035 7.719 8.0427 7.63185 7.23345 4.4322 2.87595 3.22455 -1988 1 3 1 3 3 12.5147 9.81084 0.4303 0.55939 0.98969 1.93635 4.08785 6.71268 9.20842 10.80053 12.0484 12.52173 14.32899 16.7817 20.26713 25.99012 29.99191 33.04704 27.28102 18.5029 16.91079 -1989 1 3 1 3 3 4 0.109 0.109 0.131 0.131 0.262 0.393 0.917 1.147 1.671 2.501 3.276 5.165 5.515 6.694 8.561 9.271 8.802 8.43 7.043 10.035 -1990 1 3 1 3 3 5.47527 4.123 1.031 1.546 0.515 1.804 1.289 5.137 2.835 5.652 6.168 4.123 5.395 5.395 7.456 11.837 12.868 13.108 11.064 5.91 11.837 -1991 1 3 1 3 3 6.37453 8.826 5.303 4.129 1.174 4.129 2.367 2.954 2.954 7.083 4.129 7.67 5.909 5.909 4.129 5.909 13.579 6.496 9.432 9.432 27.14 -1992 1 3 1 3 3 4 0 0 0 0 0 1.911 0 0 0 3.822 4.749 5.704 11.437 10.481 11.437 10.481 7.615 6.66 1.911 8.571 -1994 1 3 1 3 3 4 0.29402 0.29402 0.29402 0.36632 0.0723 0 0 0.0723 0.0723 0.14942 0.0723 0.14942 0.44344 0.66034 0.95436 2.05814 1.98584 2.57388 3.82708 13.9057 -1995 1 3 1 3 3 4 2.05738 0.17056 0.87412 0.6929 0.35178 0.87412 1.73758 1.73758 1.04468 1.73758 1.56702 0.6929 1.21524 1.04468 1.04468 1.73758 2.6117 2.08936 0.35178 1.21524 -1996 1 3 1 3 3 4 0 0.03052 0.08393 0.14497 0.67144 1.45733 2.39582 3.15119 3.44876 3.53269 3.50217 3.56321 2.95281 3.97523 2.54079 3.18171 2.89177 3.50217 3.41824 10.78119 -1997 1 3 1 3 3 4 0.0441 0.0441 0 0 0.0441 0.0441 0.0441 0.2156 0.1715 0.9065 1.6366 2.1511 2.3667 2.4549 3.1409 2.7979 2.4549 2.6705 2.1511 6.5856 -1998 1 3 1 3 3 4 0.21551 0.03748 0.10307 0.03748 0.03748 0.06559 0.24362 0.20614 0.52472 0.66527 1.50857 2.03329 4.17902 6.2779 7.1212 8.48922 8.14253 7.78647 6.2779 13.83012 -1999 1 3 1 3 3 4 0.5967 0.0663 0.0663 0.0663 0.1326 0.0663 0.3315 0.1989 0.5304 0.91715 1.58015 4.2653 7.41455 9.24885 12.3318 12.14395 10.4975 7.08305 5.77915 11.0279 -2000 1 3 1 3 3 4 0.04688 0 0.0293 0.01758 0.0293 0.26956 0.3809 0.89658 1.42398 1.69354 1.69354 2.02756 2.20336 2.44362 2.60184 3.78556 4.55322 4.90482 4.29538 12.16536 -2001 1 3 1 3 3 4 0.044978 0.017991 0.089955 0.044978 0.224888 0.557721 0.575712 0.755622 1.394303 1.727136 2.122938 2.077961 2.392803 2.941529 3.562218 4.020989 5.352323 5.21739 5.676161 17.937027 -2002 1 3 1 3 3 4 0.045781 0.045781 0.152604 0.518854 0.686718 0.816431 0.923254 0.450182 0.450182 0.518854 0.923254 1.747316 2.090675 2.540857 3.837991 4.112678 4.219501 3.792209 3.662496 8.248246 -2003 1 3 1 3 3 4 0.17941 0.17941 0.717639 1.076459 2.691148 2.332328 2.870558 1.076459 0.53823 1.794099 0.53823 1.794099 1.973509 1.973509 4.305837 5.202886 4.485247 3.049968 2.691148 10.944002 -2004 1 3 1 3 3 4 0.292245 0.292245 0.876735 0.292245 0.292245 0.876735 2.630206 2.045716 1.753471 2.922451 1.753471 1.753471 0.876735 0.876735 1.753471 1.753471 5.552658 2.922451 2.922451 7.598374 -2005 1 3 1 3 3 4 0.312355 0 0.937065 0.312355 0.312355 0.312355 0.312355 3.435903 1.874129 1.874129 3.123548 1.874129 4.685323 4.685323 1.874129 3.123548 4.997677 3.123548 3.123548 17.804226 -2006 1 3 1 3 3 4 0.195551 0.195551 0.195551 0.586652 0.195551 1.173304 1.564405 1.759956 0.586652 3.324361 2.542158 4.302114 4.106564 3.715462 4.106564 2.93326 3.12881 1.955506 1.173304 4.693216 -2007 1 3 1 3 3 4 0 0 0 0.017792 0.053377 0.106754 0.284676 0.604937 0.925197 1.26325 1.49455 1.779226 1.530134 2.401955 3.095853 3.167022 3.273776 3.131438 3.682998 8.362362 -2008 1 3 1 3 3 4 0 0 0.110411 0.055206 0.220823 0.38644 0.38644 0.828085 0.828085 1.324936 1.821787 2.042609 3.146723 3.533162 4.692481 3.257134 3.864396 4.968509 6.017417 18.43869 -2009 1 3 1 3 3 4 0 0 0 0 0.125999 0.106104 0.106104 0.358101 0.92841 1.286511 1.339563 2.831651 3.574379 4.06511 4.628787 4.913942 4.602261 3.959006 3.395328 7.918011 -2010 1 3 1 3 3 4 0 0 0.093517 0.066012 0.093517 0.253046 0.225541 0.445581 0.731633 0.671122 0.797645 1.688807 1.974859 2.293917 3.064057 2.711993 2.678987 1.947354 1.688807 4.945399 -1991 1 4 1 3 3 45.3805 8.881902 16.678238 9.967468 14.408419 17.763804 14.408419 35.527608 48.751773 49.936027 37.69874 55.462544 58.817929 62.074626 92.075717 99.773366 79.83843 73.226348 68.785397 57.633675 85.364947 -1992 1 4 1 3 3 16.3497 0 0 0.782296 2.346887 8.605254 12.516733 22.722137 19.592954 20.37525 25.069025 31.327391 37.585757 31.327391 21.157546 24.286729 13.299029 17.246067 25.85132 21.157546 20.37525 -1993 1 4 1 3 3 4.52167 0 0 0 0 0 0.442625 5.734446 10.583644 12.78693 14.557428 10.141019 6.177071 5.734446 7.937733 2.645911 4.849197 6.619695 3.088535 2.203286 4.849197 - -43 # Number of survey length frequency lines to read - -# Length frequency data for surveys -# Year, Season, Survey, Sex, Nsamp, DataVec -1968 1 1 1 200 1611.844192 946.839712 1010.965144 1308.633816 1897.637784 2649.726184 3448.523232 3431.898120 2565.017280 2024.305304 1938.804728 1735.345024 1638.761040 1504.968472 1197.008064 1268.258544 1391.759376 1127.340928 827.297240 1383.842656 -1969 1 1 1 200 2613.935916 2070.171000 1565.049276 2386.677144 3073.973916 4234.189752 4933.447512 6007.176204 4958.289564 4793.595960 4247.070816 2756.547696 2524.688544 2212.782780 1826.350860 1789.547820 1296.387084 931.116912 530.883852 690.057000 -1970 1 1 1 200 210.844500 501.761625 1281.564375 1418.371875 1250.983875 982.197375 1259.836125 1100.495625 1051.808250 1683.537000 1450.159500 1531.439250 1889.553000 1802.640000 1711.300875 1312.144875 1175.739750 551.656125 270.396000 227.341875 -1972 1 1 1 200 139.648929 497.856219 872.676021 2005.441683 2292.526656 2963.256828 3157.415562 2401.027125 1881.366984 1656.059790 1888.115817 1445.288544 1951.970160 1644.638688 1528.870245 1547.040180 775.596654 1035.686295 308.888895 543.021486 -1973 1 1 1 200 1976.420850 4164.476145 4669.950150 4837.858470 3671.245455 5490.252255 4960.291620 6205.611660 8050.854135 6606.142965 5107.211400 5605.689225 4393.601040 4181.966595 3125.543415 2401.438785 2259.766140 1327.525155 906.005310 848.286825 -1974 1 1 1 200 3568.883568 4842.029818 7394.433420 7099.063490 6797.582458 5793.324696 4110.734612 5585.547228 4960.177790 6143.694544 5117.029408 6801.656526 6709.989996 6520.545834 5762.769186 4998.881436 3464.994834 2130.737564 3499.624412 965.554116 -1975 1 1 1 200 8600.246960 15359.730520 9101.134960 9326.534560 9088.612760 6751.970240 6879.696680 5331.952760 5667.547720 6686.854800 6025.682640 6155.913520 6634.261560 6085.789200 5266.837320 5827.831880 4520.514200 2890.123760 2113.747360 2714.812960 -1976 1 1 1 200 721.587020 3960.986260 9098.809720 15741.746020 18919.206460 14187.082140 14790.985440 11028.203340 10065.055000 8897.508620 9523.090500 10405.718400 8070.625640 8885.120860 8008.686840 5741.726760 5326.736800 4171.578180 2737.694960 2226.699860 -1977 1 1 1 200 2449.573000 2033.145590 2575.551040 3940.313140 6662.838560 12870.756420 15229.345280 14823.416040 13889.078910 14875.906890 13686.114290 13675.616120 10326.699890 10876.104120 10862.106560 8755.473780 5623.519730 4745.172840 2911.492480 4199.268000 -1978 1 1 1 200 1310.796630 3651.286650 4158.494670 7336.183470 5267.630280 5823.725820 5447.903010 8521.705830 9031.969320 9093.078720 9175.576410 9276.406920 8851.696590 11201.353020 10584.148080 8631.702750 7947.277470 5279.852160 3312.129480 2783.533170 -1979 1 1 1 200 1647.946190 1803.260580 2267.186680 3271.687540 2957.024620 3437.087280 2559.661830 2898.529590 2811.795580 3763.852620 5191.938180 7263.469070 7380.459130 8405.130690 7334.066520 7501.483330 6894.345260 5698.222750 3184.953530 5080.999330 -1980 1 1 1 200 1510.473600 3069.468000 6069.319200 6795.021600 6786.583200 6868.857600 5655.837600 5613.645600 4873.176000 4225.528800 4797.230400 3573.662400 5084.136000 5651.618400 5742.331200 7012.310400 5780.304000 5795.071200 4801.449600 6651.568800 -1981 1 1 1 200 4128.766800 2457.211440 2180.289600 3160.166880 4797.890160 4198.937040 4002.209760 3969.630720 3641.334240 4241.540400 2915.824080 2721.602880 2326.895280 2300.581440 1826.932320 1824.426240 1331.981520 1283.112960 775.631760 1828.185360 -1982 1 1 1 200 17793.817440 18215.982720 15316.964760 6438.020520 5387.098440 6961.236000 7922.335680 6449.248320 4430.489880 3839.907600 4452.945480 3168.485160 2932.701360 1776.237960 1477.578480 972.327480 884.750640 119.014680 92.067960 395.218560 -1983 1 1 1 200 2314.253280 2530.591840 3536.850800 4731.694360 5696.678200 5568.583000 4267.705080 3331.186840 2826.634080 2838.731960 2289.345880 2198.255960 1352.827640 848.274880 759.319880 261.883520 177.910000 87.531720 0.000000 0.000000 -1984 1 1 1 200 4149.450110 17403.788740 37019.876400 39643.507280 19277.016720 9302.216690 4129.995220 3815.937710 3763.131580 3349.020350 2762.594380 1636.990030 1806.525500 1170.072670 1848.214550 661.466260 219.562330 255.692840 5.558540 80.598830 -1985 1 1 1 200 95.831631 469.611709 896.631582 1451.794134 2162.637190 2135.833707 1554.969185 1478.230446 2208.533565 2254.062769 1884.321572 1920.671501 1824.839870 1535.876293 1025.875774 871.663954 64.622096 187.257210 152.375965 0.000000 -1986 1 1 1 200 458.823846 734.200233 1017.784560 824.897970 951.300246 641.450511 1674.009363 1641.588000 2293.298436 1991.246244 2768.538162 3011.903583 2872.779000 3231.876375 2312.587095 1579.207656 1126.539765 300.821001 120.246321 95.212104 -1987 1 1 1 200 110.596628 523.686020 2427.266392 3831.330868 3446.073740 2367.207296 2170.184164 2174.578732 2278.583508 1877.945392 2445.577092 1973.893460 2704.856604 2540.792732 2144.549184 2104.265644 1352.794516 1158.701096 281.984780 291.506344 -1988 1 1 1 200 58.765740 43.629110 294.719090 475.023065 577.863110 960.285615 2074.608700 1930.365520 1749.616350 1677.494760 1179.321555 1359.180335 905.526630 1654.789815 1472.705060 2192.585375 1640.988770 1193.122600 420.709275 412.695765 -1989 1 1 1 200 63.012451 3.755709 33.801381 95.144628 590.063614 1335.363200 694.388864 1451.372878 997.349390 1799.401912 1619.127880 1533.581175 2175.390113 2533.434371 2295.155500 2631.917407 2019.736840 1911.655881 1131.720312 1092.076717 -1990 1 1 1 200 57.929916 484.504752 689.453773 1586.928608 1473.263091 442.812767 361.184249 304.570922 688.137184 1139.288348 994.024695 1306.056288 1386.807080 1591.317238 1561.913417 1754.135411 1292.451535 1427.621339 852.271946 1445.175859 -1991 1 1 1 200 54.707317 465.277764 1162.132132 871.067960 1380.430261 1127.076958 713.850816 1423.983659 1150.978213 896.031493 306.998342 1096.802035 1852.612832 2013.547949 3165.057301 3602.715837 3427.971106 2651.445888 2161.735730 4174.221401 -1992 1 1 1 200 27.848700 0.000000 56.254374 353.956977 701.787240 988.628850 1537.248240 1469.575899 1063.263366 1111.998591 810.118683 1052.959347 969.970221 780.599061 650.545632 649.710171 609.329556 853.562655 469.250595 1382.130981 -1993 1 1 1 200 77.570460 407.950101 507.381327 389.262672 326.501118 581.778450 526.068756 845.165421 1125.124263 1549.646235 1657.539693 2273.872257 1770.722046 1483.006158 1189.296189 1029.571560 1098.327195 1030.629339 812.374272 1443.868335 -1994 1 1 1 200 31.260654 0.000000 59.626803 457.331790 453.086516 292.537972 238.507212 334.411811 411.212677 682.524279 795.409974 777.657010 1210.481991 1750.403657 914.663580 889.963804 903.085560 631.580991 442.666298 972.553680 -1995 1 1 1 200 894.228354 2160.893641 1763.775246 697.093087 348.388329 535.081439 702.155951 807.843237 869.546892 963.842734 830.942554 847.713291 1086.617186 1272.361009 1551.134958 1369.504712 1022.065670 752.151733 340.477604 827.461835 -1996 1 1 1 200 1236.054384 601.804256 1324.502720 2351.659024 2807.234624 2639.227232 1224.942784 999.599536 520.022880 793.812704 623.582992 667.140464 619.582816 576.914272 967.598128 732.032208 845.814992 761.811296 812.035728 1120.493744 -1997 1 1 1 200 0.000000 252.975198 156.603694 367.770666 899.939780 3993.748504 6680.104178 7580.752572 6446.261558 3652.196556 2134.345368 1145.828838 1054.417632 936.079094 1006.231880 1192.597362 1656.030918 1191.180134 1226.610834 2845.085210 -1998 1 1 1 200 1416.052770 1181.062718 700.216022 863.894064 814.994400 688.670268 913.472890 1147.104618 1536.943606 3168.969892 3295.973186 3554.054746 3065.058106 1974.323934 1244.224784 1035.722050 1327.761710 915.510376 539.933790 1663.946900 -1999 1 1 1 200 2568.978329 1076.473832 588.972363 457.501379 527.207471 484.854402 535.148671 652.060788 206.471210 582.354696 799.855351 1027.061918 2293.242204 2363.830652 3087.362244 3031.332664 1917.358719 1335.004023 972.355871 1111.326878 -2000 1 1 1 200 89.362943 241.535270 991.673347 2013.985418 1578.404900 1016.184326 1158.654390 829.288113 1020.269489 747.074206 682.732886 1506.403901 1496.190993 2489.906922 2117.135787 1830.153078 1743.343361 1165.803425 431.495355 999.333028 -2001 1 1 1 200 300.143558 216.068512 462.194942 649.076780 679.570320 1833.532998 1618.335730 2280.045548 1507.687742 870.808378 1103.430526 724.875008 608.128312 878.649574 573.714174 486.154152 953.576558 832.909264 836.829862 1424.048318 -2002 1 1 1 200 3533.370500 4226.136300 2887.628000 1803.442900 790.123900 600.706100 503.348000 703.362600 1517.991600 1762.380300 2300.830200 1922.656900 1341.157500 1666.346800 1125.910000 1280.888200 1290.160400 1467.656800 1599.454500 1814.702000 -2003 1 1 1 200 1224.594652 564.962620 1175.733020 1935.378705 3243.954287 2639.291591 2537.751012 1404.008457 875.692061 1184.131113 977.996103 2014.778857 1703.285953 2693.497464 2456.823934 2397.273820 1691.834008 1239.100449 1061.977033 2760.682208 -2004 1 1 1 200 3991.896844 3111.531891 2883.131303 2015.549965 1897.088466 1694.255108 2457.863044 3433.678989 3076.590010 3028.864514 2249.916240 1749.650773 1059.335563 1122.401397 1406.197650 1868.112272 1661.869950 2263.552096 1332.052683 2993.070392 -2005 1 1 1 200 3594.876075 5977.182603 4267.959255 1630.696977 995.347248 2322.136971 2390.465112 2188.540158 1878.513966 1746.956799 2229.333078 2372.108298 1619.478924 1928.485293 1273.758927 1614.379809 1053.477159 1575.626535 1465.485651 2570.973783 -2006 1 1 1 200 1064.189654 1581.838467 1384.409618 2212.647719 2329.820939 2955.012297 1680.552892 1663.699210 1032.087402 1503.990506 930.162752 1028.074620 1890.020087 1642.030190 2639.607671 2241.539746 2171.717348 1597.889593 1156.483628 1971.078273 -2007 1 1 1 200 130.099200 186.828503 401.643462 631.586235 1484.038553 2048.306016 2609.547915 3296.350671 2913.616976 2172.354090 1415.963390 1760.121159 1779.787317 2378.092361 2061.164658 2171.597700 2092.176676 1979.474462 1729.865531 2187.481904 -2008 1 1 1 200 0.000000 62.696298 296.304423 530.771401 1165.464064 1470.357021 1521.888225 1873.159265 2884.029717 3650.126950 3546.205689 2566.253959 2993.962952 2479.509766 1947.879511 1802.733287 1894.630600 1846.534810 1736.601575 3656.138924 -2009 1 1 1 200 59.333210 29.978885 230.462681 327.894058 331.641418 647.668834 602.075946 1407.133928 2057.925562 1878.052251 1967.988907 2047.308041 2264.654959 2989.144686 1949.876663 2054.178202 1236.004458 1018.032979 926.222643 1054.257466 -2010 1 1 1 200 0.000000 178.912367 429.603948 505.132821 414.605306 288.188184 861.350558 719.934795 694.222838 817.961631 1444.690582 1944.466745 1617.710625 1742.520750 1966.964707 1861.438551 2265.866207 1405.586980 778.858030 1070.795874 -2011 1 1 1 200 176.662330 212.091863 605.699415 991.541591 818.276614 669.763777 813.908589 730.430785 883.796984 640.643612 876.031606 983.290878 782.361745 1432.712079 1332.247512 1248.769708 1172.571945 991.056255 560.077825 798.863171 - -# Mean Length Vector (length n-size-classes) -67.5 72.5 77.5 82.5 87.5 92.5 97.5 102.5 107.5 112.5 117.5 122.5 127.5 132.5 137.5 142.5 147.5 152.5 157.5 162.5 - -# Mean Weight Vector (length n-size-classes) -0.218 0.273 0.337 0.411 0.495 0.59 0.696 0.815 0.948 1.094 1.256 1.432 1.625 1.835 2.063 2.31 2.576 2.862 3.169 3.7 - -# Fecundity (weight * proportion mature) -0 0 0 0 0 0 0 0 0 0 0 1.432 1.625 1.835 2.063 2.31 2.576 2.862 3.169 3.7 - -0 # Number of lines of capture data to read -0 # Number of lines of mark data to read -0 # Number of lines of recapture data to read - -999 # EOF check. \ No newline at end of file +# Fisheries: 1 Pot Fishery, 2 Pot Discard, 3 Trawl by-catch, 4 BSFRF +# Surveys: 3 NMFS Trawl Survey, 4 BSFRF Survey +#======================================================================================================== + +1975 # Start year +2014 # End year +1 # Time-step (years) +4 # Number of distinct data groups (among fishing fleets and surveys) +2 # Number of sexes +2 # Number of shell condition types +1 # Number of maturity types +20 # Number of size-classes in the model +## +# size_breaks (a vector giving the break points between size intervals, dim=nclass+1) +65 70 75 80 85 90 95 100 105 110 115 120 125 130 135 140 145 150 155 160 165 +# weight-at-length allometry w_l = a•l^b +#a=0.003593,b=2.666076 female > 89mm +#a=0.000408,b=3.127956 female < 90 new shell +#a=0.000403, b=3.141334 male new shell +## a (male, female) +4.03E-07 4.08E-07 +## b (male, female) +3.141334 3.127956 +# Male mature weight-at-length (weight * proportion mature) +0 0 0 0 0 0 0 0 0 0 0 1.432 1.625 1.835 2.063 2.31 2.576 2.862 3.169 3.7 +# Proportion mature by sex. +0 0 0 0 0 0 0 0 0 0 0 1 1 1 1 1 1 1 1 1 +0 0 0 0 0 0 0 0 0 0 0 1 1 1 1 1 1 1 1 1 +# Fishing fleet names (delimited with : no spaces in names) +Pot_Fishery:Trawl_Bycatch +# Survey names (delimited with : no spaces in names) +NMFS_Trawl:BSFRF +# Number of catch data frames +4 +# Number of rows in each data frame. +39 24 24 38 +#0.5 # Time between survey and fishery +## ———————————————————————————————————————————————————————————————————————————————————— ## +## CATCH DATA +## Type of catch: 1 = retained, 2 = discard, 3 = +## Units of catch: 1 = biomass, 2 = numbers +## for BBRKC Units are in 1000 mt for landed & million crabs for discards. +## ———————————————————————————————————————————————————————————————————————————————————— ## +## year seas fleet sex obs cv type units mult effort discard_mortality +## Male Retained 1000 + 1975 1 1 1 23281.2 0.05 1 1 1 0 0 + 1976 1 1 1 28993.6 0.05 1 1 1 0 0 + 1977 1 1 1 31736.9 0.05 1 1 1 0 0 + 1978 1 1 1 39743 0.05 1 1 1 0 0 + 1979 1 1 1 48910 0.05 1 1 1 0 0 + 1980 1 1 1 58943.6 0.05 1 1 1 0 0 + 1981 1 1 1 15236.8 0.05 1 1 1 0 0 + 1982 1 1 1 1361.32 0.05 1 1 1 0 0 + 1983 1 1 1 1 0.05 1 1 1 0 0 + 1984 1 1 1 1897.1 0.05 1 1 1 0 0 + 1985 1 1 1 1893.75 0.05 1 1 1 0 0 + 1986 1 1 1 5168.19 0.05 1 1 1 0 0 + 1987 1 1 1 5574.24 0.05 1 1 1 0 0 + 1988 1 1 1 3351.05 0.05 1 1 1 0 0 + 1989 1 1 1 4656.03 0.05 1 1 1 0 0 + 1990 1 1 1 9272.79 0.05 1 1 1 0 0 + 1991 1 1 1 7885.25 0.05 1 1 1 0 0 + 1992 1 1 1 3681.81 0.05 1 1 1 0 0 + 1993 1 1 1 6659.64 0.05 1 1 1 0 0 + 1994 1 1 1 42.1841 0.05 1 1 1 0 0 + 1995 1 1 1 36.2874 0.05 1 1 1 0 0 + 1996 1 1 1 3861.89 0.05 1 1 1 0 0 + 1997 1 1 1 4042.14 0.05 1 1 1 0 0 + 1998 1 1 1 6779.39 0.05 1 1 1 0 0 + 1999 1 1 1 5377.79 0.05 1 1 1 0 0 + 2000 1 1 1 3738.05 0.05 1 1 1 0 0 + 2001 1 1 1 3865.97 0.05 1 1 1 0 0 + 2002 1 1 1 4384.42 0.05 1 1 1 0 0 + 2003 1 1 1 7135.46 0.05 1 1 1 0 0 + 2004 1 1 1 7006.64 0.05 1 1 1 0 0 + 2005 1 1 1 8399.62 0.05 1 1 1 0 0 + 2006 1 1 1 7143.17 0.05 1 1 1 0 0 + 2007 1 1 1 9303.95 0.05 1 1 1 0 0 + 2008 1 1 1 9216.07 0.05 1 1 1 0 0 + 2009 1 1 1 7272.47 0.05 1 1 1 0 0 + 2010 1 1 1 6761.53 0.05 1 1 1 0 0 + 2011 1 1 1 3607.09 0.05 1 1 1 0 0 + 2012 1 1 1 3621.73 0.05 1 1 1 0 0 + 2013 1 1 1 3990.99 0.05 1 1 1 0 0 +## Male discards Pot fishery 1000 + 1990 1 1 1 526.914 0.05 2 2 1 0 0.2 + 1991 1 1 1 407.824 0.05 2 2 1 0 0.2 + 1992 1 1 1 552.009 0.05 2 2 1 0 0.2 + 1993 1 1 1 763.157 0.05 2 2 1 0 0.2 + 1994 1 1 1 3.81194 0.05 2 2 1 0 0.2 + 1995 1 1 1 3.27373 0.05 2 2 1 0 0.2 + 1996 1 1 1 164.636 0.05 2 2 1 0 0.2 + 1997 1 1 1 244.687 0.05 2 2 1 0 0.2 + 1998 1 1 1 959.712 0.05 2 2 1 0 0.2 + 1999 1 1 1 314.171 0.05 2 2 1 0 0.2 + 2000 1 1 1 360.833 0.05 2 2 1 0 0.2 + 2001 1 1 1 417.875 0.05 2 2 1 0 0.2 + 2002 1 1 1 442.658 0.05 2 2 1 0 0.2 + 2003 1 1 1 918.858 0.05 2 2 1 0 0.2 + 2004 1 1 1 345.549 0.05 2 2 1 0 0.2 + 2005 1 1 1 1359.53 0.05 2 2 1 0 0.2 + 2006 1 1 1 563.751 0.05 2 2 1 0 0.2 + 2007 1 1 1 1001.31 0.05 2 2 1 0 0.2 + 2008 1 1 1 1165.51 0.05 2 2 1 0 0.2 + 2009 1 1 1 888.124 0.05 2 2 1 0 0.2 + 2010 1 1 1 797.476 0.05 2 2 1 0 0.2 + 2011 1 1 1 394.962 0.05 2 2 1 0 0.2 + 2012 1 1 1 205.155 0.05 2 2 1 0 0.2 + 2013 1 1 1 310.579 0.05 2 2 1 0 0.2 +## Female discards Pot fishery + 1990 1 1 2 651.495 0.05 2 2 1 0 0.2 + 1991 1 1 2 74.998 0.05 2 2 1 0 0.2 + 1992 1 1 2 418.527 0.05 2 2 1 0 0.2 + 1993 1 1 2 637.129 0.05 2 2 1 0 0.2 + 1994 1 1 2 1.87659 0.05 2 2 1 0 0.2 + 1995 1 1 2 1.61164 0.05 2 2 1 0 0.2 + 1996 1 1 2 1.03179 0.05 2 2 1 0 0.2 + 1997 1 1 2 19.6126 0.05 2 2 1 0 0.2 + 1998 1 1 2 864.943 0.05 2 2 1 0 0.2 + 1999 1 1 2 8.82255 0.05 2 2 1 0 0.2 + 2000 1 1 2 40.4682 0.05 2 2 1 0 0.2 + 2001 1 1 2 173.46 0.05 2 2 1 0 0.2 + 2002 1 1 2 7.29233 0.05 2 2 1 0 0.2 + 2003 1 1 2 430.415 0.05 2 2 1 0 0.2 + 2004 1 1 2 187.029 0.05 2 2 1 0 0.2 + 2005 1 1 2 498.31 0.05 2 2 1 0 0.2 + 2006 1 1 2 36.9551 0.05 2 2 1 0 0.2 + 2007 1 1 2 186.111 0.05 2 2 1 0 0.2 + 2008 1 1 2 148.426 0.05 2 2 1 0 0.2 + 2009 1 1 2 85.1973 0.05 2 2 1 0 0.2 + 2010 1 1 2 122.625 0.05 2 2 1 0 0.2 + 2011 1 1 2 23.9891 0.05 2 2 1 0 0.2 + 2012 1 1 2 12.3255 0.05 2 2 1 0 0.2 + 2013 1 1 2 99.7634 0.05 2 2 1 0 0.2 +## Trawl fishery discards 1000 + 1976 1 2 0 682.795 0.05 2 2 1 0 0.8 + 1977 1 2 0 1249.85 0.05 2 2 1 0 0.8 + 1978 1 2 0 1320.62 0.05 2 2 1 0 0.8 + 1979 1 2 0 1331.94 0.05 2 2 1 0 0.8 + 1980 1 2 0 1036.5 0.05 2 2 1 0 0.8 + 1981 1 2 0 219.383 0.05 2 2 1 0 0.8 + 1982 1 2 0 574.888 0.05 2 2 1 0 0.8 + 1983 1 2 0 420.443 0.05 2 2 1 0 0.8 + 1984 1 2 0 1094.04 0.05 2 2 1 0 0.8 + 1985 1 2 0 390.061 0.05 2 2 1 0 0.8 + 1986 1 2 0 200.606 0.05 2 2 1 0 0.8 + 1987 1 2 0 186.436 0.05 2 2 1 0 0.8 + 1988 1 2 0 597.816 0.05 2 2 1 0 0.8 + 1989 1 2 0 174.066 0.05 2 2 1 0 0.8 + 1990 1 2 0 247.553 0.05 2 2 1 0 0.8 + 1991 1 2 0 315.959 0.05 2 2 1 0 0.8 + 1992 1 2 0 335.39 0.05 2 2 1 0 0.8 + 1993 1 2 0 426.564 0.05 2 2 1 0 0.8 + 1994 1 2 0 88.9147 0.05 2 2 1 0 0.8 + 1995 1 2 0 194.24 0.05 2 2 1 0 0.8 + 1996 1 2 0 106.509 0.05 2 2 1 0 0.8 + 1997 1 2 0 73.4005 0.05 2 2 1 0 0.8 + 1998 1 2 0 159.848 0.05 2 2 1 0 0.8 + 1999 1 2 0 201.575 0.05 2 2 1 0 0.8 + 2000 1 2 0 100.354 0.05 2 2 1 0 0.8 + 2001 1 2 0 164.565 0.05 2 2 1 0 0.8 + 2002 1 2 0 155.091 0.05 2 2 1 0 0.8 + 2003 1 2 0 172.32 0.05 2 2 1 0 0.8 + 2004 1 2 0 119.557 0.05 2 2 1 0 0.8 + 2005 1 2 0 155.222 0.05 2 2 1 0 0.8 + 2006 1 2 0 116.676 0.05 2 2 1 0 0.8 + 2007 1 2 0 138.486 0.05 2 2 1 0 0.8 + 2008 1 2 0 159.516 0.05 2 2 1 0 0.8 + 2009 1 2 0 103.743 0.05 2 2 1 0 0.8 + 2010 1 2 0 89.0308 0.05 2 2 1 0 0.8 + 2011 1 2 0 69.2305 0.05 2 2 1 0 0.8 + 2012 1 2 0 62.2251 0.05 2 2 1 0 0.8 + 2013 1 2 0 126.832 0.05 2 2 1 0 0.8 + +## ———————————————————————————————————————————————————————————————————————————————————— ## +## RELATIVE ABUNDANCE DATA +## Units of Abundance: 1 = biomass, 2 = numbers +## TODO: add column for maturity for terminal molt life-histories +## for BBRKC Units are in million crabs for Abundance. +## ———————————————————————————————————————————————————————————————————————————————————— ## +## Number of relative abundance indicies +2 +## Number of rows in each index +80 2 +# Survey data (abundance indices, units are millions of crabs) +# Year, Seas, Fleet, Sex, Abundance, CV units + 1975 1 3 1 146028 0.188 1 + 1976 1 3 1 200083 0.169 1 + 1977 1 3 1 237777 0.141 1 + 1978 1 3 1 203160 0.155 1 + 1979 1 3 1 160779 0.133 1 + 1980 1 3 1 164259 0.221 1 + 1981 1 3 1 64005 0.121 1 + 1982 1 3 1 72147.9 0.259 1 + 1983 1 3 1 35370.1 0.216 1 + 1984 1 3 1 82562.7 0.678 1 + 1985 1 3 1 27003.7 0.158 1 + 1986 1 3 1 40811.3 0.428 1 + 1987 1 3 1 46611.1 0.209 1 + 1988 1 3 1 34918.7 0.217 1 + 1989 1 3 1 48290.5 0.214 1 + 1990 1 3 1 36269.9 0.214 1 + 1991 1 3 1 70018.5 0.441 1 + 1992 1 3 1 25255.4 0.174 1 + 1993 1 3 1 36426.3 0.174 1 + 1994 1 3 1 23115.7 0.173 1 + 1995 1 3 1 27468.5 0.276 1 + 1996 1 3 1 27078.4 0.201 1 + 1997 1 3 1 60276.3 0.263 1 + 1998 1 3 1 46352.9 0.178 1 + 1999 1 3 1 40696.1 0.161 1 + 2000 1 3 1 39292.6 0.178 1 + 2001 1 3 1 28161.3 0.178 1 + 2002 1 3 1 45261.7 0.203 1 + 2003 1 3 1 55153 0.164 1 + 2004 1 3 1 60162.2 0.163 1 + 2005 1 3 1 55066.5 0.173 1 + 2006 1 3 1 51211.5 0.122 1 + 2007 1 3 1 58063.2 0.135 1 + 2008 1 3 1 55233.2 0.104 1 + 2009 1 3 1 43948.1 0.287 1 + 2010 1 3 1 36353.3 0.15 1 + 2011 1 3 1 25064 0.141 1 + 2012 1 3 1 30605.4 0.162 1 + 2013 1 3 1 39542.5 0.245 1 + 2014 1 3 1 59205.2 0.191 1 + 1975 1 3 2 73608.4 0.188 1 + 1976 1 3 2 101371 0.169 1 + 1977 1 3 2 142574 0.141 1 + 1978 1 3 2 146277 0.155 1 + 1979 1 3 2 103468 0.133 1 + 1980 1 3 2 80534.1 0.221 1 + 1981 1 3 2 58494.2 0.121 1 + 1982 1 3 2 69462.2 0.259 1 + 1983 1 3 2 13951.7 0.216 1 + 1984 1 3 2 52031.8 0.678 1 + 1985 1 3 2 7276.89 0.158 1 + 1986 1 3 2 6992.98 0.428 1 + 1987 1 3 2 22323.8 0.209 1 + 1988 1 3 2 19137.8 0.217 1 + 1989 1 3 2 13208 0.214 1 + 1990 1 3 2 20459.9 0.214 1 + 1991 1 3 2 17480.1 0.441 1 + 1992 1 3 2 12154.8 0.174 1 + 1993 1 3 2 17471.5 0.174 1 + 1994 1 3 2 8983.35 0.173 1 + 1995 1 3 2 10647.4 0.276 1 + 1996 1 3 2 17244.3 0.201 1 + 1997 1 3 2 24376.3 0.263 1 + 1998 1 3 2 38201.5 0.178 1 + 1999 1 3 2 20181.4 0.161 1 + 2000 1 3 2 29136.8 0.178 1 + 2001 1 3 2 24639.4 0.178 1 + 2002 1 3 2 24011 0.203 1 + 2003 1 3 2 41627.7 0.164 1 + 2004 1 3 2 36067.9 0.163 1 + 2005 1 3 2 51491.2 0.173 1 + 2006 1 3 2 43702.3 0.122 1 + 2007 1 3 2 45738.1 0.135 1 + 2008 1 3 2 56763 0.104 1 + 2009 1 3 2 47835.9 0.287 1 + 2010 1 3 2 42078.2 0.15 1 + 2011 1 3 2 39490.9 0.141 1 + 2012 1 3 2 30195.7 0.162 1 + 2013 1 3 2 22411.8 0.245 1 + 2014 1 3 2 60414.9 0.191 1 + #2007 1 4 0 102.963 0.1164 2 + #2008 1 4 0 83.5895 0.0939 2 + 2007 1 4 0 130352.8 0.1164 1 + 2008 1 4 0 106040.9 0.0939 1 + + +## Number of length frequency matrixes +9 +## Number of rows in each matrix +36 22 22 37 37 +40 40 40 4 +## Number of bins in each matrix (columns of size data) +20 20 20 20 20 +20 20 20 20 +## SIZE COMPOSITION DATA FOR ALL FLEETS +## ———————————————————————————————————————————————————————————————————————————————————— ## +## SIZE COMP LEGEND +## Sex: 1 = male, 2 = female, 0 = both sexes combined +## Type of composition: 1 = retained, 2 = discard, 0 = total composition +## Maturity state: 1 = immature, 2 = mature, 0 = both states combined +## Shell condition: 1 = new shell, 2 = old shell, 0 = both shell types combined +## ———————————————————————————————————————————————————————————————————————————————————— ## +##length proportions of retained males +##Year, Seas, Fleet, Sex, Type, Shell, Maturity, Nsamp, DataVec + 1975 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0 0.0071 0.0741 0.1721 0.2239 0.2122 0.1464 0.0858 0.0785 + 1976 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0 0.0016 0.029 0.1418 0.2316 0.2199 0.1635 0.1071 0.1055 + 1977 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0 0.0017 0.0192 0.1382 0.2442 0.2226 0.1605 0.104 0.1096 + 1978 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0 0.0012 0.0209 0.1441 0.2588 0.2401 0.1673 0.0966 0.0711 + 1979 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0 0.0013 0.0119 0.0747 0.1649 0.1998 0.2004 0.1556 0.1914 + 1980 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0 0.0008 0.0138 0.0919 0.1771 0.195 0.1792 0.1404 0.2019 + 1981 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0 0.0006 0.0225 0.1164 0.1743 0.1711 0.1584 0.1284 0.2283 + 1982 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0 0 0.0544 0.2576 0.2802 0.1667 0.0837 0.0508 0.1067 + 1984 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0.0003 0.0023 0.0654 0.311 0.3135 0.1763 0.0846 0.0321 0.0145 + 1985 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0.0005 0.0044 0.079 0.2869 0.3098 0.1898 0.086 0.0306 0.0129 + 1986 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0 0.0016 0.0531 0.2613 0.3289 0.2084 0.0978 0.0352 0.0137 + 1987 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0 0.0013 0.0284 0.1895 0.3045 0.2522 0.1421 0.0565 0.0255 + 1988 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0 0 0.0202 0.1294 0.2646 0.2471 0.1876 0.1033 0.0477 + 1989 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0 0.0005 0.0187 0.1211 0.2209 0.219 0.1908 0.1197 0.1094 + 1990 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0.0003 0 0.0146 0.0887 0.1801 0.1707 0.1728 0.1431 0.2297 + 1991 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0.0001 0.0005 0.0141 0.0848 0.1651 0.179 0.1739 0.1432 0.2392 + 1992 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0.0003 0.0002 0.0005 0.0095 0.0638 0.1317 0.1673 0.1747 0.1636 0.2886 + 1993 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0 0.0014 0.0138 0.094 0.1789 0.1739 0.1596 0.1331 0.2453 + 1996 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0.0006 0.0006 0.0129 0.0779 0.1407 0.162 0.1771 0.1671 0.2612 + 1997 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0.0004 0.0003 0.0138 0.0899 0.1486 0.1603 0.1699 0.1588 0.258 + 1998 1 1 1 1 0 0 100 0 0 0 0 0 0 0.0001 0.0001 0.0001 0.0001 0.0004 0.0002 0.0008 0.0225 0.1187 0.1596 0.149 0.1432 0.1394 0.266 + 1999 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0.0001 0 0.0001 0.0147 0.1313 0.2575 0.2292 0.1624 0.0961 0.1087 + 2000 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0.0001 0.0001 0 0.0001 0.0003 0.0111 0.0931 0.1945 0.2111 0.1822 0.1247 0.1826 + 2001 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0.0001 0.0001 0.0001 0.0002 0.0002 0.0012 0.0181 0.0836 0.1681 0.1986 0.1953 0.1506 0.1838 + 2002 1 1 1 1 0 0 100 0 0 0 0 0 0 0.0001 0 0.0001 0.0001 0.0001 0 0.0002 0.0151 0.108 0.1884 0.1915 0.1683 0.1334 0.1948 + 2003 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0.0001 0.0001 0.0002 0.0009 0.0243 0.1464 0.232 0.1871 0.1497 0.0994 0.1597 + 2004 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0 0.0002 0.0064 0.0514 0.1302 0.1702 0.1971 0.1632 0.2812 + 2005 1 1 1 1 0 0 100 0 0 0 0 0 0 0.0001 0 0 0 0.0001 0.0001 0.0008 0.015 0.0859 0.1543 0.1661 0.1783 0.1516 0.2475 + 2006 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0.0001 0.0001 0.0004 0.0102 0.0739 0.1905 0.2203 0.1887 0.137 0.1787 + 2007 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0.0002 0.0003 0.0067 0.0871 0.1833 0.1934 0.1846 0.1472 0.1973 + 2008 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0.0001 0.0002 0.01 0.0746 0.1457 0.1619 0.179 0.1625 0.2659 + 2009 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0 0.0002 0.0108 0.1152 0.2215 0.1968 0.1588 0.1084 0.1882 + 2010 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0 0.0003 0.0091 0.0986 0.2244 0.2238 0.1861 0.1144 0.1433 + 2011 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0.0003 0.0001 0.0003 0.0114 0.118 0.2436 0.2292 0.1725 0.1077 0.1169 + 2012 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0.0001 0 0.0001 0 0 0.0044 0.0499 0.1249 0.173 0.1886 0.1654 0.2937 + 2013 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0.0001 0.0001 0 0 0.0001 0.0001 0.0054 0.0525 0.1271 0.1484 0.1657 0.1632 0.3374 +##length proportions of pot discarded males +##Year, ##Year, Seas, Fleet, Sex, Type, Shell, Maturity, Nsamp, DataVec + 1990 1 1 1 2 0 0 100 0.0011 0 0.0011 0.008 0.0046 0.0126 0.0069 0.0378 0.0504 0.0767 0.1226 0.1523 0.1867 0.244 0.0859 0.0092 0 0 0 0 + 1991 1 1 1 2 0 0 100 0.0033 0.0101 0.0197 0.0214 0.0242 0.0394 0.0326 0.063 0.0624 0.0692 0.0641 0.1125 0.1586 0.2154 0.0939 0.0101 0 0 0 0 + 1992 1 1 1 2 0 0 100 0 0.0009 0.0012 0.0111 0.0222 0.0549 0.0869 0.1143 0.1183 0.123 0.118 0.1251 0.1112 0.0807 0.0293 0.0028 0 0 0 0 + 1993 1 1 1 2 0 0 100 0.0019 0.0045 0.0057 0.005 0.0062 0.0122 0.0312 0.0571 0.0778 0.108 0.1334 0.1544 0.1518 0.1705 0.0747 0.0055 0 0 0 0 + 1996 1 1 1 2 0 0 100 0 0 0 0.0131 0.0524 0.083 0.0742 0.0306 0.048 0.0699 0.0611 0.1004 0.1485 0.2009 0.1048 0.0131 0 0 0 0 + 1997 1 1 1 2 0 0 100 0 0.0002 0.0005 0.0007 0.0015 0.0197 0.0553 0.109 0.1268 0.1304 0.1031 0.1002 0.1275 0.1424 0.0751 0.0076 0 0 0 0 + 1998 1 1 1 2 0 0 100 0.0002 0.0005 0.0008 0.0044 0.007 0.01 0.0104 0.0175 0.0391 0.097 0.1402 0.2062 0.2047 0.1811 0.0714 0.0097 0 0 0 0 + 1999 1 1 1 2 0 0 100 0 0 0 0.0086 0.0086 0.0029 0.0076 0.0086 0.0143 0.0286 0.063 0.126 0.2118 0.3244 0.188 0.0076 0 0 0 0 + 2000 1 1 1 2 0 0 100 0.0003 0.0051 0.0192 0.0483 0.0613 0.0576 0.0595 0.0581 0.0532 0.0558 0.0712 0.1059 0.1497 0.1554 0.0895 0.0097 0 0 0 0 + 2001 1 1 1 2 0 0 100 0.0016 0.0057 0.0093 0.0115 0.0155 0.0302 0.0568 0.0866 0.1009 0.1196 0.1239 0.1411 0.1319 0.1128 0.0481 0.0045 0 0 0 0 + 2002 1 1 1 2 0 0 100 0.0012 0.0061 0.006 0.0091 0.0065 0.0104 0.0133 0.0335 0.063 0.1142 0.1543 0.1705 0.1642 0.1582 0.0803 0.0093 0 0 0 0 + 2003 1 1 1 2 0 0 100 0.0081 0.0119 0.0146 0.0317 0.0552 0.0666 0.072 0.067 0.0642 0.0599 0.0655 0.0958 0.1322 0.1708 0.0781 0.0064 0 0 0 0 + 2004 1 1 1 2 0 0 100 0.0004 0.0074 0.0177 0.0403 0.051 0.0483 0.0615 0.1087 0.1384 0.1452 0.1102 0.0849 0.07 0.0688 0.0404 0.0059 0.0008 0 0 0 + 2005 1 1 1 2 0 0 100 0.0002 0.0008 0.0015 0.0029 0.0076 0.022 0.0343 0.0418 0.0454 0.0658 0.0956 0.1376 0.1381 0.1385 0.0729 0.0262 0.0246 0.0349 0.0345 0.075 + 2006 1 1 1 2 0 0 100 0.0003 0.0013 0.0044 0.015 0.0312 0.0377 0.0368 0.0346 0.0452 0.0766 0.0929 0.1144 0.1377 0.1764 0.1275 0.0284 0.0105 0.0085 0.0075 0.0132 + 2007 1 1 1 2 0 0 100 0.0012 0.0042 0.0068 0.0098 0.0171 0.0366 0.0658 0.085 0.0928 0.0857 0.0819 0.0987 0.1291 0.1651 0.0956 0.0126 0.0032 0.0028 0.0022 0.0037 + 2008 1 1 1 2 0 0 100 0.0001 0.0003 0.0012 0.0046 0.0108 0.0141 0.0159 0.0214 0.0441 0.0808 0.1269 0.1793 0.1988 0.1838 0.0983 0.0099 0.0014 0.0018 0.0018 0.0045 + 2009 1 1 1 2 0 0 100 0.0004 0.001 0.0018 0.0032 0.0041 0.0073 0.0178 0.0402 0.0631 0.0705 0.0798 0.118 0.1809 0.2413 0.1455 0.0149 0.0021 0.0016 0.0022 0.0043 + 2010 1 1 1 2 0 0 100 0.0007 0.0011 0.0025 0.0055 0.0085 0.0119 0.0148 0.0218 0.0341 0.0541 0.0962 0.1517 0.2017 0.2373 0.135 0.0137 0.0017 0.0018 0.0016 0.0042 + 2011 1 1 1 2 0 0 100 0.0017 0.0066 0.0112 0.0199 0.0204 0.0188 0.0272 0.0309 0.0409 0.056 0.0756 0.1176 0.1698 0.221 0.1565 0.018 0.0026 0.0017 0.0009 0.0025 + 2012 1 1 1 2 0 0 100 0.0006 0.0008 0.0024 0.0042 0.0111 0.0262 0.0416 0.0563 0.0534 0.057 0.0704 0.106 0.1521 0.2072 0.1468 0.0248 0.0054 0.0085 0.0069 0.0182 + 2013 1 1 1 2 0 0 100 0.0001 0.0016 0.004 0.0052 0.011 0.0137 0.0227 0.0353 0.06 0.0871 0.1253 0.1381 0.1523 0.1563 0.1001 0.0207 0.0088 0.0177 0.0158 0.0242 +##length proportions of pot discarded females +##Year, Seas, Fleet, Sex, Type, Shell, Maturity, Nsamp, DataVec + 1990 1 1 2 2 0 0 50 0 0.0014 0.0029 0.0029 0.0057 0.0072 0.0143 0.0672 0.1016 0.1731 0.1688 0.2132 0.1359 0.0715 0.0243 0.01 0 0 0 0 + 1991 1 1 2 2 0 0 50 0.0054 0.0239 0.0612 0.0957 0.133 0.1596 0.1223 0.0718 0.0691 0.0559 0.0691 0.0798 0.0346 0.0106 0.0053 0.0027 0 0 0 0 + 1992 1 1 2 2 0 0 50 0.0008 0.0013 0.0029 0.0176 0.0799 0.1757 0.1941 0.1694 0.0958 0.0816 0.0577 0.0406 0.0406 0.0259 0.0117 0.0046 0 0 0 0 + 1993 1 1 2 2 0 0 50 0.0015 0.0024 0.0044 0.0059 0.013 0.0326 0.1011 0.1597 0.1444 0.1137 0.0905 0.0853 0.0835 0.074 0.0434 0.0446 0 0 0 0 + 1996 1 1 2 2 0 0 50 0 0 0 0.0909 0.6364 0.2727 0 0 0 0 0 0 0 0 0 0 0 0 0 0 + 1997 1 1 2 2 0 0 50 0 0 0.0011 0.0011 0.0099 0.0265 0.0364 0.0464 0.0695 0.1391 0.1667 0.1435 0.117 0.1082 0.0607 0.074 0 0 0 0 + 1998 1 1 2 2 0 0 50 0.0002 0.0004 0.001 0.0026 0.0064 0.018 0.057 0.1813 0.2307 0.1527 0.0828 0.0855 0.0578 0.0514 0.0337 0.0386 0 0 0 0 + 1999 1 1 2 2 0 0 50 0 0 0 0.0278 0.0278 0.0278 0.0556 0 0 0.1111 0.1389 0.0833 0.1111 0.1111 0.0833 0.2222 0 0 0 0 + 2000 1 1 2 2 0 0 50 0 0.0175 0.1036 0.2234 0.2093 0.1319 0.0774 0.0323 0.0209 0.0316 0.0451 0.0518 0.0229 0.0141 0.0047 0.0135 0 0 0 0 + 2001 1 1 2 2 0 0 50 0.0027 0.005 0.0151 0.033 0.0588 0.0866 0.097 0.0866 0.0575 0.0525 0.0874 0.1392 0.1421 0.0649 0.0291 0.0426 0 0 0 0 + 2002 1 1 2 2 0 0 50 0.0258 0.1194 0.1452 0.1548 0.1161 0.0645 0.0258 0.0226 0.0548 0.0419 0.0355 0.0258 0.0323 0.0355 0.0323 0.0678 0 0 0 0 + 2003 1 1 2 2 0 0 50 0.0141 0.0187 0.0255 0.0719 0.1116 0.1157 0.0743 0.0476 0.0661 0.0902 0.1012 0.0628 0.0497 0.0504 0.046 0.054 0 0 0 0 + 2004 1 1 2 2 0 0 50 0.0005 0.0075 0.0306 0.0596 0.0754 0.09 0.1425 0.1333 0.0883 0.0484 0.0574 0.0584 0.0511 0.0394 0.0389 0.0788 0 0 0 0 + 2005 1 1 2 2 0 0 50 0.0004 0.0013 0.0022 0.005 0.0146 0.0499 0.0788 0.0931 0.1233 0.1211 0.0871 0.1021 0.0958 0.0885 0.0519 0.0848 0 0 0 0 + 2006 1 1 2 2 0 0 50 0.0003 0.0044 0.0248 0.1218 0.1937 0.1603 0.072 0.0558 0.0722 0.0778 0.0614 0.0401 0.034 0.0282 0.0199 0.0333 0 0 0 0 + 2007 1 1 2 2 0 0 50 0.003 0.0126 0.0214 0.0223 0.0436 0.0854 0.1105 0.0828 0.0558 0.0744 0.102 0.1165 0.0954 0.0684 0.0444 0.0614 0 0 0 0 + 2008 1 1 2 2 0 0 50 0.0004 0.0018 0.0097 0.0364 0.0768 0.0661 0.0469 0.0773 0.107 0.0868 0.0954 0.1265 0.1257 0.0672 0.0392 0.0369 0 0 0 0 + 2009 1 1 2 2 0 0 50 0.0037 0.008 0.01 0.0144 0.0164 0.0277 0.0647 0.0863 0.0803 0.0913 0.0858 0.09 0.1144 0.1308 0.088 0.0881 0 0 0 0 + 2010 1 1 2 2 0 0 50 0.0037 0.0051 0.0051 0.0199 0.0276 0.029 0.0271 0.0443 0.0882 0.1138 0.1322 0.1427 0.1007 0.0915 0.0879 0.0813 0 0 0 0 + 2011 1 1 2 2 0 0 50 0.0132 0.0373 0.0653 0.1089 0.0814 0.0734 0.0619 0.0436 0.0281 0.0373 0.0717 0.0896 0.0748 0.0587 0.061 0.0938 0 0 0 0 + 2012 1 1 2 2 0 0 50 0.0089 0.0107 0.0125 0.0339 0.0606 0.1159 0.0945 0.0392 0.0178 0.0125 0.041 0.0392 0.1658 0.1515 0.1105 0.0856 0 0 0 0 + 2013 1 1 2 2 0 0 50 0.0005 0.0017 0.0083 0.0109 0.0187 0.0369 0.0714 0.1329 0.1424 0.0972 0.0718 0.0635 0.0855 0.0904 0.0732 0.0947 0 0 0 0 +#length proportions of trawl male bycatch +##Year, Seas, Fleet, Sex, Type, Shell, Maturity, Nsamp, DataVec + 1976 1 2 1 0 0 0 50 0 0 0 0 0 0.013 0.0087 0.0043 0.0216 0.0087 0.026 0.039 0.0433 0.0649 0.0996 0.0866 0.0736 0.0909 0.0649 0.1299 + 1977 1 2 1 0 0 0 50 0.0036 0.0009 0.0009 0.0009 0.0026 0.0035 0.0079 0.0097 0.0317 0.0485 0.0599 0.0996 0.1084 0.1251 0.104 0.1057 0.1004 0.0634 0.0326 0.0441 + 1978 1 2 1 0 0 0 50 0 0 0 0 0 0 0 0.0025 0.0012 0.0025 0.0149 0.0274 0.0511 0.0872 0.1245 0.1158 0.0797 0.0984 0.0672 0.188 + 1979 1 2 1 0 0 0 50 0.0178 0.0013 0.0025 0.0013 0.0025 0.0076 0.0038 0.0025 0.0013 0.0063 0.0051 0.0114 0.0228 0.0556 0.0582 0.0708 0.0898 0.086 0.0809 0.1858 + 1980 1 2 1 0 0 0 50 0.0531 0.0207 0.0096 0.0135 0.0142 0.0163 0.0274 0.0263 0.038 0.0375 0.0422 0.0394 0.0368 0.0377 0.0313 0.0231 0.0207 0.0142 0.0131 0.0265 + 1981 1 2 1 0 0 0 50 0.0262 0.0028 0.0045 0.0066 0.0112 0.0175 0.0279 0.0349 0.0386 0.0504 0.0434 0.048 0.0287 0.0334 0.0241 0.0212 0.0112 0.0064 0.0051 0.0087 + 1982 1 2 1 0 0 0 50 0.0701 0.0268 0.0247 0.0326 0.0356 0.0443 0.0409 0.0403 0.0401 0.0475 0.0426 0.0479 0.0405 0.0326 0.0218 0.0153 0.0084 0.0052 0.0038 0.0099 + 1983 1 2 1 0 0 0 50 0.0231 0.0214 0.0336 0.0344 0.0311 0.0319 0.0377 0.0445 0.0473 0.0471 0.0457 0.0437 0.0409 0.0414 0.0371 0.0283 0.0204 0.0129 0.0096 0.018 + 1984 1 2 1 0 0 0 50 0.0366 0.0156 0.0147 0.0199 0.027 0.0342 0.0399 0.0407 0.0431 0.0476 0.0511 0.0596 0.0594 0.0563 0.0473 0.0355 0.0264 0.017 0.0109 0.0146 + 1985 1 2 1 0 0 0 50 0.0051 0.0014 0.0034 0.0059 0.01 0.0164 0.0256 0.0396 0.0357 0.0446 0.0538 0.0636 0.0843 0.0862 0.0883 0.0843 0.0638 0.0455 0.0299 0.0578 + 1986 1 2 1 0 0 0 50 0.0038 0.0019 0.0085 0.0019 0.0056 0.0136 0.0193 0.0357 0.016 0.0249 0.0221 0.032 0.071 0.0555 0.0527 0.0635 0.0456 0.0362 0.0259 0.0282 + 1987 1 2 1 0 0 0 50 0.002 0 0.001 0.002 0.005 0.008 0.019 0.0271 0.017 0.022 0.0441 0.0491 0.0401 0.0581 0.0852 0.0812 0.0671 0.0611 0.0511 0.0842 + 1988 1 2 1 0 0 0 50 0.0048 0.0048 0.0063 0.0016 0.0032 0 0.0095 0.0174 0.0127 0.0396 0.0523 0.0539 0.0571 0.0634 0.065 0.0887 0.0792 0.0586 0.0349 0.0396 + 1989 1 2 1 0 0 0 50 0.0049 0.0025 0.0019 0.0008 0.0021 0.0021 0.0049 0.0047 0.0098 0.0144 0.0233 0.0373 0.0435 0.0526 0.07 0.0797 0.0787 0.0774 0.0672 0.0895 + 1990 1 2 1 0 0 0 50 0.0052 0.0052 0.0078 0.0017 0.0069 0.0069 0.0225 0.0207 0.038 0.038 0.0225 0.0242 0.0328 0.0484 0.0778 0.0709 0.0691 0.0588 0.0328 0.0674 + 1991 1 2 1 0 0 0 50 0.0032 0.0063 0.0032 0.0063 0.0159 0.0127 0.0127 0.0159 0.0317 0.0222 0.0317 0.0286 0.0349 0.019 0.0254 0.0603 0.0444 0.0571 0.0571 0.1714 + 1992 1 2 1 0 0 0 50 0.0203 0.0203 0.0203 0.0023 0.0068 0.009 0.0135 0.0023 0.0113 0.0158 0.0203 0.0158 0.0293 0.0293 0.0293 0.045 0.0248 0.036 0.0158 0.1149 + 1994 1 2 1 0 0 0 50 0.0035 0.0017 0.0035 0.0069 0.0017 0 0 0 0 0 0.0017 0.0017 0.0087 0.0156 0.0208 0.0468 0.0433 0.0572 0.0832 0.2756 + 1995 1 2 1 0 0 0 50 0.0072 0.029 0.0145 0.0072 0 0.0072 0 0.0072 0.0072 0.0145 0 0.0145 0.0145 0.0145 0.029 0.0652 0.1232 0.0942 0.0507 0.2464 + 1996 1 2 1 0 0 0 50 0.001 0.0015 0.0025 0.003 0.004 0.009 0.014 0.0156 0.0206 0.0276 0.0346 0.0437 0.0341 0.0482 0.0286 0.0447 0.0301 0.0376 0.0286 0.0853 + 1997 1 2 1 0 0 0 50 0 0 0.0018 0.0018 0.0107 0.022 0.0386 0.054 0.0516 0.051 0.0427 0.0291 0.0315 0.035 0.035 0.0309 0.035 0.0427 0.0475 0.1525 + 1998 1 2 1 0 0 0 50 0.0004 0.0004 0.0004 0 0 0.0008 0.0028 0.0035 0.0067 0.013 0.0268 0.0342 0.0547 0.0625 0.0677 0.0673 0.059 0.059 0.0504 0.1306 + 1999 1 2 1 0 0 0 50 0.002 0.0007 0.001 0.0003 0.0007 0 0.0033 0.0017 0.0023 0.0056 0.0083 0.0212 0.0422 0.0707 0.0953 0.1042 0.0979 0.0803 0.0588 0.1185 + 2000 1 2 1 0 0 0 50 0 0 0.0012 0.0006 0.0006 0.003 0.0042 0.0162 0.0222 0.0258 0.0252 0.0426 0.0372 0.0426 0.036 0.0468 0.0414 0.045 0.048 0.158 + 2001 1 2 1 0 0 0 50 0 0.0001 0.001 0.0006 0.0023 0.0071 0.008 0.0111 0.0192 0.0208 0.0224 0.0211 0.0234 0.0265 0.0312 0.0432 0.0593 0.0607 0.0612 0.2159 + 2002 1 2 1 0 0 0 50 0.0004 0.0004 0.0002 0.0019 0.0012 0.0023 0.0017 0.0025 0.005 0.0105 0.0161 0.0203 0.0287 0.0354 0.0486 0.0536 0.0651 0.0703 0.0753 0.2579 + 2003 1 2 1 0 0 0 50 0.0011 0.0008 0.0034 0.0099 0.0145 0.0149 0.0202 0.0122 0.0103 0.0122 0.0118 0.0251 0.0282 0.037 0.0514 0.0564 0.0556 0.051 0.051 0.1303 + 2004 1 2 1 0 0 0 50 0 0.0003 0.0016 0.0047 0.0028 0.0072 0.0094 0.0225 0.026 0.0232 0.0282 0.0238 0.0244 0.0235 0.0291 0.0429 0.0495 0.0469 0.0429 0.1199 + 2005 1 2 1 0 0 0 50 0.0016 0.0016 0.0016 0.0027 0.003 0.0065 0.0084 0.0155 0.0098 0.013 0.0212 0.0298 0.032 0.0336 0.0331 0.0331 0.0372 0.0388 0.0388 0.131 + 2006 1 2 1 0 0 0 50 0.0006 0 0 0 0.0006 0.0014 0.0023 0.0055 0.0075 0.0179 0.0182 0.0234 0.0254 0.03 0.0413 0.0436 0.043 0.0424 0.0367 0.0878 + 2007 1 2 1 0 0 0 50 0 0.0005 0 0.0009 0.0028 0.0019 0.0028 0.0081 0.009 0.0104 0.0171 0.018 0.0194 0.0356 0.0403 0.0403 0.037 0.0403 0.0565 0.1385 + 2008 1 2 1 0 0 0 50 0.0007 0 0.0003 0.001 0.0024 0.0014 0.0021 0.0041 0.0145 0.0237 0.0299 0.0478 0.0533 0.0478 0.0571 0.0399 0.0506 0.0489 0.0499 0.1669 + 2009 1 2 1 0 0 0 50 0.0004 0.0004 0.0004 0.0017 0.0017 0.0021 0.0021 0.0072 0.0102 0.0111 0.0115 0.0247 0.0353 0.0506 0.0591 0.0778 0.074 0.0604 0.0523 0.1471 + 2010 1 2 1 0 0 0 50 0.0025 0.0031 0.0037 0.0025 0.0031 0.0056 0.005 0.0068 0.013 0.0124 0.0155 0.0236 0.0366 0.0366 0.0379 0.0329 0.0323 0.0329 0.0323 0.1174 + 2011 1 2 1 0 0 0 50 0 0.0006 0.0012 0.003 0.003 0.0053 0.0024 0.0047 0.0059 0.0041 0.0053 0.0065 0.0118 0.0207 0.0342 0.0336 0.039 0.0366 0.0336 0.1027 + 2012 1 2 1 0 0 0 50 0 0.0006 0.0003 0.0006 0.0012 0.0015 0.0051 0.0075 0.0105 0.0128 0.0212 0.0248 0.0305 0.0323 0.0385 0.0421 0.0379 0.0415 0.0353 0.127 + 2013 1 2 1 0 0 0 50 0.007 0.0095 0.0147 0.0245 0.0203 0.0178 0.0203 0.0208 0.0225 0.0254 0.0263 0.0322 0.033 0.0303 0.0295 0.0269 0.027 0.0264 0.0256 0.0887 +##length proportions of trawl female bycatch +##Year, Seas, Fleet, Sex, Type, Shell, Maturity, Nsamp, DataVec + 1976 1 2 2 0 0 0 50 0 0 0 0 0 0 0.013 0.0087 0.0216 0.026 0.0303 0.0563 0.013 0.026 0.0043 0.026 0 0 0 0 + 1977 1 2 2 0 0 0 50 0 0.0009 0.0009 0 0 0.0009 0.0026 0.0053 0.007 0.0088 0.0062 0.0053 0.0044 0.0026 0.0009 0.0009 0 0 0 0 + 1978 1 2 2 0 0 0 50 0 0 0 0 0 0 0 0 0 0 0.0075 0.005 0.0075 0.0262 0.0324 0.061 0 0 0 0 + 1979 1 2 2 0 0 0 50 0.013 0.0013 0 0 0.0063 0.0038 0.0152 0.0468 0.0354 0.0392 0.0544 0.0215 0.0164 0.0177 0.0013 0.0139 0 0 0 0 + 1980 1 2 2 0 0 0 50 0.0433 0.016 0.0096 0.0189 0.0281 0.0409 0.0497 0.0472 0.0489 0.0525 0.0362 0.0265 0.0134 0.0081 0.0039 0.004 0 0 0 0 + 1981 1 2 2 0 0 0 50 0.0612 0.0245 0.0245 0.0437 0.054 0.0608 0.0525 0.0425 0.0315 0.0383 0.0312 0.0267 0.024 0.0158 0.0093 0.0086 0 0 0 0 + 1982 1 2 2 0 0 0 50 0.0631 0.0235 0.0237 0.0285 0.0379 0.0413 0.0332 0.0246 0.019 0.0177 0.0156 0.0144 0.0104 0.008 0.0034 0.0049 0 0 0 0 + 1983 1 2 2 0 0 0 50 0.0281 0.0233 0.0351 0.0363 0.0358 0.0407 0.0392 0.0316 0.0222 0.0154 0.01 0.0087 0.0065 0.0042 0.003 0.0041 0 0 0 0 + 1984 1 2 2 0 0 0 50 0.04 0.0156 0.0155 0.0211 0.0298 0.0344 0.0399 0.0359 0.0287 0.0151 0.0085 0.006 0.0042 0.0031 0.0019 0.0029 0 0 0 0 + 1985 1 2 2 0 0 0 50 0.0034 0.0013 0.0024 0.0046 0.0096 0.0171 0.0195 0.0193 0.0163 0.0128 0.0119 0.0111 0.0108 0.0057 0.0025 0.0066 0 0 0 0 + 1986 1 2 2 0 0 0 50 0.0038 0.0014 0.0038 0 0.0038 0.0099 0.0329 0.0762 0.063 0.047 0.0494 0.0466 0.0428 0.0202 0.0085 0.0268 0 0 0 0 + 1987 1 2 2 0 0 0 50 0.002 0.002 0.003 0.01 0.018 0.0311 0.0331 0.0401 0.022 0.0311 0.016 0.0391 0.008 0.008 0.003 0.009 0 0 0 0 + 1988 1 2 2 0 0 0 50 0.0079 0.0143 0.0032 0.0079 0.0063 0.0127 0.0222 0.0349 0.0475 0.0523 0.0396 0.0222 0.0174 0.0079 0.0048 0.0063 0 0 0 0 + 1989 1 2 2 0 0 0 50 0.0028 0.0023 0.0025 0.0047 0.0081 0.0123 0.0212 0.0428 0.0498 0.0477 0.0432 0.0297 0.0252 0.017 0.0064 0.0172 0 0 0 0 + 1990 1 2 2 0 0 0 50 0.0017 0.0035 0.0078 0.0069 0.0112 0.0112 0.019 0.0268 0.0424 0.038 0.0372 0.0346 0.0251 0.0173 0.0147 0.0449 0 0 0 0 + 1991 1 2 2 0 0 0 50 0 0.0032 0.0063 0.0032 0 0.0063 0.0032 0.0063 0.0254 0.0159 0.0159 0.0349 0.0222 0.054 0.0222 0.1206 0 0 0 0 + 1992 1 2 2 0 0 0 50 0.0045 0 0 0.0023 0.0315 0.0473 0.036 0.036 0.036 0.036 0.0473 0.0608 0.0495 0.0405 0.036 0.0541 0 0 0 0 + 1994 1 2 2 0 0 0 50 0 0.0035 0.0087 0.0295 0.0329 0.0433 0.0295 0.0659 0.0451 0.0173 0.0139 0.0121 0.0139 0.0225 0.0208 0.0693 0 0 0 0 + 1995 1 2 2 0 0 0 50 0.0507 0 0 0.0217 0.0072 0.0217 0.0435 0.0145 0.0217 0 0.0217 0.0072 0.0072 0.0145 0 0.0217 0 0 0 0 + 1996 1 2 2 0 0 0 50 0.003 0.0005 0.0025 0.007 0.0186 0.0236 0.0181 0.0261 0.0326 0.0482 0.0637 0.0602 0.0487 0.0416 0.0306 0.0607 0 0 0 0 + 1997 1 2 2 0 0 0 50 0 0 0.0006 0.0006 0.0042 0.0101 0.0285 0.0297 0.0469 0.0439 0.0243 0.0184 0.0178 0.0136 0.0101 0.038 0 0 0 0 + 1998 1 2 2 0 0 0 50 0 0 0.0004 0.0008 0.0012 0.0028 0.0134 0.0389 0.0441 0.033 0.0307 0.024 0.0295 0.0256 0.0319 0.0838 0 0 0 0 + 1999 1 2 2 0 0 0 50 0 0 0.0007 0.0003 0.0003 0.0007 0.0013 0.0066 0.0166 0.0322 0.0408 0.0365 0.0295 0.0259 0.0206 0.0727 0 0 0 0 + 2000 1 2 2 0 0 0 50 0 0 0 0.0018 0.0018 0.0042 0.0078 0.0138 0.0114 0.0228 0.0402 0.0547 0.0462 0.0432 0.039 0.1159 0 0 0 0 + 2001 1 2 2 0 0 0 50 0.0003 0.0001 0.0003 0.0014 0.0036 0.0062 0.0126 0.0169 0.0159 0.0189 0.0362 0.0615 0.0554 0.0343 0.027 0.0739 0 0 0 0 + 2002 1 2 2 0 0 0 50 0.0006 0.0008 0.0008 0.0006 0.0008 0.0025 0.0035 0.0087 0.0167 0.0165 0.013 0.0242 0.0349 0.036 0.0378 0.105 0 0 0 0 + 2003 1 2 2 0 0 0 50 0.0008 0.0019 0.0019 0.0118 0.0194 0.0156 0.0107 0.0088 0.0156 0.0225 0.0297 0.0335 0.0339 0.0453 0.0434 0.1078 0 0 0 0 + 2004 1 2 2 0 0 0 50 0.0003 0.0003 0.0016 0.0025 0.0041 0.0106 0.0182 0.0307 0.0285 0.026 0.0444 0.0413 0.0435 0.041 0.0426 0.1358 0 0 0 0 + 2005 1 2 2 0 0 0 50 0.0003 0.0024 0.003 0.0016 0.0033 0.0087 0.0138 0.0269 0.0393 0.0485 0.038 0.0393 0.0499 0.0407 0.0374 0.1546 0 0 0 0 + 2006 1 2 2 0 0 0 50 0.0003 0 0.0003 0.0003 0.002 0.004 0.0092 0.024 0.0456 0.0722 0.0707 0.0661 0.0494 0.0372 0.03 0.1611 0 0 0 0 + 2007 1 2 2 0 0 0 50 0 0.0005 0.0019 0.0019 0.0028 0.0109 0.0194 0.0337 0.038 0.0541 0.0731 0.0764 0.0593 0.046 0.0289 0.0735 0 0 0 0 + 2008 1 2 2 0 0 0 50 0.0003 0.0007 0.0007 0.001 0.0038 0.0045 0.0096 0.0182 0.0365 0.0296 0.0399 0.0427 0.0502 0.031 0.0224 0.0664 0 0 0 0 + 2009 1 2 2 0 0 0 50 0.0004 0.0004 0.0013 0.0009 0.0021 0.0089 0.02 0.0327 0.0327 0.0272 0.0293 0.0315 0.0442 0.0378 0.0289 0.0714 0 0 0 0 + 2010 1 2 2 0 0 0 50 0.0006 0.0012 0.0019 0.0031 0.0037 0.0081 0.018 0.0248 0.0422 0.0466 0.0646 0.0652 0.0646 0.0453 0.0435 0.1106 0 0 0 0 + 2011 1 2 2 0 0 0 50 0 0.0018 0.0024 0.0094 0.0089 0.0159 0.023 0.0272 0.046 0.0531 0.0815 0.0762 0.0667 0.0537 0.0413 0.1387 0 0 0 0 + 2012 1 2 2 0 0 0 50 0 0 0.0012 0.0027 0.0021 0.0125 0.0209 0.0275 0.0314 0.0341 0.0329 0.0532 0.0642 0.0615 0.0624 0.1222 0 0 0 0 + 2013 1 2 2 0 0 0 50 0.0055 0.0104 0.0217 0.0256 0.0237 0.0238 0.0248 0.0325 0.0358 0.0279 0.0253 0.0241 0.0295 0.0413 0.0329 0.0865 0 0 0 0 +##length proportions of survey newshell males +##Year, Seas, Fleet, Sex, Type, Shell, Maturity, Nsamp, DataVec + 1975 1 3 1 1 1 0 200 0.03433 0.06119 0.03631 0.03701 0.03626 0.02684 0.02746 0.02043 0.02199 0.02522 0.02323 0.02322 0.02484 0.02294 0.01909 0.0197 0.0162 0.00957 0.00661 0.01009 + 1976 1 3 1 1 1 0 200 0.00232 0.01279 0.02937 0.05077 0.06104 0.04581 0.04776 0.03559 0.03199 0.02832 0.02984 0.02996 0.02334 0.02354 0.0206 0.01457 0.01294 0.00852 0.00591 0.00568 + 1977 1 3 1 1 1 0 200 0.00722 0.00558 0.00666 0.01007 0.0195 0.037 0.04363 0.04307 0.04013 0.04302 0.03906 0.03772 0.02788 0.02964 0.02865 0.02252 0.0144 0.01024 0.00661 0.00905 + 1978 1 3 1 1 1 0 200 0.00415 0.0114 0.01313 0.02219 0.01618 0.0153 0.0153 0.02585 0.02749 0.02795 0.02833 0.02739 0.02477 0.0294 0.02988 0.02505 0.02385 0.01579 0.00971 0.00755 + 1979 1 3 1 1 1 0 200 0.00801 0.008 0.01059 0.01598 0.01392 0.01592 0.01244 0.01397 0.01354 0.0178 0.02471 0.03399 0.03477 0.03788 0.03207 0.03339 0.02893 0.02384 0.01446 0.02128 + 1980 1 3 1 1 1 0 200 0.00713 0.01445 0.02854 0.0319 0.03189 0.03189 0.02635 0.02638 0.02288 0.01971 0.02217 0.01609 0.02291 0.02541 0.0251 0.0303 0.02546 0.02432 0.02153 0.02725 + 1981 1 3 1 1 1 0 200 0.03277 0.0196 0.01678 0.0252 0.03727 0.03277 0.03133 0.0292 0.02759 0.02966 0.01907 0.01635 0.01061 0.00937 0.00747 0.00654 0.00401 0.00357 0.00143 0.00509 + 1982 1 3 1 1 1 0 200 0.07924 0.08112 0.06821 0.02812 0.02304 0.03021 0.03407 0.02807 0.01868 0.01581 0.0181 0.01276 0.00951 0.00694 0.00436 0.0034 0.00225 0.00053 0.00041 0.00082 + 1983 1 3 1 1 1 0 200 0.03252 0.03556 0.0497 0.06649 0.07859 0.07774 0.05655 0.04214 0.03545 0.03417 0.02308 0.02137 0.01351 0.00898 0.00777 0.00183 0.00084 0 0 0 + 1984 1 3 1 1 1 0 200 0.01493 0.0625 0.13306 0.14261 0.06919 0.03343 0.01442 0.01346 0.0133 0.00938 0.00949 0.00565 0.00568 0.00336 0.00416 0.00175 0.00077 0.00041 0.00002 0.00016 + 1985 1 3 1 1 1 0 200 0.00261 0.01279 0.02442 0.03954 0.0589 0.05817 0.04235 0.04026 0.05909 0.06049 0.05132 0.05049 0.04397 0.04183 0.02443 0.02289 0.00176 0.00319 0.00415 0 + 1986 1 3 1 1 1 0 200 0.01118 0.01788 0.0248 0.0201 0.02318 0.01475 0.03917 0.04 0.05364 0.04764 0.06284 0.06696 0.05865 0.06369 0.04877 0.03519 0.02325 0.00733 0.00143 0.00072 + 1987 1 3 1 1 1 0 200 0.00151 0.00715 0.03314 0.0523 0.04666 0.03193 0.02963 0.02928 0.03029 0.02445 0.03113 0.02335 0.03004 0.02375 0.02059 0.01754 0.01411 0.0133 0.00347 0.00237 + 1988 1 3 1 1 1 0 200 0.00132 0.00098 0.00662 0.01068 0.01094 0.02158 0.04663 0.04339 0.03932 0.03771 0.02571 0.02768 0.01467 0.02865 0.02359 0.03421 0.02539 0.0189 0.00946 0.00793 + 1989 1 3 1 1 1 0 200 0.00151 0.00009 0 0.00228 0.01414 0.032 0.01664 0.03469 0.02244 0.03796 0.0373 0.03601 0.04465 0.05129 0.0334 0.03221 0.02538 0.02108 0.01328 0.01964 + 1990 1 3 1 1 1 0 200 0.00132 0.01104 0.01571 0.03616 0.03285 0.01009 0.0075 0.00623 0.01313 0.02143 0.01949 0.02053 0.02075 0.0213 0.01671 0.02223 0.01615 0.01075 0.01072 0.01925 + 1991 1 3 1 1 1 0 200 0.00103 0.00876 0.0213 0.01581 0.02487 0.01952 0.01114 0.02291 0.02011 0.01171 0.00363 0.01729 0.02907 0.03294 0.04485 0.05331 0.0515 0.04094 0.03382 0.06686 + 1992 1 3 1 1 1 0 200 0.001 0 0.00202 0.01106 0.0252 0.03333 0.05097 0.04886 0.03395 0.03348 0.02591 0.03451 0.02322 0.0146 0.01108 0.01594 0.01162 0.01399 0.01176 0.02854 + 1993 1 3 1 1 1 0 200 0.00208 0.01094 0.01291 0.00906 0.00804 0.01357 0.01066 0.01917 0.01955 0.03344 0.02444 0.04147 0.02119 0.01732 0.00967 0.00822 0.00732 0.00891 0.00577 0.00787 + 1994 1 3 1 1 1 0 200 0.00162 0 0.00309 0.02093 0.01757 0.01239 0.01098 0.01082 0.01688 0.03227 0.03069 0.02792 0.03848 0.05112 0.02013 0.02458 0.02607 0.01992 0.01064 0.01519 + 1995 1 3 1 1 1 0 200 0.02826 0.06829 0.05574 0.02203 0.01101 0.01592 0.02133 0.02355 0.02568 0.02873 0.02066 0.02201 0.02408 0.02322 0.035 0.02166 0.01749 0.01473 0.00622 0.01125 + 1996 1 3 1 1 1 0 200 0.02719 0.01292 0.02918 0.05291 0.06042 0.05874 0.02691 0.01981 0.01098 0.01462 0.01337 0.01035 0.00912 0.00319 0.00622 0.00716 0.00659 0.00938 0.0111 0.01276 + 1997 1 3 1 1 1 0 200 0 0.00357 0.00221 0.00519 0.0127 0.05636 0.09427 0.10657 0.09022 0.05071 0.02796 0.0136 0.01212 0.00935 0.01131 0.01348 0.01555 0.0103 0.00979 0.02598 + 1998 1 3 1 1 1 0 200 0.02085 0.01739 0.01031 0.01272 0.012 0.01014 0.01345 0.01472 0.02013 0.04373 0.04263 0.03912 0.03466 0.01846 0.00647 0.00737 0.00442 0.0029 0.00124 0.00345 + 1999 1 3 1 1 1 0 200 0.05825 0.02444 0.01335 0.01038 0.01196 0.01036 0.00963 0.01225 0.00326 0.00664 0.01252 0.02202 0.04148 0.0395 0.05441 0.05623 0.02925 0.01972 0.01072 0.0114 + 2000 1 3 1 1 1 0 200 0.00175 0.00473 0.01944 0.03949 0.03095 0.01993 0.02272 0.01626 0.01888 0.01404 0.01099 0.02078 0.01298 0.02074 0.01385 0.0111 0.01148 0.00855 0.00427 0.0067 + 2001 1 3 1 1 1 0 200 0.00689 0.00496 0.01061 0.0149 0.0156 0.04136 0.03572 0.05159 0.03394 0.01999 0.02186 0.0132 0.00984 0.01223 0.00775 0.00551 0.01066 0.01006 0.01014 0.0124 + 2002 1 3 1 1 1 0 200 0.05335 0.06381 0.0436 0.02682 0.01193 0.00793 0.00606 0.00736 0.01535 0.01781 0.02124 0.02041 0.01045 0.00875 0.00999 0.00631 0.00525 0.00883 0.00623 0.00503 + 2003 1 3 1 1 1 0 200 0.01604 0.0074 0.0154 0.02495 0.04249 0.0342 0.03247 0.018 0.00959 0.01396 0.01125 0.02279 0.01875 0.02908 0.02324 0.02414 0.01482 0.00971 0.00796 0.02164 + 2004 1 3 1 1 1 0 200 0.04684 0.03651 0.03383 0.02365 0.02226 0.01926 0.02833 0.04015 0.03578 0.0352 0.0264 0.02019 0.01236 0.01273 0.0128 0.01815 0.01566 0.02153 0.01193 0.025 + 2005 1 3 1 1 1 0 200 0.03525 0.05861 0.04185 0.01599 0.00976 0.02277 0.02344 0.02146 0.01842 0.01622 0.02073 0.02207 0.01265 0.01714 0.00954 0.01168 0.00648 0.00646 0.00805 0.01227 + 2006 1 3 1 1 1 0 200 0.01329 0.01976 0.01658 0.02765 0.02838 0.03548 0.01857 0.02076 0.01179 0.017 0.0105 0.01205 0.01881 0.01862 0.02997 0.02605 0.02056 0.01732 0.01059 0.01291 + 2007 1 3 1 1 1 0 200 0.00172 0.00246 0.00532 0.00837 0.01967 0.02715 0.03091 0.04028 0.03332 0.02419 0.01566 0.01804 0.01517 0.02261 0.01747 0.01805 0.0179 0.01359 0.01535 0.01691 + 2008 1 3 1 1 1 0 200 0 0.00076 0.00363 0.00577 0.01395 0.01669 0.01814 0.0223 0.03342 0.04313 0.03802 0.02547 0.02337 0.01707 0.01364 0.01039 0.01454 0.01071 0.00832 0.01802 + 2009 1 3 1 1 1 0 200 0.00095 0.00048 0.0037 0.00527 0.00532 0.01039 0.00965 0.02253 0.03192 0.02616 0.0236 0.02484 0.02844 0.04127 0.02429 0.02658 0.01436 0.01032 0.00775 0.0067 + 2010 1 3 1 1 1 0 200 0 0.00334 0.00803 0.00943 0.00774 0.00538 0.01608 0.01344 0.01295 0.01526 0.02418 0.03048 0.02201 0.0223 0.02723 0.02567 0.0316 0.01894 0.01048 0.0095 + 2011 1 3 1 1 1 0 200 0.00362 0.00438 0.0125 0.02044 0.01569 0.01317 0.01676 0.01505 0.01822 0.01195 0.01613 0.0164 0.01359 0.0199 0.01732 0.01617 0.01904 0.01323 0.00578 0.00808 + 2012 1 3 1 1 1 0 200 0.00247 0.00398 0.01202 0.01593 0.01281 0.0227 0.03362 0.02474 0.01742 0.01742 0.01461 0.01733 0.01843 0.01958 0.01581 0.01519 0.01481 0.01651 0.00795 0.02737 + 2013 1 3 1 1 1 0 200 0.00082 0.00253 0.01232 0.01451 0.01006 0.01741 0.01341 0.02352 0.02798 0.02607 0.03135 0.02742 0.02114 0.01964 0.01842 0.01501 0.01278 0.01693 0.0211 0.03167 + 2014 1 3 1 1 1 0 200 0 0.00046 0.00259 0.003 0.01598 0.03132 0.04239 0.03212 0.02832 0.01706 0.02131 0.02572 0.02618 0.02269 0.02763 0.01884 0.01393 0.00987 0.00856 0.01333 + + ##length proportions of survey oldshell males + ##Year, Seas, Fleet, Sex, Type, Shell, Maturity, Nsamp, DataVec + 1975 1 3 1 0 2 0 200 0 0.00011 0 0.00022 0 0.00011 0 0.00085 0.00065 0.0015 0.00086 0.00138 0.00171 0.00137 0.00195 0.00362 0.00184 0.00198 0.00188 0.00076 + 1976 1 3 1 0 2 0 200 0 0 0 0.00004 0.00004 0 0 0.00002 0.00052 0.00042 0.00093 0.00365 0.00268 0.00508 0.00529 0.00393 0.00422 0.00497 0.00294 0.00151 + 1977 1 3 1 0 2 0 200 0 0 0 0 0 0.00041 0.00065 0.00018 0.00068 0.00083 0.00118 0.0024 0.00243 0.00212 0.00307 0.00309 0.00184 0.00341 0.00157 0.00302 + 1978 1 3 1 0 2 0 200 0.00014 0.00055 0.00048 0.00182 0.00106 0.00376 0.00253 0.00205 0.00207 0.00181 0.00171 0.00297 0.00421 0.00726 0.00476 0.00321 0.00216 0.00149 0.00113 0.00156 + 1979 1 3 1 0 2 0 200 0.00015 0.00093 0.00064 0.00022 0.00073 0.00111 0.00024 0.00039 0.00039 0.00087 0.00105 0.00202 0.00181 0.00378 0.0043 0.00378 0.00524 0.0044 0.00132 0.00393 + 1980 1 3 1 0 2 0 200 0 0 0 0 0 0.00045 0.0003 0 0 0.00016 0.00038 0.00045 0.00097 0.00121 0.0018 0.00285 0.00174 0.00295 0.00104 0.00401 + 1981 1 3 1 0 2 0 200 0.00016 0 0.00061 0 0.001 0.00073 0.00059 0.00247 0.00146 0.00418 0.00419 0.00537 0.00795 0.00898 0.00711 0.00801 0.0066 0.00669 0.00476 0.00952 + 1982 1 3 1 0 2 0 200 0 0 0 0.00055 0.00095 0.00079 0.0012 0.00065 0.00105 0.00129 0.00173 0.00135 0.00355 0.00097 0.00222 0.00093 0.00169 0 0 0.00094 + 1983 1 3 1 0 2 0 200 0 0 0 0 0.00146 0.00051 0.00342 0.00467 0.00427 0.00572 0.00909 0.00952 0.0055 0.00294 0.0029 0.00185 0.00166 0.00123 0 0 + 1984 1 3 1 0 2 0 200 0 0.00012 0.00014 0.00003 0.00017 0.00004 0.00044 0.00027 0.00024 0.00267 0.00045 0.00024 0.00082 0.00085 0.00249 0.00063 0.00002 0.00051 0 0.00013 + 1985 1 3 1 0 2 0 200 0 0 0 0 0 0 0 0 0.00106 0.0009 0 0.00182 0.00573 0 0.00351 0.00085 0 0.00191 0 0 + 1986 1 3 1 0 2 0 200 0 0 0 0 0 0.00088 0.00162 0 0.00224 0.00088 0.00462 0.00643 0.01135 0.01506 0.00757 0.00329 0.0042 0 0.0015 0.0016 + 1987 1 3 1 0 2 0 200 0 0 0 0 0.00039 0.00039 0 0.00041 0.00082 0.00119 0.00226 0.0036 0.00689 0.01094 0.00869 0.01119 0.00436 0.00251 0.00038 0.00161 + 1988 1 3 1 0 2 0 200 0 0 0 0 0.00205 0 0 0 0 0 0.0008 0.00288 0.00569 0.00855 0.00952 0.01509 0.01151 0.00793 0 0.00135 + 1989 1 3 1 0 2 0 200 0 0 0.00081 0 0 0 0 0.00009 0.00146 0.00516 0.0015 0.00074 0.00748 0.00942 0.0216 0.03086 0.02302 0.02473 0.01384 0.00653 + 1990 1 3 1 0 2 0 200 0 0 0 0 0.00072 0 0.00072 0.00071 0.00255 0.00453 0.00316 0.00923 0.01085 0.01496 0.01888 0.01774 0.0133 0.02177 0.00869 0.01368 + 1991 1 3 1 0 2 0 200 0 0 0.00058 0.00059 0.00112 0.0017 0.0023 0.0039 0.00156 0.00516 0.00215 0.00336 0.00581 0.00497 0.01474 0.01452 0.01304 0.00898 0.00688 0.01173 + 1992 1 3 1 0 2 0 200 0 0 0 0.00165 0 0.00217 0.00423 0.00391 0.00423 0.00645 0.00318 0.0033 0.01161 0.01343 0.01228 0.00739 0.01026 0.01666 0.00509 0.02109 + 1993 1 3 1 0 2 0 200 0 0 0.00069 0.00137 0.00145 0.00203 0.00344 0.00422 0.01136 0.01032 0.01999 0.02171 0.0285 0.02464 0.02295 0.02012 0.02286 0.01946 0.01823 0.03231 + 1994 1 3 1 0 2 0 200 0 0 0 0.00277 0.00591 0.00277 0.00138 0.00651 0.00443 0.0031 0.01053 0.01238 0.02425 0.03959 0.02727 0.02154 0.02073 0.01281 0.0123 0.03521 + 1995 1 3 1 0 2 0 200 0 0 0 0 0 0.00099 0.00086 0.00198 0.0018 0.00173 0.0056 0.00478 0.01026 0.01699 0.01402 0.02162 0.01481 0.00904 0.00454 0.0149 + 1996 1 3 1 0 2 0 200 0.00062 0.00062 0.00062 0 0.00274 0.00064 0.00065 0.00268 0.00072 0.00324 0.00066 0.00466 0.00482 0.00979 0.01555 0.00931 0.01244 0.00776 0.00717 0.01245 + 1997 1 3 1 0 2 0 200 0 0 0 0 0 0 0 0.00041 0.00075 0.00083 0.00216 0.00257 0.00276 0.00386 0.00289 0.00335 0.00782 0.00651 0.00752 0.01417 + 1998 1 3 1 0 2 0 200 0 0 0 0 0 0 0 0.00217 0.0025 0.00293 0.00589 0.0132 0.01047 0.01061 0.01185 0.00788 0.01513 0.01058 0.00671 0.02105 + 1999 1 3 1 0 2 0 200 0 0 0 0 0 0.00062 0.0025 0.00253 0.00142 0.00658 0.00563 0.00129 0.01054 0.01416 0.01567 0.01262 0.01435 0.01064 0.01136 0.01386 + 2000 1 3 1 0 2 0 200 0 0 0 0 0 0 0 0 0.00112 0.00061 0.00239 0.00876 0.01636 0.02809 0.02766 0.02479 0.02271 0.01431 0.0042 0.01289 + 2001 1 3 1 0 2 0 200 0 0 0 0 0 0.00073 0.00143 0.00075 0.00067 0 0.00347 0.00344 0.00412 0.00794 0.00542 0.00565 0.01123 0.00906 0.00907 0.02029 + 2002 1 3 1 0 2 0 200 0 0 0 0.00041 0 0.00114 0.00154 0.00326 0.00757 0.0088 0.0135 0.00862 0.0098 0.01641 0.00701 0.01303 0.01423 0.01333 0.01792 0.02237 + 2003 1 3 1 0 2 0 200 0 0 0 0.0004 0 0.00037 0.00077 0.00039 0.00188 0.00155 0.00156 0.0036 0.00356 0.0062 0.00894 0.00726 0.00734 0.00652 0.00595 0.01452 + 2004 1 3 1 0 2 0 200 0 0 0 0 0 0.00062 0.00051 0.00014 0.00032 0.00034 0 0.00034 0.00007 0.00044 0.0037 0.00377 0.00384 0.00503 0.0037 0.01012 + 2005 1 3 1 0 2 0 200 0 0 0 0 0 0 0 0 0 0.00091 0.00113 0.00119 0.00323 0.00177 0.00295 0.00415 0.00385 0.00899 0.00632 0.01294 + 2006 1 3 1 0 2 0 200 0 0 0.00071 0 0.00073 0.00144 0.00241 0 0.00111 0.00175 0.0011 0.00076 0.00473 0.00186 0.00289 0.00183 0.00646 0.00255 0.00377 0.01163 + 2007 1 3 1 0 2 0 200 0 0 0 0 0 0 0.00369 0.00339 0.00527 0.00455 0.00307 0.00526 0.00834 0.00878 0.00976 0.01062 0.00969 0.01252 0.00746 0.01193 + 2008 1 3 1 0 2 0 200 0 0 0 0.00074 0.00037 0.00148 0.00074 0.00075 0.00203 0.00037 0.0024 0.00393 0.00599 0.00862 0.00625 0.00585 0.00539 0.00811 0.00765 0.01503 + 2009 1 3 1 0 2 0 200 0 0 0 0 0 0 0 0 0.00101 0.00386 0.00786 0.00793 0.00778 0.0066 0.00689 0.00625 0.00537 0.00593 0.00704 0.01014 + 2010 1 3 1 0 2 0 200 0 0 0 0 0 0 0 0 0 0 0.00278 0.00578 0.00817 0.01021 0.00947 0.00903 0.01066 0.00728 0.00404 0.01046 + 2011 1 3 1 0 2 0 200 0 0 0 0 0.00118 0.00061 0 0 0 0.00123 0.00193 0.00385 0.00252 0.00962 0.0101 0.00952 0.00507 0.00714 0.00576 0.0083 + 2012 1 3 1 0 2 0 200 0 0 0 0 0 0 0 0 0 0 0.00071 0.00222 0.00326 0.00686 0.0076 0.00575 0.00834 0.0116 0.00523 0.01605 + 2013 1 3 1 0 2 0 200 0 0 0 0 0 0 0 0 0 0 0.00091 0.0074 0.00914 0.01228 0.01594 0.01743 0.02119 0.02615 0.01835 0.04324 + 2014 1 3 1 0 2 0 200 0 0 0 0 0 0 0.00129 0.00267 0.00295 0.00214 0.00176 0.00686 0.00739 0.00817 0.00961 0.00696 0.00844 0.00901 0.00943 0.0306 +##length proportions of survey females +##Year, ##Year, Seas, Fleet, Sex, Type, Shell, Maturity, Nsamp, DataVec + 1975 1 3 2 0 0 0 200 0.04788 0.05622 0.05339 0.04732 0.05296 0.04081 0.03821 0.03823 0.02918 0.02491 0.01409 0.01364 0.00998 0.00433 0.00262 0.00294 0 0 0 0 + 1976 1 3 2 0 0 0 200 0.00315 0.00913 0.03175 0.05824 0.06924 0.05738 0.04759 0.03476 0.02941 0.03378 0.02521 0.0225 0.01076 0.00545 0.00156 0.0032 0 0 0 0 + 1977 1 3 2 0 0 0 200 0.00826 0.01119 0.00883 0.01951 0.03371 0.06967 0.07991 0.0704 0.04434 0.04203 0.03962 0.03103 0.01504 0.01006 0.00333 0.00453 0 0 0 0 + 1978 1 3 2 0 0 0 200 0.0061 0.01111 0.01869 0.02009 0.02332 0.04185 0.09213 0.12133 0.07873 0.04417 0.02995 0.02681 0.01751 0.00895 0.00449 0.00738 0 0 0 0 + 1979 1 3 2 0 0 0 200 0.00979 0.00667 0.00959 0.01791 0.02392 0.02895 0.04936 0.08023 0.09823 0.09691 0.05231 0.02985 0.02374 0.01009 0.00388 0.00579 0 0 0 0 + 1980 1 3 2 0 0 0 200 0.00515 0.0223 0.03324 0.02637 0.06062 0.08389 0.04983 0.055 0.05537 0.04177 0.03098 0.01355 0.01011 0.00621 0.00361 0.00202 0 0 0 0 + 1981 1 3 2 0 0 0 200 0.04661 0.02629 0.01855 0.02254 0.03911 0.04364 0.04209 0.0438 0.05581 0.06796 0.06691 0.04072 0.02115 0.01261 0.00301 0.00313 0 0 0 0 + 1982 1 3 2 0 0 0 200 0.05357 0.09537 0.06029 0.03784 0.04226 0.04818 0.03978 0.02321 0.01896 0.02571 0.02813 0.02027 0.01141 0.00625 0.00238 0.00086 0 0 0 0 + 1983 1 3 2 0 0 0 200 0.01741 0.0383 0.04749 0.06292 0.06466 0.03981 0.03406 0.01518 0.01068 0.00422 0.00904 0.00563 0.00605 0.00222 0.00129 0 0 0 0 0 + 1984 1 3 2 0 0 0 200 0.01229 0.05937 0.13213 0.12041 0.06624 0.03177 0.01564 0.00745 0.00409 0.00158 0.00031 0.00044 0.0001 0.00014 0.00002 0 0 0 0 0 + 1985 1 3 2 0 0 0 200 0.00086 0.01548 0.03765 0.05212 0.0643 0.05553 0.05156 0.03973 0.01606 0.00681 0 0 0.00149 0 0 0 0 0 0 0 + 1986 1 3 2 0 0 0 200 0.01237 0.02244 0.03547 0.02742 0.02628 0.03133 0.03617 0.03878 0.0274 0.01125 0.00715 0.00079 0 0 0.00076 0 0 0 0 0 + 1987 1 3 2 0 0 0 200 0.00134 0.01191 0.05107 0.08877 0.07579 0.04682 0.04501 0.05784 0.04186 0.02982 0.01808 0.00781 0.00185 0.00041 0 0 0 0 0 0 + 1988 1 3 2 0 0 0 200 0.00059 0.00766 0.00646 0.00618 0.01397 0.06959 0.09121 0.09804 0.07011 0.06092 0.04076 0.0184 0.00772 0.00767 0 0 0 0 0 0 + 1989 1 3 2 0 0 0 200 0.0015 0 0.00165 0.00775 0.02771 0.06879 0.06155 0.06435 0.05136 0.0367 0.02865 0.01741 0.00523 0.00405 0 0.00009 0 0 0 0 + 1990 1 3 2 0 0 0 200 0.00421 0.00542 0.02448 0.05339 0.05461 0.00738 0.02722 0.06038 0.07596 0.07194 0.06366 0.04198 0.02071 0.00609 0.00386 0.00387 0 0 0 0 + 1991 1 3 2 0 0 0 200 0.00406 0.01126 0.01915 0.03128 0.02134 0.0337 0.03354 0.0303 0.03586 0.03225 0.02769 0.0422 0.02274 0.01081 0.00674 0.00263 0 0 0 0 + 1992 1 3 2 0 0 0 200 0 0.00534 0.00737 0.01974 0.03642 0.04139 0.06251 0.04481 0.03529 0.02733 0.04503 0.04068 0.02651 0.02118 0.01619 0.01224 0 0 0 0 + 1993 1 3 2 0 0 0 200 0.00652 0.00796 0.01742 0.00845 0.01303 0.0247 0.04349 0.06393 0.06356 0.02673 0.02981 0.02663 0.02696 0.04427 0.01746 0.02183 0 0 0 0 + 1994 1 3 2 0 0 0 200 0 0.0016 0.00443 0.00296 0.01685 0.00917 0.0124 0.02131 0.04312 0.0416 0.03619 0.02802 0.03953 0.04689 0.02916 0.03206 0 0 0 0 + 1995 1 3 2 0 0 0 200 0.02942 0.04821 0.03155 0.01453 0.01391 0.01824 0.01628 0.02535 0.02343 0.03343 0.02724 0.02335 0.02398 0.0145 0.02031 0.01547 0 0 0 0 + 1996 1 3 2 0 0 0 200 0.02595 0.02186 0.04362 0.0794 0.07958 0.04357 0.02255 0.02176 0.02451 0.02017 0.01611 0.02847 0.02443 0.01563 0.00871 0.02361 0 0 0 0 + 1997 1 3 2 0 0 0 200 0.00043 0.00367 0.00162 0.00201 0.0146 0.07907 0.09694 0.06164 0.02119 0.01367 0.00948 0.01455 0.01427 0.01092 0.00836 0.02076 0 0 0 0 + 1998 1 3 2 0 0 0 200 0.0145 0.0196 0.01006 0.00876 0.01112 0.01163 0.03034 0.10415 0.11502 0.05893 0.03058 0.02523 0.02254 0.02353 0.02321 0.03365 0 0 0 0 + 1999 1 3 2 0 0 0 200 0.0243 0.01694 0.0125 0.01147 0.00435 0.00547 0.00924 0.01639 0.05112 0.07986 0.05821 0.03575 0.03393 0.01986 0.01225 0.0268 0 0 0 0 + 2000 1 3 2 0 0 0 200 0.00174 0.00673 0.02683 0.04024 0.03574 0.02719 0.02547 0.02268 0.03591 0.05249 0.06775 0.06047 0.04205 0.02091 0.01677 0.04352 0 0 0 0 + 2001 1 3 2 0 0 0 200 0.0056 0.01683 0.01951 0.01361 0.02585 0.05984 0.07787 0.05792 0.03945 0.03981 0.02909 0.06914 0.056 0.02621 0.01028 0.02048 0 0 0 0 + 2002 1 3 2 0 0 0 200 0.05063 0.07685 0.04852 0.02466 0.02215 0.01761 0.02247 0.05199 0.0399 0.02964 0.0163 0.02059 0.02046 0.02206 0.00712 0.0136 0 0 0 0 + 2003 1 3 2 0 0 0 200 0.01765 0.00633 0.01547 0.03393 0.04499 0.04991 0.02591 0.03122 0.03807 0.05789 0.05706 0.03868 0.02395 0.02881 0.02356 0.03786 0 0 0 0 + 2004 1 3 2 0 0 0 200 0.03521 0.04131 0.02444 0.01455 0.02211 0.03202 0.04847 0.05039 0.03417 0.02504 0.02492 0.02855 0.02271 0.02044 0.01579 0.02838 0 0 0 0 + 2005 1 3 2 0 0 0 200 0.04054 0.0561 0.04573 0.01155 0.00988 0.0336 0.03861 0.05206 0.05668 0.04675 0.03355 0.03825 0.03468 0.02272 0.01648 0.02455 0 0 0 0 + 2006 1 3 2 0 0 0 200 0.0143 0.01389 0.01982 0.04253 0.06161 0.04627 0.02545 0.02591 0.04813 0.06561 0.06191 0.0415 0.03015 0.03523 0.01667 0.01864 0 0 0 0 + 2007 1 3 2 0 0 0 200 0.00152 0.00228 0.00642 0.00783 0.01548 0.03569 0.05746 0.05611 0.03252 0.05702 0.06142 0.06418 0.04593 0.03432 0.02105 0.0323 0 0 0 0 + 2008 1 3 2 0 0 0 200 0 0.00256 0.00517 0.01305 0.01121 0.0161 0.02938 0.05671 0.07231 0.06068 0.06833 0.07969 0.07628 0.04659 0.02644 0.0224 0 0 0 0 + 2009 1 3 2 0 0 0 200 0.00046 0.0019 0.00504 0.00551 0.00817 0.0122 0.02058 0.04661 0.0657 0.08682 0.06453 0.06031 0.05223 0.07044 0.05132 0.04699 0 0 0 0 + 2010 1 3 2 0 0 0 200 0.00184 0.00058 0.00374 0.00481 0.00686 0.01164 0.02132 0.03646 0.05652 0.09273 0.09553 0.07009 0.0509 0.04972 0.05077 0.05456 0 0 0 0 + 2011 1 3 2 0 0 0 200 0.00576 0.00845 0.0092 0.01413 0.02844 0.03101 0.03837 0.04841 0.02992 0.05297 0.06375 0.09059 0.0635 0.05717 0.04306 0.07101 0 0 0 0 + 2012 1 3 2 0 0 0 200 0.02925 0.01803 0.0191 0.02495 0.02805 0.04611 0.03514 0.02198 0.03313 0.03551 0.03653 0.04609 0.06625 0.05206 0.04621 0.06328 0 0 0 0 + 2013 1 3 2 0 0 0 200 0.00081 0.00269 0.00929 0.01117 0.00669 0.01248 0.02018 0.03841 0.04287 0.04496 0.03041 0.03016 0.04553 0.04914 0.04049 0.07861 0 0 0 0 + 2014 1 3 2 0 0 0 200 0 0 0.00137 0.00443 0.01018 0.02893 0.02451 0.0358 0.05591 0.0863 0.06375 0.05107 0.03439 0.04466 0.05779 0.09622 0 0 0 0 +##Year, Seas, Fleet, Sex, Type, Shell, Maturity, Nsamp, DataVec + 2007 1 4 1 0 0 0 628 0.0045 0.0074 0.0103 0.0155 0.0198 0.0321 0.0532 0.0491 0.0443 0.0354 0.0268 0.0231 0.0236 0.0256 0.0223 0.032 0.0246 0.0218 0.017 0.0278 + 2008 1 4 1 0 0 0 907 0.0017 0.001 0.0093 0.0119 0.0175 0.0279 0.0267 0.0348 0.0428 0.0596 0.0581 0.0455 0.0371 0.0284 0.0218 0.0211 0.0156 0.0157 0.0202 0.0294 + 2007 1 4 2 0 0 0 623 0.0007 0.0016 0.0044 0.0198 0.0302 0.0705 0.0563 0.0345 0.0364 0.0493 0.0501 0.0448 0.0272 0.0183 0.0152 0.0243 0 0 0 0 + 2008 1 4 2 0 0 0 796 0.0004 0.0013 0.0088 0.0142 0.0286 0.0483 0.0754 0.0687 0.0463 0.0386 0.0411 0.0357 0.021 0.0179 0.0126 0.015 0 0 0 0 +## Growth data (increment) +# nobs_growth +40 +## Note SM used loewss regression for males BBRKC data +## and cubic spine to interpolate 3 sets of female BBRKC data +# MidPoint Sex Increment CV + 67.5 2 14.766667 0.2 + 72.5 2 13.333333 0.2 + 77.5 2 11.866667 0.2 + 82.5 2 10.233333 0.2 + 87.5 2 9 0.2 + 92.5 2 7.866667 0.2 + 97.5 2 7.066667 0.2 + 102.5 2 6.433333 0.2 + 107.5 2 5.933333 0.2 + 112.5 2 5.433333 0.2 + 117.5 2 4.933333 0.2 + 122.5 2 4.433333 0.2 + 127.5 2 3.933333 0.2 + 132.5 2 3.466667 0.2 + 137.5 2 3.033333 0.2 + 142.5 2 2.533333 0.2 + 147.5 2 2.033333 0.2 + 152.5 2 1.533333 0.2 + 157.5 2 1.033333 0.2 + 162.5 2 0.6 0.2 + 67.5 1 16.510674 0.2 + 72.5 1 16.454438 0.2 + 77.5 1 16.398615 0.2 + 82.5 1 16.343118 0.2 + 87.5 1 16.287715 0.2 + 92.5 1 16.23213 0.2 + 97.5 1 16.176368 0.2 + 102.5 1 16.123732 0.2 + 107.5 1 16.069744 0.2 + 112.5 1 16.013906 0.2 + 117.5 1 15.957058 0.2 + 122.5 1 15.900084 0.2 + 127.5 1 15.843143 0.2 + 132.5 1 15.786395 0.2 + 137.5 1 15.732966 0.2 + 142.5 1 15.68064 0.2 + 147.5 1 15.628775 0.2 + 152.5 1 15.577259 0.2 + 157.5 1 15.526092 0.2 + 162.5 1 15.475241 0.2 +## eof +9999 diff --git a/examples/bbrkc/bbrkc2013.ctl b/examples/bbrkc/bbrkc2013.ctl new file mode 100644 index 00000000..38ce66e7 --- /dev/null +++ b/examples/bbrkc/bbrkc2013.ctl @@ -0,0 +1,145 @@ +# Model 1, fixed multinomial sample sizes +# —————————————————————————————————————————————————————————————————————————————————————— # +# Controls for leading parameter vector theta +# LEGEND FOR PRIOR: +# 0 -> uniform +# 1 -> normal +# 2 -> lognormal +# 3 -> beta +# 4 -> gamma +# —————————————————————————————————————————————————————————————————————————————————————— # +# ntheta + 7 +# —————————————————————————————————————————————————————————————————————————————————————— # +# ival lb ub phz prior p1 p2 # parameter # +# —————————————————————————————————————————————————————————————————————————————————————— # + 0.18 0.01 1 -2 2 0.18 0.04 # M + 7.0 -10 20 -1 1 3.0 5.0 # logR0 + 7.0 -10 20 2 1 3.0 5.0 # logR1 + 7.0 -10 20 2 1 3.0 5.0 # logRbar + 72.5 55 100 -4 1 72.5 7.25 # Recruitment Expected Value + 0.40 0.1 5 -3 0 0.1 5 # Recruitment scale (variance component) + -0.51 -10 0.75 -4 0 -10 0.75 # ln(sigma_R) +## ———————————————————————————————————————————————————————————————————————————————————— ## + +## ———————————————————————————————————————————————————————————————————————————————————— ## +## GROWTH PARAM CONTROLS ## +# nGrwth +## ## +## Two lines for each parameter if split sex, one line if not ## +## ———————————————————————————————————————————————————————————————————————————————————— ## +# ival lb ub phz prior p1 p2 # parameter # +# —————————————————————————————————————————————————————————————————————————————————————— # + 17.5 10.0 30.0 -3 0 0.0 20.0 # alpha males or combined + 17.5 10.0 30.0 -3 0 0.0 20.0 # alpha + 0.10 0.0 0.5 -3 0 0.0 10.0 # beta males or combined + 0.10 0.0 0.5 -3 0 0.0 10.0 # beta + 16.0 05.0 30.0 -3 0 0.0 3.0 # gscale males or combined + 6.0 05.0 30.0 -3 0 0.0 3.0 # gscale + 115. 65.0 165.0 2 0 0.0 3.0 # molt_mu males or combined + 159. 65.0 165.0 -2 0 0.0 3.0 # molt_mu + 0.2 0.0 1.0 3 0 0.0 3.0 # molt_cv males or combined + 0.01 0.0 1.0 -3 0 0.0 3.0 # molt_cv +# ———————————————————————————————————————————————————————————————————————————————————— ## + +## ———————————————————————————————————————————————————————————————————————————————————— ## +## SELECTIVITY CONTROLS ## +## -Each gear must have a selectivity and a retention selectivity ## +## LEGEND sel_type:1=coefficients,2=logistic,3=logistic95 ## +## Index: use +ve for selectivity, -ve for retention +## ———————————————————————————————————————————————————————————————————————————————————— ## +## ivector for number of year blocks or nodes ## +## Gear-1 Gear-2 Gear-3 Gear-4 + 1 1 2 1 #Selectivity blocks + 1 1 1 1 #Retention blocks + 1 0 0 0 #male retention flag (0 -> no, 1 -> yes) + 0 0 0 0 #female retention flag (0 -> no, 1 -> yes) +## ———————————————————————————————————————————————————————————————————————————————————— ## +## sel sel sel sex size year phz start end ## +## Index type mu sd dep nodes nodes mirror lam1 lam2 lam3 | block block ## +## ———————————————————————————————————————————————————————————————————————————————————— ## +## Selectivity P(capture of all sizes) + 1 2 180 10 0 1 1 2 12.5 12.5 12.5 1975 2013 + 2 2 90 10 0 1 1 2 12.5 12.5 12.5 1975 2013 + 3 2 80 10 1 1 1 2 12.5 12.5 12.5 1975 1981 + 3 2 80 10 1 1 1 2 12.5 12.5 12.5 1982 2013 + 4 2 80 10 0 1 1 -2 12.5 12.5 12.5 1975 2013 +## ———————————————————————————————————————————————————————————————————————————————————— ## +## Retained + -1 2 135 2 0 1 1 -2 12.5 12.5 12.5 1975 2013 + -2 2 95 10 0 1 1 -2 12.5 12.5 12.5 1975 2013 + -3 2 90 10 0 1 1 -2 12.5 12.5 12.5 1975 2013 + -4 2 90 10 0 1 1 -2 12.5 12.5 12.5 1975 2013 +## ———————————————————————————————————————————————————————————————————————————————————— ## + +## ———————————————————————————————————————————————————————————————————————————————————— ## +## PRIORS FOR CATCHABILITY +## TYPE: 0 = UNINFORMATIVE, 1 - NORMAL (log-space), 2 = time-varying (nyi) +## ———————————————————————————————————————————————————————————————————————————————————— ## +## SURVEYS/INDICES ONLY +## NMFS BSFRF +## TYPE Mean_q SD_q + 1 0.896 0.03 + 0 0.00 0.00 +## ———————————————————————————————————————————————————————————————————————————————————— ## + +## ———————————————————————————————————————————————————————————————————————————————————— ## +## PENALTIES FOR AVERAGE FISHING MORTALITY RATE FOR EACH GEAR +## ———————————————————————————————————————————————————————————————————————————————————— ## +## Trap Trawl NMFS BSFRF +## Mean_F STD_PHZ1 STD_PHZ2 PHZ + 0.20 0.10 1.10 1 + 0.10 0.10 1.10 1 + 0.00 2.00 2.00 -1 + 0.00 2.00 2.00 -1 +## ———————————————————————————————————————————————————————————————————————————————————— ## + +## ———————————————————————————————————————————————————————————————————————————————————— ## +## OPTIONS FOR SIZE COMPOSTION DATA (COLUMN FOR EACH MATRIX) +## LIKELIHOOD OPTIONS: +## -1) multinomial with estimated/fixed sample size +## -2) robust_multi. Robust approximation to multinomial +## -3) logistic normal (NIY) +## -4) multivariate-t (NIY) +## AUTOTAIL COMPRESSION: +## - pmin is the cumulative proportion used in tail compression. +## ———————————————————————————————————————————————————————————————————————————————————— ## + 2 2 2 2 2 2 2 2 2 # Type of likelihood. + 0 0 0 0 0 0 0 0 0 # Auto tail compression (pmin) +-4 -4 -4 -4 -4 -4 -4 -4 -4 # Phz for estimating effective sample size (if appl.) +## ———————————————————————————————————————————————————————————————————————————————————— ## + +## ———————————————————————————————————————————————————————————————————————————————————— ## +## TIME VARYING NATURAL MORTALIIY RATES ## +## ———————————————————————————————————————————————————————————————————————————————————— ## +## TYPE: +## 0 = constant natural mortality +## 1 = Random walk (deviates constrained by variance in M) +## 2 = Cubic Spline (deviates constrained by nodes & node-placement) +## 3 = Blocked changes (deviates constrained by variance AT specific knots) + 3 +## Phase of estimation + 3 +## STDEV in m_dev for Random walk + 0.60 +## Number of nodes for cubic spline or number of step-changes for option 3 + 2 +## Year position of the knots (vector must be equal to the number of nodes) + 1980 1985 + + + +## ———————————————————————————————————————————————————————————————————————————————————— ## +## OTHER CONTROLS +## ———————————————————————————————————————————————————————————————————————————————————— ## + 3 # Estimated rec_dev phase + 0 # VERBOSE FLAG (0 = off, 1 = on, 2 = objective func) + 0 # INITIALIZE MODEL AT UNFISHED RECRUITS (0=FALSE, 1=TRUE) + 1984 # First year for average recruitment for Bspr calculation. + 2013 # Last year for average recruitment for Bspr calculation. + 0.35 # Target SPR ratio for Bmsy proxy. + 1 # Gear index for SPR calculations (i.e., directed fishery). + 1 # Lambda (proportion of mature male biomass for SPR reference points.) + 1 # Use empirical molt increment data (0=FALSE, 1=TRUE) +## EOF +9999 diff --git a/examples/bbrkc/bbrkc2013.dat b/examples/bbrkc/bbrkc2013.dat new file mode 100644 index 00000000..802e496a --- /dev/null +++ b/examples/bbrkc/bbrkc2013.dat @@ -0,0 +1,662 @@ +#======================================================================================================== +# Gmacs Main Data File Version 1.1: BBRKC Example +# Fisheries: 1 Pot Fishery, 2 Pot Discard, 3 Trawl by-catch +# Surveys: 1 NMFS Trawl Survey, 2 BSFRF Survey +#======================================================================================================== + +1975 # Start year +2013 # End year +1 # Time-step (years) + +4 # Number of distinct data groups (among fishing fleets and surveys) + +2 # Number of sexes +2 # Number of shell condition types +1 # Number of maturity types +20 # Number of size-classes in the model +#20 # Number of size-classes in the data + +# size_breaks (a vector giving the break points between size intervals, dim=nclass+1) +65 70 75 80 85 90 95 100 105 110 115 120 125 130 135 140 145 150 155 160 165 + +# weight-at-length allometry w_l = a•l^b +#a=0.003593,b=2.666076 female > 89mm +#a=0.000408,b=3.127956 female < 90 new shell +#a=0.000403, b=3.141334 male new shell +## a (male, female) +4.03e-7 4.08e-7 +## b (male, female) +3.141334 3.127956 + +# Male mature weight-at-length (weight * proportion mature) +0 0 0 0 0 0 0 0 0 0 0 1.432 1.625 1.835 2.063 2.31 2.576 2.862 3.169 3.7 +# Proportion mature by sex. +0 0 0 0 0 0 0 0 0 0 0 1 1 1 1 1 1 1 1 1 +0 0 0 0 0 0 0 0 0 0 0 1 1 1 1 1 1 1 1 1 + +# Fishing fleet names (delimited with ":" no spaces in names) +Pot_Fishery:Trawl_Bycatch + +# Survey names (delimited with ":" no spaces in names) +NMFS_Trawl:BSFRF + +#116 # Number of lines of catch data to read +4 # Number of catch data frames +# Number of rows in each data frame. +37 21 21 37 +#0.5 # Time between survey and fishery +## ———————————————————————————————————————————————————————————————————————————————————— ## +## CATCH DATA +## Type of catch: 1 = retained, 2 = discard, 3 = +## Units of catch: 1 = biomass, 2 = numbers +## for BBRKC Units are in 1000 mt for landed & million crabs for discards. +## ———————————————————————————————————————————————————————————————————————————————————— ## +## year seas fleet sex obs cv type units mult effort discard_mortality +## Male Retained + 1975 1 1 1 23.287794 0.05 1 1 1 0 0 + 1976 1 1 1 29.001814 0.05 1 1 1 0 0 + 1977 1 1 1 31.745871 0.05 1 1 1 0 0 + 1978 1 1 1 39.754219 0.05 1 1 1 0 0 + 1979 1 1 1 48.923820 0.05 1 1 1 0 0 + 1980 1 1 1 58.960299 0.05 1 1 1 0 0 + 1981 1 1 1 15.241107 0.05 1 1 1 0 0 + 1982 1 1 1 1.361705 0.05 1 1 1 0 0 + 1984 1 1 1 1.897640 0.05 1 1 1 0 0 + 1985 1 1 1 1.894283 0.05 1 1 1 0 0 + 1986 1 1 1 5.169646 0.05 1 1 1 0 0 + 1987 1 1 1 5.575816 0.05 1 1 1 0 0 + 1988 1 1 1 3.351996 0.05 1 1 1 0 0 + 1989 1 1 1 4.657350 0.05 1 1 1 0 0 + 1990 1 1 1 9.275408 0.05 1 1 1 0 0 + 1991 1 1 1 7.887477 0.05 1 1 1 0 0 + 1992 1 1 1 3.682849 0.05 1 1 1 0 0 + 1993 1 1 1 6.661524 0.05 1 1 1 0 0 + 1994 1 1 1 0.042196 0.05 1 1 1 0 0 + 1995 1 1 1 0.036297 0.05 1 1 1 0 0 + 1996 1 1 1 3.862976 0.05 1 1 1 0 0 + 1997 1 1 1 4.043284 0.05 1 1 1 0 0 + 1998 1 1 1 6.781306 0.05 1 1 1 0 0 + 1999 1 1 1 5.379310 0.05 1 1 1 0 0 + 2000 1 1 1 3.739110 0.05 1 1 1 0 0 + 2001 1 1 1 3.867059 0.05 1 1 1 0 0 + 2002 1 1 1 4.385662 0.05 1 1 1 0 0 + 2003 1 1 1 7.137477 0.05 1 1 1 0 0 + 2004 1 1 1 7.008620 0.05 1 1 1 0 0 + 2005 1 1 1 8.401996 0.05 1 1 1 0 0 + 2006 1 1 1 7.145190 0.05 1 1 1 0 0 + 2007 1 1 1 9.306578 0.05 1 1 1 0 0 + 2008 1 1 1 9.218675 0.05 1 1 1 0 0 + 2009 1 1 1 7.274523 0.05 1 1 1 0 0 + 2010 1 1 1 6.763439 0.05 1 1 1 0 0 + 2011 1 1 1 3.608112 0.05 1 1 1 0 0 + 2012 1 1 1 3.622754 0.05 1 1 1 0 0 +## Male discards Pot fishery + 1990 1 1 1 1.718800 0.05 2 2 1 0 0.20 + 1991 1 1 1 1.453700 0.05 2 2 1 0 0.20 + 1992 1 1 1 2.305600 0.05 2 2 1 0 0.20 + 1993 1 1 1 2.688000 0.05 2 2 1 0 0.20 + 1996 1 1 1 0.595000 0.05 2 2 1 0 0.20 + 1997 1 1 1 0.910000 0.05 2 2 1 0 0.20 + 1998 1 1 1 3.173000 0.05 2 2 1 0 0.20 + 1999 1 1 1 0.922000 0.05 2 2 1 0 0.20 + 2000 1 1 1 1.393000 0.05 2 2 1 0 0.20 + 2001 1 1 1 1.623500 0.05 2 2 1 0 0.20 + 2002 1 1 1 1.527000 0.05 2 2 1 0 0.20 + 2003 1 1 1 3.617000 0.05 2 2 1 0 0.20 + 2004 1 1 1 1.539000 0.05 2 2 1 0 0.20 + 2005 1 1 1 3.792300 0.05 2 2 1 0 0.20 + 2006 1 1 1 1.832000 0.05 2 2 1 0 0.20 + 2007 1 1 1 3.619800 0.05 2 2 1 0 0.20 + 2008 1 1 1 3.786757 0.05 2 2 1 0 0.20 + 2009 1 1 1 2.782675 0.05 2 2 1 0 0.20 + 2010 1 1 1 2.480059 0.05 2 2 1 0 0.20 + 2011 1 1 1 1.279960 0.05 2 2 1 0 0.20 + 2012 1 1 1 0.640960 0.05 2 2 1 0 0.20 +## Female discards Pot fishery + 1990 1 1 2 2.670800 0.05 2 2 1 0 0.20 + 1991 1 1 2 0.484600 0.05 2 2 1 0 0.20 + 1992 1 1 2 2.408600 0.05 2 2 1 0 0.20 + 1993 1 1 2 2.814500 0.05 2 2 1 0 0.20 + 1996 1 1 2 0.010000 0.05 2 2 1 0 0.20 + 1997 1 1 2 0.075000 0.05 2 2 1 0 0.20 + 1998 1 1 2 3.896500 0.05 2 2 1 0 0.20 + 1999 1 1 2 0.030300 0.05 2 2 1 0 0.20 + 2000 1 1 2 0.304000 0.05 2 2 1 0 0.20 + 2001 1 1 2 0.786100 0.05 2 2 1 0 0.20 + 2002 1 1 2 0.047600 0.05 2 2 1 0 0.20 + 2003 1 1 2 2.191200 0.05 2 2 1 0 0.20 + 2004 1 1 2 0.932000 0.05 2 2 1 0 0.20 + 2005 1 1 2 2.038700 0.05 2 2 1 0 0.20 + 2006 1 1 2 0.222200 0.05 2 2 1 0 0.20 + 2007 1 1 2 0.833890 0.05 2 2 1 0 0.20 + 2008 1 1 2 0.666098 0.05 2 2 1 0 0.20 + 2009 1 1 2 0.332340 0.05 2 2 1 0 0.20 + 2010 1 1 2 0.477993 0.05 2 2 1 0 0.20 + 2011 1 1 2 0.115860 0.05 2 2 1 0 0.20 + 2012 1 1 2 0.049933 0.05 2 2 1 0 0.20 +## Trawl fishery discards + 1976 1 2 0 0.384600 0.05 2 2 1 0 0.80 + 1977 1 2 0 0.787700 0.05 2 2 1 0 0.80 + 1978 1 2 0 0.646500 0.05 2 2 1 0 0.80 + 1979 1 2 0 0.736200 0.05 2 2 1 0 0.80 + 1980 1 2 0 1.141300 0.05 2 2 1 0 0.80 + 1981 1 2 0 0.267100 0.05 2 2 1 0 0.80 + 1982 1 2 0 0.785400 0.05 2 2 1 0 0.80 + 1983 1 2 0 0.492800 0.05 2 2 1 0 0.80 + 1984 1 2 0 1.168200 0.05 2 2 1 0 0.80 + 1985 1 2 0 0.274700 0.05 2 2 1 0 0.80 + 1986 1 2 0 0.159300 0.05 2 2 1 0 0.80 + 1987 1 2 0 0.124500 0.05 2 2 1 0 0.80 + 1988 1 2 0 0.430300 0.05 2 2 1 0 0.80 + 1989 1 2 0 0.109200 0.05 2 2 1 0 0.80 + 1990 1 2 0 0.171800 0.05 2 2 1 0 0.80 + 1991 1 2 0 0.183500 0.05 2 2 1 0 0.80 + 1992 1 2 0 0.248100 0.05 2 2 1 0 0.80 + 1993 1 2 0 0.281000 0.05 2 2 1 0 0.80 + 1994 1 2 0 0.048200 0.05 2 2 1 0 0.80 + 1995 1 2 0 0.106600 0.05 2 2 1 0 0.80 + 1996 1 2 0 0.076300 0.05 2 2 1 0 0.80 + 1997 1 2 0 0.049000 0.05 2 2 1 0 0.80 + 1998 1 2 0 0.093700 0.05 2 2 1 0 0.80 + 1999 1 2 0 0.110500 0.05 2 2 1 0 0.80 + 2000 1 2 0 0.058600 0.05 2 2 1 0 0.80 + 2001 1 2 0 0.089955 0.05 2 2 1 0 0.80 + 2002 1 2 0 0.076302 0.05 2 2 1 0 0.80 + 2003 1 2 0 0.105493 0.05 2 2 1 0 0.80 + 2004 1 2 0 0.075107 0.05 2 2 1 0 0.80 + 2005 1 2 0 0.096834 0.05 2 2 1 0 0.80 + 2006 1 2 0 0.075290 0.05 2 2 1 0 0.80 + 2007 1 2 0 0.086417 0.05 2 2 1 0 0.80 + 2008 1 2 0 0.093077 0.05 2 2 1 0 0.80 + 2009 1 2 0 0.061900 0.05 2 2 1 0 0.80 + 2010 1 2 0 0.059390 0.05 2 2 1 0 0.80 + 2011 1 2 0 0.046370 0.05 2 2 1 0 0.80 + 2012 1 2 0 0.032770 0.05 2 2 1 0 0.80 + + +## ———————————————————————————————————————————————————————————————————————————————————— ## +## RELATIVE ABUNDANCE DATA +## Units of Abundance: 1 = biomass, 2 = numbers +## for BBRKC Units are in million crabs for Abundance. +## ———————————————————————————————————————————————————————————————————————————————————— ## +## Number of relative abundance indicies +2 +## Number of rows in each index +78 2 +# Survey data (abundance indices, units are millions of crabs) +# Year, Seas, Fleet, Sex, Abundance, CV units + 1975 1 3 1 146028 0.188 1 + 1976 1 3 1 200083 0.169 1 + 1977 1 3 1 237777 0.141 1 + 1978 1 3 1 203160 0.155 1 + 1979 1 3 1 160779 0.133 1 + 1980 1 3 1 164259 0.221 1 + 1981 1 3 1 64005 0.121 1 + 1982 1 3 1 72147.9 0.259 1 + 1983 1 3 1 35370.1 0.216 1 + 1984 1 3 1 82562.7 0.678 1 + 1985 1 3 1 27003.7 0.158 1 + 1986 1 3 1 40811.3 0.428 1 + 1987 1 3 1 46611.1 0.209 1 + 1988 1 3 1 34918.7 0.217 1 + 1989 1 3 1 48290.5 0.214 1 + 1990 1 3 1 36269.9 0.214 1 + 1991 1 3 1 70018.5 0.441 1 + 1992 1 3 1 25255.4 0.174 1 + 1993 1 3 1 36426.3 0.174 1 + 1994 1 3 1 23115.7 0.173 1 + 1995 1 3 1 27468.5 0.276 1 + 1996 1 3 1 27078.4 0.201 1 + 1997 1 3 1 60276.3 0.263 1 + 1998 1 3 1 46352.9 0.178 1 + 1999 1 3 1 40696.1 0.161 1 + 2000 1 3 1 39292.6 0.178 1 + 2001 1 3 1 28161.3 0.178 1 + 2002 1 3 1 45261.7 0.203 1 + 2003 1 3 1 55153 0.164 1 + 2004 1 3 1 60162.2 0.163 1 + 2005 1 3 1 55066.5 0.173 1 + 2006 1 3 1 51211.5 0.122 1 + 2007 1 3 1 58063.2 0.135 1 + 2008 1 3 1 55233.2 0.104 1 + 2009 1 3 1 43948.1 0.287 1 + 2010 1 3 1 36353.3 0.15 1 + 2011 1 3 1 25064 0.141 1 + 2012 1 3 1 30605.4 0.162 1 + 2013 1 3 1 39542.5 0.245 1 + 1975 1 3 2 73608.4 0.188 1 + 1976 1 3 2 101371 0.169 1 + 1977 1 3 2 142574 0.141 1 + 1978 1 3 2 146277 0.155 1 + 1979 1 3 2 103468 0.133 1 + 1980 1 3 2 80534.1 0.221 1 + 1981 1 3 2 58494.2 0.121 1 + 1982 1 3 2 69462.2 0.259 1 + 1983 1 3 2 13951.7 0.216 1 + 1984 1 3 2 52031.8 0.678 1 + 1985 1 3 2 7276.89 0.158 1 + 1986 1 3 2 6992.98 0.428 1 + 1987 1 3 2 22323.8 0.209 1 + 1988 1 3 2 19137.8 0.217 1 + 1989 1 3 2 13208 0.214 1 + 1990 1 3 2 20459.9 0.214 1 + 1991 1 3 2 17480.1 0.441 1 + 1992 1 3 2 12154.8 0.174 1 + 1993 1 3 2 17471.5 0.174 1 + 1994 1 3 2 8983.35 0.173 1 + 1995 1 3 2 10647.4 0.276 1 + 1996 1 3 2 17244.3 0.201 1 + 1997 1 3 2 24376.3 0.263 1 + 1998 1 3 2 38201.5 0.178 1 + 1999 1 3 2 20181.4 0.161 1 + 2000 1 3 2 29136.8 0.178 1 + 2001 1 3 2 24639.4 0.178 1 + 2002 1 3 2 24011 0.203 1 + 2003 1 3 2 41627.7 0.164 1 + 2004 1 3 2 36067.9 0.163 1 + 2005 1 3 2 51491.2 0.173 1 + 2006 1 3 2 43702.3 0.122 1 + 2007 1 3 2 45738.1 0.135 1 + 2008 1 3 2 56763 0.104 1 + 2009 1 3 2 47835.9 0.287 1 + 2010 1 3 2 42078.2 0.15 1 + 2011 1 3 2 39490.9 0.141 1 + 2012 1 3 2 30195.7 0.162 1 + 2013 1 3 2 22411.8 0.245 1 + 2007 1 4 0 102.9622 0.1164 1 + 2008 1 4 0 83.5895 0.0939 1 + +## # Discard mortalities per fishery +## 1.0 # Pot Landings (Retained) +## 1.0 # Pot Discards +## 0.8 # Trawl Bycatch +## +## # Fishery high-grading rates (rescaling of retention values (retention maximum of 1 becomes 1-hg) +## # 75 76 77 78 79 80 81 82 83 84 85 86 87 88 89 90 91 92 93 94 95 96 97 98 99 00 01 02 03 04 2005 2006 2007 2008 09 10 11 12 13 +## 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.2785 0.0440 0.0197 0.019875 0 0 0 0 0 +## +## # Fishery timing (as fraction of year) +## # 1975 1976 1977 1978 1979 1980 1981 1982 1983 1984 1985 1986 1987 1988 1989 1990 1991 1992 1993 1994 1995 1996 1997 1998 1999 2000 2001 2002 2003 2004 2005 2006 2007 2008 2009 2010 2011 2012 2013 +## 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 +## 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 +## +## # Effort (by fishery) +## # 1975 1976 1977 1978 1979 1980 1981 1982 1983 1984 1985 1986 1987 1988 1989 1990 1991 1992 1993 1994 1995 1996 1997 1998 1999 2000 2001 2002 2003 2004 2005 2006 2007 2008 2009 2010 2011 2012 2013 +## 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 0.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 0.0 0.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 +## 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 +## +## # Use effort to compute F (by fishery) +## 0 1900 1900 1900 1900 +## 0 1900 1900 1900 1900 + +## Number of length frequency matrixes +9 +## Number of rows in each matrix +35 21 21 36 36 +39 39 39 4 +## Number of bins in each matrix (columns of size data) +20 20 20 20 20 +20 20 20 20 + +## SIZE COMPOSITION DATA FOR ALL FLEETS +## ———————————————————————————————————————————————————————————————————————————————————— ## +## SIZE COMP LEGEND +## Sex: 1 = male, 2 = female, 0 = both sexes combined +## Type of composition: 1 = retained, 2 = discard, 0 = selectivity +## Maturity state: 1 = immature, 2 = mature, 0 = both states combined +## Shell condition: 1 = new shell, 2 = old shell, 0 = both shell types combined +## ———————————————————————————————————————————————————————————————————————————————————— ## +##length proportions of retained males +##Year, Seas, Fleet, Sex, Type, Shell, Maturity, Nsamp, DataVec + 1975 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0 0.0071 0.0741 0.1721 0.2239 0.2122 0.1464 0.0858 0.0785 + 1976 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0 0.0016 0.029 0.1418 0.2316 0.2199 0.1635 0.1071 0.1055 + 1977 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0 0.0017 0.0192 0.1382 0.2442 0.2226 0.1605 0.104 0.1096 + 1978 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0 0.0012 0.0209 0.1441 0.2588 0.2401 0.1673 0.0966 0.0711 + 1979 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0 0.0013 0.0119 0.0747 0.1649 0.1998 0.2004 0.1556 0.1914 + 1980 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0 0.0008 0.0138 0.0919 0.1771 0.195 0.1792 0.1404 0.2019 + 1981 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0 0.0006 0.0225 0.1164 0.1743 0.1711 0.1584 0.1284 0.2283 + 1982 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0 0 0.0544 0.2576 0.2802 0.1667 0.0837 0.0508 0.1067 + 1984 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0.0003 0.0023 0.0654 0.311 0.3135 0.1763 0.0846 0.0321 0.0145 + 1985 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0.0005 0.0044 0.079 0.2869 0.3098 0.1898 0.086 0.0306 0.0129 + 1986 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0 0.0016 0.0531 0.2613 0.3289 0.2084 0.0978 0.0352 0.0137 + 1987 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0 0.0013 0.0284 0.1895 0.3045 0.2522 0.1421 0.0565 0.0255 + 1988 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0 0 0.0202 0.1294 0.2646 0.2471 0.1876 0.1033 0.0477 + 1989 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0 0.0005 0.0187 0.1211 0.2209 0.219 0.1908 0.1197 0.1094 + 1990 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0.0003 0 0.0146 0.0887 0.1801 0.1707 0.1728 0.1431 0.2297 + 1991 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0.0001 0.0005 0.0141 0.0848 0.1651 0.179 0.1739 0.1432 0.2392 + 1992 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0.0003 0.0002 0.0005 0.0095 0.0638 0.1317 0.1673 0.1747 0.1636 0.2886 + 1993 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0 0.0014 0.0138 0.094 0.1789 0.1739 0.1596 0.1331 0.2453 + 1996 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0.0006 0.0006 0.0129 0.0779 0.1407 0.162 0.1771 0.1671 0.2612 + 1997 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0.0004 0.0003 0.0138 0.0899 0.1486 0.1603 0.1699 0.1588 0.258 + 1998 1 1 1 1 0 0 100 0 0 0 0 0 0 0.0001 0.0001 0.0001 0.0001 0.0004 0.0002 0.0008 0.0225 0.1187 0.1596 0.149 0.1432 0.1394 0.266 + 1999 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0.0001 0 0.0001 0.0147 0.1313 0.2575 0.2292 0.1624 0.0961 0.1087 + 2000 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0.0001 0.0001 0 0.0001 0.0003 0.0111 0.0931 0.1945 0.2111 0.1822 0.1247 0.1826 + 2001 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0.0001 0.0001 0.0001 0.0002 0.0002 0.0012 0.0181 0.0836 0.1681 0.1986 0.1953 0.1506 0.1838 + 2002 1 1 1 1 0 0 100 0 0 0 0 0 0 0.0001 0 0.0001 0.0001 0.0001 0 0.0002 0.0151 0.108 0.1884 0.1915 0.1683 0.1334 0.1948 + 2003 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0.0001 0.0001 0.0002 0.0009 0.0243 0.1464 0.232 0.1871 0.1497 0.0994 0.1597 + 2004 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0 0.0002 0.0064 0.0514 0.1302 0.1702 0.1971 0.1632 0.2812 + 2005 1 1 1 1 0 0 100 0 0 0 0 0 0 0.0001 0 0 0 0.0001 0.0001 0.0008 0.015 0.0859 0.1543 0.1661 0.1783 0.1516 0.2475 + 2006 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0.0001 0.0001 0.0004 0.0102 0.0739 0.1905 0.2203 0.1887 0.137 0.1787 + 2007 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0.0002 0.0003 0.0067 0.0871 0.1833 0.1934 0.1846 0.1472 0.1973 + 2008 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0.0001 0.0002 0.01 0.0746 0.1457 0.1619 0.179 0.1625 0.2659 + 2009 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0 0.0002 0.0108 0.1152 0.2215 0.1968 0.1588 0.1084 0.1882 + 2010 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0 0.0003 0.0091 0.0986 0.2244 0.2238 0.1861 0.1144 0.1433 + 2011 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0.0003 0.0001 0.0003 0.0114 0.118 0.2436 0.2292 0.1725 0.1077 0.1169 + 2012 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0.0001 0 0.0001 0 0 0.0044 0.0499 0.1249 0.173 0.1886 0.1654 0.2937 +##length proportions of pot discarded males +##Year, Seas, Fleet, Sex, Type, Shell, Maturity, Nsamp, DataVec + 1990 1 1 1 2 0 0 100 0.0011 0 0.0011 0.008 0.0046 0.0126 0.0069 0.0378 0.0504 0.0767 0.1226 0.1523 0.1867 0.244 0.0859 0.0092 0 0 0 0 + 1991 1 1 1 2 0 0 100 0.0033 0.0101 0.0197 0.0214 0.0242 0.0394 0.0326 0.063 0.0624 0.0692 0.0641 0.1125 0.1586 0.2154 0.0939 0.0101 0 0 0 0 + 1992 1 1 1 2 0 0 100 0 0.0009 0.0012 0.0111 0.0222 0.0549 0.0869 0.1143 0.1183 0.123 0.118 0.1251 0.1112 0.0807 0.0293 0.0028 0 0 0 0 + 1993 1 1 1 2 0 0 100 0.0019 0.0045 0.0057 0.005 0.0062 0.0122 0.0312 0.0571 0.0778 0.108 0.1334 0.1544 0.1518 0.1705 0.0747 0.0055 0 0 0 0 + 1996 1 1 1 2 0 0 100 0 0 0 0.0131 0.0524 0.083 0.0742 0.0306 0.048 0.0699 0.0611 0.1004 0.1485 0.2009 0.1048 0.0131 0 0 0 0 + 1997 1 1 1 2 0 0 100 0 0.0002 0.0005 0.0007 0.0015 0.0197 0.0553 0.109 0.1268 0.1304 0.1031 0.1002 0.1275 0.1424 0.0751 0.0076 0 0 0 0 + 1998 1 1 1 2 0 0 100 0.0002 0.0005 0.0008 0.0044 0.007 0.01 0.0104 0.0175 0.0391 0.097 0.1402 0.2062 0.2047 0.1811 0.0714 0.0097 0 0 0 0 + 1999 1 1 1 2 0 0 100 0 0 0 0.0086 0.0086 0.0029 0.0076 0.0086 0.0143 0.0286 0.063 0.126 0.2118 0.3244 0.188 0.0076 0 0 0 0 + 2000 1 1 1 2 0 0 100 0.0003 0.0051 0.0192 0.0483 0.0613 0.0576 0.0595 0.0581 0.0532 0.0558 0.0712 0.1059 0.1497 0.1554 0.0895 0.0097 0 0 0 0 + 2001 1 1 1 2 0 0 100 0.0016 0.0057 0.0093 0.0115 0.0155 0.0302 0.0568 0.0866 0.1009 0.1196 0.1239 0.1411 0.1319 0.1128 0.0481 0.0045 0 0 0 0 + 2002 1 1 1 2 0 0 100 0.0012 0.0061 0.006 0.0091 0.0065 0.0104 0.0133 0.0335 0.063 0.1142 0.1543 0.1705 0.1642 0.1582 0.0803 0.0093 0 0 0 0 + 2003 1 1 1 2 0 0 100 0.0081 0.0119 0.0146 0.0317 0.0552 0.0666 0.072 0.067 0.0642 0.0599 0.0655 0.0958 0.1322 0.1708 0.0781 0.0064 0 0 0 0 + 2004 1 1 1 2 0 0 100 0.0004 0.0074 0.0177 0.0403 0.051 0.0483 0.0615 0.1087 0.1384 0.1452 0.1102 0.0849 0.07 0.0688 0.0404 0.0059 0.0008 0 0 0 + 2005 1 1 1 2 0 0 100 0.0002 0.0008 0.0015 0.0029 0.0076 0.022 0.0343 0.0418 0.0454 0.0658 0.0956 0.1376 0.1381 0.1385 0.0729 0.0262 0.0246 0.0349 0.0345 0.075 + 2006 1 1 1 2 0 0 100 0.0003 0.0013 0.0044 0.015 0.0312 0.0377 0.0368 0.0346 0.0452 0.0766 0.0929 0.1144 0.1377 0.1764 0.1275 0.0284 0.0105 0.0085 0.0075 0.0132 + 2007 1 1 1 2 0 0 100 0.0012 0.0042 0.0068 0.0098 0.0171 0.0366 0.0658 0.085 0.0928 0.0857 0.0819 0.0987 0.1291 0.1651 0.0956 0.0126 0.0032 0.0028 0.0022 0.0037 + 2008 1 1 1 2 0 0 100 0.0001 0.0003 0.0012 0.0046 0.0108 0.0141 0.0159 0.0214 0.0441 0.0808 0.1269 0.1793 0.1988 0.1838 0.0983 0.0099 0.0014 0.0018 0.0018 0.0045 + 2009 1 1 1 2 0 0 100 0.0004 0.001 0.0018 0.0032 0.0041 0.0073 0.0178 0.0402 0.0631 0.0705 0.0798 0.118 0.1809 0.2413 0.1455 0.0149 0.0021 0.0016 0.0022 0.0043 + 2010 1 1 1 2 0 0 100 0.0007 0.0011 0.0025 0.0055 0.0085 0.0119 0.0148 0.0218 0.0341 0.0541 0.0962 0.1517 0.2017 0.2373 0.135 0.0137 0.0017 0.0018 0.0016 0.0042 + 2011 1 1 1 2 0 0 100 0.0017 0.0066 0.0112 0.0199 0.0204 0.0188 0.0272 0.0309 0.0409 0.056 0.0756 0.1176 0.1698 0.221 0.1565 0.018 0.0026 0.0017 0.0009 0.0025 + 2012 1 1 1 2 0 0 100 0.0006 0.0008 0.0024 0.0042 0.0111 0.0262 0.0416 0.0563 0.0534 0.057 0.0704 0.106 0.1521 0.2072 0.1468 0.0248 0.0054 0.0085 0.0069 0.0182 +##length proportions of pot discarded females +##Year, Seas, Fleet, Sex, Type, Shell, Maturity, Nsamp, DataVec + 1990 1 1 2 2 0 0 50 0 0.0014 0.0029 0.0029 0.0057 0.0072 0.0143 0.0672 0.1016 0.1731 0.1688 0.2132 0.1359 0.0715 0.0243 0.01 0 0 0 0 + 1991 1 1 2 2 0 0 50 0.0054 0.0239 0.0612 0.0957 0.133 0.1596 0.1223 0.0718 0.0691 0.0559 0.0691 0.0798 0.0346 0.0106 0.0053 0.0027 0 0 0 0 + 1992 1 1 2 2 0 0 50 0.0008 0.0013 0.0029 0.0176 0.0799 0.1757 0.1941 0.1694 0.0958 0.0816 0.0577 0.0406 0.0406 0.0259 0.0117 0.0046 0 0 0 0 + 1993 1 1 2 2 0 0 50 0.0015 0.0024 0.0044 0.0059 0.013 0.0326 0.1011 0.1597 0.1444 0.1137 0.0905 0.0853 0.0835 0.074 0.0434 0.0446 0 0 0 0 + 1996 1 1 2 2 0 0 50 0 0 0 0.0909 0.6364 0.2727 0 0 0 0 0 0 0 0 0 0 0 0 0 0 + 1997 1 1 2 2 0 0 50 0 0 0.0011 0.0011 0.0099 0.0265 0.0364 0.0464 0.0695 0.1391 0.1667 0.1435 0.117 0.1082 0.0607 0.074 0 0 0 0 + 1998 1 1 2 2 0 0 50 0.0002 0.0004 0.001 0.0026 0.0064 0.018 0.057 0.1813 0.2307 0.1527 0.0828 0.0855 0.0578 0.0514 0.0337 0.0386 0 0 0 0 + 1999 1 1 2 2 0 0 50 0 0 0 0.0278 0.0278 0.0278 0.0556 0 0 0.1111 0.1389 0.0833 0.1111 0.1111 0.0833 0.2222 0 0 0 0 + 2000 1 1 2 2 0 0 50 0 0.0175 0.1036 0.2234 0.2093 0.1319 0.0774 0.0323 0.0209 0.0316 0.0451 0.0518 0.0229 0.0141 0.0047 0.0135 0 0 0 0 + 2001 1 1 2 2 0 0 50 0.0027 0.005 0.0151 0.033 0.0588 0.0866 0.097 0.0866 0.0575 0.0525 0.0874 0.1392 0.1421 0.0649 0.0291 0.0426 0 0 0 0 + 2002 1 1 2 2 0 0 50 0.0258 0.1194 0.1452 0.1548 0.1161 0.0645 0.0258 0.0226 0.0548 0.0419 0.0355 0.0258 0.0323 0.0355 0.0323 0.0678 0 0 0 0 + 2003 1 1 2 2 0 0 50 0.0141 0.0187 0.0255 0.0719 0.1116 0.1157 0.0743 0.0476 0.0661 0.0902 0.1012 0.0628 0.0497 0.0504 0.046 0.054 0 0 0 0 + 2004 1 1 2 2 0 0 50 0.0005 0.0075 0.0306 0.0596 0.0754 0.09 0.1425 0.1333 0.0883 0.0484 0.0574 0.0584 0.0511 0.0394 0.0389 0.0788 0 0 0 0 + 2005 1 1 2 2 0 0 50 0.0004 0.0013 0.0022 0.005 0.0146 0.0499 0.0788 0.0931 0.1233 0.1211 0.0871 0.1021 0.0958 0.0885 0.0519 0.0848 0 0 0 0 + 2006 1 1 2 2 0 0 50 0.0003 0.0044 0.0248 0.1218 0.1937 0.1603 0.072 0.0558 0.0722 0.0778 0.0614 0.0401 0.034 0.0282 0.0199 0.0333 0 0 0 0 + 2007 1 1 2 2 0 0 50 0.003 0.0126 0.0214 0.0223 0.0436 0.0854 0.1105 0.0828 0.0558 0.0744 0.102 0.1165 0.0954 0.0684 0.0444 0.0614 0 0 0 0 + 2008 1 1 2 2 0 0 50 0.0004 0.0018 0.0097 0.0364 0.0768 0.0661 0.0469 0.0773 0.107 0.0868 0.0954 0.1265 0.1257 0.0672 0.0392 0.0369 0 0 0 0 + 2009 1 1 2 2 0 0 50 0.0037 0.008 0.01 0.0144 0.0164 0.0277 0.0647 0.0863 0.0803 0.0913 0.0858 0.09 0.1144 0.1308 0.088 0.0881 0 0 0 0 + 2010 1 1 2 2 0 0 50 0.0037 0.0051 0.0051 0.0199 0.0276 0.029 0.0271 0.0443 0.0882 0.1138 0.1322 0.1427 0.1007 0.0915 0.0879 0.0813 0 0 0 0 + 2011 1 1 2 2 0 0 50 0.0132 0.0373 0.0653 0.1089 0.0814 0.0734 0.0619 0.0436 0.0281 0.0373 0.0717 0.0896 0.0748 0.0587 0.061 0.0938 0 0 0 0 + 2012 1 1 2 2 0 0 50 0.0089 0.0107 0.0125 0.0339 0.0606 0.1159 0.0945 0.0392 0.0178 0.0125 0.041 0.0392 0.1658 0.1515 0.1105 0.0856 0 0 0 0 +#length proportions of trawl male bycatch +##Year, Seas, Fleet, Sex, Type, Shell, Maturity, Nsamp, DataVec + 1976 1 2 1 0 0 0 50 0 0 0 0 0 0.013 0.0087 0.0043 0.0216 0.0087 0.026 0.039 0.0433 0.0649 0.0996 0.0866 0.0736 0.0909 0.0649 0.1299 + 1977 1 2 1 0 0 0 50 0.0036 0.0009 0.0009 0.0009 0.0026 0.0035 0.0079 0.0097 0.0317 0.0485 0.0599 0.0996 0.1084 0.1251 0.104 0.1057 0.1004 0.0634 0.0326 0.0441 + 1978 1 2 1 0 0 0 50 0 0 0 0 0 0 0 0.0025 0.0012 0.0025 0.0149 0.0274 0.0511 0.0872 0.1245 0.1158 0.0797 0.0984 0.0672 0.188 + 1979 1 2 1 0 0 0 50 0.0178 0.0013 0.0025 0.0013 0.0025 0.0076 0.0038 0.0025 0.0013 0.0063 0.0051 0.0114 0.0228 0.0556 0.0582 0.0708 0.0898 0.086 0.0809 0.1858 + 1980 1 2 1 0 0 0 50 0.0531 0.0207 0.0096 0.0135 0.0142 0.0163 0.0274 0.0263 0.038 0.0375 0.0422 0.0394 0.0368 0.0377 0.0313 0.0231 0.0207 0.0142 0.0131 0.0265 + 1981 1 2 1 0 0 0 50 0.0262 0.0028 0.0045 0.0066 0.0112 0.0175 0.0279 0.0349 0.0386 0.0504 0.0434 0.048 0.0287 0.0334 0.0241 0.0212 0.0112 0.0064 0.0051 0.0087 + 1982 1 2 1 0 0 0 50 0.0701 0.0268 0.0247 0.0326 0.0356 0.0443 0.0409 0.0403 0.0401 0.0475 0.0426 0.0479 0.0405 0.0326 0.0218 0.0153 0.0084 0.0052 0.0038 0.0099 + 1983 1 2 1 0 0 0 50 0.0231 0.0214 0.0336 0.0344 0.0311 0.0319 0.0377 0.0445 0.0473 0.0471 0.0457 0.0437 0.0409 0.0414 0.0371 0.0283 0.0204 0.0129 0.0096 0.018 + 1984 1 2 1 0 0 0 50 0.0366 0.0156 0.0147 0.0199 0.027 0.0342 0.0399 0.0407 0.0431 0.0476 0.0511 0.0596 0.0594 0.0563 0.0473 0.0355 0.0264 0.017 0.0109 0.0146 + 1985 1 2 1 0 0 0 50 0.0051 0.0014 0.0034 0.0059 0.01 0.0164 0.0256 0.0396 0.0357 0.0446 0.0538 0.0636 0.0843 0.0862 0.0883 0.0843 0.0638 0.0455 0.0299 0.0578 + 1986 1 2 1 0 0 0 50 0.0139 0.0028 0.008 0.0106 0.0159 0.0199 0.0237 0.0263 0.0245 0.0316 0.0393 0.0532 0.0739 0.0772 0.0803 0.0706 0.0604 0.0396 0.0327 0.0401 + 1987 1 2 1 0 0 0 50 0.0017 0.0024 0.0056 0.0076 0.0115 0.017 0.0231 0.0293 0.0331 0.0349 0.0471 0.0506 0.0543 0.062 0.0646 0.0613 0.0581 0.0356 0.0231 0.0259 + 1988 1 2 1 0 0 0 50 0.0228 0.001 0.0013 0.0023 0.0045 0.0095 0.0156 0.0214 0.0251 0.028 0.0291 0.0333 0.039 0.0471 0.0604 0.0697 0.0768 0.0634 0.043 0.0393 + 1989 1 2 1 0 0 0 50 0.001 0.001 0.0012 0.0012 0.0024 0.0036 0.0084 0.0105 0.0153 0.0229 0.03 0.0473 0.0505 0.0613 0.0784 0.0849 0.0806 0.0772 0.0645 0.0919 + 1990 1 2 1 0 0 0 50 0.024 0.006 0.009 0.003 0.0105 0.0075 0.0299 0.0165 0.0329 0.0359 0.024 0.0314 0.0314 0.0434 0.0689 0.0749 0.0763 0.0644 0.0344 0.0689 + 1991 1 2 1 0 0 0 50 0.0481 0.0289 0.0225 0.0064 0.0225 0.0129 0.0161 0.0161 0.0386 0.0225 0.0418 0.0322 0.0322 0.0225 0.0322 0.074 0.0354 0.0514 0.0514 0.1479 + 1992 1 2 1 0 0 0 50 0 0 0 0 0 0.0068 0 0 0 0.0136 0.0169 0.0203 0.0407 0.0373 0.0407 0.0373 0.0271 0.0237 0.0068 0.0305 + 1994 1 2 1 0 0 0 50 0.0061 0.0061 0.0061 0.0076 0.0015 0 0 0.0015 0.0015 0.0031 0.0015 0.0031 0.0092 0.0137 0.0198 0.0427 0.0412 0.0534 0.0794 0.2885 + 1995 1 2 1 0 0 0 50 0.0193 0.0016 0.0082 0.0065 0.0033 0.0082 0.0163 0.0163 0.0098 0.0163 0.0147 0.0065 0.0114 0.0098 0.0098 0.0163 0.0245 0.0196 0.0033 0.0114 + 1996 1 2 1 0 0 0 50 0 0.0004 0.0011 0.0019 0.0088 0.0191 0.0314 0.0413 0.0452 0.0463 0.0459 0.0467 0.0387 0.0521 0.0333 0.0417 0.0379 0.0459 0.0448 0.1413 + 1997 1 2 1 0 0 0 50 0.0009 0.0009 0 0 0.0009 0.0009 0.0009 0.0044 0.0035 0.0185 0.0334 0.0439 0.0483 0.0501 0.0641 0.0571 0.0501 0.0545 0.0439 0.1344 + 1998 1 2 1 0 0 0 50 0.0023 0.0004 0.0011 0.0004 0.0004 0.0007 0.0026 0.0022 0.0056 0.0071 0.0161 0.0217 0.0446 0.067 0.076 0.0906 0.0869 0.0831 0.067 0.1476 + 1999 1 2 1 0 0 0 50 0.0054 0.0006 0.0006 0.0006 0.0012 0.0006 0.003 0.0018 0.0048 0.0083 0.0143 0.0386 0.0671 0.0837 0.1116 0.1099 0.095 0.0641 0.0523 0.0998 + 2000 1 2 1 0 0 0 50 0.0008 0 0.0005 0.0003 0.0005 0.0046 0.0065 0.0153 0.0243 0.0289 0.0289 0.0346 0.0376 0.0417 0.0444 0.0646 0.0777 0.0837 0.0733 0.2076 + 2001 1 2 1 0 0 0 50 0.0005 0.0002 0.001 0.0005 0.0025 0.0062 0.0064 0.0084 0.0155 0.0192 0.0236 0.0231 0.0266 0.0327 0.0396 0.0447 0.0595 0.058 0.0631 0.1994 + 2002 1 2 1 0 0 0 50 0.0006 0.0006 0.002 0.0068 0.009 0.0107 0.0121 0.0059 0.0059 0.0068 0.0121 0.0229 0.0274 0.0333 0.0503 0.0539 0.0553 0.0497 0.048 0.1081 + 2003 1 2 1 0 0 0 50 0.0017 0.0017 0.0068 0.0102 0.0255 0.0221 0.0272 0.0102 0.0051 0.017 0.0051 0.017 0.0187 0.0187 0.0408 0.0493 0.0425 0.0289 0.0255 0.1037 + 2004 1 2 1 0 0 0 50 0.0039 0.0039 0.0117 0.0039 0.0039 0.0117 0.035 0.0272 0.0233 0.0389 0.0233 0.0233 0.0117 0.0117 0.0233 0.0233 0.0739 0.0389 0.0389 0.1012 + 2005 1 2 1 0 0 0 50 0.0032 0 0.0097 0.0032 0.0032 0.0032 0.0032 0.0355 0.0194 0.0194 0.0323 0.0194 0.0484 0.0484 0.0194 0.0323 0.0516 0.0323 0.0323 0.1839 + 2006 1 2 1 0 0 0 50 0.0026 0.0026 0.0026 0.0078 0.0026 0.0156 0.0208 0.0234 0.0078 0.0442 0.0338 0.0571 0.0545 0.0494 0.0545 0.039 0.0416 0.026 0.0156 0.0623 + 2007 1 2 1 0 0 0 50 0 0 0 0.0002 0.0006 0.0012 0.0033 0.007 0.0107 0.0146 0.0173 0.0206 0.0177 0.0278 0.0358 0.0366 0.0379 0.0362 0.0426 0.0968 + 2008 1 2 1 0 0 0 50 0 0 0.0012 0.0006 0.0024 0.0042 0.0042 0.0089 0.0089 0.0142 0.0196 0.0219 0.0338 0.038 0.0504 0.035 0.0415 0.0534 0.0647 0.1981 + 2009 1 2 1 0 0 0 50 0 0 0 0 0.0019 0.0016 0.0016 0.0054 0.014 0.0194 0.0202 0.0427 0.0539 0.0613 0.0698 0.0741 0.0694 0.0597 0.0512 0.1194 + 2010 1 2 1 0 0 0 50 0 0 0.0017 0.0012 0.0017 0.0046 0.0041 0.0081 0.0133 0.0122 0.0145 0.0307 0.0359 0.0417 0.0557 0.0493 0.0487 0.0354 0.0307 0.0899 + 2011 1 2 1 0 0 0 50 0 0 0.0022 0.0066 0.0109 0.0109 0.0022 0.0066 0.0131 0.0087 0.0066 0.0066 0.0218 0.0284 0.048 0.059 0.059 0.059 0.0437 0.1266 + 2012 1 2 1 0 0 0 50 0 0.0037 0 0 0 0.0037 0.0037 0.0037 0.0037 0.0037 0.0111 0.0074 0.0295 0.0369 0.0517 0.0332 0.0517 0.0554 0.0554 0.1697 +##length proportions of trawl female bycatch +##Year, Seas, Fleet, Sex, Type, Shell, Maturity, Nsamp, DataVec + 1976 1 2 2 0 0 0 50 0 0 0 0 0 0 0.013 0.0087 0.0216 0.026 0.0303 0.0563 0.013 0.026 0.0043 0.026 0 0 0 0 + 1977 1 2 2 0 0 0 50 0 0.0009 0.0009 0 0 0.0009 0.0026 0.0053 0.007 0.0088 0.0062 0.0053 0.0044 0.0026 0.0009 0.0009 0 0 0 0 + 1978 1 2 2 0 0 0 50 0 0 0 0 0 0 0 0 0 0 0.0075 0.005 0.0075 0.0262 0.0324 0.061 0 0 0 0 + 1979 1 2 2 0 0 0 50 0.013 0.0013 0 0 0.0063 0.0038 0.0152 0.0468 0.0354 0.0392 0.0544 0.0215 0.0164 0.0177 0.0013 0.0139 0 0 0 0 + 1980 1 2 2 0 0 0 50 0.0433 0.016 0.0096 0.0189 0.0281 0.0409 0.0497 0.0472 0.0489 0.0525 0.0362 0.0265 0.0134 0.0081 0.0039 0.004 0 0 0 0 + 1981 1 2 2 0 0 0 50 0.0612 0.0245 0.0245 0.0437 0.054 0.0608 0.0525 0.0425 0.0315 0.0383 0.0312 0.0267 0.024 0.0158 0.0093 0.0086 0 0 0 0 + 1982 1 2 2 0 0 0 50 0.0631 0.0235 0.0237 0.0285 0.0379 0.0413 0.0332 0.0246 0.019 0.0177 0.0156 0.0144 0.0104 0.008 0.0034 0.0049 0 0 0 0 + 1983 1 2 2 0 0 0 50 0.0281 0.0233 0.0351 0.0363 0.0358 0.0407 0.0392 0.0316 0.0222 0.0154 0.01 0.0087 0.0065 0.0042 0.003 0.0041 0 0 0 0 + 1984 1 2 2 0 0 0 50 0.04 0.0156 0.0155 0.0211 0.0298 0.0344 0.0399 0.0359 0.0287 0.0151 0.0085 0.006 0.0042 0.0031 0.0019 0.0029 0 0 0 0 + 1985 1 2 2 0 0 0 50 0.0034 0.0013 0.0024 0.0046 0.0096 0.0171 0.0195 0.0193 0.0163 0.0128 0.0119 0.0111 0.0108 0.0057 0.0025 0.0066 0 0 0 0 + 1986 1 2 2 0 0 0 50 0.0144 0.0052 0.0083 0.0132 0.0245 0.0297 0.0388 0.0333 0.0308 0.0203 0.014 0.0069 0.0055 0.0029 0.0023 0.0054 0 0 0 0 + 1987 1 2 2 0 0 0 50 0.0029 0.0015 0.0117 0.0253 0.0271 0.0409 0.0546 0.0479 0.0436 0.0299 0.0221 0.0165 0.0089 0.0047 0.0028 0.0108 0 0 0 0 + 1988 1 2 2 0 0 0 50 0.0239 0.0035 0.0061 0.0111 0.0218 0.0368 0.052 0.0446 0.0464 0.0435 0.0316 0.0179 0.0115 0.0062 0.0026 0.0078 0 0 0 0 + 1989 1 2 2 0 0 0 50 0.001 0.0004 0.0006 0.0024 0.0082 0.0125 0.0151 0.032 0.033 0.0348 0.0302 0.0255 0.0221 0.0167 0.009 0.0225 0 0 0 0 + 1990 1 2 2 0 0 0 50 0.0015 0.0045 0.0105 0.009 0.009 0.0105 0.0254 0.0284 0.0494 0.0404 0.0404 0.0329 0.018 0.009 0.0015 0.0165 0 0 0 0 + 1991 1 2 2 0 0 0 50 0.0096 0.0032 0.0064 0.0032 0 0.0064 0.0032 0.0064 0.0257 0.0129 0.0161 0.0257 0.0161 0.0257 0.0032 0.0804 0 0 0 0 + 1992 1 2 2 0 0 0 50 0 0 0 0.0034 0.0475 0.0712 0.0542 0.0542 0.0508 0.0542 0.0712 0.078 0.0542 0.0508 0.0441 0.0644 0 0 0 0 + 1994 1 2 2 0 0 0 50 0.0306 0.0031 0.0076 0.026 0.029 0.0397 0.026 0.0595 0.0397 0.0153 0.0122 0.0107 0.0137 0.0183 0.0183 0.0641 0 0 0 0 + 1995 1 2 2 0 0 0 50 0.0213 0.0016 0.0065 0.0098 0.0163 0.0082 0.0228 0.0408 0.0555 0.0718 0.1289 0.1109 0.075 0.0685 0.0538 0.0734 0 0 0 0 + 1996 1 2 2 0 0 0 50 0 0 0.0008 0.0042 0.013 0.023 0.0245 0.0234 0.0283 0.0291 0.0257 0.0218 0.0207 0.0165 0.0103 0.0348 0 0 0 0 + 1997 1 2 2 0 0 0 50 0 0 0 0 0.0009 0 0.0132 0.022 0.029 0.0457 0.0343 0.0308 0.0413 0.029 0.0299 0.1134 0 0 0 0 + 1998 1 2 2 0 0 0 50 0 0 0.0004 0.0004 0.0007 0.0022 0.0109 0.0322 0.0386 0.027 0.024 0.0161 0.0187 0.0199 0.0243 0.061 0 0 0 0 + 1999 1 2 2 0 0 0 50 0 0 0 0.0018 0.0012 0.0006 0.0018 0.0018 0.0071 0.0143 0.0208 0.0273 0.041 0.0321 0.0208 0.0665 0 0 0 0 + 2000 1 2 2 0 0 0 50 0.001 0.0003 0.0003 0.0011 0.0005 0.0035 0.0079 0.012 0.0076 0.0125 0.0267 0.039 0.0313 0.0218 0.0158 0.0428 0 0 0 0 + 2001 1 2 2 0 0 0 50 0.0008 0.0002 0.0007 0.001 0.004 0.0062 0.0116 0.0159 0.0172 0.0196 0.0334 0.0577 0.0514 0.0336 0.0275 0.0882 0 0 0 0 + 2002 1 2 2 0 0 0 50 0 0.0008 0.0011 0.0056 0.011 0.0099 0.0085 0.0141 0.0265 0.0285 0.0285 0.0432 0.0536 0.057 0.0559 0.1341 0 0 0 0 + 2003 1 2 2 0 0 0 50 0 0.0017 0.0051 0.0238 0.0357 0.0102 0.0102 0.0289 0.0595 0.0408 0.0289 0.0255 0.0476 0.0391 0.0476 0.1173 0 0 0 0 + 2004 1 2 2 0 0 0 50 0.0039 0.0039 0.0039 0.0039 0.0039 0.0039 0.0117 0.0272 0.0389 0.0506 0.0389 0.0389 0.0467 0.0584 0.0389 0.0934 0 0 0 0 + 2005 1 2 2 0 0 0 50 0 0 0 0.0032 0.0032 0.0129 0.0097 0.0484 0.0516 0.0194 0.0323 0.0323 0.0323 0.0323 0.0323 0.0903 0 0 0 0 + 2006 1 2 2 0 0 0 50 0.0026 0.0078 0.0078 0.0078 0.0078 0.0156 0.0078 0.026 0.0545 0.039 0.026 0.039 0.0545 0.0156 0.039 0.0857 0 0 0 0 + 2007 1 2 2 0 0 0 50 0 0 0.001 0.0002 0.0023 0.0058 0.0124 0.028 0.0519 0.0813 0.0807 0.0774 0.0634 0.0502 0.0397 0.0986 0 0 0 0 + 2008 1 2 2 0 0 0 50 0 0 0.0006 0.0012 0.0047 0.0136 0.0208 0.0308 0.0255 0.0326 0.0403 0.051 0.0344 0.0332 0.0261 0.0842 0 0 0 0 + 2009 1 2 2 0 0 0 50 0 0 0 0.0004 0.0031 0.0031 0.0081 0.0198 0.0345 0.0271 0.0364 0.0415 0.0473 0.031 0.0213 0.0609 0 0 0 0 + 2010 1 2 2 0 0 0 50 0 0 0 0.0012 0.0029 0.0145 0.0313 0.0441 0.0464 0.0412 0.0522 0.0429 0.0638 0.0545 0.0394 0.0864 0 0 0 0 + 2011 1 2 2 0 0 0 50 0 0 0.0066 0.0175 0.0131 0.0131 0.0262 0.0109 0.0218 0.0262 0.0415 0.0437 0.0524 0.0306 0.0393 0.1376 0 0 0 0 + 2012 1 2 2 0 0 0 50 0 0 0 0 0.0037 0.0332 0.0221 0.0443 0.0148 0.0369 0.0295 0.0295 0.059 0.048 0.0332 0.1218 0 0 0 0 +##length proportions of survey newshell males +##Year, Seas, Fleet, Sex, Type, Shell, Maturity, Nsamp, DataVec + 1975 1 3 1 1 1 0 200 0.03433 0.06119 0.03631 0.03701 0.03626 0.02684 0.02746 0.02043 0.02199 0.02522 0.02323 0.02322 0.02484 0.02294 0.01909 0.0197 0.0162 0.00957 0.00661 0.01009 + 1976 1 3 1 1 1 0 200 0.00232 0.01279 0.02937 0.05077 0.06104 0.04581 0.04776 0.03559 0.03199 0.02832 0.02984 0.02996 0.02334 0.02354 0.0206 0.01457 0.01294 0.00852 0.00591 0.00568 + 1977 1 3 1 1 1 0 200 0.00722 0.00558 0.00666 0.01007 0.0195 0.037 0.04363 0.04307 0.04013 0.04302 0.03906 0.03772 0.02788 0.02964 0.02865 0.02252 0.0144 0.01024 0.00661 0.00905 + 1978 1 3 1 1 1 0 200 0.00415 0.0114 0.01313 0.02219 0.01618 0.0153 0.0153 0.02585 0.02749 0.02795 0.02833 0.02739 0.02477 0.0294 0.02988 0.02505 0.02385 0.01579 0.00971 0.00755 + 1979 1 3 1 1 1 0 200 0.00801 0.008 0.01059 0.01598 0.01392 0.01592 0.01244 0.01397 0.01354 0.0178 0.02471 0.03399 0.03477 0.03788 0.03207 0.03339 0.02893 0.02384 0.01446 0.02128 + 1980 1 3 1 1 1 0 200 0.00713 0.01445 0.02854 0.0319 0.03189 0.03189 0.02635 0.02638 0.02288 0.01971 0.02217 0.01609 0.02291 0.02541 0.0251 0.0303 0.02546 0.02432 0.02153 0.02725 + 1981 1 3 1 1 1 0 200 0.03277 0.0196 0.01678 0.0252 0.03727 0.03277 0.03133 0.0292 0.02759 0.02966 0.01907 0.01635 0.01061 0.00937 0.00747 0.00654 0.00401 0.00357 0.00143 0.00509 + 1982 1 3 1 1 1 0 200 0.07924 0.08112 0.06821 0.02812 0.02304 0.03021 0.03407 0.02807 0.01868 0.01581 0.0181 0.01276 0.00951 0.00694 0.00436 0.0034 0.00225 0.00053 0.00041 0.00082 + 1983 1 3 1 1 1 0 200 0.03252 0.03556 0.0497 0.06649 0.07859 0.07774 0.05655 0.04214 0.03545 0.03417 0.02308 0.02137 0.01351 0.00898 0.00777 0.00183 0.00084 0 0 0 + 1984 1 3 1 1 1 0 200 0.01493 0.0625 0.13306 0.14261 0.06919 0.03343 0.01442 0.01346 0.0133 0.00938 0.00949 0.00565 0.00568 0.00336 0.00416 0.00175 0.00077 0.00041 0.00002 0.00016 + 1985 1 3 1 1 1 0 200 0.00261 0.01279 0.02442 0.03954 0.0589 0.05817 0.04235 0.04026 0.05909 0.06049 0.05132 0.05049 0.04397 0.04183 0.02443 0.02289 0.00176 0.00319 0.00415 0 + 1986 1 3 1 1 1 0 200 0.01118 0.01788 0.0248 0.0201 0.02318 0.01475 0.03917 0.04 0.05364 0.04764 0.06284 0.06696 0.05865 0.06369 0.04877 0.03519 0.02325 0.00733 0.00143 0.00072 + 1987 1 3 1 1 1 0 200 0.00151 0.00715 0.03314 0.0523 0.04666 0.03193 0.02963 0.02928 0.03029 0.02445 0.03113 0.02335 0.03004 0.02375 0.02059 0.01754 0.01411 0.0133 0.00347 0.00237 + 1988 1 3 1 1 1 0 200 0.00132 0.00098 0.00662 0.01068 0.01094 0.02158 0.04663 0.04339 0.03932 0.03771 0.02571 0.02768 0.01467 0.02865 0.02359 0.03421 0.02539 0.0189 0.00946 0.00793 + 1989 1 3 1 1 1 0 200 0.00151 0.00009 0 0.00228 0.01414 0.032 0.01664 0.03469 0.02244 0.03796 0.0373 0.03601 0.04465 0.05129 0.0334 0.03221 0.02538 0.02108 0.01328 0.01964 + 1990 1 3 1 1 1 0 200 0.00132 0.01104 0.01571 0.03616 0.03285 0.01009 0.0075 0.00623 0.01313 0.02143 0.01949 0.02053 0.02075 0.0213 0.01671 0.02223 0.01615 0.01075 0.01072 0.01925 + 1991 1 3 1 1 1 0 200 0.00103 0.00876 0.0213 0.01581 0.02487 0.01952 0.01114 0.02291 0.02011 0.01171 0.00363 0.01729 0.02907 0.03294 0.04485 0.05331 0.0515 0.04094 0.03382 0.06686 + 1992 1 3 1 1 1 0 200 0.001 0 0.00202 0.01106 0.0252 0.03333 0.05097 0.04886 0.03395 0.03348 0.02591 0.03451 0.02322 0.0146 0.01108 0.01594 0.01162 0.01399 0.01176 0.02854 + 1993 1 3 1 1 1 0 200 0.00208 0.01094 0.01291 0.00906 0.00804 0.01357 0.01066 0.01917 0.01955 0.03344 0.02444 0.04147 0.02119 0.01732 0.00967 0.00822 0.00732 0.00891 0.00577 0.00787 + 1994 1 3 1 1 1 0 200 0.00162 0 0.00309 0.02093 0.01757 0.01239 0.01098 0.01082 0.01688 0.03227 0.03069 0.02792 0.03848 0.05112 0.02013 0.02458 0.02607 0.01992 0.01064 0.01519 + 1995 1 3 1 1 1 0 200 0.02826 0.06829 0.05574 0.02203 0.01101 0.01592 0.02133 0.02355 0.02568 0.02873 0.02066 0.02201 0.02408 0.02322 0.035 0.02166 0.01749 0.01473 0.00622 0.01125 + 1996 1 3 1 1 1 0 200 0.02719 0.01292 0.02918 0.05291 0.06042 0.05874 0.02691 0.01981 0.01098 0.01462 0.01337 0.01035 0.00912 0.00319 0.00622 0.00716 0.00659 0.00938 0.0111 0.01276 + 1997 1 3 1 1 1 0 200 0 0.00357 0.00221 0.00519 0.0127 0.05636 0.09427 0.10657 0.09022 0.05071 0.02796 0.0136 0.01212 0.00935 0.01131 0.01348 0.01555 0.0103 0.00979 0.02598 + 1998 1 3 1 1 1 0 200 0.02085 0.01739 0.01031 0.01272 0.012 0.01014 0.01345 0.01472 0.02013 0.04373 0.04263 0.03912 0.03466 0.01846 0.00647 0.00737 0.00442 0.0029 0.00124 0.00345 + 1999 1 3 1 1 1 0 200 0.05825 0.02444 0.01335 0.01038 0.01196 0.01036 0.00963 0.01225 0.00326 0.00664 0.01252 0.02202 0.04148 0.0395 0.05441 0.05623 0.02925 0.01972 0.01072 0.0114 + 2000 1 3 1 1 1 0 200 0.00175 0.00473 0.01944 0.03949 0.03095 0.01993 0.02272 0.01626 0.01888 0.01404 0.01099 0.02078 0.01298 0.02074 0.01385 0.0111 0.01148 0.00855 0.00427 0.0067 + 2001 1 3 1 1 1 0 200 0.00689 0.00496 0.01061 0.0149 0.0156 0.04136 0.03572 0.05159 0.03394 0.01999 0.02186 0.0132 0.00984 0.01223 0.00775 0.00551 0.01066 0.01006 0.01014 0.0124 + 2002 1 3 1 1 1 0 200 0.05335 0.06381 0.0436 0.02682 0.01193 0.00793 0.00606 0.00736 0.01535 0.01781 0.02124 0.02041 0.01045 0.00875 0.00999 0.00631 0.00525 0.00883 0.00623 0.00503 + 2003 1 3 1 1 1 0 200 0.01604 0.0074 0.0154 0.02495 0.04249 0.0342 0.03247 0.018 0.00959 0.01396 0.01125 0.02279 0.01875 0.02908 0.02324 0.02414 0.01482 0.00971 0.00796 0.02164 + 2004 1 3 1 1 1 0 200 0.04684 0.03651 0.03383 0.02365 0.02226 0.01926 0.02833 0.04015 0.03578 0.0352 0.0264 0.02019 0.01236 0.01273 0.0128 0.01815 0.01566 0.02153 0.01193 0.025 + 2005 1 3 1 1 1 0 200 0.03525 0.05861 0.04185 0.01599 0.00976 0.02277 0.02344 0.02146 0.01842 0.01622 0.02073 0.02207 0.01265 0.01714 0.00954 0.01168 0.00648 0.00646 0.00805 0.01227 + 2006 1 3 1 1 1 0 200 0.01329 0.01976 0.01658 0.02765 0.02838 0.03548 0.01857 0.02076 0.01179 0.017 0.0105 0.01205 0.01881 0.01862 0.02997 0.02605 0.02056 0.01732 0.01059 0.01291 + 2007 1 3 1 1 1 0 200 0.00172 0.00246 0.00532 0.00837 0.01967 0.02715 0.03091 0.04028 0.03332 0.02419 0.01566 0.01804 0.01517 0.02261 0.01747 0.01805 0.0179 0.01359 0.01535 0.01691 + 2008 1 3 1 1 1 0 200 0 0.00076 0.00363 0.00577 0.01395 0.01669 0.01814 0.0223 0.03342 0.04313 0.03802 0.02547 0.02337 0.01707 0.01364 0.01039 0.01454 0.01071 0.00832 0.01802 + 2009 1 3 1 1 1 0 200 0.00095 0.00048 0.0037 0.00527 0.00532 0.01039 0.00965 0.02253 0.03192 0.02616 0.0236 0.02484 0.02844 0.04127 0.02429 0.02658 0.01436 0.01032 0.00775 0.0067 + 2010 1 3 1 1 1 0 200 0 0.00334 0.00803 0.00943 0.00774 0.00538 0.01608 0.01344 0.01295 0.01526 0.02418 0.03048 0.02201 0.0223 0.02723 0.02567 0.0316 0.01894 0.01048 0.0095 + 2011 1 3 1 1 1 0 200 0.00362 0.00438 0.0125 0.02044 0.01569 0.01317 0.01676 0.01505 0.01822 0.01195 0.01613 0.0164 0.01359 0.0199 0.01732 0.01617 0.01904 0.01323 0.00578 0.00808 + 2012 1 3 1 1 1 0 200 0.00247 0.00398 0.01202 0.01593 0.01281 0.0227 0.03362 0.02474 0.01742 0.01742 0.01461 0.01733 0.01843 0.01958 0.01581 0.01519 0.01481 0.01651 0.00795 0.02737 + 2013 1 3 1 1 1 0 200 0.00082 0.00253 0.01232 0.01451 0.01006 0.01741 0.01341 0.02352 0.02798 0.02607 0.03135 0.02742 0.02114 0.01964 0.01842 0.01501 0.01278 0.01693 0.0211 0.03167 +##length proportions of survey oldshell males +##Year, Seas, Fleet, Sex, Type, Shell, Maturity, Nsamp, DataVec + 1975 1 3 1 0 2 0 200 0 0.00011 0 0.00022 0 0.00011 0 0.00085 0.00065 0.0015 0.00086 0.00138 0.00171 0.00137 0.00195 0.00362 0.00184 0.00198 0.00188 0.00076 + 1976 1 3 1 0 2 0 200 0 0 0 0.00004 0.00004 0 0 0.00002 0.00052 0.00042 0.00093 0.00365 0.00268 0.00508 0.00529 0.00393 0.00422 0.00497 0.00294 0.00151 + 1977 1 3 1 0 2 0 200 0 0 0 0 0 0.00041 0.00065 0.00018 0.00068 0.00083 0.00118 0.0024 0.00243 0.00212 0.00307 0.00309 0.00184 0.00341 0.00157 0.00302 + 1978 1 3 1 0 2 0 200 0.00014 0.00055 0.00048 0.00182 0.00106 0.00376 0.00253 0.00205 0.00207 0.00181 0.00171 0.00297 0.00421 0.00726 0.00476 0.00321 0.00216 0.00149 0.00113 0.00156 + 1979 1 3 1 0 2 0 200 0.00015 0.00093 0.00064 0.00022 0.00073 0.00111 0.00024 0.00039 0.00039 0.00087 0.00105 0.00202 0.00181 0.00378 0.0043 0.00378 0.00524 0.0044 0.00132 0.00393 + 1980 1 3 1 0 2 0 200 0 0 0 0 0 0.00045 0.0003 0 0 0.00016 0.00038 0.00045 0.00097 0.00121 0.0018 0.00285 0.00174 0.00295 0.00104 0.00401 + 1981 1 3 1 0 2 0 200 0.00016 0 0.00061 0 0.001 0.00073 0.00059 0.00247 0.00146 0.00418 0.00419 0.00537 0.00795 0.00898 0.00711 0.00801 0.0066 0.00669 0.00476 0.00952 + 1982 1 3 1 0 2 0 200 0 0 0 0.00055 0.00095 0.00079 0.0012 0.00065 0.00105 0.00129 0.00173 0.00135 0.00355 0.00097 0.00222 0.00093 0.00169 0 0 0.00094 + 1983 1 3 1 0 2 0 200 0 0 0 0 0.00146 0.00051 0.00342 0.00467 0.00427 0.00572 0.00909 0.00952 0.0055 0.00294 0.0029 0.00185 0.00166 0.00123 0 0 + 1984 1 3 1 0 2 0 200 0 0.00012 0.00014 0.00003 0.00017 0.00004 0.00044 0.00027 0.00024 0.00267 0.00045 0.00024 0.00082 0.00085 0.00249 0.00063 0.00002 0.00051 0 0.00013 + 1985 1 3 1 0 2 0 200 0 0 0 0 0 0 0 0 0.00106 0.0009 0 0.00182 0.00573 0 0.00351 0.00085 0 0.00191 0 0 + 1986 1 3 1 0 2 0 200 0 0 0 0 0 0.00088 0.00162 0 0.00224 0.00088 0.00462 0.00643 0.01135 0.01506 0.00757 0.00329 0.0042 0 0.0015 0.0016 + 1987 1 3 1 0 2 0 200 0 0 0 0 0.00039 0.00039 0 0.00041 0.00082 0.00119 0.00226 0.0036 0.00689 0.01094 0.00869 0.01119 0.00436 0.00251 0.00038 0.00161 + 1988 1 3 1 0 2 0 200 0 0 0 0 0.00205 0 0 0 0 0 0.0008 0.00288 0.00569 0.00855 0.00952 0.01509 0.01151 0.00793 0 0.00135 + 1989 1 3 1 0 2 0 200 0 0 0.00081 0 0 0 0 0.00009 0.00146 0.00516 0.0015 0.00074 0.00748 0.00942 0.0216 0.03086 0.02302 0.02473 0.01384 0.00653 + 1990 1 3 1 0 2 0 200 0 0 0 0 0.00072 0 0.00072 0.00071 0.00255 0.00453 0.00316 0.00923 0.01085 0.01496 0.01888 0.01774 0.0133 0.02177 0.00869 0.01368 + 1991 1 3 1 0 2 0 200 0 0 0.00058 0.00059 0.00112 0.0017 0.0023 0.0039 0.00156 0.00516 0.00215 0.00336 0.00581 0.00497 0.01474 0.01452 0.01304 0.00898 0.00688 0.01173 + 1992 1 3 1 0 2 0 200 0 0 0 0.00165 0 0.00217 0.00423 0.00391 0.00423 0.00645 0.00318 0.0033 0.01161 0.01343 0.01228 0.00739 0.01026 0.01666 0.00509 0.02109 + 1993 1 3 1 0 2 0 200 0 0 0.00069 0.00137 0.00145 0.00203 0.00344 0.00422 0.01136 0.01032 0.01999 0.02171 0.0285 0.02464 0.02295 0.02012 0.02286 0.01946 0.01823 0.03231 + 1994 1 3 1 0 2 0 200 0 0 0 0.00277 0.00591 0.00277 0.00138 0.00651 0.00443 0.0031 0.01053 0.01238 0.02425 0.03959 0.02727 0.02154 0.02073 0.01281 0.0123 0.03521 + 1995 1 3 1 0 2 0 200 0 0 0 0 0 0.00099 0.00086 0.00198 0.0018 0.00173 0.0056 0.00478 0.01026 0.01699 0.01402 0.02162 0.01481 0.00904 0.00454 0.0149 + 1996 1 3 1 0 2 0 200 0.00062 0.00062 0.00062 0 0.00274 0.00064 0.00065 0.00268 0.00072 0.00324 0.00066 0.00466 0.00482 0.00979 0.01555 0.00931 0.01244 0.00776 0.00717 0.01245 + 1997 1 3 1 0 2 0 200 0 0 0 0 0 0 0 0.00041 0.00075 0.00083 0.00216 0.00257 0.00276 0.00386 0.00289 0.00335 0.00782 0.00651 0.00752 0.01417 + 1998 1 3 1 0 2 0 200 0 0 0 0 0 0 0 0.00217 0.0025 0.00293 0.00589 0.0132 0.01047 0.01061 0.01185 0.00788 0.01513 0.01058 0.00671 0.02105 + 1999 1 3 1 0 2 0 200 0 0 0 0 0 0.00062 0.0025 0.00253 0.00142 0.00658 0.00563 0.00129 0.01054 0.01416 0.01567 0.01262 0.01435 0.01064 0.01136 0.01386 + 2000 1 3 1 0 2 0 200 0 0 0 0 0 0 0 0 0.00112 0.00061 0.00239 0.00876 0.01636 0.02809 0.02766 0.02479 0.02271 0.01431 0.0042 0.01289 + 2001 1 3 1 0 2 0 200 0 0 0 0 0 0.00073 0.00143 0.00075 0.00067 0 0.00347 0.00344 0.00412 0.00794 0.00542 0.00565 0.01123 0.00906 0.00907 0.02029 + 2002 1 3 1 0 2 0 200 0 0 0 0.00041 0 0.00114 0.00154 0.00326 0.00757 0.0088 0.0135 0.00862 0.0098 0.01641 0.00701 0.01303 0.01423 0.01333 0.01792 0.02237 + 2003 1 3 1 0 2 0 200 0 0 0 0.0004 0 0.00037 0.00077 0.00039 0.00188 0.00155 0.00156 0.0036 0.00356 0.0062 0.00894 0.00726 0.00734 0.00652 0.00595 0.01452 + 2004 1 3 1 0 2 0 200 0 0 0 0 0 0.00062 0.00051 0.00014 0.00032 0.00034 0 0.00034 0.00007 0.00044 0.0037 0.00377 0.00384 0.00503 0.0037 0.01012 + 2005 1 3 1 0 2 0 200 0 0 0 0 0 0 0 0 0 0.00091 0.00113 0.00119 0.00323 0.00177 0.00295 0.00415 0.00385 0.00899 0.00632 0.01294 + 2006 1 3 1 0 2 0 200 0 0 0.00071 0 0.00073 0.00144 0.00241 0 0.00111 0.00175 0.0011 0.00076 0.00473 0.00186 0.00289 0.00183 0.00646 0.00255 0.00377 0.01163 + 2007 1 3 1 0 2 0 200 0 0 0 0 0 0 0.00369 0.00339 0.00527 0.00455 0.00307 0.00526 0.00834 0.00878 0.00976 0.01062 0.00969 0.01252 0.00746 0.01193 + 2008 1 3 1 0 2 0 200 0 0 0 0.00074 0.00037 0.00148 0.00074 0.00075 0.00203 0.00037 0.0024 0.00393 0.00599 0.00862 0.00625 0.00585 0.00539 0.00811 0.00765 0.01503 + 2009 1 3 1 0 2 0 200 0 0 0 0 0 0 0 0 0.00101 0.00386 0.00786 0.00793 0.00778 0.0066 0.00689 0.00625 0.00537 0.00593 0.00704 0.01014 + 2010 1 3 1 0 2 0 200 0 0 0 0 0 0 0 0 0 0 0.00278 0.00578 0.00817 0.01021 0.00947 0.00903 0.01066 0.00728 0.00404 0.01046 + 2011 1 3 1 0 2 0 200 0 0 0 0 0.00118 0.00061 0 0 0 0.00123 0.00193 0.00385 0.00252 0.00962 0.0101 0.00952 0.00507 0.00714 0.00576 0.0083 + 2012 1 3 1 0 2 0 200 0 0 0 0 0 0 0 0 0 0 0.00071 0.00222 0.00326 0.00686 0.0076 0.00575 0.00834 0.0116 0.00523 0.01605 + 2013 1 3 1 0 2 0 200 0 0 0 0 0 0 0 0 0 0 0.00091 0.0074 0.00914 0.01228 0.01594 0.01743 0.02119 0.02615 0.01835 0.04324 +##length proportions of survey females +##Year, Seas, Fleet, Sex, Type, Shell, Maturity, Nsamp, DataVec + 1975 1 3 2 0 0 0 200 0.04788 0.05622 0.05339 0.04732 0.05296 0.04081 0.03821 0.03823 0.02918 0.02491 0.01409 0.01364 0.00998 0.00433 0.00262 0.00294 0 0 0 0 + 1976 1 3 2 0 0 0 200 0.00315 0.00913 0.03175 0.05824 0.06924 0.05738 0.04759 0.03476 0.02941 0.03378 0.02521 0.0225 0.01076 0.00545 0.00156 0.0032 0 0 0 0 + 1977 1 3 2 0 0 0 200 0.00826 0.01119 0.00883 0.01951 0.03371 0.06967 0.07991 0.0704 0.04434 0.04203 0.03962 0.03103 0.01504 0.01006 0.00333 0.00453 0 0 0 0 + 1978 1 3 2 0 0 0 200 0.0061 0.01111 0.01869 0.02009 0.02332 0.04185 0.09213 0.12133 0.07873 0.04417 0.02995 0.02681 0.01751 0.00895 0.00449 0.00738 0 0 0 0 + 1979 1 3 2 0 0 0 200 0.00979 0.00667 0.00959 0.01791 0.02392 0.02895 0.04936 0.08023 0.09823 0.09691 0.05231 0.02985 0.02374 0.01009 0.00388 0.00579 0 0 0 0 + 1980 1 3 2 0 0 0 200 0.00515 0.0223 0.03324 0.02637 0.06062 0.08389 0.04983 0.055 0.05537 0.04177 0.03098 0.01355 0.01011 0.00621 0.00361 0.00202 0 0 0 0 + 1981 1 3 2 0 0 0 200 0.04661 0.02629 0.01855 0.02254 0.03911 0.04364 0.04209 0.0438 0.05581 0.06796 0.06691 0.04072 0.02115 0.01261 0.00301 0.00313 0 0 0 0 + 1982 1 3 2 0 0 0 200 0.05357 0.09537 0.06029 0.03784 0.04226 0.04818 0.03978 0.02321 0.01896 0.02571 0.02813 0.02027 0.01141 0.00625 0.00238 0.00086 0 0 0 0 + 1983 1 3 2 0 0 0 200 0.01741 0.0383 0.04749 0.06292 0.06466 0.03981 0.03406 0.01518 0.01068 0.00422 0.00904 0.00563 0.00605 0.00222 0.00129 0 0 0 0 0 + 1984 1 3 2 0 0 0 200 0.01229 0.05937 0.13213 0.12041 0.06624 0.03177 0.01564 0.00745 0.00409 0.00158 0.00031 0.00044 0.0001 0.00014 0.00002 0 0 0 0 0 + 1985 1 3 2 0 0 0 200 0.00086 0.01548 0.03765 0.05212 0.0643 0.05553 0.05156 0.03973 0.01606 0.00681 0 0 0.00149 0 0 0 0 0 0 0 + 1986 1 3 2 0 0 0 200 0.01237 0.02244 0.03547 0.02742 0.02628 0.03133 0.03617 0.03878 0.0274 0.01125 0.00715 0.00079 0 0 0.00076 0 0 0 0 0 + 1987 1 3 2 0 0 0 200 0.00134 0.01191 0.05107 0.08877 0.07579 0.04682 0.04501 0.05784 0.04186 0.02982 0.01808 0.00781 0.00185 0.00041 0 0 0 0 0 0 + 1988 1 3 2 0 0 0 200 0.00059 0.00766 0.00646 0.00618 0.01397 0.06959 0.09121 0.09804 0.07011 0.06092 0.04076 0.0184 0.00772 0.00767 0 0 0 0 0 0 + 1989 1 3 2 0 0 0 200 0.0015 0 0.00165 0.00775 0.02771 0.06879 0.06155 0.06435 0.05136 0.0367 0.02865 0.01741 0.00523 0.00405 0 0.00009 0 0 0 0 + 1990 1 3 2 0 0 0 200 0.00421 0.00542 0.02448 0.05339 0.05461 0.00738 0.02722 0.06038 0.07596 0.07194 0.06366 0.04198 0.02071 0.00609 0.00386 0.00387 0 0 0 0 + 1991 1 3 2 0 0 0 200 0.00406 0.01126 0.01915 0.03128 0.02134 0.0337 0.03354 0.0303 0.03586 0.03225 0.02769 0.0422 0.02274 0.01081 0.00674 0.00263 0 0 0 0 + 1992 1 3 2 0 0 0 200 0 0.00534 0.00737 0.01974 0.03642 0.04139 0.06251 0.04481 0.03529 0.02733 0.04503 0.04068 0.02651 0.02118 0.01619 0.01224 0 0 0 0 + 1993 1 3 2 0 0 0 200 0.00652 0.00796 0.01742 0.00845 0.01303 0.0247 0.04349 0.06393 0.06356 0.02673 0.02981 0.02663 0.02696 0.04427 0.01746 0.02183 0 0 0 0 + 1994 1 3 2 0 0 0 200 0 0.0016 0.00443 0.00296 0.01685 0.00917 0.0124 0.02131 0.04312 0.0416 0.03619 0.02802 0.03953 0.04689 0.02916 0.03206 0 0 0 0 + 1995 1 3 2 0 0 0 200 0.02942 0.04821 0.03155 0.01453 0.01391 0.01824 0.01628 0.02535 0.02343 0.03343 0.02724 0.02335 0.02398 0.0145 0.02031 0.01547 0 0 0 0 + 1996 1 3 2 0 0 0 200 0.02595 0.02186 0.04362 0.0794 0.07958 0.04357 0.02255 0.02176 0.02451 0.02017 0.01611 0.02847 0.02443 0.01563 0.00871 0.02361 0 0 0 0 + 1997 1 3 2 0 0 0 200 0.00043 0.00367 0.00162 0.00201 0.0146 0.07907 0.09694 0.06164 0.02119 0.01367 0.00948 0.01455 0.01427 0.01092 0.00836 0.02076 0 0 0 0 + 1998 1 3 2 0 0 0 200 0.0145 0.0196 0.01006 0.00876 0.01112 0.01163 0.03034 0.10415 0.11502 0.05893 0.03058 0.02523 0.02254 0.02353 0.02321 0.03365 0 0 0 0 + 1999 1 3 2 0 0 0 200 0.0243 0.01694 0.0125 0.01147 0.00435 0.00547 0.00924 0.01639 0.05112 0.07986 0.05821 0.03575 0.03393 0.01986 0.01225 0.0268 0 0 0 0 + 2000 1 3 2 0 0 0 200 0.00174 0.00673 0.02683 0.04024 0.03574 0.02719 0.02547 0.02268 0.03591 0.05249 0.06775 0.06047 0.04205 0.02091 0.01677 0.04352 0 0 0 0 + 2001 1 3 2 0 0 0 200 0.0056 0.01683 0.01951 0.01361 0.02585 0.05984 0.07787 0.05792 0.03945 0.03981 0.02909 0.06914 0.056 0.02621 0.01028 0.02048 0 0 0 0 + 2002 1 3 2 0 0 0 200 0.05063 0.07685 0.04852 0.02466 0.02215 0.01761 0.02247 0.05199 0.0399 0.02964 0.0163 0.02059 0.02046 0.02206 0.00712 0.0136 0 0 0 0 + 2003 1 3 2 0 0 0 200 0.01765 0.00633 0.01547 0.03393 0.04499 0.04991 0.02591 0.03122 0.03807 0.05789 0.05706 0.03868 0.02395 0.02881 0.02356 0.03786 0 0 0 0 + 2004 1 3 2 0 0 0 200 0.03521 0.04131 0.02444 0.01455 0.02211 0.03202 0.04847 0.05039 0.03417 0.02504 0.02492 0.02855 0.02271 0.02044 0.01579 0.02838 0 0 0 0 + 2005 1 3 2 0 0 0 200 0.04054 0.0561 0.04573 0.01155 0.00988 0.0336 0.03861 0.05206 0.05668 0.04675 0.03355 0.03825 0.03468 0.02272 0.01648 0.02455 0 0 0 0 + 2006 1 3 2 0 0 0 200 0.0143 0.01389 0.01982 0.04253 0.06161 0.04627 0.02545 0.02591 0.04813 0.06561 0.06191 0.0415 0.03015 0.03523 0.01667 0.01864 0 0 0 0 + 2007 1 3 2 0 0 0 200 0.00152 0.00228 0.00642 0.00783 0.01548 0.03569 0.05746 0.05611 0.03252 0.05702 0.06142 0.06418 0.04593 0.03432 0.02105 0.0323 0 0 0 0 + 2008 1 3 2 0 0 0 200 0 0.00256 0.00517 0.01305 0.01121 0.0161 0.02938 0.05671 0.07231 0.06068 0.06833 0.07969 0.07628 0.04659 0.02644 0.0224 0 0 0 0 + 2009 1 3 2 0 0 0 200 0.00046 0.0019 0.00504 0.00551 0.00817 0.0122 0.02058 0.04661 0.0657 0.08682 0.06453 0.06031 0.05223 0.07044 0.05132 0.04699 0 0 0 0 + 2010 1 3 2 0 0 0 200 0.00184 0.00058 0.00374 0.00481 0.00686 0.01164 0.02132 0.03646 0.05652 0.09273 0.09553 0.07009 0.0509 0.04972 0.05077 0.05456 0 0 0 0 + 2011 1 3 2 0 0 0 200 0.00576 0.00845 0.0092 0.01413 0.02844 0.03101 0.03837 0.04841 0.02992 0.05297 0.06375 0.09059 0.0635 0.05717 0.04306 0.07101 0 0 0 0 + 2012 1 3 2 0 0 0 200 0.02925 0.01803 0.0191 0.02495 0.02805 0.04611 0.03514 0.02198 0.03313 0.03551 0.03653 0.04609 0.06625 0.05206 0.04621 0.06328 0 0 0 0 + 2013 1 3 2 0 0 0 200 0.00081 0.00269 0.00929 0.01117 0.00669 0.01248 0.02018 0.03841 0.04287 0.04496 0.03041 0.03016 0.04553 0.04914 0.04049 0.07861 0 0 0 0 +##Year, Seas, Fleet, Sex, Type, Shell, Maturity, Nsamp, DataVec + 2007 1 4 1 0 0 0 628 0.0045 0.0074 0.0103 0.0155 0.0198 0.0321 0.0532 0.0491 0.0443 0.0354 0.0268 0.0231 0.0236 0.0256 0.0223 0.032 0.0246 0.0218 0.017 0.0278 + 2008 1 4 1 0 0 0 907 0.0017 0.001 0.0093 0.0119 0.0175 0.0279 0.0267 0.0348 0.0428 0.0596 0.0581 0.0455 0.0371 0.0284 0.0218 0.0211 0.0156 0.0157 0.0202 0.0294 + 2007 1 4 2 0 0 0 623 0.0007 0.0016 0.0044 0.0198 0.0302 0.0705 0.0563 0.0345 0.0364 0.0493 0.0501 0.0448 0.0272 0.0183 0.0152 0.0243 0 0 0 0 + 2008 1 4 2 0 0 0 796 0.0004 0.0013 0.0088 0.0142 0.0286 0.0483 0.0754 0.0687 0.0463 0.0386 0.0411 0.0357 0.021 0.0179 0.0126 0.015 0 0 0 0 +## Growth data (increment) +# nobs_growth +40 +## Note SM used loewss regression for males BBRKC data +## and cubic spine to interpolate 3 sets of female BBRKC data +# MidPoint Sex Increment CV + 67.5 2 14.766667 0.2 + 72.5 2 13.333333 0.2 + 77.5 2 11.866667 0.2 + 82.5 2 10.233333 0.2 + 87.5 2 9.000000 0.2 + 92.5 2 7.866667 0.2 + 97.5 2 7.066667 0.2 + 102.5 2 6.433333 0.2 + 107.5 2 5.933333 0.2 + 112.5 2 5.433333 0.2 + 117.5 2 4.933333 0.2 + 122.5 2 4.433333 0.2 + 127.5 2 3.933333 0.2 + 132.5 2 3.466667 0.2 + 137.5 2 3.033333 0.2 + 142.5 2 2.533333 0.2 + 147.5 2 2.033333 0.2 + 152.5 2 1.533333 0.2 + 157.5 2 1.033333 0.2 + 162.5 2 0.600000 0.2 + 67.5 1 16.510674 0.2 + 72.5 1 16.454438 0.2 + 77.5 1 16.398615 0.2 + 82.5 1 16.343118 0.2 + 87.5 1 16.287715 0.2 + 92.5 1 16.232130 0.2 + 97.5 1 16.176368 0.2 + 102.5 1 16.123732 0.2 + 107.5 1 16.069744 0.2 + 112.5 1 16.013906 0.2 + 117.5 1 15.957058 0.2 + 122.5 1 15.900084 0.2 + 127.5 1 15.843143 0.2 + 132.5 1 15.786395 0.2 + 137.5 1 15.732966 0.2 + 142.5 1 15.680640 0.2 + 147.5 1 15.628775 0.2 + 152.5 1 15.577259 0.2 + 157.5 1 15.526092 0.2 + 162.5 1 15.475241 0.2 +## eof +9999 + + +# Size bin-width +5 + +# Midpoint of size bins (vector length = nclass) +67.5 72.5 77.5 82.5 87.5 92.5 97.5 102.5 107.5 112.5 117.5 122.5 127.5 132.5 137.5 142.5 147.5 152.5 157.5 162.5 + +# Mean-weight vector (vector length = nclass, males then females) +0.22478 0.28135 0.34692 0.42221 0.50793 0.6048 0.71356 0.83495 0.9697 1.11856 1.28229 1.46163 1.65736 1.87023 2.10101 2.35048 2.61942 2.90861 3.21882 3.90595 +0.2151 0.26898 0.33137 0.40294 0.48437 0.62711 0.7216 0.82452 0.93615 1.05678 1.18669 1.32613 1.47539 1.63473 1.80441 2.18315 2.18315 2.18315 2.18315 2.18315 + + +0 # Number of lines of capture data to read +0 # Number of lines of mark data to read +0 # Number of lines of recapture data to read + + +999 # EOF check. diff --git a/examples/bbrkc/bbrkc_ss.ctl b/examples/bbrkc/bbrkc_ss.ctl new file mode 100644 index 00000000..a31d99dd --- /dev/null +++ b/examples/bbrkc/bbrkc_ss.ctl @@ -0,0 +1,139 @@ +# Model 1, fixed multinomial sample sizes +# —————————————————————————————————————————————————————————————————————————————————————— # +# Controls for leading parameter vector theta +# LEGEND FOR PRIOR: +# 0 -> uniform +# 1 -> normal +# 2 -> lognormal +# 3 -> beta +# 4 -> gamma +# —————————————————————————————————————————————————————————————————————————————————————— # +# ntheta + 7 +# —————————————————————————————————————————————————————————————————————————————————————— # +# ival lb ub phz prior p1 p2 # parameter # +# —————————————————————————————————————————————————————————————————————————————————————— # + 0.18 0.01 1 -2 2 0.18 0.04 # M + 7.0 -10 20 -1 1 3.0 5.0 # logR0 + 7.0 -10 20 2 1 3.0 5.0 # logR1 + 7.0 -10 20 2 1 3.0 5.0 # logRbar + 72.5 55 100 -4 1 72.5 7.25 # Recruitment Expected Value + 0.40 0.1 5 -3 0 0.1 5 # Recruitment scale (variance component) + -0.51 -10 0.75 -4 0 -10 0.75 # ln(sigma_R) +## ———————————————————————————————————————————————————————————————————————————————————— ## + +## ———————————————————————————————————————————————————————————————————————————————————— ## +## GROWTH PARAM CONTROLS ## +## nGrwth +## ## +## Two lines for each parameter if split sex, one line if not ## +## ———————————————————————————————————————————————————————————————————————————————————— ## +# ival lb ub phz prior p1 p2 # parameter # +# —————————————————————————————————————————————————————————————————————————————————————— # + 17.5 10.0 30.0 3 0 0.0 20.0 # alpha males or combined + 0.10 0.0 0.5 3 0 0.0 10.0 # beta males or combined + 0.8 0.01 30.0 -3 0 0.0 3.0 # gscale males or combined + 140. 65.0 165.0 4 0 0.0 3.0 # molt_mu males or combined + 0.2 0.0 1.0 3 0 0.0 3.0 # molt_cv males or combined +# ———————————————————————————————————————————————————————————————————————————————————— ## + +## ———————————————————————————————————————————————————————————————————————————————————— ## +## SELECTIVITY CONTROLS ## +## -Each gear must have a selectivity and a retention selectivity ## +## LEGEND sel_type:1=coefficients,2=logistic,3=logistic95 ## +## Index: use +ve for selectivity, -ve for retention +## sex dep: 0 for sex-independent, 1 for sex-dependent. +## ———————————————————————————————————————————————————————————————————————————————————— ## +## ivector for number of year blocks or nodes ## +## Gear-1 Gear-2 Gear-3 Gear-4 + 1 1 2 1 #Selectivity blocks + 1 1 1 1 #Retention blocks + 1 0 0 0 #male retention flag (0 -> no, 1 -> yes) +## ———————————————————————————————————————————————————————————————————————————————————— ## +## sel sel sel sex size year phz start end ## +## Index type mu sd dep nodes nodes mirror lam1 lam2 lam3 | block block ## +## ———————————————————————————————————————————————————————————————————————————————————— ## +## Selectivity P(capture of all sizes) + 1 3 95 140 0 1 1 3 12.5 12.5 12.5 1975 2014 + 2 3 110 150 0 1 1 -2 12.5 12.5 12.5 1975 2014 + 3 2 90 10 0 1 1 4 12.5 12.5 12.5 1975 1981 + 3 2 90 10 0 1 1 4 12.5 12.5 12.5 1982 2014 + 4 2 70 10 0 1 1 -3 12.5 12.5 12.5 1975 2014 +## ———————————————————————————————————————————————————————————————————————————————————— ## +## Retained + -1 2 135 2 0 1 1 -2 12.5 12.5 12.5 1975 2014 + -2 2 95 10 0 1 1 -2 12.5 12.5 12.5 1975 2014 + -3 2 90 10 0 1 1 -2 12.5 12.5 12.5 1975 2014 + -4 2 90 10 0 1 1 -2 12.5 12.5 12.5 1975 2014 +## ———————————————————————————————————————————————————————————————————————————————————— ## + +## ———————————————————————————————————————————————————————————————————————————————————— ## +## PRIORS FOR CATCHABILITY +## TYPE: 0 = UNINFORMATIVE, 1 - NORMAL (log-space), 2 = time-varying (nyi) +## ———————————————————————————————————————————————————————————————————————————————————— ## +## SURVEYS/INDICES ONLY +## NMFS BSFRF +## TYPE Mean_q SD_q + 1 0.896 0.13 + 0 0.001 0.01 +## ———————————————————————————————————————————————————————————————————————————————————— ## +## ———————————————————————————————————————————————————————————————————————————————————— ## +## PENALTIES FOR AVERAGE FISHING MORTALITY RATE FOR EACH GEAR +## ———————————————————————————————————————————————————————————————————————————————————— ## +## Trap Trawl NMFS BSFRF +## Mean_F STD_PHZ1 STD_PHZ2 PHZ + 0.20 0.10 1.10 1 + 0.10 0.10 1.10 2 + 0.00 2.00 2.00 -1 + 0.00 2.00 2.00 -1 +## ———————————————————————————————————————————————————————————————————————————————————— ## + +## ———————————————————————————————————————————————————————————————————————————————————— ## +## OPTIONS FOR SIZE COMPOSTION DATA (COLUMN FOR EACH MATRIX) +## LIKELIHOOD OPTIONS: +## -1) multinomial with estimated/fixed sample size +## -2) robust_multi. Robust approximation to multinomial +## -3) logistic normal (NIY) +## -4) multivariate-t (NIY) +## AUTOTAIL COMPRESSION: +## - pmin is the cumulative proportion used in tail compression. +## ———————————————————————————————————————————————————————————————————————————————————— ## + 1 1 1 1 1 1 # 2 2 2 # Type of likelihood. + 0 0 0 0 0 0 # 0 0 0 # Auto tail compression (pmin) +-4 -4 -4 -4 -4 -4 # -4 -4 -4 # Phz for estimating effective sample size (if appl.) +## ———————————————————————————————————————————————————————————————————————————————————— ## + +## ———————————————————————————————————————————————————————————————————————————————————— ## +## TIME VARYING NATURAL MORTALIIY RATES ## +## ———————————————————————————————————————————————————————————————————————————————————— ## +## TYPE: +## 0 = constant natural mortality +## 1 = Random walk (deviates constrained by variance in M) +## 2 = Cubic Spline (deviates constrained by nodes & node-placement) +## 3 = Blocked changes (deviates constrained by variance AT specific knots) + 3 +## Phase of estimation + 3 +## STDEV in m_dev for Random walk + 0.60 +## Number of nodes for cubic spline or number of step-changes for option 3 + 2 +## Year position of the knots (vector must be equal to the number of nodes) + 1980 1985 + + + +## ———————————————————————————————————————————————————————————————————————————————————— ## +## OTHER CONTROLS +## ———————————————————————————————————————————————————————————————————————————————————— ## + 3 # Estimated rec_dev phase + 0 # VERBOSE FLAG (0 = off, 1 = on, 2 = objective func) + 0 # INITIALIZE MODEL AT UNFISHED RECRUITS (0=FALSE, 1=TRUE) + 1984 # First year for average recruitment for Bspr calculation. + 2014 # Last year for average recruitment for Bspr calculation. + 0.35 # Target SPR ratio for Bmsy proxy. + 1 # Gear index for SPR calculations (i.e., directed fishery). + 1 # Lambda (proportion of mature male biomass for SPR reference points.) + 1 # Use empirical molt increment data (0=FALSE, 1=TRUE) +## EOF +9999 diff --git a/examples/bbrkc/bbrkc_ss.dat b/examples/bbrkc/bbrkc_ss.dat new file mode 100644 index 00000000..4902dd04 --- /dev/null +++ b/examples/bbrkc/bbrkc_ss.dat @@ -0,0 +1,462 @@ +#======================================================================================================== +#======================================================================================================== +# Gmacs Main Data File Version 1.1: BBRKC Example +# GEAR_INDEX DESCRIPTION +# 1 : Pot fishery retained catch. +# 1 : Pot fishery with discarded catch. +# 2 : Trawl bycatch +# 3 : Trawl survey + +# Fisheries: 1 Pot Fishery, 2 Pot Discard, 3 Trawl by-catch, 4 BSFRF +# Surveys: 3 NMFS Trawl Survey, 4 BSFRF Survey +#======================================================================================================== + +1975 # Start year +2014 # End year +1 # Time-step (years) +4 # Number of distinct data groups (among fishing fleets and surveys) +1 # Number of sexes +2 # Number of shell condition types +1 # Number of maturity types +20 # Number of size-classes in the model +## +# size_breaks (a vector giving the break points between size intervals, dim=nclass+1) +65 70 75 80 85 90 95 100 105 110 115 120 125 130 135 140 145 150 155 160 165 +# weight-at-length allometry w_l = a•l^b +## a (male, female) +4.03E-07 +## b (male, female) +3.141334 +# Male mature weight-at-length (weight * proportion mature) +0 0 0 0 0 0 0 0 0 0 0 1.432 1.625 1.835 2.063 2.31 2.576 2.862 3.169 3.7 +# Proportion mature by sex. +0 0 0 0 0 0 0 0 0 0 0 1 1 1 1 1 1 1 1 1 +# Fishing fleet names (delimited with : no spaces in names) +Pot_Fishery:Trawl_Bycatch +# Survey names (delimited with : no spaces in names) +NMFS_Trawl:BSFRF +# Number of catch data frames +3 +# Number of rows in each data frame. +39 24 38 +#0.5 # Time between survey and fishery +## ———————————————————————————————————————————————————————————————————————————————————— ## +## CATCH DATA +## Type of catch: 1 = retained, 2 = discard, 3 = +## Units of catch: 1 = biomass, 2 = numbers +## for BBRKC Units are in 1000 mt for landed & million crabs for discards. +## ———————————————————————————————————————————————————————————————————————————————————— ## +## year seas fleet sex obs cv type units mult effort discard_mortality +## Male Retained 1000 + 1975 1 1 1 23281.2 0.05 1 1 1 0 0 + 1976 1 1 1 28993.6 0.05 1 1 1 0 0 + 1977 1 1 1 31736.9 0.05 1 1 1 0 0 + 1978 1 1 1 39743 0.05 1 1 1 0 0 + 1979 1 1 1 48910 0.05 1 1 1 0 0 + 1980 1 1 1 58943.6 0.05 1 1 1 0 0 + 1981 1 1 1 15236.8 0.05 1 1 1 0 0 + 1982 1 1 1 1361.32 0.05 1 1 1 0 0 + 1983 1 1 1 1 0.05 1 1 1 0 0 + 1984 1 1 1 1897.1 0.05 1 1 1 0 0 + 1985 1 1 1 1893.75 0.05 1 1 1 0 0 + 1986 1 1 1 5168.19 0.05 1 1 1 0 0 + 1987 1 1 1 5574.24 0.05 1 1 1 0 0 + 1988 1 1 1 3351.05 0.05 1 1 1 0 0 + 1989 1 1 1 4656.03 0.05 1 1 1 0 0 + 1990 1 1 1 9272.79 0.05 1 1 1 0 0 + 1991 1 1 1 7885.25 0.05 1 1 1 0 0 + 1992 1 1 1 3681.81 0.05 1 1 1 0 0 + 1993 1 1 1 6659.64 0.05 1 1 1 0 0 + 1994 1 1 1 42.1841 0.05 1 1 1 0 0 + 1995 1 1 1 36.2874 0.05 1 1 1 0 0 + 1996 1 1 1 3861.89 0.05 1 1 1 0 0 + 1997 1 1 1 4042.14 0.05 1 1 1 0 0 + 1998 1 1 1 6779.39 0.05 1 1 1 0 0 + 1999 1 1 1 5377.79 0.05 1 1 1 0 0 + 2000 1 1 1 3738.05 0.05 1 1 1 0 0 + 2001 1 1 1 3865.97 0.05 1 1 1 0 0 + 2002 1 1 1 4384.42 0.05 1 1 1 0 0 + 2003 1 1 1 7135.46 0.05 1 1 1 0 0 + 2004 1 1 1 7006.64 0.05 1 1 1 0 0 + 2005 1 1 1 8399.62 0.05 1 1 1 0 0 + 2006 1 1 1 7143.17 0.05 1 1 1 0 0 + 2007 1 1 1 9303.95 0.05 1 1 1 0 0 + 2008 1 1 1 9216.07 0.05 1 1 1 0 0 + 2009 1 1 1 7272.47 0.05 1 1 1 0 0 + 2010 1 1 1 6761.53 0.05 1 1 1 0 0 + 2011 1 1 1 3607.09 0.05 1 1 1 0 0 + 2012 1 1 1 3621.73 0.05 1 1 1 0 0 + 2013 1 1 1 3990.99 0.05 1 1 1 0 0 +## Male discards Pot fishery 1000 + 1990 1 1 1 526.914 0.05 2 2 1 0 0.2 + 1991 1 1 1 407.824 0.05 2 2 1 0 0.2 + 1992 1 1 1 552.009 0.05 2 2 1 0 0.2 + 1993 1 1 1 763.157 0.05 2 2 1 0 0.2 + 1994 1 1 1 3.81194 0.05 2 2 1 0 0.2 + 1995 1 1 1 3.27373 0.05 2 2 1 0 0.2 + 1996 1 1 1 164.636 0.05 2 2 1 0 0.2 + 1997 1 1 1 244.687 0.05 2 2 1 0 0.2 + 1998 1 1 1 959.712 0.05 2 2 1 0 0.2 + 1999 1 1 1 314.171 0.05 2 2 1 0 0.2 + 2000 1 1 1 360.833 0.05 2 2 1 0 0.2 + 2001 1 1 1 417.875 0.05 2 2 1 0 0.2 + 2002 1 1 1 442.658 0.05 2 2 1 0 0.2 + 2003 1 1 1 918.858 0.05 2 2 1 0 0.2 + 2004 1 1 1 345.549 0.05 2 2 1 0 0.2 + 2005 1 1 1 1359.53 0.05 2 2 1 0 0.2 + 2006 1 1 1 563.751 0.05 2 2 1 0 0.2 + 2007 1 1 1 1001.31 0.05 2 2 1 0 0.2 + 2008 1 1 1 1165.51 0.05 2 2 1 0 0.2 + 2009 1 1 1 888.124 0.05 2 2 1 0 0.2 + 2010 1 1 1 797.476 0.05 2 2 1 0 0.2 + 2011 1 1 1 394.962 0.05 2 2 1 0 0.2 + 2012 1 1 1 205.155 0.05 2 2 1 0 0.2 + 2013 1 1 1 310.579 0.05 2 2 1 0 0.2 +## Trawl fishery discards 1000 + 1976 1 2 0 682.795 0.05 2 2 1 0 0.8 + 1977 1 2 0 1249.85 0.05 2 2 1 0 0.8 + 1978 1 2 0 1320.62 0.05 2 2 1 0 0.8 + 1979 1 2 0 1331.94 0.05 2 2 1 0 0.8 + 1980 1 2 0 1036.5 0.05 2 2 1 0 0.8 + 1981 1 2 0 219.383 0.05 2 2 1 0 0.8 + 1982 1 2 0 574.888 0.05 2 2 1 0 0.8 + 1983 1 2 0 420.443 0.05 2 2 1 0 0.8 + 1984 1 2 0 1094.04 0.05 2 2 1 0 0.8 + 1985 1 2 0 390.061 0.05 2 2 1 0 0.8 + 1986 1 2 0 200.606 0.05 2 2 1 0 0.8 + 1987 1 2 0 186.436 0.05 2 2 1 0 0.8 + 1988 1 2 0 597.816 0.05 2 2 1 0 0.8 + 1989 1 2 0 174.066 0.05 2 2 1 0 0.8 + 1990 1 2 0 247.553 0.05 2 2 1 0 0.8 + 1991 1 2 0 315.959 0.05 2 2 1 0 0.8 + 1992 1 2 0 335.39 0.05 2 2 1 0 0.8 + 1993 1 2 0 426.564 0.05 2 2 1 0 0.8 + 1994 1 2 0 88.9147 0.05 2 2 1 0 0.8 + 1995 1 2 0 194.24 0.05 2 2 1 0 0.8 + 1996 1 2 0 106.509 0.05 2 2 1 0 0.8 + 1997 1 2 0 73.4005 0.05 2 2 1 0 0.8 + 1998 1 2 0 159.848 0.05 2 2 1 0 0.8 + 1999 1 2 0 201.575 0.05 2 2 1 0 0.8 + 2000 1 2 0 100.354 0.05 2 2 1 0 0.8 + 2001 1 2 0 164.565 0.05 2 2 1 0 0.8 + 2002 1 2 0 155.091 0.05 2 2 1 0 0.8 + 2003 1 2 0 172.32 0.05 2 2 1 0 0.8 + 2004 1 2 0 119.557 0.05 2 2 1 0 0.8 + 2005 1 2 0 155.222 0.05 2 2 1 0 0.8 + 2006 1 2 0 116.676 0.05 2 2 1 0 0.8 + 2007 1 2 0 138.486 0.05 2 2 1 0 0.8 + 2008 1 2 0 159.516 0.05 2 2 1 0 0.8 + 2009 1 2 0 103.743 0.05 2 2 1 0 0.8 + 2010 1 2 0 89.0308 0.05 2 2 1 0 0.8 + 2011 1 2 0 69.2305 0.05 2 2 1 0 0.8 + 2012 1 2 0 62.2251 0.05 2 2 1 0 0.8 + 2013 1 2 0 126.832 0.05 2 2 1 0 0.8 + +## ———————————————————————————————————————————————————————————————————————————————————— ## +## RELATIVE ABUNDANCE DATA +## Units of Abundance: 1 = biomass, 2 = numbers +## TODO: add column for maturity for terminal molt life-histories +## for BBRKC Units are in million crabs for Abundance. +## ———————————————————————————————————————————————————————————————————————————————————— ## +## Number of relative abundance indicies +2 +## Number of rows in each index +40 2 +# Survey data (abundance indices, units are tons of crabs) +# Year, Seas, Fleet, Sex, Abundance, CV units + 1975 1 3 1 146028 0.188 1 + 1976 1 3 1 200083 0.169 1 + 1977 1 3 1 237777 0.141 1 + 1978 1 3 1 203160 0.155 1 + 1979 1 3 1 160779 0.133 1 + 1980 1 3 1 164259 0.221 1 + 1981 1 3 1 64005 0.121 1 + 1982 1 3 1 72147.9 0.259 1 + 1983 1 3 1 35370.1 0.216 1 + 1984 1 3 1 82562.7 0.678 1 + 1985 1 3 1 27003.7 0.158 1 + 1986 1 3 1 40811.3 0.428 1 + 1987 1 3 1 46611.1 0.209 1 + 1988 1 3 1 34918.7 0.217 1 + 1989 1 3 1 48290.5 0.214 1 + 1990 1 3 1 36269.9 0.214 1 + 1991 1 3 1 70018.5 0.441 1 + 1992 1 3 1 25255.4 0.174 1 + 1993 1 3 1 36426.3 0.174 1 + 1994 1 3 1 23115.7 0.173 1 + 1995 1 3 1 27468.5 0.276 1 + 1996 1 3 1 27078.4 0.201 1 + 1997 1 3 1 60276.3 0.263 1 + 1998 1 3 1 46352.9 0.178 1 + 1999 1 3 1 40696.1 0.161 1 + 2000 1 3 1 39292.6 0.178 1 + 2001 1 3 1 28161.3 0.178 1 + 2002 1 3 1 45261.7 0.203 1 + 2003 1 3 1 55153 0.164 1 + 2004 1 3 1 60162.2 0.163 1 + 2005 1 3 1 55066.5 0.173 1 + 2006 1 3 1 51211.5 0.122 1 + 2007 1 3 1 58063.2 0.135 1 + 2008 1 3 1 55233.2 0.104 1 + 2009 1 3 1 43948.1 0.287 1 + 2010 1 3 1 36353.3 0.15 1 + 2011 1 3 1 25064 0.141 1 + 2012 1 3 1 30605.4 0.162 1 + 2013 1 3 1 39542.5 0.245 1 + 2014 1 3 1 59205.2 0.191 1 + 2007 1 4 0 130352.8 0.2164 1 + 2008 1 4 0 106040.9 0.1939 1 + +## Number of length frequency matrixes +6 +## Number of rows in each matrix +36 +22 +#22 +37 +#37 +40 +#40 +40 +2 +## Number of bins in each matrix (columns of size data) +20 +20 +20 +20 +20 +20 +#20 +#20 +#20 +## SIZE COMPOSITION DATA FOR ALL FLEETS +## ———————————————————————————————————————————————————————————————————————————————————— ## +## SIZE COMP LEGEND +## Sex: 1 = male, 2 = female, 0 = both sexes combined +## Type of composition: 1 = retained, 2 = discard, 0 = total composition +## Maturity state: 1 = immature, 2 = mature, 0 = both states combined +## Shell condition: 1 = new shell, 2 = old shell, 0 = both shell types combined +## ———————————————————————————————————————————————————————————————————————————————————— ## +##length proportions of retained males +##Year, Seas, Fleet, Sex, Type, Shell, Maturity, Nsamp, DataVec + 1975 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0 0.0071 0.0741 0.1721 0.2239 0.2122 0.1464 0.0858 0.0785 + 1976 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0 0.0016 0.029 0.1418 0.2316 0.2199 0.1635 0.1071 0.1055 + 1977 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0 0.0017 0.0192 0.1382 0.2442 0.2226 0.1605 0.104 0.1096 + 1978 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0 0.0012 0.0209 0.1441 0.2588 0.2401 0.1673 0.0966 0.0711 + 1979 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0 0.0013 0.0119 0.0747 0.1649 0.1998 0.2004 0.1556 0.1914 + 1980 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0 0.0008 0.0138 0.0919 0.1771 0.195 0.1792 0.1404 0.2019 + 1981 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0 0.0006 0.0225 0.1164 0.1743 0.1711 0.1584 0.1284 0.2283 + 1982 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0 0 0.0544 0.2576 0.2802 0.1667 0.0837 0.0508 0.1067 + 1984 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0.0003 0.0023 0.0654 0.311 0.3135 0.1763 0.0846 0.0321 0.0145 + 1985 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0.0005 0.0044 0.079 0.2869 0.3098 0.1898 0.086 0.0306 0.0129 + 1986 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0 0.0016 0.0531 0.2613 0.3289 0.2084 0.0978 0.0352 0.0137 + 1987 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0 0.0013 0.0284 0.1895 0.3045 0.2522 0.1421 0.0565 0.0255 + 1988 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0 0 0.0202 0.1294 0.2646 0.2471 0.1876 0.1033 0.0477 + 1989 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0 0.0005 0.0187 0.1211 0.2209 0.219 0.1908 0.1197 0.1094 + 1990 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0.0003 0 0.0146 0.0887 0.1801 0.1707 0.1728 0.1431 0.2297 + 1991 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0.0001 0.0005 0.0141 0.0848 0.1651 0.179 0.1739 0.1432 0.2392 + 1992 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0.0003 0.0002 0.0005 0.0095 0.0638 0.1317 0.1673 0.1747 0.1636 0.2886 + 1993 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0 0.0014 0.0138 0.094 0.1789 0.1739 0.1596 0.1331 0.2453 + 1996 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0.0006 0.0006 0.0129 0.0779 0.1407 0.162 0.1771 0.1671 0.2612 + 1997 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0.0004 0.0003 0.0138 0.0899 0.1486 0.1603 0.1699 0.1588 0.258 + 1998 1 1 1 1 0 0 100 0 0 0 0 0 0 0.0001 0.0001 0.0001 0.0001 0.0004 0.0002 0.0008 0.0225 0.1187 0.1596 0.149 0.1432 0.1394 0.266 + 1999 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0.0001 0 0.0001 0.0147 0.1313 0.2575 0.2292 0.1624 0.0961 0.1087 + 2000 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0.0001 0.0001 0 0.0001 0.0003 0.0111 0.0931 0.1945 0.2111 0.1822 0.1247 0.1826 + 2001 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0.0001 0.0001 0.0001 0.0002 0.0002 0.0012 0.0181 0.0836 0.1681 0.1986 0.1953 0.1506 0.1838 + 2002 1 1 1 1 0 0 100 0 0 0 0 0 0 0.0001 0 0.0001 0.0001 0.0001 0 0.0002 0.0151 0.108 0.1884 0.1915 0.1683 0.1334 0.1948 + 2003 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0.0001 0.0001 0.0002 0.0009 0.0243 0.1464 0.232 0.1871 0.1497 0.0994 0.1597 + 2004 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0 0.0002 0.0064 0.0514 0.1302 0.1702 0.1971 0.1632 0.2812 + 2005 1 1 1 1 0 0 100 0 0 0 0 0 0 0.0001 0 0 0 0.0001 0.0001 0.0008 0.015 0.0859 0.1543 0.1661 0.1783 0.1516 0.2475 + 2006 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0.0001 0.0001 0.0004 0.0102 0.0739 0.1905 0.2203 0.1887 0.137 0.1787 + 2007 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0.0002 0.0003 0.0067 0.0871 0.1833 0.1934 0.1846 0.1472 0.1973 + 2008 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0.0001 0.0002 0.01 0.0746 0.1457 0.1619 0.179 0.1625 0.2659 + 2009 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0 0.0002 0.0108 0.1152 0.2215 0.1968 0.1588 0.1084 0.1882 + 2010 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0 0.0003 0.0091 0.0986 0.2244 0.2238 0.1861 0.1144 0.1433 + 2011 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0.0003 0.0001 0.0003 0.0114 0.118 0.2436 0.2292 0.1725 0.1077 0.1169 + 2012 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0.0001 0 0.0001 0 0 0.0044 0.0499 0.1249 0.173 0.1886 0.1654 0.2937 + 2013 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0.0001 0.0001 0 0 0.0001 0.0001 0.0054 0.0525 0.1271 0.1484 0.1657 0.1632 0.3374 +##length proportions of pot discarded males +##Year, ##Year, Seas, Fleet, Sex, Type, Shell, Maturity, Nsamp, DataVec + 1990 1 1 1 2 0 0 100 0.0011 0 0.0011 0.008 0.0046 0.0126 0.0069 0.0378 0.0504 0.0767 0.1226 0.1523 0.1867 0.244 0.0859 0.0092 0 0 0 0 + 1991 1 1 1 2 0 0 100 0.0033 0.0101 0.0197 0.0214 0.0242 0.0394 0.0326 0.063 0.0624 0.0692 0.0641 0.1125 0.1586 0.2154 0.0939 0.0101 0 0 0 0 + 1992 1 1 1 2 0 0 100 0 0.0009 0.0012 0.0111 0.0222 0.0549 0.0869 0.1143 0.1183 0.123 0.118 0.1251 0.1112 0.0807 0.0293 0.0028 0 0 0 0 + 1993 1 1 1 2 0 0 100 0.0019 0.0045 0.0057 0.005 0.0062 0.0122 0.0312 0.0571 0.0778 0.108 0.1334 0.1544 0.1518 0.1705 0.0747 0.0055 0 0 0 0 + 1996 1 1 1 2 0 0 100 0 0 0 0.0131 0.0524 0.083 0.0742 0.0306 0.048 0.0699 0.0611 0.1004 0.1485 0.2009 0.1048 0.0131 0 0 0 0 + 1997 1 1 1 2 0 0 100 0 0.0002 0.0005 0.0007 0.0015 0.0197 0.0553 0.109 0.1268 0.1304 0.1031 0.1002 0.1275 0.1424 0.0751 0.0076 0 0 0 0 + 1998 1 1 1 2 0 0 100 0.0002 0.0005 0.0008 0.0044 0.007 0.01 0.0104 0.0175 0.0391 0.097 0.1402 0.2062 0.2047 0.1811 0.0714 0.0097 0 0 0 0 + 1999 1 1 1 2 0 0 100 0 0 0 0.0086 0.0086 0.0029 0.0076 0.0086 0.0143 0.0286 0.063 0.126 0.2118 0.3244 0.188 0.0076 0 0 0 0 + 2000 1 1 1 2 0 0 100 0.0003 0.0051 0.0192 0.0483 0.0613 0.0576 0.0595 0.0581 0.0532 0.0558 0.0712 0.1059 0.1497 0.1554 0.0895 0.0097 0 0 0 0 + 2001 1 1 1 2 0 0 100 0.0016 0.0057 0.0093 0.0115 0.0155 0.0302 0.0568 0.0866 0.1009 0.1196 0.1239 0.1411 0.1319 0.1128 0.0481 0.0045 0 0 0 0 + 2002 1 1 1 2 0 0 100 0.0012 0.0061 0.006 0.0091 0.0065 0.0104 0.0133 0.0335 0.063 0.1142 0.1543 0.1705 0.1642 0.1582 0.0803 0.0093 0 0 0 0 + 2003 1 1 1 2 0 0 100 0.0081 0.0119 0.0146 0.0317 0.0552 0.0666 0.072 0.067 0.0642 0.0599 0.0655 0.0958 0.1322 0.1708 0.0781 0.0064 0 0 0 0 + 2004 1 1 1 2 0 0 100 0.0004 0.0074 0.0177 0.0403 0.051 0.0483 0.0615 0.1087 0.1384 0.1452 0.1102 0.0849 0.07 0.0688 0.0404 0.0059 0.0008 0 0 0 + 2005 1 1 1 2 0 0 100 0.0002 0.0008 0.0015 0.0029 0.0076 0.022 0.0343 0.0418 0.0454 0.0658 0.0956 0.1376 0.1381 0.1385 0.0729 0.0262 0.0246 0.0349 0.0345 0.075 + 2006 1 1 1 2 0 0 100 0.0003 0.0013 0.0044 0.015 0.0312 0.0377 0.0368 0.0346 0.0452 0.0766 0.0929 0.1144 0.1377 0.1764 0.1275 0.0284 0.0105 0.0085 0.0075 0.0132 + 2007 1 1 1 2 0 0 100 0.0012 0.0042 0.0068 0.0098 0.0171 0.0366 0.0658 0.085 0.0928 0.0857 0.0819 0.0987 0.1291 0.1651 0.0956 0.0126 0.0032 0.0028 0.0022 0.0037 + 2008 1 1 1 2 0 0 100 0.0001 0.0003 0.0012 0.0046 0.0108 0.0141 0.0159 0.0214 0.0441 0.0808 0.1269 0.1793 0.1988 0.1838 0.0983 0.0099 0.0014 0.0018 0.0018 0.0045 + 2009 1 1 1 2 0 0 100 0.0004 0.001 0.0018 0.0032 0.0041 0.0073 0.0178 0.0402 0.0631 0.0705 0.0798 0.118 0.1809 0.2413 0.1455 0.0149 0.0021 0.0016 0.0022 0.0043 + 2010 1 1 1 2 0 0 100 0.0007 0.0011 0.0025 0.0055 0.0085 0.0119 0.0148 0.0218 0.0341 0.0541 0.0962 0.1517 0.2017 0.2373 0.135 0.0137 0.0017 0.0018 0.0016 0.0042 + 2011 1 1 1 2 0 0 100 0.0017 0.0066 0.0112 0.0199 0.0204 0.0188 0.0272 0.0309 0.0409 0.056 0.0756 0.1176 0.1698 0.221 0.1565 0.018 0.0026 0.0017 0.0009 0.0025 + 2012 1 1 1 2 0 0 100 0.0006 0.0008 0.0024 0.0042 0.0111 0.0262 0.0416 0.0563 0.0534 0.057 0.0704 0.106 0.1521 0.2072 0.1468 0.0248 0.0054 0.0085 0.0069 0.0182 + 2013 1 1 1 2 0 0 100 0.0001 0.0016 0.004 0.0052 0.011 0.0137 0.0227 0.0353 0.06 0.0871 0.1253 0.1381 0.1523 0.1563 0.1001 0.0207 0.0088 0.0177 0.0158 0.0242 +##length proportions of pot discarded females +##Year, Seas, Fleet, Sex, Type, Shell, Maturity, Nsamp, DataVec +#length proportions of trawl male bycatch +##Year, Seas, Fleet, Sex, Type, Shell, Maturity, Nsamp, DataVec + 1976 1 2 1 0 0 0 50 0 0 0 0 0 0.013 0.0087 0.0043 0.0216 0.0087 0.026 0.039 0.0433 0.0649 0.0996 0.0866 0.0736 0.0909 0.0649 0.1299 + 1977 1 2 1 0 0 0 50 0.0036 0.0009 0.0009 0.0009 0.0026 0.0035 0.0079 0.0097 0.0317 0.0485 0.0599 0.0996 0.1084 0.1251 0.104 0.1057 0.1004 0.0634 0.0326 0.0441 + 1978 1 2 1 0 0 0 50 0 0 0 0 0 0 0 0.0025 0.0012 0.0025 0.0149 0.0274 0.0511 0.0872 0.1245 0.1158 0.0797 0.0984 0.0672 0.188 + 1979 1 2 1 0 0 0 50 0.0178 0.0013 0.0025 0.0013 0.0025 0.0076 0.0038 0.0025 0.0013 0.0063 0.0051 0.0114 0.0228 0.0556 0.0582 0.0708 0.0898 0.086 0.0809 0.1858 + 1980 1 2 1 0 0 0 50 0.0531 0.0207 0.0096 0.0135 0.0142 0.0163 0.0274 0.0263 0.038 0.0375 0.0422 0.0394 0.0368 0.0377 0.0313 0.0231 0.0207 0.0142 0.0131 0.0265 + 1981 1 2 1 0 0 0 50 0.0262 0.0028 0.0045 0.0066 0.0112 0.0175 0.0279 0.0349 0.0386 0.0504 0.0434 0.048 0.0287 0.0334 0.0241 0.0212 0.0112 0.0064 0.0051 0.0087 + 1982 1 2 1 0 0 0 50 0.0701 0.0268 0.0247 0.0326 0.0356 0.0443 0.0409 0.0403 0.0401 0.0475 0.0426 0.0479 0.0405 0.0326 0.0218 0.0153 0.0084 0.0052 0.0038 0.0099 + 1983 1 2 1 0 0 0 50 0.0231 0.0214 0.0336 0.0344 0.0311 0.0319 0.0377 0.0445 0.0473 0.0471 0.0457 0.0437 0.0409 0.0414 0.0371 0.0283 0.0204 0.0129 0.0096 0.018 + 1984 1 2 1 0 0 0 50 0.0366 0.0156 0.0147 0.0199 0.027 0.0342 0.0399 0.0407 0.0431 0.0476 0.0511 0.0596 0.0594 0.0563 0.0473 0.0355 0.0264 0.017 0.0109 0.0146 + 1985 1 2 1 0 0 0 50 0.0051 0.0014 0.0034 0.0059 0.01 0.0164 0.0256 0.0396 0.0357 0.0446 0.0538 0.0636 0.0843 0.0862 0.0883 0.0843 0.0638 0.0455 0.0299 0.0578 + 1986 1 2 1 0 0 0 50 0.0038 0.0019 0.0085 0.0019 0.0056 0.0136 0.0193 0.0357 0.016 0.0249 0.0221 0.032 0.071 0.0555 0.0527 0.0635 0.0456 0.0362 0.0259 0.0282 + 1987 1 2 1 0 0 0 50 0.002 0 0.001 0.002 0.005 0.008 0.019 0.0271 0.017 0.022 0.0441 0.0491 0.0401 0.0581 0.0852 0.0812 0.0671 0.0611 0.0511 0.0842 + 1988 1 2 1 0 0 0 50 0.0048 0.0048 0.0063 0.0016 0.0032 0 0.0095 0.0174 0.0127 0.0396 0.0523 0.0539 0.0571 0.0634 0.065 0.0887 0.0792 0.0586 0.0349 0.0396 + 1989 1 2 1 0 0 0 50 0.0049 0.0025 0.0019 0.0008 0.0021 0.0021 0.0049 0.0047 0.0098 0.0144 0.0233 0.0373 0.0435 0.0526 0.07 0.0797 0.0787 0.0774 0.0672 0.0895 + 1990 1 2 1 0 0 0 50 0.0052 0.0052 0.0078 0.0017 0.0069 0.0069 0.0225 0.0207 0.038 0.038 0.0225 0.0242 0.0328 0.0484 0.0778 0.0709 0.0691 0.0588 0.0328 0.0674 + 1991 1 2 1 0 0 0 50 0.0032 0.0063 0.0032 0.0063 0.0159 0.0127 0.0127 0.0159 0.0317 0.0222 0.0317 0.0286 0.0349 0.019 0.0254 0.0603 0.0444 0.0571 0.0571 0.1714 + 1992 1 2 1 0 0 0 50 0.0203 0.0203 0.0203 0.0023 0.0068 0.009 0.0135 0.0023 0.0113 0.0158 0.0203 0.0158 0.0293 0.0293 0.0293 0.045 0.0248 0.036 0.0158 0.1149 + 1994 1 2 1 0 0 0 50 0.0035 0.0017 0.0035 0.0069 0.0017 0 0 0 0 0 0.0017 0.0017 0.0087 0.0156 0.0208 0.0468 0.0433 0.0572 0.0832 0.2756 + 1995 1 2 1 0 0 0 50 0.0072 0.029 0.0145 0.0072 0 0.0072 0 0.0072 0.0072 0.0145 0 0.0145 0.0145 0.0145 0.029 0.0652 0.1232 0.0942 0.0507 0.2464 + 1996 1 2 1 0 0 0 50 0.001 0.0015 0.0025 0.003 0.004 0.009 0.014 0.0156 0.0206 0.0276 0.0346 0.0437 0.0341 0.0482 0.0286 0.0447 0.0301 0.0376 0.0286 0.0853 + 1997 1 2 1 0 0 0 50 0 0 0.0018 0.0018 0.0107 0.022 0.0386 0.054 0.0516 0.051 0.0427 0.0291 0.0315 0.035 0.035 0.0309 0.035 0.0427 0.0475 0.1525 + 1998 1 2 1 0 0 0 50 0.0004 0.0004 0.0004 0 0 0.0008 0.0028 0.0035 0.0067 0.013 0.0268 0.0342 0.0547 0.0625 0.0677 0.0673 0.059 0.059 0.0504 0.1306 + 1999 1 2 1 0 0 0 50 0.002 0.0007 0.001 0.0003 0.0007 0 0.0033 0.0017 0.0023 0.0056 0.0083 0.0212 0.0422 0.0707 0.0953 0.1042 0.0979 0.0803 0.0588 0.1185 + 2000 1 2 1 0 0 0 50 0 0 0.0012 0.0006 0.0006 0.003 0.0042 0.0162 0.0222 0.0258 0.0252 0.0426 0.0372 0.0426 0.036 0.0468 0.0414 0.045 0.048 0.158 + 2001 1 2 1 0 0 0 50 0 0.0001 0.001 0.0006 0.0023 0.0071 0.008 0.0111 0.0192 0.0208 0.0224 0.0211 0.0234 0.0265 0.0312 0.0432 0.0593 0.0607 0.0612 0.2159 + 2002 1 2 1 0 0 0 50 0.0004 0.0004 0.0002 0.0019 0.0012 0.0023 0.0017 0.0025 0.005 0.0105 0.0161 0.0203 0.0287 0.0354 0.0486 0.0536 0.0651 0.0703 0.0753 0.2579 + 2003 1 2 1 0 0 0 50 0.0011 0.0008 0.0034 0.0099 0.0145 0.0149 0.0202 0.0122 0.0103 0.0122 0.0118 0.0251 0.0282 0.037 0.0514 0.0564 0.0556 0.051 0.051 0.1303 + 2004 1 2 1 0 0 0 50 0 0.0003 0.0016 0.0047 0.0028 0.0072 0.0094 0.0225 0.026 0.0232 0.0282 0.0238 0.0244 0.0235 0.0291 0.0429 0.0495 0.0469 0.0429 0.1199 + 2005 1 2 1 0 0 0 50 0.0016 0.0016 0.0016 0.0027 0.003 0.0065 0.0084 0.0155 0.0098 0.013 0.0212 0.0298 0.032 0.0336 0.0331 0.0331 0.0372 0.0388 0.0388 0.131 + 2006 1 2 1 0 0 0 50 0.0006 0 0 0 0.0006 0.0014 0.0023 0.0055 0.0075 0.0179 0.0182 0.0234 0.0254 0.03 0.0413 0.0436 0.043 0.0424 0.0367 0.0878 + 2007 1 2 1 0 0 0 50 0 0.0005 0 0.0009 0.0028 0.0019 0.0028 0.0081 0.009 0.0104 0.0171 0.018 0.0194 0.0356 0.0403 0.0403 0.037 0.0403 0.0565 0.1385 + 2008 1 2 1 0 0 0 50 0.0007 0 0.0003 0.001 0.0024 0.0014 0.0021 0.0041 0.0145 0.0237 0.0299 0.0478 0.0533 0.0478 0.0571 0.0399 0.0506 0.0489 0.0499 0.1669 + 2009 1 2 1 0 0 0 50 0.0004 0.0004 0.0004 0.0017 0.0017 0.0021 0.0021 0.0072 0.0102 0.0111 0.0115 0.0247 0.0353 0.0506 0.0591 0.0778 0.074 0.0604 0.0523 0.1471 + 2010 1 2 1 0 0 0 50 0.0025 0.0031 0.0037 0.0025 0.0031 0.0056 0.005 0.0068 0.013 0.0124 0.0155 0.0236 0.0366 0.0366 0.0379 0.0329 0.0323 0.0329 0.0323 0.1174 + 2011 1 2 1 0 0 0 50 0 0.0006 0.0012 0.003 0.003 0.0053 0.0024 0.0047 0.0059 0.0041 0.0053 0.0065 0.0118 0.0207 0.0342 0.0336 0.039 0.0366 0.0336 0.1027 + 2012 1 2 1 0 0 0 50 0 0.0006 0.0003 0.0006 0.0012 0.0015 0.0051 0.0075 0.0105 0.0128 0.0212 0.0248 0.0305 0.0323 0.0385 0.0421 0.0379 0.0415 0.0353 0.127 + 2013 1 2 1 0 0 0 50 0.007 0.0095 0.0147 0.0245 0.0203 0.0178 0.0203 0.0208 0.0225 0.0254 0.0263 0.0322 0.033 0.0303 0.0295 0.0269 0.027 0.0264 0.0256 0.0887 +##length proportions of trawl female bycatch +##Year, Seas, Fleet, Sex, Type, Shell, Maturity, Nsamp, DataVec +##length proportions of survey newshell males +##Year, Seas, Fleet, Sex, Type, Shell, Maturity, Nsamp, DataVec + 1975 1 3 1 1 1 0 200 0.03433 0.06119 0.03631 0.03701 0.03626 0.02684 0.02746 0.02043 0.02199 0.02522 0.02323 0.02322 0.02484 0.02294 0.01909 0.0197 0.0162 0.00957 0.00661 0.01009 + 1976 1 3 1 1 1 0 200 0.00232 0.01279 0.02937 0.05077 0.06104 0.04581 0.04776 0.03559 0.03199 0.02832 0.02984 0.02996 0.02334 0.02354 0.0206 0.01457 0.01294 0.00852 0.00591 0.00568 + 1977 1 3 1 1 1 0 200 0.00722 0.00558 0.00666 0.01007 0.0195 0.037 0.04363 0.04307 0.04013 0.04302 0.03906 0.03772 0.02788 0.02964 0.02865 0.02252 0.0144 0.01024 0.00661 0.00905 + 1978 1 3 1 1 1 0 200 0.00415 0.0114 0.01313 0.02219 0.01618 0.0153 0.0153 0.02585 0.02749 0.02795 0.02833 0.02739 0.02477 0.0294 0.02988 0.02505 0.02385 0.01579 0.00971 0.00755 + 1979 1 3 1 1 1 0 200 0.00801 0.008 0.01059 0.01598 0.01392 0.01592 0.01244 0.01397 0.01354 0.0178 0.02471 0.03399 0.03477 0.03788 0.03207 0.03339 0.02893 0.02384 0.01446 0.02128 + 1980 1 3 1 1 1 0 200 0.00713 0.01445 0.02854 0.0319 0.03189 0.03189 0.02635 0.02638 0.02288 0.01971 0.02217 0.01609 0.02291 0.02541 0.0251 0.0303 0.02546 0.02432 0.02153 0.02725 + 1981 1 3 1 1 1 0 200 0.03277 0.0196 0.01678 0.0252 0.03727 0.03277 0.03133 0.0292 0.02759 0.02966 0.01907 0.01635 0.01061 0.00937 0.00747 0.00654 0.00401 0.00357 0.00143 0.00509 + 1982 1 3 1 1 1 0 200 0.07924 0.08112 0.06821 0.02812 0.02304 0.03021 0.03407 0.02807 0.01868 0.01581 0.0181 0.01276 0.00951 0.00694 0.00436 0.0034 0.00225 0.00053 0.00041 0.00082 + 1983 1 3 1 1 1 0 200 0.03252 0.03556 0.0497 0.06649 0.07859 0.07774 0.05655 0.04214 0.03545 0.03417 0.02308 0.02137 0.01351 0.00898 0.00777 0.00183 0.00084 0 0 0 + 1984 1 3 1 1 1 0 200 0.01493 0.0625 0.13306 0.14261 0.06919 0.03343 0.01442 0.01346 0.0133 0.00938 0.00949 0.00565 0.00568 0.00336 0.00416 0.00175 0.00077 0.00041 0.00002 0.00016 + 1985 1 3 1 1 1 0 200 0.00261 0.01279 0.02442 0.03954 0.0589 0.05817 0.04235 0.04026 0.05909 0.06049 0.05132 0.05049 0.04397 0.04183 0.02443 0.02289 0.00176 0.00319 0.00415 0 + 1986 1 3 1 1 1 0 200 0.01118 0.01788 0.0248 0.0201 0.02318 0.01475 0.03917 0.04 0.05364 0.04764 0.06284 0.06696 0.05865 0.06369 0.04877 0.03519 0.02325 0.00733 0.00143 0.00072 + 1987 1 3 1 1 1 0 200 0.00151 0.00715 0.03314 0.0523 0.04666 0.03193 0.02963 0.02928 0.03029 0.02445 0.03113 0.02335 0.03004 0.02375 0.02059 0.01754 0.01411 0.0133 0.00347 0.00237 + 1988 1 3 1 1 1 0 200 0.00132 0.00098 0.00662 0.01068 0.01094 0.02158 0.04663 0.04339 0.03932 0.03771 0.02571 0.02768 0.01467 0.02865 0.02359 0.03421 0.02539 0.0189 0.00946 0.00793 + 1989 1 3 1 1 1 0 200 0.00151 0.00009 0 0.00228 0.01414 0.032 0.01664 0.03469 0.02244 0.03796 0.0373 0.03601 0.04465 0.05129 0.0334 0.03221 0.02538 0.02108 0.01328 0.01964 + 1990 1 3 1 1 1 0 200 0.00132 0.01104 0.01571 0.03616 0.03285 0.01009 0.0075 0.00623 0.01313 0.02143 0.01949 0.02053 0.02075 0.0213 0.01671 0.02223 0.01615 0.01075 0.01072 0.01925 + 1991 1 3 1 1 1 0 200 0.00103 0.00876 0.0213 0.01581 0.02487 0.01952 0.01114 0.02291 0.02011 0.01171 0.00363 0.01729 0.02907 0.03294 0.04485 0.05331 0.0515 0.04094 0.03382 0.06686 + 1992 1 3 1 1 1 0 200 0.001 0 0.00202 0.01106 0.0252 0.03333 0.05097 0.04886 0.03395 0.03348 0.02591 0.03451 0.02322 0.0146 0.01108 0.01594 0.01162 0.01399 0.01176 0.02854 + 1993 1 3 1 1 1 0 200 0.00208 0.01094 0.01291 0.00906 0.00804 0.01357 0.01066 0.01917 0.01955 0.03344 0.02444 0.04147 0.02119 0.01732 0.00967 0.00822 0.00732 0.00891 0.00577 0.00787 + 1994 1 3 1 1 1 0 200 0.00162 0 0.00309 0.02093 0.01757 0.01239 0.01098 0.01082 0.01688 0.03227 0.03069 0.02792 0.03848 0.05112 0.02013 0.02458 0.02607 0.01992 0.01064 0.01519 + 1995 1 3 1 1 1 0 200 0.02826 0.06829 0.05574 0.02203 0.01101 0.01592 0.02133 0.02355 0.02568 0.02873 0.02066 0.02201 0.02408 0.02322 0.035 0.02166 0.01749 0.01473 0.00622 0.01125 + 1996 1 3 1 1 1 0 200 0.02719 0.01292 0.02918 0.05291 0.06042 0.05874 0.02691 0.01981 0.01098 0.01462 0.01337 0.01035 0.00912 0.00319 0.00622 0.00716 0.00659 0.00938 0.0111 0.01276 + 1997 1 3 1 1 1 0 200 0 0.00357 0.00221 0.00519 0.0127 0.05636 0.09427 0.10657 0.09022 0.05071 0.02796 0.0136 0.01212 0.00935 0.01131 0.01348 0.01555 0.0103 0.00979 0.02598 + 1998 1 3 1 1 1 0 200 0.02085 0.01739 0.01031 0.01272 0.012 0.01014 0.01345 0.01472 0.02013 0.04373 0.04263 0.03912 0.03466 0.01846 0.00647 0.00737 0.00442 0.0029 0.00124 0.00345 + 1999 1 3 1 1 1 0 200 0.05825 0.02444 0.01335 0.01038 0.01196 0.01036 0.00963 0.01225 0.00326 0.00664 0.01252 0.02202 0.04148 0.0395 0.05441 0.05623 0.02925 0.01972 0.01072 0.0114 + 2000 1 3 1 1 1 0 200 0.00175 0.00473 0.01944 0.03949 0.03095 0.01993 0.02272 0.01626 0.01888 0.01404 0.01099 0.02078 0.01298 0.02074 0.01385 0.0111 0.01148 0.00855 0.00427 0.0067 + 2001 1 3 1 1 1 0 200 0.00689 0.00496 0.01061 0.0149 0.0156 0.04136 0.03572 0.05159 0.03394 0.01999 0.02186 0.0132 0.00984 0.01223 0.00775 0.00551 0.01066 0.01006 0.01014 0.0124 + 2002 1 3 1 1 1 0 200 0.05335 0.06381 0.0436 0.02682 0.01193 0.00793 0.00606 0.00736 0.01535 0.01781 0.02124 0.02041 0.01045 0.00875 0.00999 0.00631 0.00525 0.00883 0.00623 0.00503 + 2003 1 3 1 1 1 0 200 0.01604 0.0074 0.0154 0.02495 0.04249 0.0342 0.03247 0.018 0.00959 0.01396 0.01125 0.02279 0.01875 0.02908 0.02324 0.02414 0.01482 0.00971 0.00796 0.02164 + 2004 1 3 1 1 1 0 200 0.04684 0.03651 0.03383 0.02365 0.02226 0.01926 0.02833 0.04015 0.03578 0.0352 0.0264 0.02019 0.01236 0.01273 0.0128 0.01815 0.01566 0.02153 0.01193 0.025 + 2005 1 3 1 1 1 0 200 0.03525 0.05861 0.04185 0.01599 0.00976 0.02277 0.02344 0.02146 0.01842 0.01622 0.02073 0.02207 0.01265 0.01714 0.00954 0.01168 0.00648 0.00646 0.00805 0.01227 + 2006 1 3 1 1 1 0 200 0.01329 0.01976 0.01658 0.02765 0.02838 0.03548 0.01857 0.02076 0.01179 0.017 0.0105 0.01205 0.01881 0.01862 0.02997 0.02605 0.02056 0.01732 0.01059 0.01291 + 2007 1 3 1 1 1 0 200 0.00172 0.00246 0.00532 0.00837 0.01967 0.02715 0.03091 0.04028 0.03332 0.02419 0.01566 0.01804 0.01517 0.02261 0.01747 0.01805 0.0179 0.01359 0.01535 0.01691 + 2008 1 3 1 1 1 0 200 0 0.00076 0.00363 0.00577 0.01395 0.01669 0.01814 0.0223 0.03342 0.04313 0.03802 0.02547 0.02337 0.01707 0.01364 0.01039 0.01454 0.01071 0.00832 0.01802 + 2009 1 3 1 1 1 0 200 0.00095 0.00048 0.0037 0.00527 0.00532 0.01039 0.00965 0.02253 0.03192 0.02616 0.0236 0.02484 0.02844 0.04127 0.02429 0.02658 0.01436 0.01032 0.00775 0.0067 + 2010 1 3 1 1 1 0 200 0 0.00334 0.00803 0.00943 0.00774 0.00538 0.01608 0.01344 0.01295 0.01526 0.02418 0.03048 0.02201 0.0223 0.02723 0.02567 0.0316 0.01894 0.01048 0.0095 + 2011 1 3 1 1 1 0 200 0.00362 0.00438 0.0125 0.02044 0.01569 0.01317 0.01676 0.01505 0.01822 0.01195 0.01613 0.0164 0.01359 0.0199 0.01732 0.01617 0.01904 0.01323 0.00578 0.00808 + 2012 1 3 1 1 1 0 200 0.00247 0.00398 0.01202 0.01593 0.01281 0.0227 0.03362 0.02474 0.01742 0.01742 0.01461 0.01733 0.01843 0.01958 0.01581 0.01519 0.01481 0.01651 0.00795 0.02737 + 2013 1 3 1 1 1 0 200 0.00082 0.00253 0.01232 0.01451 0.01006 0.01741 0.01341 0.02352 0.02798 0.02607 0.03135 0.02742 0.02114 0.01964 0.01842 0.01501 0.01278 0.01693 0.0211 0.03167 + 2014 1 3 1 1 1 0 200 0 0.00046 0.00259 0.003 0.01598 0.03132 0.04239 0.03212 0.02832 0.01706 0.02131 0.02572 0.02618 0.02269 0.02763 0.01884 0.01393 0.00987 0.00856 0.01333 + + ##length proportions of survey oldshell males + ##Year, Seas, Fleet, Sex, Type, Shell, Maturity, Nsamp, DataVec + 1975 1 3 1 0 2 0 200 0 0.00011 0 0.00022 0 0.00011 0 0.00085 0.00065 0.0015 0.00086 0.00138 0.00171 0.00137 0.00195 0.00362 0.00184 0.00198 0.00188 0.00076 + 1976 1 3 1 0 2 0 200 0 0 0 0.00004 0.00004 0 0 0.00002 0.00052 0.00042 0.00093 0.00365 0.00268 0.00508 0.00529 0.00393 0.00422 0.00497 0.00294 0.00151 + 1977 1 3 1 0 2 0 200 0 0 0 0 0 0.00041 0.00065 0.00018 0.00068 0.00083 0.00118 0.0024 0.00243 0.00212 0.00307 0.00309 0.00184 0.00341 0.00157 0.00302 + 1978 1 3 1 0 2 0 200 0.00014 0.00055 0.00048 0.00182 0.00106 0.00376 0.00253 0.00205 0.00207 0.00181 0.00171 0.00297 0.00421 0.00726 0.00476 0.00321 0.00216 0.00149 0.00113 0.00156 + 1979 1 3 1 0 2 0 200 0.00015 0.00093 0.00064 0.00022 0.00073 0.00111 0.00024 0.00039 0.00039 0.00087 0.00105 0.00202 0.00181 0.00378 0.0043 0.00378 0.00524 0.0044 0.00132 0.00393 + 1980 1 3 1 0 2 0 200 0 0 0 0 0 0.00045 0.0003 0 0 0.00016 0.00038 0.00045 0.00097 0.00121 0.0018 0.00285 0.00174 0.00295 0.00104 0.00401 + 1981 1 3 1 0 2 0 200 0.00016 0 0.00061 0 0.001 0.00073 0.00059 0.00247 0.00146 0.00418 0.00419 0.00537 0.00795 0.00898 0.00711 0.00801 0.0066 0.00669 0.00476 0.00952 + 1982 1 3 1 0 2 0 200 0 0 0 0.00055 0.00095 0.00079 0.0012 0.00065 0.00105 0.00129 0.00173 0.00135 0.00355 0.00097 0.00222 0.00093 0.00169 0 0 0.00094 + 1983 1 3 1 0 2 0 200 0 0 0 0 0.00146 0.00051 0.00342 0.00467 0.00427 0.00572 0.00909 0.00952 0.0055 0.00294 0.0029 0.00185 0.00166 0.00123 0 0 + 1984 1 3 1 0 2 0 200 0 0.00012 0.00014 0.00003 0.00017 0.00004 0.00044 0.00027 0.00024 0.00267 0.00045 0.00024 0.00082 0.00085 0.00249 0.00063 0.00002 0.00051 0 0.00013 + 1985 1 3 1 0 2 0 200 0 0 0 0 0 0 0 0 0.00106 0.0009 0 0.00182 0.00573 0 0.00351 0.00085 0 0.00191 0 0 + 1986 1 3 1 0 2 0 200 0 0 0 0 0 0.00088 0.00162 0 0.00224 0.00088 0.00462 0.00643 0.01135 0.01506 0.00757 0.00329 0.0042 0 0.0015 0.0016 + 1987 1 3 1 0 2 0 200 0 0 0 0 0.00039 0.00039 0 0.00041 0.00082 0.00119 0.00226 0.0036 0.00689 0.01094 0.00869 0.01119 0.00436 0.00251 0.00038 0.00161 + 1988 1 3 1 0 2 0 200 0 0 0 0 0.00205 0 0 0 0 0 0.0008 0.00288 0.00569 0.00855 0.00952 0.01509 0.01151 0.00793 0 0.00135 + 1989 1 3 1 0 2 0 200 0 0 0.00081 0 0 0 0 0.00009 0.00146 0.00516 0.0015 0.00074 0.00748 0.00942 0.0216 0.03086 0.02302 0.02473 0.01384 0.00653 + 1990 1 3 1 0 2 0 200 0 0 0 0 0.00072 0 0.00072 0.00071 0.00255 0.00453 0.00316 0.00923 0.01085 0.01496 0.01888 0.01774 0.0133 0.02177 0.00869 0.01368 + 1991 1 3 1 0 2 0 200 0 0 0.00058 0.00059 0.00112 0.0017 0.0023 0.0039 0.00156 0.00516 0.00215 0.00336 0.00581 0.00497 0.01474 0.01452 0.01304 0.00898 0.00688 0.01173 + 1992 1 3 1 0 2 0 200 0 0 0 0.00165 0 0.00217 0.00423 0.00391 0.00423 0.00645 0.00318 0.0033 0.01161 0.01343 0.01228 0.00739 0.01026 0.01666 0.00509 0.02109 + 1993 1 3 1 0 2 0 200 0 0 0.00069 0.00137 0.00145 0.00203 0.00344 0.00422 0.01136 0.01032 0.01999 0.02171 0.0285 0.02464 0.02295 0.02012 0.02286 0.01946 0.01823 0.03231 + 1994 1 3 1 0 2 0 200 0 0 0 0.00277 0.00591 0.00277 0.00138 0.00651 0.00443 0.0031 0.01053 0.01238 0.02425 0.03959 0.02727 0.02154 0.02073 0.01281 0.0123 0.03521 + 1995 1 3 1 0 2 0 200 0 0 0 0 0 0.00099 0.00086 0.00198 0.0018 0.00173 0.0056 0.00478 0.01026 0.01699 0.01402 0.02162 0.01481 0.00904 0.00454 0.0149 + 1996 1 3 1 0 2 0 200 0.00062 0.00062 0.00062 0 0.00274 0.00064 0.00065 0.00268 0.00072 0.00324 0.00066 0.00466 0.00482 0.00979 0.01555 0.00931 0.01244 0.00776 0.00717 0.01245 + 1997 1 3 1 0 2 0 200 0 0 0 0 0 0 0 0.00041 0.00075 0.00083 0.00216 0.00257 0.00276 0.00386 0.00289 0.00335 0.00782 0.00651 0.00752 0.01417 + 1998 1 3 1 0 2 0 200 0 0 0 0 0 0 0 0.00217 0.0025 0.00293 0.00589 0.0132 0.01047 0.01061 0.01185 0.00788 0.01513 0.01058 0.00671 0.02105 + 1999 1 3 1 0 2 0 200 0 0 0 0 0 0.00062 0.0025 0.00253 0.00142 0.00658 0.00563 0.00129 0.01054 0.01416 0.01567 0.01262 0.01435 0.01064 0.01136 0.01386 + 2000 1 3 1 0 2 0 200 0 0 0 0 0 0 0 0 0.00112 0.00061 0.00239 0.00876 0.01636 0.02809 0.02766 0.02479 0.02271 0.01431 0.0042 0.01289 + 2001 1 3 1 0 2 0 200 0 0 0 0 0 0.00073 0.00143 0.00075 0.00067 0 0.00347 0.00344 0.00412 0.00794 0.00542 0.00565 0.01123 0.00906 0.00907 0.02029 + 2002 1 3 1 0 2 0 200 0 0 0 0.00041 0 0.00114 0.00154 0.00326 0.00757 0.0088 0.0135 0.00862 0.0098 0.01641 0.00701 0.01303 0.01423 0.01333 0.01792 0.02237 + 2003 1 3 1 0 2 0 200 0 0 0 0.0004 0 0.00037 0.00077 0.00039 0.00188 0.00155 0.00156 0.0036 0.00356 0.0062 0.00894 0.00726 0.00734 0.00652 0.00595 0.01452 + 2004 1 3 1 0 2 0 200 0 0 0 0 0 0.00062 0.00051 0.00014 0.00032 0.00034 0 0.00034 0.00007 0.00044 0.0037 0.00377 0.00384 0.00503 0.0037 0.01012 + 2005 1 3 1 0 2 0 200 0 0 0 0 0 0 0 0 0 0.00091 0.00113 0.00119 0.00323 0.00177 0.00295 0.00415 0.00385 0.00899 0.00632 0.01294 + 2006 1 3 1 0 2 0 200 0 0 0.00071 0 0.00073 0.00144 0.00241 0 0.00111 0.00175 0.0011 0.00076 0.00473 0.00186 0.00289 0.00183 0.00646 0.00255 0.00377 0.01163 + 2007 1 3 1 0 2 0 200 0 0 0 0 0 0 0.00369 0.00339 0.00527 0.00455 0.00307 0.00526 0.00834 0.00878 0.00976 0.01062 0.00969 0.01252 0.00746 0.01193 + 2008 1 3 1 0 2 0 200 0 0 0 0.00074 0.00037 0.00148 0.00074 0.00075 0.00203 0.00037 0.0024 0.00393 0.00599 0.00862 0.00625 0.00585 0.00539 0.00811 0.00765 0.01503 + 2009 1 3 1 0 2 0 200 0 0 0 0 0 0 0 0 0.00101 0.00386 0.00786 0.00793 0.00778 0.0066 0.00689 0.00625 0.00537 0.00593 0.00704 0.01014 + 2010 1 3 1 0 2 0 200 0 0 0 0 0 0 0 0 0 0 0.00278 0.00578 0.00817 0.01021 0.00947 0.00903 0.01066 0.00728 0.00404 0.01046 + 2011 1 3 1 0 2 0 200 0 0 0 0 0.00118 0.00061 0 0 0 0.00123 0.00193 0.00385 0.00252 0.00962 0.0101 0.00952 0.00507 0.00714 0.00576 0.0083 + 2012 1 3 1 0 2 0 200 0 0 0 0 0 0 0 0 0 0 0.00071 0.00222 0.00326 0.00686 0.0076 0.00575 0.00834 0.0116 0.00523 0.01605 + 2013 1 3 1 0 2 0 200 0 0 0 0 0 0 0 0 0 0 0.00091 0.0074 0.00914 0.01228 0.01594 0.01743 0.02119 0.02615 0.01835 0.04324 + 2014 1 3 1 0 2 0 200 0 0 0 0 0 0 0.00129 0.00267 0.00295 0.00214 0.00176 0.00686 0.00739 0.00817 0.00961 0.00696 0.00844 0.00901 0.00943 0.0306 +##length proportions of survey females +##Year, ##Year, Seas, Fleet, Sex, Type, Shell, Maturity, Nsamp, DataVec +##Year, Seas, Fleet, Sex, Type, Shell, Maturity, Nsamp, DataVec + 2007 1 4 1 0 0 0 628 0.0045 0.0074 0.0103 0.0155 0.0198 0.0321 0.0532 0.0491 0.0443 0.0354 0.0268 0.0231 0.0236 0.0256 0.0223 0.032 0.0246 0.0218 0.017 0.0278 + 2008 1 4 1 0 0 0 907 0.0017 0.001 0.0093 0.0119 0.0175 0.0279 0.0267 0.0348 0.0428 0.0596 0.0581 0.0455 0.0371 0.0284 0.0218 0.0211 0.0156 0.0157 0.0202 0.0294 +## Growth data (increment) +# nobs_growth +20 +## Note SM used loewss regression for males BBRKC data +## and cubic spine to interpolate 3 sets of female BBRKC data +# MidPoint Sex Increment CV + 67.5 1 16.510674 0.2 + 72.5 1 16.454438 0.2 + 77.5 1 16.398615 0.2 + 82.5 1 16.343118 0.2 + 87.5 1 16.287715 0.2 + 92.5 1 16.23213 0.2 + 97.5 1 16.176368 0.2 + 102.5 1 16.123732 0.2 + 107.5 1 16.069744 0.2 + 112.5 1 16.013906 0.2 + 117.5 1 15.957058 0.2 + 122.5 1 15.900084 0.2 + 127.5 1 15.843143 0.2 + 132.5 1 15.786395 0.2 + 137.5 1 15.732966 0.2 + 142.5 1 15.68064 0.2 + 147.5 1 15.628775 0.2 + 152.5 1 15.577259 0.2 + 157.5 1 15.526092 0.2 + 162.5 1 15.475241 0.2 +## eof +9999 diff --git a/examples/bbrkc/clean_gmacs.bat b/examples/bbrkc/clean_gmacs.bat deleted file mode 100644 index 73fbbdaf..00000000 --- a/examples/bbrkc/clean_gmacs.bat +++ /dev/null @@ -1,11 +0,0 @@ -del admodel.* -del gmacs.b0* -del gmacs.p0* -del gmacs.r0* -del gmacs.eva -del gmacs.log -del gmacs.bar -del *.rpt - - - diff --git a/examples/bbrkc/forecast.gm b/examples/bbrkc/forecast.gm deleted file mode 100644 index 1a18d7cd..00000000 --- a/examples/bbrkc/forecast.gm +++ /dev/null @@ -1,6 +0,0 @@ -# Gmacs Forecast File Version 1.02 - -1995 2010 # Start and end years for BMSY calculation -#1 # BMSY option [1 is Tier 3, 0 is other]. - -999 # EOF check. diff --git a/examples/bbrkc/get_gmacs.bat b/examples/bbrkc/get_gmacs.bat deleted file mode 100644 index 9be32191..00000000 --- a/examples/bbrkc/get_gmacs.bat +++ /dev/null @@ -1 +0,0 @@ -copy C:\Dropbox\Github\gmacs\src\gmacs.exe C:\Dropbox\Github\gmacs\examples\bbrkc\gmacs.exe diff --git a/examples/bbrkc/gmacs.dat b/examples/bbrkc/gmacs.dat new file mode 100644 index 00000000..0ff307ec --- /dev/null +++ b/examples/bbrkc/gmacs.dat @@ -0,0 +1,2 @@ +bbrkc_ss.dat +bbrkc_ss.ctl diff --git a/examples/bbrkc/gmacs_bbrkc.r b/examples/bbrkc/gmacs_bbrkc.r deleted file mode 100644 index 7595c8ae..00000000 --- a/examples/bbrkc/gmacs_bbrkc.r +++ /dev/null @@ -1,95 +0,0 @@ -#========================================================================================================= -# -# Gmacs.r : Version 1.0 (January 2014) -# R script: Import content from Gmacs model output; produce plots. -# Authors: Athol R. Whitten, James N. Ianelli -# Updated: January 2014 -# -# Acknowledgements: 'Read' functions based on code developed for ADMB by Steve Martell -# Some plotting functions based on code developed for Stock Synthesis by Ian Taylor (r4ss). -# -# Returns: A list containing elements of gmacs_r.rep -# Plots: Various fits to data, summary statistics. -# -#========================================================================================================= - -# Remove previous R console objects; load required packages: -rm(list=ls()) - -#======================================= -# Set and load directories/files -#======================================= -layout(matrix(1:8, 4, 2, byrow = TRUE)) -# Set directory and source read-in script: -#rootdir <- "C:/Dropbox/Gmacs" -#setwd(rootdir) -source('reptoRlist.r') -?layout - -# Read and assign gmacs_r.rep output file: -gmout <- reptoRlist('gmacs_r.rep') -names(gmout) -summary(gmout) -# -------------------------------------------------------------------------------------------------------- - -# Plot fits to catch data (main fisheries): -plot(1, type="n", main="Fit to catch data", xlab="Years", ylab ="Catch (tonnes)", xlim=(c(min(gmout$years),max(gmout$years)+1)), ylim=c(0,max(gmout$catch_biom_obs[2, ])), cex.main=1.2) -nfleet_ret <- 2 -for(ifleet in nfleet_ret) - { - abline(h=0) - lines(gmout$years, gmout$catch_biom_obs[ifleet, ], type="p", pch=20, col=ifleet, cex=1.2) - lines(gmout$years, gmout$catch_biom_pred[ifleet, ], type= "l", col=ifleet+2, lwd=2) - legend("topright", legend=c("Observed","Predicted"), pch=20, col=c(ifleet,ifleet+2), bty="n") - } -# Plot fits to catch data (main fisheries): -plot(1, type="n", main="Fit to catch data", xlab="Years", ylab ="Catch (tonnes)", xlim=(c(min(gmout$years),max(gmout$years)+1)), ylim=c(0,max(gmout$catch_biom_obs[3, ])), cex.main=1.2) -nfleet_ret <- 3 -for(ifleet in nfleet_ret) -{ - abline(h=0) - lines(gmout$years, gmout$catch_biom_obs[ifleet, ], type="p", pch=20, col=ifleet, cex=1.2) - lines(gmout$years, gmout$catch_biom_pred[ifleet, ], type= "l", col=ifleet+2, lwd=2) - legend("topright", legend=c("Observed","Predicted"), pch=20, col=c(ifleet,ifleet+2), bty="n") -} - -# Plot fits to survey data: -plot(1, type="n", main="Fit to survey data", xlab="Years", ylab ="Survey Observation", xlim=(c(min(gmout$years),max(gmout$years)+1)), ylim=c(0,max(c(gmout$survey_num_pred[1, ],gmout$survey_num_obs[1, ]))), cex.main=1.2) - -# Survey 1 (NMFS) -nsurvey <- 1 -for(isrv in 1:nsurvey) -{ - lines(gmout$yr_survey[isrv,], gmout$survey_num_obs[isrv, ], type="p", pch=20, col=isrv, cex=1.2) - lines(gmout$yr_survey[isrv,], gmout$survey_num_pred[isrv, ], type= "l", col=isrv+2, lwd=2) - legend("topright", legend=c("Observed","Predicted"), pch=20, col=c(isrv,isrv+2), bty='n') -} - -# Survey 2 (BRSF) -nsurvey <- 2 -for(isrv in 1:nsurvey) -{ - lines(gmout$yr_survey[isrv,], gmout$survey_num_obs[isrv, ], type="p", pch=20, col=isrv, cex=1.2) - lines(gmout$yr_survey[isrv,], gmout$survey_num_pred[isrv, ], type= "l", col=isrv+2, lwd=2) - legend("topright", legend=c("Observed","Predicted"), pch=20, col=c(isrv,isrv+2), bty='n') -} - - -# Plot Selectivity -plot(1:5,gmout$select_fish_2[43,2:6], type="b", main="Selectivity", xlab="Size bin", ylab ="selectivity" , pch=19,col="blue",cex.main=1.2) -for(i in 1:43) -{ -# lines(1:5, gmout$select_fish_2[i,2:6]) - lines(1:5, gmout$select_fish_1[i,2:6],col="salmon") - lines(1:5, gmout$select_fish_3[i,2:6],col="grey") -} -# Plot Natural mortality -plot(gmout$years,gmout$M, type="b", main="Natural mortality", xlab="Years", ylab ="M", xlim=(c(min(gmout$years),max(gmout$years)+1)), ylim=c(0,max(gmout$M)), pch=19,col="blue",cex.main=1.2) - -# Plot Recruitment -plot(gmout$years,gmout$recruits, type="b", main="Recruits", xlab="Years", ylab ="Recruits", xlim=(c(min(gmout$years),max(gmout$years)+1)), ylim=c(0,max(gmout$recruits)), pch=19,col="blue",cex.main=1.2) - -# Plot Fishign mortality rate -plot(gmout$exp_rate_2[,1], gmout$exp_rate_2[,2], type="b", main="Exploitation rate", xlab="Years", ylab ="rate", xlim=(c(min(gmout$years),max(gmout$years)+1)), ylim=c(0,max(gmout$exp_rate_2[,2])), pch=19,col="red",cex.main=1.2) -#========================================================================================================= -# EOF diff --git a/examples/bbrkc/growth.dat b/examples/bbrkc/growth.dat deleted file mode 100644 index 7316d304..00000000 --- a/examples/bbrkc/growth.dat +++ /dev/null @@ -1,978 +0,0 @@ -# Gmacs Growth Data File Version 1.02 - -1990 # Start year -2010 # End year -46 # Number of growth data classes - -# Growth bins (n = number of growth data classes) -50 60 70 80 90 100 110 120 130 140 150 160 170 180 190 200 210 220 230 240 250 260 270 280 290 300 310 320 330 340 350 360 370 380 390 400 410 420 430 440 450 460 470 480 490 500 - -#Array of year specific growth matrices -#1990 - 0 0 0 0 0.00133675 0.0324045 0.254607 0.458267 0.22968 0.0231787 0.000526174 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0.00333498 0.0533849 0.324131 0.452343 0.154451 0.0121431 0.000213115 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0.000453163 0.0070091 0.0930088 0.380861 0.407959 0.105681 0.005028 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0.000520159 0.0111913 0.153175 0.424476 0.339763 0.0676304 0.00324381 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0.000448805 0.0305227 0.199215 0.456331 0.276417 0.0365418 0.000523144 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0.0043572 0.0444236 0.270041 0.45554 0.203572 0.0220666 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0.000738428 0.00840115 0.081239 0.332364 0.410787 0.153395 0.0130492 2.64718e-05 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0.00068828 0.0159082 0.138702 0.36236 0.364331 0.105575 0.0124349 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0.00113268 0.038097 0.167636 0.402302 0.315543 0.0720674 0.00322166 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0.00629633 0.0545743 0.226412 0.405469 0.25567 0.0499266 0.0015445 0.000108204 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0.000390005 0.016285 0.0840198 0.278344 0.385501 0.193159 0.0398403 0.00246098 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0.00215508 0.0205838 0.125874 0.32606 0.339327 0.161665 0.0236229 0.000712614 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0.000967197 0.00307298 0.0368169 0.167732 0.33972 0.311853 0.116976 0.0220905 0.000770557 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000124394 0.0118763 0.067295 0.195629 0.343386 0.266478 0.102259 0.0121014 0.000851199 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000406355 0.00364864 0.0235386 0.086016 0.234875 0.329746 0.239976 0.071026 0.0107669 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000791211 0.00674598 0.0331394 0.114521 0.271393 0.305019 0.20553 0.0574954 0.00534719 1.86785e-05 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000105328 0.002691 0.0103895 0.0543404 0.136734 0.283102 0.29827 0.166715 0.0418091 0.00572236 0.000121222 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 6.14926e-06 0.00328719 0.0191976 0.073839 0.161703 0.299331 0.26523 0.139697 0.0327269 0.00498152 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000736251 0.0067449 0.0308754 0.0910791 0.201316 0.285741 0.241081 0.114656 0.0245066 0.00326422 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00203042 0.0110969 0.041385 0.109617 0.221386 0.288955 0.205871 0.0952725 0.0217279 0.00183123 0.000826913 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00546016 0.0109988 0.0595121 0.134438 0.249821 0.250305 0.193843 0.0745024 0.0194181 0.001701 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00152231 0.0104717 0.0243503 0.0727925 0.156146 0.239183 0.243418 0.178623 0.0569522 0.0163451 0.000195849 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00312501 0.00922599 0.0376171 0.0963147 0.17019 0.249971 0.218394 0.151146 0.0504721 0.0117763 0.00176741 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000588789 0.00453531 0.014457 0.0539276 0.102383 0.199439 0.238774 0.204672 0.124751 0.0461701 0.00901681 0.00128633 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000163136 0.00265709 0.00554343 0.0202207 0.0622603 0.129085 0.200681 0.237316 0.18947 0.106561 0.0374132 0.00778666 0.000842489 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.0018038 0.00304848 0.00500124 0.0335015 0.0795546 0.139175 0.213105 0.218504 0.171166 0.0926174 0.0350252 0.00695295 0.000545078 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00147731 0.0053298 0.0154413 0.0421698 0.0903488 0.153509 0.21735 0.199972 0.168388 0.0738483 0.0268637 0.00508168 0.000221212 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000190483 0.00210436 0.00434576 0.0252213 0.0552623 0.0963935 0.165508 0.222164 0.185411 0.147909 0.0679005 0.0225639 0.00391955 0.000938174 0.000169603 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000116612 0.000883388 0.00296785 0.0115303 0.028918 0.0717691 0.105847 0.184632 0.206099 0.173095 0.129376 0.0534749 0.0266348 0.00421789 0.000438592 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.001 0.000984039 0.00441982 0.0126396 0.0378217 0.0743413 0.128417 0.192578 0.190654 0.170623 0.115109 0.0495137 0.015579 0.0063199 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000192492 0.0017864 0.0020724 0.00572201 0.0204039 0.0488638 0.0774368 0.146379 0.194711 0.177784 0.16113 0.100658 0.0396791 0.021444 0.00173731 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00485328 0.0123356 0.0252951 0.0514561 0.103997 0.153971 0.18499 0.172499 0.147593 0.0847336 0.0397801 0.0161632 0.00228175 5.12608e-05 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00138605 0.00543131 0.0147395 0.0325456 0.0649314 0.111229 0.158607 0.189564 0.162551 0.132387 0.0783278 0.0338533 0.0136679 0.00077935 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00128021 0.00257376 0.00607212 0.0212315 0.0457318 0.0700786 0.115364 0.16278 0.181027 0.15051 0.138624 0.0633793 0.033919 0.00642877 0.000976167 2.38329e-05 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00103082 0.00211909 0.0102202 0.0301494 0.0560565 0.0727491 0.128029 0.172582 0.168194 0.145461 0.120005 0.0547734 0.0295288 0.00810114 0.000447843 0.000552157 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.0022494 0.000908042 0.00346605 0.0126334 0.0291583 0.0664719 0.0897182 0.13366 0.172287 0.164691 0.128782 0.108676 0.0576781 0.020453 0.00709115 0.00113523 0.000941661 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00185498 0.0040902 0.00570596 0.0174257 0.0403225 0.0650787 0.0940213 0.146511 0.165511 0.166497 0.124484 0.0893694 0.0505262 0.0212064 0.00648365 0.000913229 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000805152 0.000856244 0.0013386 0.00149857 0.00914373 0.0220608 0.0465396 0.0695044 0.113889 0.145987 0.171296 0.134404 0.136142 0.0748879 0.0429896 0.0223967 0.00552741 0.000732936 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000170325 0.00242019 0.000997217 0.002791 0.0152007 0.028221 0.0512603 0.0815204 0.114455 0.152162 0.160387 0.136873 0.115099 0.0727883 0.03736 0.0220529 0.00613945 0.000103249 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000366328 0.00401898 0.00553868 0.0140307 0.0356245 0.0612091 0.0899783 0.131824 0.147547 0.145743 0.136631 0.0980279 0.0659742 0.045073 0.0104855 0.00581878 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 2.14804e-06 0.00200433 0.00370305 0.00901776 0.0179202 0.0493073 0.0616645 0.0954474 0.131226 0.152122 0.144082 0.123331 0.0980354 0.0612089 0.0314573 0.0149505 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 3.75847e-05 0.00176993 0.00299563 0.00694273 0.0113989 0.0270166 0.0484821 0.0603479 0.0990648 0.143227 0.15812 0.133007 0.114297 0.0889985 0.057703 0.0338508 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00141338 0.00603445 0.00544992 0.014222 0.0274445 0.0582186 0.0742389 0.110545 0.142402 0.14395 0.129414 0.111061 0.0802124 0.0531645 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00016296 0.00083704 0.00260977 0.00469009 0.00949461 0.0237753 0.0367092 0.0466949 0.0872611 0.1216 0.139961 0.139695 0.117327 0.101665 0.0866594 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000244504 0.00168773 0.00308982 0.00484254 0.0126409 0.0219563 0.043358 0.0563557 0.0888345 0.135203 0.139788 0.132082 0.114536 0.104092 -#1991 - 0 0 0 0 0 0 0.00752112 0.71771 0.274757 1.20176e-05 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0.0485899 0.850183 0.101227 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0.000358241 0.168769 0.806124 0.0247489 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0.00124951 0.380245 0.6153 0.00320568 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0.00758076 0.621222 0.370885 0.000311914 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0.0412676 0.785035 0.173668 2.96531e-05 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0.134281 0.800593 0.0651259 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0.00187056 0.312712 0.666 0.019417 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0.00955378 0.519029 0.467092 0.00432493 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 4.25117e-05 0.0421829 0.684237 0.272788 0.000749507 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000233901 0.125518 0.738255 0.135993 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00254586 0.268161 0.672466 0.0568275 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.0161649 0.437887 0.523351 0.0225972 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 3.19351e-05 0.0534798 0.579784 0.361651 0.00505332 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00281877 0.114661 0.669312 0.210423 0.002785 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00896999 0.229847 0.645254 0.115655 0.000274094 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000948041 0.0216805 0.366808 0.551423 0.059128 1.23991e-05 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00111995 0.0542638 0.496315 0.426084 0.0222173 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00602365 0.11779 0.573964 0.290563 0.0116589 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00975233 0.211188 0.587925 0.185634 0.00550107 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00165382 0.0259164 0.318682 0.543765 0.108238 0.0017448 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00200961 0.0644067 0.419953 0.457465 0.0556386 0.00052781 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000143665 0.00852957 0.117062 0.498475 0.344688 0.0305623 0.000538355 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000106554 0.0184051 0.186555 0.53214 0.247415 0.0153116 6.64774e-05 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00146319 0.0396608 0.280399 0.502982 0.166744 0.00875096 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00456037 0.0712068 0.361799 0.453103 0.106434 0.00289716 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000517014 0.0106034 0.119051 0.428846 0.377599 0.0613465 0.0020376 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000814075 0.0255707 0.174632 0.47119 0.290633 0.0363088 0.000851422 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00236868 0.0439907 0.248707 0.4653 0.217864 0.0216647 0.000104776 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000103051 0.00898066 0.0707355 0.323306 0.435674 0.149885 0.0111951 0.000119792 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000407815 0.0168074 0.115859 0.380922 0.375297 0.103247 0.00746065 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00173683 0.0302139 0.16351 0.418832 0.31759 0.0661682 0.0019486 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 4.83583e-05 0.00508053 0.0447146 0.226059 0.430949 0.253827 0.0379263 0.00139505 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00150469 0.00874394 0.0752237 0.285678 0.411814 0.189702 0.0264325 0.000900056 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00255269 0.0170416 0.112417 0.339133 0.37672 0.138251 0.0138839 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000597234 0.00206214 0.0356982 0.154628 0.375358 0.329438 0.0959266 0.00629204 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00133003 0.00743087 0.0536661 0.199517 0.39253 0.273768 0.0676562 0.00406361 3.78426e-05 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 5.52025e-05 0.00275348 0.010936 0.0763108 0.254454 0.388095 0.220449 0.0443522 0.00259412 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00441192 0.0255898 0.0990582 0.308131 0.363912 0.175141 0.0230426 0.000713433 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00429314 0.0323621 0.159465 0.334396 0.322544 0.128597 0.0179622 0.000379251 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00131775 0.00697617 0.0619963 0.185596 0.358103 0.280261 0.0934747 0.0120782 0.000196814 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000242541 0.00155464 0.0159175 0.0802413 0.233777 0.353311 0.242826 0.0648012 0.00732825 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000634176 0.0030635 0.0291582 0.104468 0.279209 0.325589 0.205448 0.0477563 0.00467506 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000939689 0.00886886 0.0392778 0.145584 0.299766 0.316685 0.152793 0.0341834 0.00190221 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00202679 0.013827 0.0652092 0.169274 0.320194 0.285804 0.120865 0.0213606 -#1992 - 0 0 0 0 0 0 0.00464318 0.814943 0.180414 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0.0518734 0.906089 0.042038 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0.208463 0.787128 0.00440831 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0.000140645 0.459101 0.540758 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0.00356855 0.71044 0.285865 0.000127262 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0.0380143 0.856071 0.105915 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0.150069 0.823905 0.0260259 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0.000971184 0.356911 0.637643 0.00447451 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0.00594561 0.591945 0.402104 5.87476e-06 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0.0362376 0.76484 0.198923 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.120612 0.804357 0.0750314 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000976089 0.286658 0.689256 0.02311 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00804904 0.4923 0.493317 0.00633381 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.0385036 0.662347 0.298463 0.000686192 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 8.06625e-05 0.102805 0.749813 0.147282 1.99296e-05 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00225344 0.234796 0.699993 0.0629581 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.0114014 0.401642 0.564191 0.0227658 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.039517 0.55732 0.395879 0.00728403 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00108844 0.0986788 0.658911 0.23968 0.00164215 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00323088 0.20102 0.667517 0.127797 0.000434872 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000118336 0.0136993 0.337254 0.588613 0.0603157 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 5.3155e-05 0.0414874 0.472246 0.462274 0.0239393 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00162494 0.0929569 0.578476 0.317908 0.00903434 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00678877 0.175722 0.613846 0.200175 0.00346842 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 3.02546e-05 0.019737 0.287339 0.575767 0.116381 0.000745904 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00151317 0.0469422 0.400307 0.489956 0.0612819 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00322187 0.0903263 0.498645 0.38204 0.0257671 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00933165 0.161197 0.544391 0.27301 0.0120696 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000385995 0.0205973 0.255156 0.538729 0.180141 0.0049902 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.0020285 0.0479935 0.348753 0.489024 0.110918 0.00128333 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00486428 0.0904647 0.432194 0.409848 0.0625669 6.17782e-05 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.0114853 0.14938 0.486143 0.321985 0.0310066 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000789283 0.0221041 0.22598 0.502851 0.234357 0.0139189 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.0028326 0.0493367 0.306533 0.481147 0.154617 0.00553406 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00653274 0.0916771 0.375139 0.429666 0.0939332 0.00305123 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 7.45087e-05 0.017412 0.13493 0.437935 0.350635 0.0581718 0.000841553 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00217581 0.028958 0.196149 0.461097 0.279304 0.0323159 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00406166 0.0512896 0.268802 0.452542 0.205729 0.0175761 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000680158 0.00918037 0.0858801 0.337098 0.414547 0.144639 0.00797518 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000796738 0.0186203 0.125134 0.392752 0.363159 0.0961102 0.00342828 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00263967 0.0330637 0.179801 0.419922 0.300164 0.063557 0.000852456 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00501475 0.0560077 0.239175 0.421316 0.241205 0.037215 6.67968e-05 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000317942 0.00909678 0.092949 0.289971 0.403817 0.18368 0.0201679 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 3.56747e-05 0.00166875 0.0182888 0.124397 0.351476 0.362452 0.129987 0.0116953 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00380271 0.0349826 0.165496 0.385858 0.315082 0.0896167 0.00516151 -#1993 - 0 0 0 0 0.0365832 0.890293 0.0731238 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0.12223 0.853145 0.0246249 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0.253759 0.740341 0.00589946 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0.000760131 0.41693 0.580136 0.00217395 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0.00440406 0.578044 0.416587 0.000965003 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0.0232947 0.702108 0.274282 0.000315355 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0.0635724 0.772813 0.163614 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0.000453407 0.139586 0.768316 0.0916449 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0.00203744 0.244452 0.702748 0.0507627 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0.00739673 0.36997 0.596055 0.0265781 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0.0205988 0.488199 0.47786 0.0133421 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0.000116239 0.0483257 0.583965 0.363407 0.00418575 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000841028 0.096261 0.63954 0.259925 0.00343336 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00312903 0.163274 0.651851 0.180367 0.00137883 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00817746 0.24946 0.619761 0.12189 0.000711958 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.0231826 0.333839 0.563675 0.0790694 0.000233421 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000275992 0.0439045 0.41632 0.488478 0.0505249 0.000496823 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00258822 0.0745043 0.481923 0.408921 0.0318371 0.00022608 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00632715 0.12205 0.522334 0.327885 0.0210453 0.000358442 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000313648 0.0115233 0.176184 0.544078 0.25171 0.0161913 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000387675 0.0236136 0.236769 0.534395 0.197123 0.00771125 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000739746 0.0445094 0.297007 0.504448 0.147975 0.00532065 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00254693 0.0685111 0.359396 0.454575 0.110315 0.00465577 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00727857 0.102179 0.40452 0.404369 0.0790791 0.00257326 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000469442 0.015571 0.136263 0.435941 0.348832 0.0624374 0.0004866 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00147028 0.0261731 0.180946 0.448008 0.29935 0.043868 0.000184105 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00126706 0.0430566 0.226222 0.449337 0.249752 0.0297368 0.000628477 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00540731 0.0592806 0.276461 0.431215 0.206353 0.0212345 4.78537e-05 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 5.36811e-05 0.0101295 0.085556 0.313687 0.410818 0.164717 0.0148948 0.000144721 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000647102 0.0147105 0.11712 0.347799 0.375744 0.134608 0.00937184 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00209777 0.0250759 0.144969 0.376136 0.34013 0.105851 0.00574015 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00469431 0.0372609 0.179254 0.387981 0.304242 0.082449 0.00411874 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000422159 0.00546746 0.0594473 0.210101 0.389767 0.271676 0.0596827 0.00337357 6.29394e-05 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000440014 0.0112864 0.0755517 0.24907 0.378892 0.235897 0.0458193 0.00304421 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00194292 0.0154664 0.0958968 0.283312 0.365842 0.196884 0.038849 0.00180667 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00273201 0.024685 0.124141 0.305951 0.344166 0.170921 0.0274037 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000249296 0.00703838 0.0353074 0.142606 0.328061 0.322599 0.140912 0.0228196 0.000407385 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 7.90393e-05 0.00173688 0.0096335 0.0495196 0.169569 0.33886 0.301759 0.112848 0.0150796 0.000915577 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00147148 0.0103901 0.0674203 0.201293 0.343872 0.270592 0.0922245 0.0127366 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00234768 0.0191804 0.0877938 0.217403 0.344443 0.240522 0.0788179 0.00923839 0.000254223 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000334602 0.0041547 0.0234978 0.10664 0.252236 0.327721 0.214403 0.0617683 0.00924497 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000620115 0.00501213 0.034349 0.127604 0.276511 0.306255 0.189815 0.0565293 0.00330476 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.0015478 0.00825205 0.0510736 0.14672 0.280593 0.29973 0.166924 0.0421169 0.00304285 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000499384 0.00192489 0.00902708 0.0663445 0.160922 0.309287 0.269809 0.144836 0.0348351 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00362109 0.0214646 0.0770267 0.181651 0.305481 0.257806 0.12425 -#1994 - 0 0 0.00288412 0.549122 0.44744 0.000554007 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0.00789949 0.652403 0.339408 0.000289147 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0.0161623 0.74636 0.237417 6.16182e-05 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0.0349823 0.812682 0.152336 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0.0687689 0.84391 0.0873212 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0.120154 0.839879 0.0399667 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0.194123 0.790801 0.0150756 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0.290897 0.704366 0.00473687 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0.00020654 0.397797 0.601042 0.000954383 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0.000666431 0.511654 0.487442 0.000237491 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0.00221425 0.6228 0.374906 7.97469e-05 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0.00626486 0.731629 0.262106 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0.017083 0.81349 0.169427 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.0431494 0.862021 0.0948294 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.0876003 0.866163 0.0462371 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.157668 0.825553 0.0167791 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.249396 0.743629 0.00697465 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000885012 0.35181 0.644627 0.00267779 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00122986 0.464985 0.532714 0.00107122 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00334128 0.575278 0.421246 0.000135247 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.0100575 0.67996 0.309528 0.000455154 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 6.89298e-05 0.017319 0.770482 0.21213 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.0383387 0.831268 0.130393 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000370073 0.0785752 0.846636 0.0744184 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000487769 0.141277 0.819265 0.0389703 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000539418 0.220177 0.760381 0.0189029 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00143456 0.324335 0.66518 0.00905033 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00620918 0.422299 0.565019 0.00647225 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.0059488 0.52499 0.464041 0.00501975 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.0173727 0.621726 0.359435 0.00146682 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000418389 0.0312864 0.699672 0.267742 0.000880995 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.0507361 0.765017 0.183802 0.000444865 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.0018527 0.0895384 0.786636 0.121827 0.000145815 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00128674 0.140873 0.783454 0.0741562 0.000230625 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00338344 0.211979 0.735575 0.0489663 9.63806e-05 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00789553 0.295474 0.667416 0.0292142 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.0101312 0.385875 0.58475 0.0191843 5.94456e-05 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.0143695 0.480144 0.491286 0.0142002 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000374236 0.023372 0.563368 0.405459 0.00742635 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000521783 0.0443468 0.634733 0.316254 0.00414384 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00155258 0.0683072 0.678143 0.247396 0.00460044 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 9.80953e-05 0.003509 0.110844 0.701327 0.182182 0.00204101 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00314494 0.153919 0.708759 0.132505 0.00167244 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000234339 0.0055659 0.219429 0.684852 0.0887707 0.00114827 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 3.41553e-05 0.00887143 0.286195 0.638053 0.0664526 -#1995 - 0 0 0.0255896 0.268639 0.508676 0.185876 0.010961 0.000258622 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0.0353139 0.310023 0.511643 0.137007 0.00595954 5.42436e-05 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 1.87022e-05 0.0465079 0.358257 0.496168 0.096248 0.00280095 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0.061512 0.410089 0.465172 0.0617038 0.00152243 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 8.84674e-05 0.0813768 0.462126 0.416783 0.0389643 0.000660841 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0.00046544 0.104576 0.515589 0.356223 0.0231433 3.39356e-06 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0.00122744 0.133516 0.565455 0.286913 0.0126889 0.000200139 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0.00189434 0.171512 0.6015 0.217181 0.00785338 5.85446e-05 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0.00320758 0.214783 0.622829 0.155509 0.0036712 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0.00482043 0.275537 0.617687 0.100886 0.00106974 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0.00992118 0.338598 0.590954 0.0603522 0.000175087 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0.0152625 0.416761 0.531642 0.0363013 3.31218e-05 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0.0268456 0.493303 0.462501 0.0173504 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.0428548 0.572986 0.376055 0.00810451 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000296929 0.0632979 0.642814 0.290051 0.00353991 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.0963312 0.699362 0.203259 0.00104743 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000689864 0.134559 0.732709 0.131293 0.000749041 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000440502 0.191805 0.732853 0.0749018 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000718372 0.275218 0.682751 0.0413122 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00421228 0.361021 0.613643 0.021124 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00742736 0.463702 0.520738 0.00813288 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.0129676 0.566171 0.415805 0.00505677 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.0260958 0.666846 0.305581 0.00147668 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 7.33029e-05 0.0450298 0.744828 0.208378 0.00169064 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000841576 0.0895965 0.770549 0.138937 7.53895e-05 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000530031 0.13758 0.788318 0.0735727 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00225982 0.203719 0.757505 0.0365156 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00604484 0.301828 0.671838 0.0202897 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00879941 0.407951 0.567865 0.0153846 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.0161626 0.515162 0.461603 0.00707271 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000260476 0.0303005 0.605537 0.361076 0.00282612 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000875781 0.0502592 0.681988 0.265312 0.00156505 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000782013 0.0736546 0.732456 0.191006 0.0021016 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00258269 0.130714 0.736304 0.129647 0.00075293 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000259407 0.00465844 0.196402 0.714993 0.0835538 0.000133338 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000758097 0.0142127 0.268954 0.659155 0.0563548 0.000565461 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000367598 0.0138592 0.375472 0.569271 0.0408864 0.000143629 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00090143 0.02448 0.454762 0.49319 0.0266667 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000888998 0.0427048 0.532774 0.404523 0.0191087 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00207685 0.0688218 0.582979 0.333204 0.0129177 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00070268 0.00479414 0.112777 0.607006 0.262956 0.0117639 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00931077 0.153538 0.621401 0.208135 0.00761535 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00123365 0.0151305 0.213581 0.609599 0.157272 0.0031834 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000166701 0.00121512 0.0217609 0.274149 0.582907 0.11679 0.00301128 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000981769 0.0280204 0.336233 0.541487 0.0888612 -#1996 - 0 0.00073729 0.0289064 0.143455 0.283347 0.292626 0.183862 0.0594858 0.00758011 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0.000813389 0.0345294 0.160154 0.305666 0.289956 0.161217 0.0437523 0.00388035 3.16146e-05 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0.0013738 0.0406613 0.187195 0.31858 0.283684 0.137237 0.0286976 0.0019955 0.000575848 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0.00113916 0.0517385 0.207064 0.340233 0.269586 0.111107 0.0190115 0.000120366 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0.00316653 0.0629967 0.23752 0.345918 0.246385 0.0922199 0.0117288 6.57719e-05 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0.00389483 0.0763595 0.264263 0.355882 0.232402 0.0583401 0.00787311 0.000985553 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0.00500052 0.0931745 0.301357 0.356095 0.193923 0.0461047 0.00334488 0.001 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0.000302177 0.000812251 0.0114923 0.116646 0.314897 0.345923 0.174296 0.0332746 0.00235682 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0.00050668 0.00049332 0 0.00821999 0.13242 0.372586 0.325634 0.137682 0.0218729 0.000585892 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0.000500246 0.0180098 0.170615 0.373508 0.31396 0.105847 0.0170887 0.000471314 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0.000120565 0.024976 0.189688 0.405512 0.288551 0.0832278 0.00782581 9.90144e-05 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0.001 0.00113325 0.0346901 0.225558 0.419787 0.259547 0.0538856 0.0043988 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0.000418855 0.0384235 0.27581 0.424641 0.216713 0.0415402 0.00245377 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00465266 0.0532815 0.311654 0.421047 0.180353 0.0269643 0.00204761 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00279442 0.0703654 0.363253 0.398578 0.14895 0.0156767 0.000382632 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 7.31724e-05 0.00892344 0.100469 0.385653 0.388551 0.103856 0.0115567 0.00091834 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000785854 0.00171823 0.00874451 0.124869 0.429832 0.351114 0.0731108 0.00796123 0.0018642 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.001 0.00085443 0.0152918 0.15605 0.468336 0.29646 0.0567461 0.00500038 0.000261496 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000124378 0.000889915 0.00515591 0.0181062 0.196593 0.484249 0.255145 0.0357412 0.00326419 0.000731393 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00103787 0.0030858 0.0288304 0.254716 0.479047 0.203167 0.025629 0.00376192 0.000725501 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000299947 0.00122868 0.00599686 0.0427946 0.288325 0.475793 0.168534 0.01417 0.00285764 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00036387 0.00772779 0.0646404 0.333823 0.464187 0.114014 0.0139494 0.00129418 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000520126 0.00248954 0.00815248 0.0656754 0.416132 0.407485 0.08693 0.0105244 0.00170601 0.000385152 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000340626 0.00133751 0.00227887 0.0122685 0.0978898 0.460378 0.355095 0.0591855 0.00934442 0.00088222 0.000284756 0.000715244 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00192229 0.0186209 0.146715 0.47873 0.301974 0.0445427 0.00656705 0.00092891 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000506221 0.000493779 0 0.000925055 0.00481455 0.0276739 0.170975 0.505272 0.250149 0.0349798 0.00409235 0.000119005 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00129432 0.00194001 0.00555367 0.0345252 0.224827 0.522231 0.186899 0.020857 0.00187335 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00080802 0.00104357 0.00760112 0.0447019 0.274255 0.497398 0.152092 0.018011 0.00407457 1.42772e-05 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00176309 0.0152873 0.0633684 0.321743 0.461174 0.120032 0.0149758 0.00165688 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000743944 0.00411742 0.0143508 0.0840881 0.370305 0.418081 0.0953669 0.0105901 0.00232463 3.22349e-05 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.001 0.001 0.000602403 0.000947564 0.00466087 0.0215795 0.114616 0.408535 0.369947 0.0668385 0.00794948 0.00230753 1.5493e-05 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 7.33699e-05 0.00092663 0.00104217 0.00693431 0.0240798 0.140939 0.448842 0.314425 0.0539892 0.00613297 0.00223953 0.000375585 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000353889 0.000646111 0.000124603 0.00396738 0.00862385 0.0426035 0.16171 0.471699 0.260954 0.0413418 0.00664725 0.00132823 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000446428 0.00109326 0.00127086 0.0116872 0.0446587 0.213048 0.486505 0.198963 0.0319519 0.00862514 0.00075079 0 0.001 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000728331 0.000271669 0 0.000327061 0.00188755 0.00274374 0.0173736 0.0614013 0.244332 0.458813 0.179032 0.0248233 0.00616655 0.0020996 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000173754 0.00338317 0.00711472 0.0184407 0.0752805 0.292734 0.430108 0.147511 0.0191648 0.00508901 0.001 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 8.53239e-06 0.00100426 0.00434209 0.0085927 0.024736 0.101269 0.324159 0.402681 0.104634 0.0216687 0.00690424 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00195102 0.00307028 0.0059296 0.0319574 0.123168 0.36764 0.361188 0.0841203 0.0151525 0.00466573 0.0011573 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000969875 0.000523394 0.00113162 0.00370636 0.00951038 0.0383191 0.156304 0.39476 0.310057 0.0699652 0.0129916 0.00176252 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00110095 0.00112874 0.00118096 0.00416536 0.0246041 0.0547562 0.16063 0.402159 0.27951 0.054071 0.013452 0.00224204 0.000972926 2.7074e-05 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000681226 0.000609227 0.00655228 0.0189268 0.054002 0.212135 0.419151 0.223268 0.0457988 0.0107092 0.00335826 0.00328823 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000459204 0.00095079 0.000740301 0.000849705 0.001 0.00263045 0.00867799 0.0249108 0.0658783 0.246433 0.404417 0.184738 0.0447721 0.00978869 0.00362881 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000476735 0.00104632 0.000476945 0.00142832 0.00754315 0.0130205 0.0301407 0.0904698 0.262162 0.372848 0.173882 0.038326 0.00545759 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000903421 9.65785e-05 0.00186213 0.00400832 0.016255 0.0478956 0.11275 0.293474 0.33702 0.144971 0.0356232 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000782005 0.00157406 0.00409979 0.00571397 0.0241121 0.0404481 0.142732 0.28956 0.319016 0.141752 -#1997 - 0 0.0030724 0.0535837 0.256322 0.381 0.23783 0.0562544 0.0105812 0.000805994 0.000549818 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0.00390743 0.0657722 0.293447 0.38239 0.203342 0.0435309 0.00651452 0.000648657 0.000447582 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0.00029341 0.00585311 0.0763226 0.335507 0.374837 0.167098 0.0338436 0.00404982 0.00119527 0.001 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0.00027414 0.00735204 0.097652 0.365338 0.368333 0.133467 0.0246164 0.00196682 0.000748873 0.000251127 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0.00876106 0.118744 0.394171 0.35758 0.103994 0.0145375 0.00221188 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0.0108044 0.142288 0.427357 0.329168 0.0807943 0.00843759 0.000742883 0.000407169 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0.00121577 0.0166294 0.183934 0.43818 0.294406 0.0589069 0.00572737 0 0.001 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0.0241003 0.219464 0.46382 0.247489 0.0395799 0.00554641 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0.00117013 0.0313059 0.268739 0.462445 0.20672 0.0256027 0.00221313 0.00174075 6.30299e-05 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0.0001402 0.00269917 0.0383464 0.306828 0.472148 0.157796 0.020041 0.00200102 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0.000722327 0.00302492 0.0607965 0.351772 0.439214 0.130468 0.0101795 0.00314543 0.000677515 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0.00113874 0.00735699 0.073692 0.411008 0.404928 0.0917134 0.00590221 0.00355085 0.000710028 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 9.07133e-05 0.000909287 0.00174427 0.00846422 0.103185 0.439211 0.368423 0.0694712 0.00521465 0.00190075 0.00132509 6.1174e-05 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0.00153564 0.0140406 0.126847 0.487865 0.318267 0.0460744 0.00397669 0.00101754 0.000376162 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0.00127122 0.00100558 0.0158904 0.162979 0.510181 0.270123 0.0362677 0.00211995 0.000162168 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000409156 0.0052643 0.0216839 0.212199 0.513612 0.215063 0.0264087 0.00380608 0.00147442 7.84178e-05 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000124853 0.00535967 0.0305929 0.259216 0.51625 0.161481 0.0183412 0.00581607 0.00181753 0.000756478 0.000243522 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000857175 0.000142825 0.000158626 0.0056183 0.0477479 0.302489 0.49224 0.131716 0.0147025 0.00231615 1.16618e-05 0.001 0 0.000254282 0.000745718 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00157111 0.00424918 0.00568548 0.0579132 0.362925 0.443007 0.110606 0.00984887 0.00392395 0.000270724 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00118949 0.00210677 0.0039349 0.00909452 0.0740593 0.414632 0.403522 0.0807344 0.00923774 0.000489685 0 0.001 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00139007 0.0163965 0.109921 0.45319 0.35315 0.0570777 0.0065507 0.00232408 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000259193 0.00452749 0.0030313 0.0233771 0.143339 0.484195 0.289186 0.0426801 0.00770463 0.00170033 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000488692 0.000609675 0.00527532 0.0313177 0.173969 0.506164 0.239562 0.0335608 0.00400949 0.000897349 0.0021461 0.00111104 0.000888964 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000746229 0.00154698 0.00360248 0.00479691 0.035543 0.210808 0.506878 0.19708 0.0340706 0.00307612 0.00171677 0.000135051 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 4.28281e-05 0.00140935 0.00435468 0.0122408 0.0501064 0.265575 0.486449 0.159341 0.0173948 0.00308581 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00133968 0.00112903 0.00639471 0.015899 0.0561245 0.311357 0.467507 0.117614 0.0162078 0.00342687 0.00199987 0.000300432 0.000699568 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 2.05016e-05 0.00493579 0.017698 0.0834673 0.364336 0.416666 0.0895111 0.0178124 0.00301665 0.00232821 0.000208211 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00207375 0.00123453 0.0124889 0.0235815 0.0810422 0.405884 0.380735 0.0694017 0.0159239 0.00476452 0.00269684 0.000172842 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000579391 0.000420609 0.000423098 0.00672124 0.011853 0.0270878 0.129231 0.415697 0.335591 0.052868 0.0124933 0.00438983 0.00220618 0.000439126 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000651545 0.0016991 0.00260693 0.00800662 0.0397015 0.160959 0.437134 0.27878 0.0609614 0.00828462 0.00121501 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000979427 0.000225232 0.000795341 0 0.00447267 0.00990357 0.0390894 0.194298 0.444905 0.244942 0.0473779 0.00705783 0.00265256 0.00130084 0.00138153 0.000618469 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000366532 0.000633468 0.00280513 0.00427929 0.0150257 0.0640154 0.224528 0.435935 0.20213 0.0374823 0.0102813 0.00151869 0 0.000898748 0.000101252 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000101199 0.00156844 0.00170119 0.00891778 0.0213812 0.0741766 0.250347 0.436141 0.170684 0.0265414 0.00465882 0.00299462 0.000787418 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00136548 0.00268851 0.0105801 0.0191737 0.0913613 0.293178 0.400794 0.140995 0.0283688 0.00481078 0.00328397 0.00264134 0.000758938 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000403332 0.000596668 0 0 0 0.000399305 0.00256908 0.00302513 0.0114313 0.0327851 0.0917912 0.338253 0.376614 0.106974 0.0264354 0.00588927 0.00199794 0.00083527 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000695546 0.000304454 4.55031e-05 0.00125675 0.00209757 0.00298399 0.00311028 0.0121165 0.0345792 0.119721 0.351586 0.34691 0.0953345 0.0205502 0.00295605 0.00266704 0.00108573 0.000549881 0.00145012 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 8.20634e-05 0.000917937 0.00125088 0.000964594 0.00492483 0.0162504 0.0437677 0.143735 0.374042 0.305996 0.0777063 0.0199777 0.00514861 0.00269161 0.00054505 0 0.000515228 0.00144841 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 2.73258e-05 0.00167956 0.000293111 0.000611174 0.00206149 0.00462331 0.00528368 0.0211938 0.0503965 0.167658 0.381729 0.267881 0.0718934 0.0138581 0.00578705 0.00338333 0.000640207 0.000730871 0.000269129 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000547835 0.000989398 0.00146277 0.00562632 0.0110394 0.0159607 0.0617661 0.220238 0.365119 0.238445 0.0561479 0.0136744 0.00281131 0.00396731 0.00149873 0.000705862 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000163156 0.000836844 0 0.00324059 0.00358432 0.0103571 0.0223514 0.0843948 0.235439 0.352349 0.213628 0.04783 0.0162528 0.00478925 0.00178357 0.00111264 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000596153 0.000403847 0.00173058 0.00258394 0.00241848 0.0125238 0.0297191 0.111264 0.247793 0.355806 0.170986 0.0471849 0.0125796 0.00237567 0.000659792 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00110544 0.00189456 0.000762646 0.000782804 0.00519964 0.0061054 0.0178589 0.0439699 0.0961114 0.274681 0.334749 0.157099 0.0389631 0.0113804 0.0063807 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.0013586 0.00466024 0.00481987 0.00870309 0.0171619 0.0383374 0.129444 0.288517 0.330055 0.136571 0.0294259 0.00587088 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00034421 0.00065579 0.000510922 0.00299755 0.00241582 0.0035058 0.0104585 0.0199418 0.0594245 0.151652 0.292471 0.289992 0.109079 0.0378607 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000685067 0.000314933 0 0 0 0 0.000730296 0.0022697 0.00100294 0.00342176 0.00428849 0.0136382 0.0241172 0.0661613 0.162521 0.301713 0.256608 0.118397 -#1998 - 0 0 0 0.000896261 0.0263091 0.154451 0.386399 0.311753 0.105525 0.0124325 0.00223464 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0.00229764 0.0365572 0.189324 0.421244 0.268921 0.0709267 0.00906747 0.00166217 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0.00323368 0.0511386 0.241464 0.432632 0.220961 0.0433944 0.00562791 0.00154727 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0.0089932 0.0667186 0.290446 0.420821 0.18618 0.0237564 0.00249888 0.000585243 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0.000541893 0.0122298 0.0821268 0.358855 0.396284 0.131271 0.0156913 0.00292281 7.71876e-05 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0.00150033 0.0132755 0.123894 0.401651 0.358313 0.0914948 0.00879809 0.00107299 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0.000633198 0.0207511 0.155713 0.455424 0.308397 0.0549678 0.0041142 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0.000298195 0.000701805 0.00199485 0.0289666 0.2182 0.468988 0.248675 0.0292615 0.00223304 0.000680778 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0.00242764 0.0429184 0.275222 0.482185 0.179065 0.0174595 0.000722553 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0.000613454 0.00516756 0.0630043 0.333376 0.457113 0.131706 0.00771254 0.000307703 0.001 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0.00113647 0.00111593 0.00830997 0.0846288 0.416584 0.405013 0.0769854 0.00568657 0.000540881 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0.00219225 0.013355 0.129052 0.478276 0.325329 0.0465047 0.00453788 0.000752166 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0.000402112 0.0034889 0.0222288 0.168292 0.512987 0.265925 0.0250869 0.00158886 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 8.04107e-05 0.000919589 0.000840975 0.00328392 0.0284181 0.231824 0.5291 0.185486 0.0185839 0.00146395 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00208204 0.00902157 0.0510956 0.301031 0.502367 0.123818 0.00894361 0.00107121 0.000569833 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000439396 0.00218863 0.0152303 0.0687785 0.371207 0.456549 0.0778404 0.00562226 0.00214379 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 3.91706e-05 0.00481284 0.0193503 0.104582 0.444657 0.376218 0.0480571 0.00228404 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000457237 0.000542763 0 0.00093461 0.00399116 0.0181037 0.141315 0.515251 0.291748 0.0241911 0.00283296 0.000632107 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 2.47232e-05 0.0018278 0.00145579 0.00202912 0.0335534 0.193623 0.536403 0.205534 0.0224244 0.00312483 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000774717 0.00316465 0.00519575 0.0412148 0.272584 0.530967 0.13292 0.0126781 0.000501139 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.001 0.00105725 0.0118541 0.0663752 0.332695 0.480853 0.0960667 0.00871047 0.00138816 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.0028239 0.019093 0.0899349 0.412102 0.417018 0.0541014 0.00392647 0 0.000730045 0.000269955 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000136198 0.0018638 0.00499629 0.0262463 0.1272 0.467107 0.327776 0.0392879 0.00438646 0 0.000604715 0.000395285 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00015016 0.00155815 0.00861097 0.0346096 0.175281 0.501095 0.24284 0.0316369 0.00369529 0.000522795 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000626057 0.00165854 0.00896172 0.0466664 0.227331 0.53099 0.15805 0.0241934 0.00104903 0.000473556 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00495331 0.0157811 0.0687037 0.303426 0.461846 0.13097 0.00901343 0.00492215 0.000384855 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000402985 0.00109162 0.000592992 0.00183388 0.0219491 0.089221 0.37822 0.408767 0.0879206 0.0077814 0.00121926 0.001 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000391848 0.000608152 0.0002922 0.0067901 0.0313905 0.143423 0.403725 0.33752 0.0652315 0.00850029 0.0020529 7.40494e-05 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00175726 0.00124274 0.00291256 0.00737349 0.034746 0.184043 0.436661 0.272119 0.0493922 0.00900391 0.000747899 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000255296 0.000744704 0.000374424 0.00229572 0.0170789 0.0586221 0.209727 0.459881 0.20507 0.0334664 0.00698208 0.00321949 0.00217062 0.000112968 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00115177 0.00791038 0.016356 0.079401 0.280065 0.420374 0.162388 0.0247575 0.0057393 0.000855983 0 1.53836e-05 0.000984616 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00044698 0.00122485 0.00032817 0 0.000386662 0.006431 0.0242925 0.110974 0.330525 0.363734 0.130783 0.0242512 0.00462317 0.001 0 0.001 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 5.78196e-05 0.00201193 0.00358637 0.00538321 0.037445 0.136211 0.358393 0.341015 0.0933686 0.0178515 0.00446708 0.000209036 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.0012201 0.00192737 0.00539204 0.016575 0.0466406 0.149993 0.401333 0.28293 0.0743287 0.0172731 0.00238687 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000101303 0.000898697 0.001 0.00125832 0.00229663 0.00293329 0.019412 0.0678071 0.213655 0.389306 0.23293 0.0583729 0.00687828 0.0011508 0.000241191 0.00132172 0.000437093 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00067108 0.000812546 0.00816897 0.00542425 0.023014 0.0813269 0.244635 0.390498 0.194635 0.0382351 0.00890619 0.00267283 0.001 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000465135 0.000534865 0.00106236 0.0015045 0.00414455 0.0136234 0.0335902 0.0932625 0.290922 0.36183 0.14947 0.0348847 0.00832217 0.00296274 0.0034209 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000643589 0.00180551 0.00269341 0.00384707 0.0195266 0.0385661 0.137234 0.311421 0.32423 0.121383 0.0324961 0.00615293 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000998185 5.81889e-05 0.00612655 0.0074048 0.0169224 0.0520376 0.168418 0.336191 0.275692 0.101777 0.0228393 0.00610005 0.00155212 0.00167453 0.00204725 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000651009 0.000348991 0 0.000951673 0.00118767 0.00237917 0.00311136 0.0094516 0.0267386 0.0572816 0.199959 0.343279 0.260173 0.0723582 0.0116522 0.00527825 0.00318982 0.00200885 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00179554 0.00398602 0.00657805 0.0153812 0.0313926 0.0965644 0.209618 0.334691 0.211205 0.0683169 0.014427 0.00456149 0.000965975 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00044557 0.00055443 0.000364196 0.000635804 0.000878029 0.00284164 0.00424578 0.00870488 0.0131801 0.0365546 0.10471 0.249642 0.322221 0.189755 0.0472071 0.0121146 0.00525863 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000356517 0.000643483 0 0 0 0.000440321 0.00480878 0.010423 0.0196177 0.0476402 0.137151 0.260413 0.31369 0.151839 0.0365202 0.0125524 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000670765 0.00226841 0.00494625 0.00738125 0.0248038 0.0621363 0.165042 0.29343 0.258889 0.133919 0.0327807 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000133346 0.000866654 0 0 0.001 0.000880592 0.00232183 0.00519975 0.0158584 0.0236184 0.0751616 0.195114 0.280426 0.259669 0.0961397 -#1999 - 0 0 0 0 0.00703552 0.224373 0.598431 0.165727 0.00443401 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0.000598607 0.0123245 0.313637 0.57446 0.0955177 0.00311256 0.000349165 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 4.1187e-05 0.0262027 0.419181 0.499107 0.0538636 0.00160516 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0.00102111 0.0501746 0.517102 0.406575 0.0244273 0.000699598 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0.00215205 0.0873869 0.603456 0.294672 0.0121457 0.000187181 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0.00286956 0.14919 0.647397 0.193577 0.00658634 0.000380104 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0.000639722 0.00691217 0.219362 0.657734 0.11052 0.00383167 0.000514927 0.000485073 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0.0019358 0.0120777 0.33213 0.591527 0.0611333 0.00119596 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0.000294067 0.000719873 0.0329785 0.443304 0.490302 0.0306736 0.00172827 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 9.52155e-05 0.00247182 0.0511208 0.559159 0.37034 0.0168128 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0.000528837 0.00441969 0.0905507 0.63318 0.259536 0.011647 0.000137556 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0.000667821 0.000465196 0.0111507 0.163693 0.658344 0.160278 0.00505014 0.000350977 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0.000363472 0.00163653 0.000516588 0.0140817 0.248702 0.625438 0.102303 0.0065538 0.000403777 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000631239 0.0259193 0.353712 0.566265 0.0516465 0.00182657 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.001 0.00379648 0.0425004 0.466012 0.453906 0.030951 0.00183436 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000786747 0.00504402 0.0768424 0.55986 0.326483 0.0283158 0.0026687 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.001 0.00039789 0.00569754 0.123461 0.615582 0.241046 0.0111357 0.00168028 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000128357 0.0011139 0.00172251 0.0202299 0.19041 0.613726 0.160382 0.0108577 0.0014293 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00116313 0.00552137 0.027734 0.269732 0.580221 0.105401 0.00979093 0.000436987 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000484594 0.00806819 0.0423526 0.370549 0.504947 0.0662226 0.00522038 0.00215479 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000242319 0.000949116 0.00238577 0.012045 0.072233 0.453921 0.412546 0.0426088 0.00273845 0.000330577 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000406389 0.00251108 0.0135242 0.103887 0.5346 0.309292 0.0324135 0.00319575 0.000170012 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000594556 0.00162201 0.0028138 0.0188177 0.152883 0.564464 0.230098 0.0224242 0.00320788 0.00186944 0.00120526 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.0003111 0.0006889 0.000741714 0.00649688 0.0295746 0.221712 0.553914 0.167269 0.0162919 0.00158121 0.00141879 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000301564 0.00506865 0.00997271 0.0421929 0.305927 0.514736 0.109094 0.011091 0.0016153 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00185827 0.00428432 0.0153097 0.0654085 0.371193 0.447579 0.0823896 0.0106469 0.000330672 0.000931352 6.86477e-05 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.0010896 0.00226204 0.0169456 0.0985593 0.443847 0.380269 0.0506334 0.00539344 0 0.000191 0.000809 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000323225 0.00166582 0.00478062 0.0284382 0.139909 0.474985 0.296317 0.0447023 0.00728957 0.00158988 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00135715 0.00144552 0.0117567 0.0338743 0.1975 0.485341 0.234508 0.0258674 0.00703217 0.00131761 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000540311 0.00159711 0.00332494 0.00963818 0.0515176 0.25115 0.47849 0.172214 0.0287841 0.00174442 0.000732591 0.000267409 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00074595 0.00529521 0.021469 0.0688567 0.302032 0.441603 0.13562 0.0198584 0.00388318 0.000636162 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000576258 0.00182441 0.00585275 0.0214415 0.0917704 0.366662 0.390869 0.0993147 0.0174469 0.00224218 0.000793874 0.000953546 0.00025258 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00179289 0.000207113 0 0 0.00752176 0.0279702 0.136781 0.393057 0.3403 0.0750215 0.0132005 0.00414785 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000262463 0.00126495 0.000472588 0.000523995 0.0106103 0.0403822 0.161855 0.43776 0.281564 0.0576044 0.00490302 0.00270839 8.74526e-05 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000253942 0.000746058 0 0.000543016 0.00194698 0.00699467 0.0149781 0.0582156 0.188521 0.443545 0.231737 0.043983 0.00826655 0.000268313 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000567968 0.000432032 0.0021305 0.0088971 0.0197795 0.0726771 0.237192 0.44176 0.178675 0.031498 0.00462232 0.000784355 0.000983811 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.001 0.00082668 0.00153919 0.00325594 0.00923901 0.0228637 0.0915449 0.294042 0.398693 0.143099 0.0287531 0.00290001 0.00194058 0.000303118 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 5.69878e-05 0.000943012 0 0 0.00136246 0.00145908 0.00142044 0.00736187 0.0323665 0.115106 0.338971 0.362691 0.111937 0.0211691 0.00194866 0.00281461 0.000391871 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00146056 0.00242096 0.00465113 0.0129433 0.0532006 0.136811 0.367286 0.313049 0.0836563 0.016147 0.00563755 0.00224372 0.000492713 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 7.68153e-05 0.00129965 0.00465779 0.0190594 0.0637456 0.170194 0.380343 0.274497 0.0719753 0.00794307 0.00307758 0.00158511 0.00147179 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000365427 0.000649506 0.0042361 0.00502747 0.023612 0.0704043 0.215566 0.396908 0.214725 0.0531607 0.0124538 0.0022435 0.000648658 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00227814 0.00713169 0.0125064 0.0278434 0.0862088 0.261225 0.362845 0.178254 0.046323 0.00956892 0.00219564 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 1.92122e-05 0.00156076 0.0026781 0.013466 0.035114 0.10842 0.292619 0.349694 0.145457 0.0400662 0.0108991 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000224161 0.00230488 0.00124253 0.00905177 0.0164519 0.0446293 0.134227 0.315886 0.311895 0.123233 0.036127 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00191799 0.000377917 0.00283802 0.00743521 0.0124312 0.0644133 0.158292 0.347567 0.26883 0.0961339 -#2000 - 0 0 0 0 0.00348667 0.335784 0.629174 0.0315546 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0.0116338 0.507648 0.472316 0.00840212 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0.0471411 0.641064 0.307583 0.00421115 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0.00140446 0.117555 0.693964 0.186051 0.00102635 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0.00496239 0.227287 0.66824 0.0984569 0.00105448 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0.000132516 0.0166417 0.367467 0.561935 0.0529745 0.000849987 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0.000220895 0.0409459 0.490474 0.439608 0.028641 0.000110111 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0.00402292 0.0947131 0.568508 0.321676 0.0110794 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0.00764781 0.179859 0.584804 0.22053 0.00715991 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0.000959227 0.0230725 0.272571 0.551829 0.147399 0.00416933 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0.00130988 0.0540579 0.366445 0.482361 0.0945383 0.00128828 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0.00766637 0.0900107 0.444716 0.388468 0.0686974 0.000441699 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0.000609496 0.0148875 0.144475 0.488197 0.312523 0.0374615 0.0018464 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00122411 0.0315952 0.21507 0.48724 0.240116 0.0236373 0.00111787 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00470196 0.0520698 0.284166 0.466851 0.174782 0.0164551 0.000974209 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000228944 0.0123272 0.0835455 0.351689 0.406013 0.135343 0.0107304 0.00012325 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000303746 0.00278153 0.0161028 0.130712 0.388508 0.362997 0.0899433 0.00845743 0.000194451 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000413577 0.00459894 0.0331012 0.183726 0.40405 0.295961 0.0728718 0.00527767 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000399263 0.00851078 0.0552407 0.229502 0.406012 0.242127 0.0552336 0.00297511 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00249803 0.0153621 0.084766 0.273922 0.382346 0.200583 0.0367995 0.00372363 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00224767 0.030952 0.114521 0.307988 0.360811 0.152695 0.0270776 0.0030797 0.000628989 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000621459 0.00387645 0.0405406 0.154242 0.337846 0.316909 0.124172 0.0193814 0.0023469 6.35546e-05 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00319985 0.00755098 0.0581349 0.194302 0.350551 0.267232 0.100006 0.0189659 5.75244e-05 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000291651 0.00319089 0.016289 0.086343 0.221055 0.344359 0.238212 0.0756969 0.0138863 0.000675734 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00120014 0.00571189 0.0297366 0.108616 0.252449 0.331612 0.198829 0.0611952 0.0101953 0.000454818 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000175735 0.00281941 0.0135876 0.0467255 0.129901 0.2729 0.3092 0.166089 0.053847 0.00368678 0.00106821 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00271134 0.0185267 0.058754 0.156035 0.298824 0.274236 0.144564 0.0389596 0.00738904 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000350179 0.00538965 0.0289583 0.0713713 0.188977 0.304976 0.246698 0.114467 0.0335543 0.00419843 0.00105968 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000450306 0.00755842 0.0390735 0.103275 0.20043 0.298942 0.221945 0.106777 0.0183394 0.00300442 0.000204181 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000659487 0.00452202 0.0142968 0.0494939 0.12055 0.231447 0.275814 0.199532 0.0850504 0.0163886 0.00197665 0.00026863 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00160064 0.00334851 0.0231076 0.0634353 0.132865 0.253464 0.266074 0.180473 0.0653746 0.00942958 0.000827996 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00189839 0.00235401 0.00691364 0.0290257 0.06945 0.167808 0.256522 0.248147 0.15784 0.0482514 0.0107406 0.00104967 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000116959 0.000892394 0.00455528 0.00877602 0.0355588 0.0889745 0.188843 0.263485 0.231266 0.119718 0.0480586 0.0079082 0.00122591 0.00062107 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000296603 0.000703397 0.001 0.00202968 0.0177636 0.0428054 0.112747 0.203986 0.256712 0.209494 0.100718 0.0420062 0.00923886 0.000499417 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 6.24922e-05 0.00240549 0.00946925 0.0217952 0.0538477 0.127667 0.217614 0.238888 0.202596 0.0913036 0.0240243 0.00733815 0.00293839 4.99185e-05 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00125294 0.00344945 0.0114936 0.0281498 0.0717761 0.144132 0.229761 0.22566 0.174196 0.0841275 0.0217386 0.00426366 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.001 0 0.00406087 0.0139259 0.0343014 0.0895922 0.154018 0.235601 0.222008 0.157144 0.0663438 0.0187691 0.00323618 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00171839 0.00365055 0.0199624 0.0486821 0.0935403 0.179779 0.23498 0.209222 0.136932 0.0519928 0.0175272 0.00201366 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000126023 0.00341765 0.012457 0.0256569 0.0545506 0.100002 0.193541 0.245596 0.190588 0.115314 0.0428024 0.0105111 0.00443758 0.001 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000886783 0.00548085 0.0101881 0.0304601 0.0667884 0.133124 0.204275 0.210232 0.175161 0.10896 0.0416267 0.0103197 0.00238641 0.000109915 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00106221 0.00289289 0.00387429 0.0151861 0.0365524 0.0815628 0.138004 0.218065 0.201545 0.165213 0.0951403 0.0275551 0.0130008 0.000347284 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000218812 0.000781188 0 0.00275139 0.00826684 0.0193736 0.047069 0.0803061 0.157559 0.21966 0.200982 0.148401 0.0779264 0.0279272 0.00750106 0.00127642 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00116173 0.00172511 0.00540468 0.0123666 0.0237269 0.0614708 0.0966298 0.159856 0.218878 0.18381 0.1401 0.0618037 0.0257635 0.00492235 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000475662 0.000524338 0.00258017 0.016933 0.0374696 0.0648623 0.115673 0.174248 0.193264 0.192637 0.121527 0.0475428 0.0228315 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000261251 0.00108481 0.00319981 0.0085002 0.0173378 0.040569 0.0733779 0.115849 0.20329 0.191605 0.161558 0.107572 0.0479648 -#2001 - 0 0 0 0 0 0 0 0.000248628 0.0662673 0.699202 0.232626 0.00165633 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0.00134617 0.220653 0.672403 0.105584 1.33483e-05 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0.0210846 0.405971 0.534501 0.0384429 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0.0016734 0.0755432 0.560703 0.35002 0.0120609 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0.00748784 0.196401 0.585712 0.204163 0.00619485 4.19298e-05 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0.000902222 0.0358549 0.33179 0.515239 0.113767 0.00244772 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0.00618332 0.0920897 0.44278 0.402342 0.0558532 0.000751724 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0.000972997 0.020154 0.181572 0.480114 0.285441 0.0315425 0.000203374 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0.00335209 0.0501434 0.276887 0.462219 0.190639 0.016598 0.000162123 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0.000417933 0.0124063 0.104582 0.357641 0.394097 0.122794 0.00800358 5.83626e-05 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00442567 0.0283304 0.163646 0.409034 0.316515 0.0748415 0.00320774 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000657975 0.00673215 0.0660082 0.237636 0.400091 0.242779 0.0435635 0.00253134 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00184808 0.0203114 0.103869 0.30591 0.357165 0.17904 0.0310508 0.000805472 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00560841 0.0430205 0.153065 0.339488 0.310179 0.128104 0.0201995 0.00033531 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000613892 0.01595 0.0711962 0.20637 0.342497 0.265047 0.085694 0.0126317 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00532727 0.0249537 0.106485 0.258229 0.328556 0.209108 0.0604818 0.00585918 0.001 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00207605 0.00982901 0.0495786 0.138749 0.295981 0.289641 0.163688 0.0446554 0.00580245 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000130372 0.00314745 0.0178622 0.0820464 0.176341 0.30019 0.263463 0.123808 0.0312719 0.00173915 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00104063 0.00711826 0.0345303 0.0997439 0.231033 0.286897 0.22236 0.0925893 0.0237997 0.000887477 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000627059 0.00307161 0.0121147 0.0557401 0.134603 0.251388 0.266173 0.186565 0.0731323 0.01533 0.00125473 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 7.18017e-06 0.00237249 0.00486137 0.026304 0.0727478 0.171012 0.262534 0.235081 0.158553 0.0554664 0.0100611 0.001 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00194154 0.0109212 0.0368918 0.099838 0.201546 0.260853 0.221296 0.114476 0.0446085 0.00762883 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 7.66345e-05 0.00192337 0.00357531 0.0225327 0.0633367 0.113931 0.224127 0.244608 0.192475 0.0972696 0.0305902 0.00512882 0.000426383 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.0015559 0.0104134 0.0296432 0.0718586 0.157854 0.232815 0.218785 0.172532 0.0798688 0.0208422 0.00356353 0.000267449 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000892787 0.00473183 0.0144237 0.0409464 0.101857 0.171787 0.234174 0.208981 0.140758 0.0591081 0.0214468 0.000894084 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00216603 0.00707185 0.0255491 0.0589906 0.113296 0.192681 0.231138 0.188935 0.117071 0.0478532 0.0125041 0.00274388 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00606007 0.00710775 0.0358379 0.0790367 0.130215 0.220169 0.207924 0.16986 0.0922415 0.0386889 0.0115742 0.00128544 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000196196 0.0017027 0.00878718 0.013933 0.0506927 0.0876437 0.161495 0.210647 0.193618 0.154121 0.0791033 0.0276717 0.00908695 0.00130102 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00161894 0.00204024 0.0131925 0.0269608 0.0571751 0.115362 0.163574 0.2128 0.180776 0.132822 0.0649197 0.0218086 0.00688697 6.32106e-05 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.001 0.00204145 0.00460498 0.0114332 0.0438354 0.0735441 0.125527 0.189643 0.196171 0.167087 0.105933 0.0549438 0.0185314 0.0055783 0.000126226 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000254188 0.00325818 0.00848777 0.0211043 0.0528282 0.0836513 0.148036 0.185688 0.18988 0.156417 0.0918069 0.0386767 0.0164692 0.00332201 0.000119798 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00162685 0.00566067 0.011343 0.0232199 0.0703095 0.094484 0.168977 0.187557 0.170651 0.142695 0.0701441 0.0390239 0.0126219 0.00168652 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00129289 0.00941304 0.0150078 0.0420066 0.0753387 0.119195 0.166363 0.186776 0.152073 0.131239 0.0641012 0.0269284 0.00910442 0.00116129 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.001 0.00186658 0.00519138 0.00818464 0.0235892 0.044963 0.0899121 0.141316 0.168077 0.175949 0.145207 0.108374 0.0533832 0.0277873 0.00494779 0.000251954 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00098659 0.0021224 0.00599335 0.0161167 0.0288388 0.0584841 0.10542 0.139224 0.18023 0.158359 0.146177 0.0874062 0.0431321 0.0224769 0.00303224 0.002 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000357028 0.000642972 0.0021768 0.00757664 0.0171252 0.0434441 0.0703165 0.112382 0.165895 0.170681 0.14295 0.129157 0.0825755 0.0344225 0.0172177 0.00192397 0.00115607 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00162077 0.00518846 0.00925928 0.0260048 0.0523105 0.0861281 0.116945 0.165878 0.167535 0.135147 0.125302 0.0582785 0.0359084 0.0116228 0.00260015 0.000271877 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000564548 0.00138423 0.00241891 0.00564589 0.0161086 0.0386033 0.0542509 0.0935967 0.136513 0.167096 0.154294 0.135012 0.103205 0.0521422 0.0269232 0.00919368 0.00233115 0.000716056 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00188809 0.00783475 0.00898916 0.0196319 0.0461131 0.0691344 0.097663 0.142018 0.157819 0.151376 0.131896 0.0862407 0.0460322 0.0259779 0.00476218 0.00215209 0.000472145 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000895317 0.00161797 0.00747915 0.0122009 0.0332904 0.0508075 0.0750154 0.124362 0.140571 0.147317 0.145071 0.113556 0.085993 0.0304693 0.0195016 0.0102563 0.00159572 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00068624 0.00224453 0.00316967 0.0105845 0.0180473 0.0316704 0.0618765 0.0868968 0.123808 0.157726 0.147875 0.130811 0.101215 0.0629108 0.0376443 0.0180969 0.002633 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.0004992 0.000551224 0.0018976 0.00333382 0.0106812 0.0255503 0.0501086 0.0620868 0.0947598 0.134507 0.161472 0.128965 0.123752 0.108785 0.0449776 0.0314627 0.0133939 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00233031 0.00165155 0.00874179 0.0136932 0.0373736 0.0488351 0.0712063 0.10236 0.150826 0.140585 0.136331 0.108918 0.0849971 0.0528965 0.0255207 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000236499 0.0025176 0.00507365 0.00789157 0.0200965 0.0434368 0.0600933 0.0775825 0.11809 0.144856 0.127628 0.135602 0.102024 0.0740205 0.0483957 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.001 0.00247093 0.00303419 0.00601748 0.0123154 0.0321887 0.0384111 0.062432 0.0825145 0.134152 0.149005 0.130885 0.111798 0.0984495 0.0736138 -#2002 - 0 0 0 0 0 0 0.0248465 0.690495 0.284376 0.000282991 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0.000659495 0.0955214 0.767467 0.135983 0.000369246 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0.00165994 0.233961 0.707644 0.0567356 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0.000198023 0.0118739 0.407832 0.557305 0.0227909 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0.0437734 0.560319 0.386177 0.00973005 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0.000826475 0.112432 0.637682 0.244885 0.00417383 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0.0127169 0.218926 0.619928 0.146775 0.00165316 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0.000879681 0.030146 0.341447 0.544728 0.0817396 0.00105975 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0.00261542 0.0658846 0.451728 0.433915 0.0457938 6.34763e-05 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 2.46225e-05 0.0061607 0.135503 0.50941 0.321423 0.0273781 0.000100927 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0.000136059 0.0173376 0.215 0.525022 0.224508 0.0179213 7.52127e-05 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00433886 0.040736 0.302262 0.488546 0.156203 0.007914 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00760983 0.0869426 0.371419 0.422451 0.106843 0.00473385 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00171181 0.0193588 0.139331 0.419174 0.347638 0.0683616 0.00442461 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00327356 0.0328821 0.200518 0.436944 0.276328 0.0483073 0.00174774 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000258754 0.00697457 0.0684748 0.253334 0.42241 0.214257 0.0335363 0.000754552 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00182077 0.0157355 0.096541 0.314547 0.383552 0.167096 0.0196707 0.00103729 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00373634 0.0277791 0.137627 0.353833 0.338262 0.125663 0.0130936 6.75763e-06 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000595979 0.0077273 0.0491342 0.177323 0.371909 0.292204 0.0893277 0.0114672 0.00031215 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000470835 0.00185925 0.012643 0.0814666 0.223872 0.357939 0.249674 0.0656698 0.00625756 0.000147972 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00347457 0.0206731 0.109116 0.265552 0.34382 0.207351 0.0455712 0.00444258 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.0015539 0.00555663 0.0407252 0.132665 0.303185 0.313956 0.16409 0.0347581 0.00346657 4.34706e-05 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000132466 0.00212324 0.00991445 0.0638701 0.1679 0.318117 0.280365 0.124027 0.0310913 0.00245962 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00102656 0.00287395 0.0206933 0.0780498 0.211863 0.315061 0.243299 0.10538 0.0201278 0.00162524 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 6.4963e-05 0.00147755 0.00600278 0.0339036 0.107393 0.233968 0.306241 0.220025 0.0725819 0.0176402 0.000701848 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.0008241 0.00141913 0.0126854 0.0496946 0.127791 0.263206 0.279502 0.188884 0.0634108 0.0118726 0.000709739 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000641497 0.00551583 0.0183333 0.0642464 0.153828 0.278834 0.264317 0.153848 0.0511358 0.00863721 0.000662473 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000539278 0.000610849 0.00812273 0.0273188 0.0873521 0.182656 0.268713 0.25061 0.130574 0.0371219 0.0063811 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00255395 0.0124524 0.0414684 0.101044 0.216822 0.265898 0.218979 0.102663 0.0318056 0.00617722 0.000136268 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00105515 0.00707909 0.014351 0.0574113 0.123322 0.229349 0.255911 0.197275 0.0903884 0.0216118 0.00224633 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 4.55064e-05 0.00159823 0.00686331 0.0254072 0.0712848 0.149059 0.243966 0.232499 0.17818 0.0690368 0.0200451 0.00201385 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00188057 0.00371268 0.00569194 0.04065 0.0818518 0.167167 0.248479 0.227696 0.153581 0.053183 0.0157223 0.000385162 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000186758 0.000813242 3.5455e-05 0.00410808 0.013411 0.0457093 0.107593 0.186912 0.247028 0.20815 0.125379 0.0488306 0.01121 0.000632148 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000130225 0.00218005 0.0063573 0.0198524 0.0597817 0.115208 0.218506 0.232591 0.187001 0.11059 0.0360897 0.0105111 0.00120049 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000759611 0.00238463 0.0102878 0.0264785 0.0777564 0.134828 0.222024 0.220491 0.176027 0.0877912 0.033106 0.00666441 0.0014016 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000945784 0.00408591 0.0143261 0.0366236 0.0994573 0.146878 0.218092 0.217028 0.153501 0.0760959 0.0274019 0.0050316 0.000533328 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000585302 0.0021131 0.00754966 0.0154166 0.0563399 0.105566 0.159392 0.226523 0.189067 0.148033 0.0651572 0.0222181 0.00203939 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000425521 0.00407756 0.010423 0.0271337 0.0610893 0.113212 0.185789 0.213549 0.189356 0.119587 0.053287 0.0183312 0.00324997 0.000490141 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000396884 0.000797675 0.00641174 0.0122488 0.0287731 0.0806373 0.121687 0.20602 0.201655 0.171764 0.108156 0.04669 0.0138677 0.00089479 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00109069 0.00722635 0.0168651 0.0462561 0.0810923 0.144635 0.209315 0.197316 0.153431 0.0856666 0.0384924 0.0140995 0.00351337 0.001 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000348054 0.00351628 0.0112765 0.0206363 0.0501196 0.0994563 0.166881 0.193123 0.186708 0.143833 0.0826715 0.0298682 0.00892921 0.00263245 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00075372 0.00124628 0.00423696 0.0125368 0.0286567 0.0632443 0.108707 0.163943 0.21452 0.172076 0.135762 0.0545255 0.028256 0.0106181 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000588865 0.00146319 0.00201136 0.00463399 0.0147607 0.0412282 0.0719331 0.108358 0.193667 0.192866 0.161287 0.12488 0.0506589 0.0254061 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 7.12257e-05 0.00244207 0.0014867 0.00640839 0.018934 0.0503163 0.0776306 0.138977 0.186676 0.186499 0.146503 0.112717 0.0486979 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.001 0 0.000137565 0.00328288 0.00975314 0.0237431 0.0579597 0.0987969 0.14599 0.190606 0.161784 0.150462 0.0918257 -#2003 - 0 0 0 0 0 0.00985729 0.392725 0.558203 0.0392142 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0.0355034 0.533464 0.410285 0.0207477 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0.00168381 0.0964109 0.601393 0.291605 0.00890722 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0.00417189 0.187318 0.615323 0.186233 0.00695482 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0.000190895 0.0218644 0.28731 0.565211 0.121055 0.00436897 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0.00116714 0.0444925 0.403546 0.467719 0.0798646 0.00321103 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0.00435453 0.0978823 0.466506 0.373788 0.0557634 0.0017055 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0.000267913 0.0133376 0.159489 0.497459 0.294138 0.0352499 5.83963e-05 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0.00178004 0.0270086 0.233998 0.490399 0.224748 0.0220621 3.75874e-06 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0.00509188 0.0629526 0.296645 0.450124 0.171533 0.0136535 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0.00115764 0.0130683 0.0993804 0.354617 0.399269 0.119974 0.0123826 0.000151265 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0.000160106 0.00250509 0.0243245 0.14641 0.390594 0.332708 0.0948733 0.00811154 0.000313417 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 2.00297e-05 0.00796136 0.0414853 0.197016 0.389018 0.290489 0.0681817 0.00582836 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000648219 0.0116576 0.0760569 0.23493 0.385569 0.232188 0.0554556 0.00349494 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000194641 0.00471513 0.0170514 0.102249 0.279941 0.357558 0.193035 0.0416592 0.00359591 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000405484 0.00399298 0.0384359 0.129807 0.309208 0.326694 0.156165 0.033226 0.00206522 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00190189 0.00799833 0.0538554 0.161962 0.329105 0.290858 0.128714 0.0235515 0.00205346 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000973222 0.002867 0.0160961 0.0795677 0.193497 0.322175 0.26253 0.0993835 0.0222182 0.000692468 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000394903 0.00637493 0.0240673 0.10056 0.232855 0.313859 0.224684 0.0769075 0.0180654 0.00223263 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000442046 0.000658421 0.00988635 0.0450296 0.118287 0.255983 0.285495 0.205272 0.0648767 0.0130494 0.00102072 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000698401 0.00146149 0.0150993 0.0573976 0.145487 0.271149 0.269007 0.172236 0.0543452 0.0118779 0.00124071 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000330315 0.0013896 0.00479338 0.0186373 0.0866433 0.167829 0.268283 0.248369 0.148079 0.0448339 0.0094268 0.00138587 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.0023626 0.00686939 0.0318888 0.0988215 0.199595 0.26698 0.228238 0.114622 0.0438649 0.00675802 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00125284 0.00430373 0.0132167 0.0473793 0.112075 0.215148 0.25206 0.2105 0.102175 0.0356768 0.00621241 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00223606 0.00427745 0.019488 0.0672658 0.125556 0.230734 0.241135 0.185345 0.0888781 0.0283903 0.00669417 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00166609 0.00133391 0.00659391 0.03173 0.0776913 0.147103 0.232214 0.222696 0.174666 0.0741868 0.025067 0.00443436 0.000618164 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000998069 0.00228404 0.0111765 0.0370445 0.0907798 0.173599 0.227598 0.216997 0.151796 0.0610819 0.0217061 0.0035502 0.00138766 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00182786 0.00294737 0.00184304 0.0176026 0.0471796 0.116591 0.179458 0.224069 0.190892 0.142355 0.0530475 0.0178358 0.00434973 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00100657 0.00128319 0.00738053 0.0199115 0.0721933 0.118937 0.193994 0.216246 0.181094 0.119608 0.0493924 0.0144583 0.00449429 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.0015784 0.000805689 0.0029397 0.0128228 0.0367387 0.0706489 0.126627 0.202951 0.216727 0.163661 0.109856 0.0394129 0.0118506 0.00300891 0.00037111 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000645078 0.000354922 0.0010811 0.00572499 0.0176064 0.042789 0.0863882 0.13902 0.205368 0.207708 0.153876 0.088926 0.0365126 0.0111373 0.00258139 0.000281782 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000190825 0.00173311 0.00406452 0.00860973 0.0203504 0.050394 0.102686 0.15701 0.200922 0.188413 0.148657 0.0760491 0.0288784 0.0107925 0.00124898 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 1.67221e-05 0.00524627 0.00957871 0.0275505 0.0642793 0.113474 0.163335 0.204898 0.176198 0.132909 0.0641371 0.0258896 0.0114676 0.00101904 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000192105 0.00141966 0.00593516 0.0153882 0.038643 0.0720258 0.112596 0.188022 0.182745 0.170438 0.119198 0.0595514 0.0280765 0.00548104 0.000288925 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000326688 0.00192731 0.00199763 0.011139 0.0185587 0.0427036 0.0784056 0.129826 0.185809 0.176942 0.167506 0.103017 0.0523098 0.0242498 0.00432819 0.000953942 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00154645 0.000453548 0.0038252 0.0119319 0.0270192 0.0487433 0.0886228 0.142734 0.179355 0.174723 0.154251 0.0939753 0.0457415 0.0198028 0.00585237 0.00142187 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.001 0.000359179 0.0043632 0.00502858 0.0179961 0.0330031 0.0508207 0.0988123 0.149781 0.184613 0.166269 0.136069 0.0942624 0.0349103 0.0186812 0.00403039 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000697091 0.00170665 0.00192679 0.00975636 0.017085 0.0354278 0.0626958 0.109735 0.168223 0.176281 0.15951 0.120598 0.0813324 0.036794 0.0123205 0.00378545 0.00212499 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00189666 0.00110334 3.95398e-05 0.002202 0.0128938 0.0247848 0.0399291 0.0790068 0.108069 0.171075 0.174425 0.143337 0.125384 0.0669567 0.0328613 0.0128124 0.00322469 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000960174 0.000659161 0.00349023 0.0152939 0.0333982 0.0481397 0.0780828 0.132466 0.166342 0.162304 0.144878 0.114908 0.0515613 0.0351132 0.00822314 0.00301164 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.002 0.000134073 0.00130253 0.00241956 0.0106622 0.0136771 0.0336363 0.0513686 0.0938235 0.138654 0.162391 0.158325 0.138771 0.094787 0.0602738 0.0259233 0.0105931 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000266632 0.00141285 0.0028366 0.011542 0.0264594 0.034341 0.0703704 0.0919251 0.152436 0.149359 0.154677 0.12562 0.0997426 0.042461 0.0224553 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00178554 0.00235594 0.00424538 0.0100371 0.0335106 0.0441715 0.0785987 0.101328 0.139348 0.159228 0.143441 0.119692 0.0846471 0.0459951 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000970744 0.00102926 0.00134803 0.00923203 0.0155864 0.0218325 0.0530471 0.0841054 0.123656 0.135719 0.159355 0.134414 0.109245 0.0776318 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000172659 0.00107245 0.000754888 0.00238988 0.00639748 0.00968883 0.0201024 0.0317521 0.0525301 0.0817098 0.125031 0.152966 0.141426 0.129302 0.10831 -#2004 - 0 0 0 0 0 0 0.000501622 0.0609272 0.528765 0.386428 0.0230678 0.000310457 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0.00343718 0.153996 0.584555 0.249848 0.00816385 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0.020702 0.28169 0.55315 0.140555 0.00390268 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0.00221666 0.0559542 0.405306 0.455974 0.0796679 0.000881467 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0.000181807 0.00882447 0.137999 0.458711 0.34293 0.0499998 0.00135387 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0.000922938 0.0317614 0.223639 0.466119 0.245399 0.0304166 0.00174235 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0.000248314 0.00743848 0.0687199 0.30942 0.414165 0.18177 0.0182385 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0.00283442 0.0178055 0.119961 0.358145 0.371701 0.123317 0.00623666 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0.000516575 0.00408192 0.0414869 0.177603 0.392902 0.28914 0.0854542 0.00863471 0.000181118 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0.000989316 0.0127997 0.0758035 0.237239 0.375983 0.234481 0.0594143 0.0032902 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0.00220367 0.0264701 0.115433 0.284691 0.346021 0.183319 0.0393537 0.00246054 4.90546e-05 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0.000682252 0.00729233 0.0484176 0.150801 0.321929 0.299537 0.140388 0.0301947 0.000757601 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0.000551297 0.00217332 0.017172 0.0786626 0.193206 0.319111 0.259474 0.107171 0.0213082 0.00116998 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000341478 0.00578521 0.0334545 0.11073 0.231542 0.301265 0.221628 0.0757441 0.0193287 0.000180822 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00135476 0.0143105 0.0488416 0.138457 0.264892 0.271294 0.188159 0.056801 0.0154747 0.0004157 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000127931 0.00827419 0.0228515 0.0700144 0.166229 0.273065 0.252644 0.149377 0.0469878 0.0102528 0.000175687 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000321429 0.00162663 0.0106599 0.0320929 0.105735 0.197751 0.258028 0.228554 0.118281 0.0379781 0.00812977 0.000842114 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00099589 0.00455286 0.0148795 0.0531832 0.122983 0.219907 0.251788 0.196857 0.0973973 0.0305047 0.00695103 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00122111 0.00717191 0.0246243 0.0778602 0.142157 0.234054 0.229211 0.172066 0.0805305 0.027149 0.00391004 4.48758e-05 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.001 0.00439129 0.0109544 0.0441103 0.0840012 0.171618 0.235663 0.205805 0.15489 0.0658582 0.0200574 0.00165111 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.0019482 0.00400188 0.0243572 0.0580257 0.101852 0.19506 0.218641 0.190235 0.136528 0.0534275 0.0137659 0.00215712 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000348718 0.00390621 0.00963648 0.0343067 0.0656521 0.129673 0.199032 0.212087 0.173136 0.110688 0.048676 0.0120116 0.000846545 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000218018 0.00168076 0.00576159 0.0129373 0.0484737 0.081022 0.142755 0.214978 0.192487 0.15899 0.089484 0.0394324 0.0105161 0.00126321 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00267385 0.00777022 0.0266906 0.0521892 0.105171 0.160347 0.204505 0.178752 0.145779 0.0747766 0.0316117 0.00911997 0.000613959 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.0018724 0.00410813 0.0118835 0.033835 0.0734014 0.111025 0.172432 0.195301 0.171835 0.128235 0.0632984 0.027155 0.0046153 0.000952853 5.01591e-05 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000715831 0.00138277 0.00627175 0.021206 0.0461949 0.0809964 0.127356 0.181314 0.177702 0.161708 0.110549 0.0560782 0.0231523 0.00536619 5.96938e-06 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000827375 0.0015798 0.00291817 0.0111512 0.0309821 0.0516881 0.0829127 0.149263 0.187706 0.161976 0.15373 0.0931296 0.0497256 0.01829 0.00368297 0.000437756 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.001 0.00196589 0.00938043 0.0137739 0.0357752 0.0627296 0.0998036 0.153823 0.18391 0.158813 0.133438 0.083738 0.0394412 0.0175205 0.00383132 0.0010565 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00213139 0.00564691 0.00794929 0.0200304 0.0474991 0.076639 0.112594 0.158846 0.173764 0.141644 0.13173 0.0690935 0.0346141 0.0151644 0.00213213 0.000521896 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 5.18344e-05 0.000948166 0.00227178 0.00751254 0.0124241 0.0301777 0.0531915 0.0761357 0.128915 0.169192 0.162205 0.142284 0.109043 0.0632443 0.0300535 0.0100494 0.00230011 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00032526 0.00200736 0.00266738 0.00653809 0.0203094 0.0357714 0.0602569 0.0913274 0.143112 0.162974 0.147659 0.135196 0.0989509 0.0571705 0.0253579 0.00920742 0.00116848 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00163477 0.00283306 0.00314399 0.00947866 0.020278 0.0498553 0.0668049 0.104022 0.15179 0.154726 0.138637 0.13552 0.0830145 0.0447275 0.0245518 0.00777195 0.00121011 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000106611 0.00262879 0.00368602 0.00495314 0.0121401 0.0339539 0.058916 0.067112 0.115878 0.15474 0.1487 0.139759 0.109698 0.0799616 0.0407647 0.0172706 0.00873181 0.001 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000986629 0.00101337 0.00069254 0.00444659 0.00865081 0.0186151 0.0386407 0.0546353 0.0867162 0.131221 0.149733 0.14207 0.125762 0.115008 0.059382 0.0348907 0.0205001 0.00671566 0.000319807 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.001 0.0013366 0.00194261 0.00485976 0.0143627 0.0285152 0.0435535 0.0611161 0.0957383 0.13158 0.145273 0.139462 0.120372 0.108264 0.0525985 0.028557 0.0145075 0.00537996 0.00158068 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000136539 0.00102654 0.00152153 0.00445684 0.00995631 0.0135128 0.0335291 0.0510735 0.0690678 0.102959 0.1425 0.13756 0.130327 0.109872 0.0949887 0.0526233 0.0281661 0.0147443 0.00197914 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 1.24959e-05 0.000987504 0.002 0.00512522 0.0106377 0.0225069 0.0443613 0.046289 0.0807 0.111615 0.138509 0.147507 0.115025 0.1014 0.086671 0.0458842 0.0221458 0.0130127 0.00520525 0.000404654 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.001 0.000646821 0.005074 0.00395482 0.0141374 0.0252232 0.0501958 0.0543559 0.0906656 0.122352 0.141758 0.123405 0.118501 0.10943 0.0629014 0.03706 0.0224559 0.0133328 0.00354996 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00211186 0.00288814 0.0025369 0.00700192 0.01922 0.0390232 0.0449133 0.0602334 0.0915804 0.13314 0.141027 0.11724 0.112006 0.0992973 0.0673735 0.0318954 0.017018 0.00700691 0.00425073 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.001 0 0.00207429 0.00336487 0.0053787 0.0117376 0.0266938 0.0391322 0.0487263 0.0675384 0.0950266 0.14598 0.131719 0.104184 0.113939 0.0893808 0.0586534 0.0287253 0.0166837 0.00762792 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.001 0.00137145 0.00393291 0.00998682 0.0237314 0.0253394 0.04188 0.0528719 0.0780236 0.11636 0.128772 0.121523 0.108304 0.102625 0.0813845 0.0494602 0.0244759 0.0190658 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00035724 0.000793846 0.00434288 0.00591761 0.0095968 0.0213126 0.0336146 0.0410521 0.0660406 0.0872131 0.114656 0.127528 0.123433 0.101734 0.101062 0.0707783 0.0486616 0.0216737 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000594396 0.00223843 0.00587683 0.00723938 0.013217 0.0265224 0.0373522 0.0528799 0.0554181 0.10693 0.109464 0.126693 0.11982 0.0879083 0.0948155 0.0707275 0.038314 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00135525 0.00247154 0.00273208 0.00493491 0.0125849 0.0111871 0.025618 0.0439523 0.0576086 0.0755854 0.0959677 0.121519 0.114815 0.113598 0.0933359 0.102032 0.0520537 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.001 0.00151783 0.00118022 0.00327227 0.00563052 0.0115624 0.0221193 0.0300267 0.0471127 0.0583525 0.0849981 0.106882 0.117074 0.115162 0.109144 0.0791715 0.0887348 -#2005 - 0 0 0 0 0 0 0 0 0 0 0.00309248 0.133551 0.585116 0.260456 0.0177645 2.006e-05 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0.001 0.0234502 0.329112 0.53072 0.112356 0.003362 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0.00330515 0.0999238 0.513966 0.342783 0.0400221 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0.0247569 0.25987 0.524505 0.181572 0.00929693 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0.00705915 0.0898691 0.412522 0.407026 0.0808079 0.00271655 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0.00200259 0.0237343 0.223549 0.465746 0.245586 0.0377128 0.00166909 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 2.546e-05 0.00842244 0.0835053 0.353704 0.398409 0.138588 0.0173458 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00204501 0.0288307 0.179173 0.416679 0.299828 0.0702509 0.00319354 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000940435 0.00927321 0.0874369 0.276481 0.38904 0.199271 0.0363425 0.00121537 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 5.9773e-05 0.004815 0.0312518 0.153033 0.36201 0.322986 0.105695 0.0201494 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00132756 0.0128384 0.0757119 0.238814 0.369504 0.2313 0.0621392 0.00768633 0.000677437 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000162127 0.00629487 0.0386965 0.134223 0.302668 0.315681 0.16179 0.0376374 0.00284595 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000655236 0.00234178 0.0162567 0.0773899 0.204983 0.325888 0.248154 0.103438 0.019893 0.000250068 0.000749932 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00240361 0.00538226 0.0448675 0.117868 0.264513 0.304349 0.190293 0.0558363 0.0141893 0.000297324 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.001 0.00453261 0.0166407 0.0779289 0.173391 0.295221 0.249817 0.135876 0.0395983 0.00584826 0.000146074 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.0014709 0.0106621 0.0431758 0.10846 0.225326 0.287814 0.205959 0.0915955 0.0234389 0.00209848 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000150566 0.00470562 0.0227537 0.0694659 0.158303 0.25751 0.24978 0.168529 0.0554239 0.010891 0.00248608 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000853122 0.00247337 0.0115878 0.0356352 0.105784 0.20067 0.25981 0.219637 0.117197 0.0392644 0.00614104 0.000946615 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.001 0.00718308 0.0229407 0.0734309 0.128761 0.227085 0.247798 0.183812 0.0793523 0.0245561 0.00408103 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000566298 0.0014337 0.00554469 0.0103763 0.0492442 0.0872805 0.176819 0.244989 0.208967 0.140418 0.0554099 0.0160532 0.00289824 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000546649 0.00930955 0.0251561 0.0586121 0.131774 0.208655 0.220987 0.190333 0.104072 0.0421199 0.0070595 0.000889423 0.000486715 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00148259 0.00470154 0.0121135 0.0469596 0.0896907 0.151417 0.219671 0.204899 0.154672 0.0795494 0.0303177 0.00396963 0.000556555 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00217148 0.00914374 0.03081 0.0568099 0.121496 0.17752 0.223221 0.177155 0.126266 0.0516033 0.0212987 0.00218016 0.000324102 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00189198 0.00601795 0.0155372 0.0457032 0.0785464 0.142749 0.198346 0.203698 0.156104 0.0988831 0.0353393 0.0153801 0.00107557 0.000727548 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00125174 0.00180937 0.011864 0.0275701 0.0578433 0.108126 0.175459 0.196891 0.167566 0.139227 0.0710167 0.0320373 0.00745924 0.00187995 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.001 0 0.00413481 0.0064392 0.0180892 0.0396534 0.0781965 0.131232 0.184058 0.181514 0.160239 0.111991 0.0506098 0.0255474 0.00529618 0.000658747 0.000916146 0.000425108 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00175704 0.00215334 0.00425442 0.0129924 0.0286922 0.061649 0.0864424 0.149143 0.194802 0.169978 0.145786 0.0836942 0.0404532 0.0160765 0.00212638 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00142666 0.00157334 0.00210144 0.00831743 0.0197921 0.0333257 0.0754493 0.12494 0.164694 0.175736 0.161066 0.122258 0.0707585 0.0282327 0.00586245 0.00446754 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00152378 0.0024398 0.006848 0.00849355 0.0287136 0.0636826 0.0815557 0.152585 0.160831 0.168487 0.14393 0.103886 0.0442842 0.0216408 0.00910304 0.00199653 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.001 0.000268019 0.00174958 0.00548273 0.00818822 0.0144802 0.0479579 0.0691857 0.0993442 0.165169 0.160926 0.153834 0.139562 0.073074 0.0388871 0.0154483 0.00503935 0.000404398 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.001 0.000536712 0.00413445 0.00493453 0.0107533 0.0329552 0.0505566 0.0834891 0.130399 0.160012 0.167581 0.133414 0.116716 0.0620349 0.0249237 0.0116016 0.0049585 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000109423 0.00270325 0.00290629 0.00398678 0.00846621 0.0191073 0.0375493 0.0672031 0.0987008 0.141039 0.168659 0.145362 0.132039 0.094695 0.0435815 0.0266229 0.00696976 0.000299087 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00167998 0.00436521 0.00514726 0.0149607 0.0256516 0.0566964 0.0746416 0.13022 0.14383 0.146736 0.136291 0.131428 0.0647418 0.043605 0.0122705 0.00682715 0.000907446 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.0015295 0.00217063 0.0025429 0.0100288 0.0241808 0.0411932 0.0611382 0.0945391 0.130642 0.153537 0.148248 0.120002 0.104244 0.0628219 0.0250435 0.0124646 0.00360185 0.00207212 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000809243 0.00219076 0.001 0.00381134 0.0074997 0.0120159 0.0313488 0.0515659 0.0705973 0.108774 0.141723 0.155901 0.123015 0.117076 0.0960548 0.0461752 0.0131578 0.0131821 0.00310199 0.001 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000338949 0.00166105 0.00148108 0.00907452 0.00951461 0.0224594 0.0410965 0.0611778 0.0832847 0.11939 0.148953 0.132034 0.126179 0.114925 0.0662564 0.0355566 0.0192395 0.00564734 0.00076792 0.000962258 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.0014408 0.00401166 0.00560493 0.00898476 0.00973388 0.0260737 0.0520844 0.0660181 0.102421 0.136776 0.135939 0.14325 0.108479 0.0868194 0.0585253 0.0367834 0.0121073 0.00353327 0.00141469 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.001 0.000255104 0.00470586 0.00514719 0.0132213 0.0181264 0.0421461 0.0627388 0.0755351 0.112749 0.132402 0.139452 0.120336 0.111793 0.0733503 0.0475367 0.0237744 0.00949372 0.00320068 0.0029559 7.90497e-05 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000849508 0.00500383 0.0114983 0.0163378 0.0245375 0.0451574 0.0743339 0.084934 0.130565 0.137304 0.129713 0.111752 0.0958705 0.070233 0.0384525 0.0168 0.00427944 0.00237942 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00227291 0.00312733 0.00753419 0.0128467 0.0265643 0.038976 0.0584534 0.0658062 0.113266 0.12335 0.129496 0.128319 0.0991471 0.0857652 0.0517018 0.0263903 0.0187368 0.00482779 0.000417434 0.00242943 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 1.05361e-07 0.00299989 0.00616394 0.00812505 0.0150478 0.0290624 0.0487899 0.0717515 0.0834127 0.128589 0.123194 0.106374 0.118945 0.0962228 0.0753743 0.0414652 0.0274752 0.0122138 0.00407499 0.000718298 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00201717 0.00381371 0.00737727 0.0116409 0.0182438 0.0374127 0.0610789 0.0775587 0.0973381 0.118188 0.133322 0.102581 0.106692 0.0962918 0.0620513 0.0325294 0.0172583 0.00998573 0.00351623 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00210579 0.00568729 0.00651952 0.00933564 0.0183867 0.0342505 0.036744 0.0552924 0.0812912 0.120689 0.124331 0.109371 0.102189 0.11125 0.0709557 0.0601673 0.0248054 0.0148346 0.00843264 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.001 5.84733e-05 0.00175043 0.00368687 0.00782582 0.0125104 0.0231083 0.0395186 0.0542511 0.0655583 0.0939426 0.122462 0.120429 0.112128 0.0875029 0.101613 0.0681326 0.0411367 0.0249719 0.0150577 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.001 0 0.00226617 0.00073383 0.00575633 0.0133863 0.0200976 0.031411 0.0408577 0.0586441 0.0875016 0.089348 0.119452 0.104008 0.111328 0.100236 0.0852949 0.0673292 0.0295031 0.0187252 -#2006 - 0 0 0 0 0 0 0 0 0.0285989 0.554183 0.409811 0.00740651 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0.000778807 0.133427 0.662565 0.201281 0.00194866 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0.000110839 0.0174525 0.30894 0.589867 0.0830266 0.000603071 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0.00134879 0.0695728 0.485886 0.410114 0.0330785 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0.00955854 0.179923 0.543986 0.249308 0.0172234 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0.00108152 0.0437689 0.312508 0.485973 0.150788 0.00588046 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0.00902087 0.110315 0.412638 0.385393 0.0804803 0.00215338 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0.00151711 0.0295265 0.202188 0.444592 0.27753 0.0441684 0.000478544 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0.000252549 0.0072045 0.0779312 0.285632 0.414697 0.191032 0.0232504 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0.0015976 0.023909 0.137465 0.35601 0.344936 0.122607 0.013475 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0.000162589 0.00717674 0.0554608 0.203103 0.371369 0.281979 0.0754772 0.00527081 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00218912 0.0196887 0.103474 0.263634 0.346722 0.214523 0.0473038 0.00246623 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00681028 0.0426362 0.148614 0.31121 0.302089 0.158782 0.0285458 0.00131313 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00177766 0.0147687 0.0799981 0.195051 0.321153 0.258547 0.107055 0.0212903 0.00035886 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 2.60571e-05 0.0062026 0.037505 0.108829 0.24557 0.301798 0.214883 0.0733331 0.011695 0.000158594 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00340945 0.0106864 0.0608094 0.148008 0.282491 0.265735 0.170229 0.0502436 0.00835022 3.8215e-05 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00055012 0.00535027 0.0267051 0.0908937 0.186353 0.282047 0.241153 0.124822 0.0373666 0.00476004 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000119162 0.00179069 0.0106474 0.0476711 0.118502 0.221674 0.26667 0.209087 0.0945876 0.0271732 0.00207728 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000379989 0.00608189 0.0195247 0.0744062 0.142193 0.250009 0.238717 0.18034 0.0701457 0.0164399 0.00176199 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00236837 0.0108665 0.0396567 0.0921797 0.179273 0.24847 0.219021 0.143726 0.049657 0.0144087 0.000373152 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000630638 0.00539989 0.0166485 0.061775 0.115321 0.20913 0.234649 0.195208 0.115368 0.0370848 0.00810562 0.000679439 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 2.99396e-05 0.00491262 0.00567457 0.0349128 0.0819408 0.135695 0.227002 0.216533 0.171874 0.084412 0.0316566 0.00496933 0.000388157 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00143697 0.00475261 0.0167365 0.0488104 0.0939389 0.174444 0.221058 0.193742 0.154836 0.0622077 0.0243037 0.00336476 0.000368408 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000273215 0.00382841 0.00730776 0.0254864 0.0703323 0.109928 0.19795 0.210606 0.176524 0.127147 0.0499713 0.019541 0.00110518 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000635887 0.0048961 0.0130942 0.0443134 0.0802296 0.140014 0.204576 0.190968 0.165804 0.0999645 0.0407566 0.0134382 0.00130932 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000608401 0.00298613 0.00706669 0.0249536 0.0582683 0.0957012 0.161258 0.195692 0.180111 0.15352 0.0773632 0.0339483 0.00820216 0.000321138 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00121087 0.00522123 0.0117643 0.0371784 0.0696798 0.111786 0.181928 0.185253 0.168617 0.134229 0.0578886 0.0294579 0.00578601 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000612678 0.00520415 0.00548468 0.0174954 0.0501325 0.0785626 0.135784 0.193249 0.177655 0.150897 0.109532 0.0494453 0.0211105 0.00483508 7.57314e-07 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00230736 0.00389293 0.0123318 0.0275891 0.0697419 0.0952005 0.149786 0.180601 0.159376 0.147665 0.0876833 0.0438739 0.0179364 0.0020139 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000560981 0.00362947 0.00683122 0.0178254 0.0419183 0.0697923 0.114949 0.17144 0.168327 0.150272 0.126799 0.0817043 0.0297301 0.0135174 0.00270277 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00258882 0.00417138 0.0107197 0.0281794 0.056216 0.0740704 0.133283 0.171973 0.165876 0.140488 0.116614 0.0556501 0.0295036 0.0100091 0.000657354 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000255507 0.00418302 0.00457497 0.0191801 0.0392243 0.0635163 0.0853307 0.150432 0.169699 0.150162 0.136557 0.101161 0.0428787 0.0260002 0.00679982 4.60737e-05 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 3.61202e-05 0.00318897 0.0027744 0.00755519 0.0270232 0.0486095 0.0687396 0.112449 0.141478 0.175238 0.143217 0.126838 0.0784316 0.0400326 0.0203809 0.00400726 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00158788 0.00414548 0.00340704 0.0160035 0.0323459 0.0494697 0.0855545 0.128706 0.157576 0.150112 0.134636 0.118683 0.0693366 0.0290561 0.0148445 0.00453564 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 7.91469e-05 0.00436092 0.00137863 0.00702683 0.0227426 0.0431851 0.0612509 0.0871895 0.147366 0.158815 0.145005 0.11849 0.111954 0.0460258 0.0304199 0.0117023 0.00300791 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00184128 0.00359239 0.00437516 0.00918681 0.0349577 0.0437189 0.0796535 0.100142 0.14591 0.149606 0.144644 0.113272 0.0877736 0.0453613 0.0280949 0.00658138 0.00129028 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000604685 0.00341503 0.00392297 0.00830151 0.0151709 0.0425953 0.0552514 0.078894 0.116458 0.150634 0.148641 0.120453 0.119148 0.0736384 0.0313374 0.0233073 0.00690583 0.00132065 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.001 0.000832262 0.00197026 0.00552241 0.00943251 0.0233683 0.0487102 0.0683822 0.0896513 0.127724 0.140667 0.142061 0.129146 0.0951389 0.0639264 0.0291353 0.016955 0.00571216 0.000664442 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00310175 0.00304393 0.00668332 0.0164707 0.0331322 0.0548547 0.0676777 0.103228 0.136418 0.140837 0.126445 0.118437 0.0950674 0.0484207 0.0298389 0.0125379 0.00322806 0.000578923 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00130381 0.00340007 0.00467661 0.00820885 0.0260031 0.040251 0.0585677 0.0821882 0.120002 0.130605 0.13428 0.115447 0.103584 0.0913117 0.040428 0.0246765 0.0114415 0.00362475 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.0017879 0.000463008 0.00408621 0.00786056 0.0144748 0.0284994 0.0464056 0.0648851 0.0930709 0.121467 0.141102 0.127531 0.105512 0.103925 0.0676049 0.0371311 0.0236473 0.00895844 0.00158774 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00180726 0.00419274 0.00481366 0.0077554 0.0178349 0.0384623 0.0571374 0.061706 0.107205 0.133574 0.129941 0.111017 0.114012 0.100096 0.0526095 0.0305913 0.0162083 0.00879763 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00247802 0.00552769 0.00524256 0.0120856 0.0283667 0.0402851 0.0604349 0.0800903 0.111172 0.130421 0.128715 0.106315 0.108915 0.0819886 0.043538 0.0286852 0.0157689 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00330104 0.00259932 0.00200952 0.00915254 0.0219098 0.0311349 0.0508931 0.0549441 0.0919329 0.120796 0.130748 0.123537 0.100269 0.096231 0.0701031 0.049993 0.0241783 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00132418 0.00313964 0.00253618 0.0031556 0.012645 0.0221419 0.0359136 0.0574123 0.0735755 0.100297 0.120918 0.130787 0.108099 0.0987165 0.0881694 0.0665076 0.0416428 -#2007 - 0 0 0 0 0 0.000682362 0.32338 0.670657 0.00528065 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0.00549042 0.535704 0.458104 0.000701372 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0.0310262 0.702508 0.266177 0.000288708 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0.0951552 0.776598 0.128247 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0.000806671 0.22683 0.713742 0.0586216 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0.00924964 0.386717 0.578135 0.0258985 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0.0334921 0.533905 0.42323 0.00937325 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0.000782404 0.0863209 0.630192 0.279473 0.00323182 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0.00397978 0.176164 0.64448 0.173649 0.00172769 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0.0152442 0.292889 0.58907 0.102705 9.21371e-05 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0.000589417 0.0400871 0.40489 0.4991 0.0552665 6.64506e-05 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00184955 0.0837134 0.493017 0.390565 0.030855 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00907197 0.148867 0.537902 0.288267 0.0158911 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000157824 0.0205095 0.233602 0.530354 0.207937 0.00743866 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00168441 0.0465102 0.315356 0.491673 0.13983 0.00494633 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00609802 0.0829491 0.387769 0.428311 0.0928356 0.00203666 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000553896 0.0114183 0.133396 0.437137 0.355088 0.0610919 0.00131563 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000964714 0.0263262 0.189286 0.455177 0.289309 0.0387831 0.00015354 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00482809 0.0496198 0.251728 0.444 0.223001 0.0268234 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000199289 0.00819309 0.0851699 0.306957 0.411584 0.172258 0.0155291 0.00010906 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00122043 0.0185076 0.123141 0.353267 0.37002 0.123883 0.00996149 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00364896 0.0280985 0.166276 0.382045 0.322352 0.0921219 0.0054579 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 9.45345e-06 0.0082212 0.0528106 0.211074 0.387062 0.270255 0.0680578 0.00250994 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00131814 0.00998123 0.0839585 0.255732 0.369642 0.229587 0.0465885 0.00319216 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.0025019 0.0227362 0.112823 0.295085 0.344499 0.187798 0.0331737 0.00138337 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000123562 0.00525226 0.0378086 0.142857 0.325345 0.318481 0.144509 0.0242399 0.00138386 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000732522 0.0088907 0.0607035 0.177582 0.333769 0.288994 0.109903 0.0194254 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00211549 0.0133034 0.0831983 0.216003 0.328228 0.256106 0.0878908 0.0130922 6.2537e-05 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000194034 0.00612437 0.0223177 0.10504 0.250803 0.319006 0.2202 0.0691423 0.00697041 0.000203314 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00116737 0.00874964 0.0394409 0.129907 0.272873 0.298165 0.194224 0.0498817 0.00559183 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00144174 0.0122535 0.0611437 0.154224 0.293918 0.273299 0.160081 0.0414069 0.00223243 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000193913 0.00438354 0.018455 0.0835261 0.176023 0.300123 0.254415 0.132509 0.0292963 0.00107525 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000570893 0.00749611 0.0277021 0.0987983 0.210759 0.290891 0.236295 0.101547 0.0255905 0.000349491 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.0019664 0.00944075 0.0477777 0.117635 0.231373 0.276641 0.212749 0.0833403 0.0188022 0.000275475 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00296766 0.0136206 0.0588125 0.136176 0.256617 0.265785 0.189386 0.0644202 0.0113041 0.000910358 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000166069 0.0051521 0.0194941 0.0836034 0.153326 0.264668 0.247982 0.162551 0.054619 0.00843855 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000675531 0.00874167 0.0350034 0.0917613 0.179642 0.267187 0.230593 0.13369 0.0437475 0.00895876 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 7.20129e-05 0.00400583 0.00964574 0.0392551 0.118212 0.201747 0.258945 0.213468 0.116136 0.0329072 0.0047595 0.00084666 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00118436 0.00382903 0.0163949 0.0614967 0.122969 0.217904 0.253999 0.198512 0.0933775 0.027286 0.00304781 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000201137 0.00179656 0.00731881 0.0236904 0.0755017 0.133051 0.240245 0.236352 0.18364 0.0718201 0.0217401 0.00464334 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 8.75566e-05 0.00347382 0.00800238 0.0353133 0.0860319 0.162432 0.242743 0.222585 0.154428 0.0677763 0.0161881 0.000939051 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000221292 0.00312252 0.0136643 0.0431625 0.107709 0.180381 0.234687 0.20958 0.139255 0.0504222 0.0167421 0.00105408 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00288878 0.00430211 0.0199773 0.056287 0.110003 0.202115 0.231362 0.199505 0.117273 0.0439545 0.0121947 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000205553 0.00196225 0.00802579 0.024613 0.069998 0.127353 0.218801 0.220873 0.174745 0.107623 0.0379062 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00156293 0.00472624 0.0125078 0.0356423 0.081944 0.142344 0.209852 0.212585 0.179172 0.0809388 -#2008 - 0 0 0 0 0 1.76668e-05 0.430127 0.569738 0.000117405 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0.00127966 0.700683 0.298037 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0.0183782 0.885806 0.0958157 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0.113085 0.869533 0.017382 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0.324542 0.673748 0.0017101 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0.00161466 0.594272 0.40387 0.000243244 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0.0101112 0.821487 0.168402 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0.0687103 0.891127 0.0401626 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0.232713 0.762087 0.00520019 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0.00104768 0.481635 0.516878 0.000439553 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00690932 0.73226 0.26083 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.0449068 0.863925 0.0911681 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.16823 0.808036 0.0237343 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000906678 0.384432 0.610126 0.00453547 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00940256 0.619467 0.370354 0.000776328 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.0400859 0.791944 0.167613 0.00035629 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 5.40916e-05 0.126282 0.813418 0.060246 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00196467 0.296563 0.684046 0.0174263 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.010547 0.51035 0.473527 0.00557616 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.0368723 0.696636 0.265246 0.00124598 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00109205 0.102211 0.776659 0.11993 0.000107843 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.0032723 0.23653 0.713978 0.0462198 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.0119335 0.422324 0.550356 0.0153864 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000185151 0.0426121 0.588544 0.363254 0.00540415 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000547827 0.0994771 0.704101 0.195187 0.000687063 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00448579 0.199095 0.702046 0.0935662 0.000807294 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000446879 0.0140863 0.345544 0.600368 0.0395367 1.8961e-05 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000886474 0.0387762 0.500201 0.444543 0.0155935 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00202714 0.0861372 0.617815 0.288088 0.00593215 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00794632 0.170858 0.65478 0.164337 0.00207827 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.0167532 0.289593 0.616362 0.0768731 0.000419571 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00042059 0.0402028 0.434197 0.492624 0.0325557 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00305242 0.0839595 0.545158 0.353911 0.0139191 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000255638 0.00783082 0.153395 0.616484 0.216697 0.00533734 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000204914 0.0220191 0.247909 0.599232 0.128154 0.00248165 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00125239 0.0388554 0.370487 0.525615 0.0626224 0.00116774 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00238617 0.0766767 0.482499 0.399968 0.0379458 0.000523765 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00813633 0.140267 0.548572 0.285934 0.0169814 0.000108781 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000174246 0.0174773 0.2216 0.572988 0.180986 0.00677466 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00212989 0.0445068 0.319856 0.518011 0.112078 0.00341811 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000893543 0.00721696 0.075599 0.420083 0.433744 0.0611213 0.00134247 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000802044 0.0117628 0.122056 0.501158 0.328875 0.0346059 0.000739658 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 3.17884e-05 0.0013839 0.0218236 0.1975 0.527042 0.235575 0.0162648 0.000379282 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00239985 0.0378442 0.292644 0.50605 0.152418 0.00864464 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000868389 0.00903848 0.0770417 0.359465 0.449621 0.101231 0.00273555 0 -#2009 - 0 0 0 0 0 0 0 0.183679 0.780778 0.0355428 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0.00542915 0.457009 0.530557 0.00700477 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0.0491671 0.67565 0.274219 0.000963183 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0.00125398 0.181629 0.705769 0.111046 0.000302415 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0.01928 0.382515 0.555736 0.0424142 5.46987e-05 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0.000876846 0.0712817 0.551762 0.361348 0.0147313 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0.00776188 0.186957 0.59209 0.209188 0.00400278 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0.000980434 0.033361 0.330103 0.525026 0.108995 0.001535 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0.0041987 0.089901 0.452362 0.401976 0.0513987 0.000163932 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0.00023531 0.0159407 0.184993 0.499056 0.27611 0.023665 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0.0029472 0.0483444 0.291488 0.471595 0.17476 0.0108651 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0.000122303 0.00951375 0.103996 0.382258 0.394869 0.104837 0.00440384 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00134359 0.0266996 0.179024 0.423193 0.307717 0.0610754 0.00094724 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00560892 0.0653322 0.25527 0.413334 0.227909 0.0323348 0.000211375 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000468778 0.0177099 0.109911 0.329026 0.368879 0.155926 0.0177656 0.00031352 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00378328 0.0400093 0.165795 0.372277 0.30737 0.101404 0.00936131 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000725919 0.00977665 0.0736136 0.22778 0.368873 0.250406 0.0644342 0.00439102 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00385513 0.0225156 0.114778 0.286132 0.33282 0.197248 0.0409182 0.001733 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000542695 0.00763174 0.0477443 0.15701 0.324495 0.294246 0.14133 0.0256032 0.00139625 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00246069 0.0146529 0.0827695 0.205978 0.321552 0.255229 0.0994229 0.0179343 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000771411 0.00533453 0.031285 0.111045 0.257255 0.303845 0.213162 0.068456 0.00874282 0.000102587 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00258995 0.0103965 0.0599194 0.140471 0.288643 0.276305 0.169244 0.0496603 0.00203449 0.000736022 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00043508 0.00518131 0.0209489 0.0866421 0.186148 0.290724 0.248748 0.124939 0.033439 0.0027954 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00178017 0.00771499 0.038919 0.110977 0.227569 0.281355 0.217685 0.0901211 0.0226173 0.00126114 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000326846 0.004349 0.0153002 0.0601027 0.139626 0.256015 0.259075 0.181594 0.0680117 0.0154499 0.000150389 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00179908 0.00539471 0.0264656 0.0863124 0.17145 0.26484 0.236373 0.144502 0.0519482 0.0107869 0.000127527 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00388362 0.010839 0.046603 0.109191 0.207627 0.248634 0.214136 0.114756 0.039959 0.00437148 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000706624 0.00596162 0.0201025 0.0661744 0.129582 0.230631 0.240248 0.188231 0.0883151 0.0272465 0.00251199 0.000288698 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00403564 0.00778653 0.0343038 0.0861159 0.156037 0.235636 0.223405 0.163393 0.0694224 0.0178802 0.00198535 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000632085 0.00452412 0.0132988 0.0548662 0.0977534 0.193305 0.230512 0.202366 0.136943 0.0504829 0.0143141 0.00100198 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000159685 0.00252173 0.00612591 0.0229245 0.0725471 0.125201 0.206179 0.220287 0.185136 0.111668 0.0394956 0.00775475 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00507454 0.0103158 0.0386156 0.0849351 0.146843 0.217987 0.205165 0.172789 0.0844195 0.0300031 0.00385352 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00177219 0.00533461 0.0194718 0.0564354 0.0965336 0.172892 0.217543 0.191324 0.146353 0.0662358 0.0223933 0.00371221 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00460256 0.00631493 0.0316071 0.070111 0.117295 0.193664 0.205929 0.177064 0.122194 0.0530743 0.0171402 0.00100434 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.0018104 0.00517628 0.013545 0.0431233 0.0810759 0.132687 0.210428 0.191407 0.170686 0.0958027 0.0400626 0.0135737 0.000622754 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00337201 0.00652908 0.02142 0.0568674 0.0954855 0.160466 0.202161 0.179937 0.157528 0.0736874 0.034566 0.00736908 0.000611416 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00010043 0.000916236 0.00462984 0.0114947 0.0310134 0.0714707 0.10861 0.177461 0.198096 0.170372 0.133143 0.057769 0.0274998 0.00682416 0.000599106 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000208281 0.00253071 0.00553061 0.0190448 0.0424401 0.0824089 0.125976 0.190263 0.186019 0.155864 0.118082 0.0441457 0.0233511 0.00413592 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000236214 0.000763786 0.0032431 0.00996086 0.0233684 0.0621503 0.0839781 0.152781 0.187099 0.178513 0.14646 0.0945436 0.0399855 0.0151937 0.00172346 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00126208 0.00682969 0.0128003 0.0329458 0.0688659 0.107291 0.167544 0.186501 0.153802 0.141725 0.0750242 0.0330653 0.0107623 0.00158097 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00462047 0.00699273 0.0203713 0.0501046 0.0757429 0.117836 0.181406 0.168193 0.156355 0.121312 0.0621891 0.0266015 0.00748169 0.000792009 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00199252 0.00464247 0.0123102 0.025489 0.0614968 0.0863826 0.138168 0.183313 0.162421 0.14008 0.105249 0.0504453 0.0207798 0.00573355 0.0014968 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000923354 0.00420709 0.00365266 0.0183218 0.0390064 0.0657273 0.0988851 0.154355 0.169832 0.164147 0.131723 0.0824831 0.0374044 0.0249912 0.00433996 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00120512 0.00668241 0.0095967 0.0189592 0.0530971 0.0698496 0.122201 0.155715 0.172002 0.14333 0.127791 0.0666367 0.038474 0.0111966 0.00326345 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000918926 0.00329924 0.00379372 0.00963221 0.0357829 0.0594292 0.084328 0.136092 0.16334 0.150104 0.142781 0.107686 0.0599079 0.0322666 0.00850197 -#2010 - 0 0 0 0 0 0 0 0.000219361 0.193864 0.780693 0.0252237 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0.0056519 0.518633 0.474279 0.00143542 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0.0527285 0.770327 0.176812 0.00013214 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0.00154375 0.239936 0.71396 0.0445596 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0.0177339 0.51467 0.462353 0.00524316 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0.00075498 0.0935548 0.700984 0.204361 0.000345634 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0.00549529 0.28138 0.642213 0.070912 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0.000131268 0.0396307 0.498385 0.443984 0.0178692 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0.00331023 0.134909 0.617283 0.240973 0.00352406 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0.000343323 0.0195537 0.298179 0.57754 0.103706 0.000677612 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00112403 0.0680108 0.473632 0.424302 0.0324513 0.000479943 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.0108681 0.168243 0.552171 0.257893 0.0108247 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00209936 0.0357866 0.311678 0.512502 0.133568 0.00436555 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00755803 0.0948193 0.441642 0.395237 0.0597692 0.000974904 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.0010173 0.023011 0.191922 0.490401 0.266173 0.0274141 6.19465e-05 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00490083 0.0575776 0.311494 0.458607 0.156637 0.0107836 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00125601 0.0137162 0.124223 0.40273 0.373289 0.0827368 0.00204984 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00373186 0.0379645 0.20199 0.443096 0.270993 0.0410089 0.00121549 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000537155 0.00924512 0.0788264 0.302308 0.410503 0.179246 0.0190957 0.000238399 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00185419 0.0227387 0.139328 0.373862 0.348815 0.106162 0.00723952 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00767841 0.0552187 0.209372 0.397296 0.270638 0.0566935 0.00310409 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00103624 0.0147902 0.100922 0.289358 0.367838 0.19512 0.0300823 0.000854322 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 7.69326e-05 0.00527668 0.0344872 0.154467 0.346323 0.315258 0.12621 0.0176795 0.000221176 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000835632 0.0102844 0.0716666 0.216157 0.357859 0.256024 0.0803058 0.00686769 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00015221 0.00341688 0.0260154 0.113756 0.276948 0.33225 0.192411 0.0525037 0.00254617 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00251287 0.00758172 0.0532419 0.154141 0.318724 0.299482 0.134187 0.0290636 0.00106502 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00306147 0.0143691 0.0828198 0.218209 0.325968 0.247753 0.0912769 0.0147834 0.00175962 0 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00160064 0.00689709 0.0336052 0.11907 0.27216 0.290862 0.208725 0.0600896 0.00599337 0.000997074 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 3.68043e-05 0.00472305 0.0109035 0.0628886 0.161118 0.297447 0.272466 0.151814 0.0371224 0.00148092 0 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00103853 0.00628769 0.0273821 0.0871724 0.214197 0.291261 0.239727 0.111082 0.0201253 0.00172704 0 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000107573 0.00344791 0.0104536 0.0470506 0.122752 0.257845 0.274892 0.206239 0.0615898 0.014702 0.000920337 0 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000766577 0.00630149 0.0150209 0.083355 0.160944 0.268303 0.252478 0.157587 0.0500126 0.00466223 0.000569138 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00151696 0.0086324 0.0407641 0.0867986 0.218521 0.269753 0.227997 0.110421 0.0322325 0.00336297 0 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000982709 0.0020979 0.0181342 0.0564408 0.127665 0.247305 0.242722 0.206467 0.0787941 0.0184583 0.000933109 0 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.0012682 0.00879205 0.0250109 0.0734526 0.170201 0.261827 0.229912 0.164364 0.0550352 0.00977352 0.000363853 0 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000531717 0.00386982 0.0119017 0.0483054 0.104379 0.186821 0.26607 0.209543 0.123574 0.0351501 0.00916301 0.000691577 0 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.0017879 0.00426642 0.0228597 0.0705365 0.117974 0.233171 0.243492 0.187403 0.0901186 0.022727 0.00527908 0.000385321 0 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 2.71447e-05 0.0035826 0.0098013 0.0361114 0.0885786 0.154227 0.245775 0.21789 0.159608 0.0661458 0.0146215 0.00320847 0.000422423 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00495741 0.0235064 0.0503329 0.110357 0.191802 0.231737 0.198942 0.129018 0.0473531 0.00991916 0.00207592 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00275253 0.00963457 0.0295488 0.0682192 0.123619 0.227463 0.218203 0.182298 0.101024 0.0320021 0.00523668 0 0 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00758656 0.0173545 0.0405944 0.0815878 0.158421 0.236542 0.20176 0.160984 0.0727891 0.015486 0.00539012 0.00150399 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.00463472 0.00393387 0.0186752 0.0685104 0.0977482 0.192977 0.224431 0.19766 0.116549 0.0536116 0.0154264 0.00584287 0 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000176657 0.000823343 0.00201395 0.0126646 0.0411321 0.0655619 0.138672 0.203069 0.207014 0.175633 0.0977352 0.0436373 0.0116795 0.000187934 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.001 0.000974692 0.00759465 0.0178656 0.0492826 0.0954047 0.157101 0.196149 0.209101 0.152464 0.0723843 0.0330695 0.00761036 0 0 - 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.000244132 0.00480657 0.00798763 0.0243133 0.0669152 0.113042 0.177495 0.204845 0.19357 0.124784 0.0563659 0.0177416 0.00747034 0.000418928 - -999 # EOF check. diff --git a/examples/bbrkc/jie_len_sched.rep b/examples/bbrkc/jie_len_sched.rep new file mode 100644 index 00000000..1785d541 --- /dev/null +++ b/examples/bbrkc/jie_len_sched.rep @@ -0,0 +1,21 @@ +Size FemaleWt MaleWt Female_R_sd Male_R_sd SelMale N1975_female N1975_male_n N1976_male_o N2014_female N2014_male_n N2014_male_o +67.5 0.2151 0.22478 0.2511 0.250982 9.83243E-17 48840300 31905100 882.404 151356 287311 647.793 +72.5 0.26898 0.28135 0.359556 0.349354 1.38808E-15 45601500 32895100 1786.36 232705 429556 1520.83 +77.5 0.33137 0.34692 0.261237 0.258107 1.95959E-14 37924800 15065900 1606.37 384698 590687 2343.83 +82.5 0.40294 0.42221 0.10395 0.108767 2.76642E-13 29631300 14706600 3078.58 747066 917431 3603.43 +87.5 0.48437 0.50793 0.0241569 0.0277739 3.90544E-12 29401300 14128500 5805.72 1129500 1218570 6305.76 +92.5 0.62711 0.6048 0 0.00452512 0.0136852 19919300 10405400 8343.11 1600580 1334820 10746.4 +97.5 0.7216 0.71356 0 0.000491782 0.0321486 14990900 10686900 16677 2376130 1331410 17287 +102.5 0.82452 0.83495 0 0 0.050612 13807800 8484200 25744 2971550 1339780 27908.6 +107.5 0.93615 0.9697 0 0 0.0690755 11362000 8989610 52953.4 2947440 1353600 44445.4 +112.5 1.05678 1.11856 0 0 0.0875409 9524850 10085000 114941 2513850 1347860 68062.2 +117.5 1.18669 1.28229 0 0 0.106033 5561500 8681000 190183 2185840 1314560 99570.4 +122.5 1.32613 1.46163 0 0 0.124902 4615130 8555630 355750 2407890 1258390 140620 +127.5 1.47539 1.65736 0 0 0.149053 3031690 8689700 668559 3239560 1165680 193628 +132.5 1.63473 1.87023 0 0 0.241416 1357150 8232140 1093290 3835400 1044110 269073 +137.5 1.80441 2.10101 0 0 0.63649 881196 7519970 1422010 3417710 903778 366992 +142.5 2.18315 2.35048 0 0 0.954724 2044630 6805050 1722360 5263260 762070 512801 +147.5 2.18315 2.61942 0 0 0.995932 0 5828640 1984020 0 636318 715777 +152.5 2.18315 2.90861 0 0 0.999712 0 4070160 1702510 0 530632 855073 +157.5 2.18315 3.21882 0 0 0.999981 0 2480290 1175540 0 443813 853326 +162.5 2.18315 3.90595 0 0 1 0 2396550 1218500 0 1021100 1730600 diff --git a/examples/bbrkc/jie_mmb.rep b/examples/bbrkc/jie_mmb.rep new file mode 100644 index 00000000..8e4920a2 --- /dev/null +++ b/examples/bbrkc/jie_mmb.rep @@ -0,0 +1,41 @@ +yr mmb mmb_sd R +1975 81.839 5.183 NA +1976 89.398 4.362 29.784 +1977 91.434 3.66 50.657 +1978 96.141 3.035 58.201 +1979 84.571 2.553 57.263 +1980 25.74 0.935 70.522 +1981 9.006 0.399 40.607 +1982 8.638 0.36 150.183 +1983 8.831 0.348 67.045 +1984 6.783 0.341 73.233 +1985 11.865 0.509 10.462 +1986 17.617 0.743 41.461 +1987 23.754 0.899 12.337 +1988 29.138 0.979 7.432 +1989 32.731 1.016 8.157 +1990 30.546 1.021 22.506 +1991 25.367 0.991 13.971 +1992 23.062 0.942 2.278 +1993 20.463 0.908 10.395 +1994 25.892 0.922 1.86 +1995 28.525 0.892 56.251 +1996 26.408 0.844 7.126 +1997 24.369 0.802 3.16 +1998 26.566 0.852 11.904 +1999 31.029 0.933 33.007 +2000 30.814 0.925 11.602 +2001 29.598 0.89 10.496 +2002 31.594 0.888 52.294 +2003 30.41 0.884 10.007 +2004 28.171 0.852 17.283 +2005 28.066 0.861 52.408 +2006 29.864 0.909 17.029 +2007 27.069 0.934 12.678 +2008 28.092 1.062 8.755 +2009 31.346 1.255 9.584 +2010 31.286 1.394 14.577 +2011 31.338 1.462 15.041 +2012 30.003 1.487 11.597 +2013 28.669 1.537 7.829 +2014 25.735 1.291 1.767 diff --git a/examples/bbrkc/jie_surv.rep b/examples/bbrkc/jie_surv.rep new file mode 100644 index 00000000..8a57eecf --- /dev/null +++ b/examples/bbrkc/jie_surv.rep @@ -0,0 +1,41 @@ +year obs pred +1975 23363500 27389100 +1976 28216600 32824700 +1977 36453000 34574700 +1978 38536300 35407100 +1979 35687700 38010200 +1980 35798900 32134600 +1981 8874280 8025880 +1982 3940950 2953110 +1983 1286650 2826270 +1984 3071090 2796970 +1985 2301790 2373620 +1986 5534260 4834600 +1987 7248730 6874630 +1988 7328170 8806910 +1989 11082300 10275400 +1990 8322550 11197600 +1991 19183100 10020700 +1992 4614530 7976360 +1993 6852220 7177820 +1994 4754510 6594630 +1995 5862800 8267530 +1996 5239790 8822400 +1997 9117740 7942940 +1998 6727290 7596930 +1999 10286700 9014360 +2000 8203680 10266300 +2001 5107230 9804750 +2002 8578770 9360730 +2003 11607700 10185100 +2004 11524800 9716600 +2005 9553700 9128600 +2006 11054500 9483110 +2007 12183300 9951420 +2008 9801610 9176170 +2009 8519360 9784010 +2010 8024150 10683400 +2011 5620110 10270000 +2012 6652340 9846060 +2013 9308440 9150020 +2014 12338900 8718720 diff --git a/examples/bbrkc/jie_survb.rep b/examples/bbrkc/jie_survb.rep new file mode 100644 index 00000000..a345f04a --- /dev/null +++ b/examples/bbrkc/jie_survb.rep @@ -0,0 +1,41 @@ +year obs pred +1975 219637 262081 +1976 301454 299722 +1977 380351 309978 +1978 349437 302629 +1979 264248 279160 +1980 244793 240906 +1981 122499 98759.1 +1982 141610 54087.5 +1983 49321.8 47164.7 +1984 134594 46437.3 +1985 34280.5 38059.1 +1986 47804.3 50082.3 +1987 68934.9 56677.6 +1988 54056.4 60705.1 +1989 61498.5 63753.5 +1990 56729.8 63656.4 +1991 87498.6 57758.5 +1992 37410.2 51685.7 +1993 53897.8 49835.7 +1994 32099 44119.7 +1995 38116 50377.1 +1996 44322.7 57838.6 +1997 84652.6 62397 +1998 84554.4 65693.5 +1999 60877.5 65324 +2000 68429.4 67559 +2001 52800.7 70463.8 +2002 69272.7 75011.1 +2003 96780.6 79956.7 +2004 96230.1 81927 +2005 106558 86913.1 +2006 94913.8 89880.1 +2007 103801 94880.9 +2008 111996 94469.2 +2009 91784 91145.3 +2010 78431.5 87648.9 +2011 64554.9 83116.2 +2012 60801.1 81553.6 +2013 61954.2 79776.9 +2014 119620 76294.5 diff --git a/examples/bbrkc/readme.md b/examples/bbrkc/readme.md new file mode 100644 index 00000000..cc7a05aa --- /dev/null +++ b/examples/bbrkc/readme.md @@ -0,0 +1,13 @@ +# Setup for comparing Bristol Bay red king crab models + +## Alternative configurations + +The following specifies model configurations to mimic Jie's application +1. Natural mortality configuration (block-change in 19??) +2. Fixed sample size (not estimated) for multinomial +3. Output likelihood values +3. Method for reading in results from Jie's model + +## Files + + * Script for running alternative model configurations diff --git a/examples/bbrkc/run.bat b/examples/bbrkc/run.bat new file mode 100644 index 00000000..68ef9c23 --- /dev/null +++ b/examples/bbrkc/run.bat @@ -0,0 +1,5 @@ +@echo off +set exec=..\..\src\build\release\gmacs.exe +:: if EXIST %exec% (mklink /D %exec% gmacs.exe ) ELSE echo "file missing, compile source code in gmacs\src directory " +if EXIST %exec% (copy %exec% gmacs.exe ) ELSE echo "file missing, compile source code in gmacs\src directory " +gmacs -nox %1 %2 %3 %4 %5 %6 diff --git a/examples/bbrkc/starter.gm b/examples/bbrkc/starter.gm deleted file mode 100644 index 0bd9917f..00000000 --- a/examples/bbrkc/starter.gm +++ /dev/null @@ -1,11 +0,0 @@ -# Gmacs Starter File Version 1.02 -bbrkc.dat -bbrkc.ctl -growth.dat - -1 # Display detail on output screen (0==off, 1==verbose) -44 # Turn off estimation for parameters entering after this phase -0 # Use PIN file to get starting parameters (0 no, 1 yes) -0 # Read growth transition matrix data file (0 no, 1 yes) - -999 # EOF check. diff --git a/examples/demo/Makefile b/examples/demo/Makefile new file mode 100644 index 00000000..e415900a --- /dev/null +++ b/examples/demo/Makefile @@ -0,0 +1,23 @@ +EXEC = gmacs +ifeq ($(OPT),TRUE) + DIST = ../../src/build/release/ +else + DIST = ../../src/build/debug/ +endif +ARGS = -nox -iprint 50 + +all: run + +$(EXEC): $(DIST)$(EXEC).tpl + ln -sf $(DIST)$(EXEC) $@ + +$(DIST)$(EXEC).tpl: + $(MAKE) --directory=../../src + +run: $(EXEC) + ./$(EXEC) $(ARGS) + +clean: + rm -f $(EXEC) + rm -f admodel.* + rm -f $(EXEC) $(EXEC).[brces]* $(EXEC).*[0123456789] *.rpt *.log variance diff --git a/examples/demo/bbrkc.ctl b/examples/demo/bbrkc.ctl new file mode 100644 index 00000000..85863b88 --- /dev/null +++ b/examples/demo/bbrkc.ctl @@ -0,0 +1,367 @@ +# —————————————————————————————————————————————————————————————————————————————————————— # +# Controls for leading parameter vector theta +# LEGEND FOR PRIOR: +# 0 -> uniform +# 1 -> normal +# 2 -> lognormal +# 3 -> beta +# 4 -> gamma +# —————————————————————————————————————————————————————————————————————————————————————— # +# ntheta +12 +# —————————————————————————————————————————————————————————————————————————————————————— # +# ival lb ub phz prior p1 p2 # parameter # +# —————————————————————————————————————————————————————————————————————————————————————— # + 0.18 0.01 1 5 2 0.18 0.04 # M + 7.0 -10 20 -1 1 3.0 5.0 # logR0 + 7.0 -10 20 2 1 3.0 5.0 # logR1 + 7.0 -10 20 2 1 3.0 5.0 # logRbar + 72.5 65 100 4 1 72.5 7.25 # Recruitment mBeta + 1.50 0.1 5 4 0 0.1 5 # Recruitment m50 + 17.5 10.0 20.0 4 0 0.0 20.0 # alpha + 0.10 0.0 0.5 3 0 0.0 10.0 # beta + 14.0 10.0 30.0 -3 0 0.0 3.0 # gscale + 115. 65.0 165.0 2 0 0.0 3.0 # molt_mu + 0.2 0.01 1.0 3 0 0.0 3.0 # molt_cv + -0.51 -10 0.75 -4 0 -10 0.75 # ln(sigma_R) +# —————————————————————————————————————————————————————————————————————————————————————— # + +## ———————————————————————————————————————————————————————————————————————————————————— ## +## SELECTIVITY CONTROLS ## +## -Each gear must have a selectivity and a retention selectivity ## +## LEGEND sel_type:1=coefficients,2=logistic,3=logistic95 ## +## Index: use +ve for selectivity, -ve for retention +## ———————————————————————————————————————————————————————————————————————————————————— ## +## ivector for number of year blocks or nodes ## +## Gear-1 Gear-2 Gear-3 Gear-4 + 1 1 1 1 #Selectivity blocks + 1 1 1 1 #Retention blocks + 1 0 0 0 #male retention flag (0 -> no, 1 -> yes) + 0 0 0 0 #female retention flag (0 -> no, 1 -> yes) +## ———————————————————————————————————————————————————————————————————————————————————— ## +## sel sel sel sex size year phz start end ## +## Index type mu sd dep nodes nodes mirror lam1 lam2 lam3 | block block ## +## ———————————————————————————————————————————————————————————————————————————————————— ## +## Selectivity P(capture of all sizes) + 1 2 180 10 0 1 1 2 12.5 12.5 12.5 1975 2013 + 2 2 90 10 0 1 1 2 12.5 12.5 12.5 1975 2013 + 3 2 80 10 0 1 1 -2 12.5 12.5 12.5 1975 2013 + 4 2 80 10 0 1 1 -2 12.5 12.5 12.5 1975 2013 +## ———————————————————————————————————————————————————————————————————————————————————— ## +## Retained + -1 2 135 2 0 1 1 -2 12.5 12.5 12.5 1975 2013 + -2 2 95 10 0 1 1 -2 12.5 12.5 12.5 1975 2013 + -3 2 90 10 0 1 1 -2 12.5 12.5 12.5 1975 2013 + -4 2 90 10 0 1 1 -2 12.5 12.5 12.5 1975 2013 +## ———————————————————————————————————————————————————————————————————————————————————— ## + +## ———————————————————————————————————————————————————————————————————————————————————— ## +## PRIORS FOR CATCHABILITY +## TYPE: 0 = UNINFORMATIVE, 1 - NORMAL (log-space), 2 = time-varying (nyi) +## ———————————————————————————————————————————————————————————————————————————————————— ## +## SURVEYS/INDICES ONLY +## NMFS BSFRF +## TYPE Mean_q SD_q + 1 0.896 0.03 + 0 0.00 0.00 +## ———————————————————————————————————————————————————————————————————————————————————— ## + + +## ———————————————————————————————————————————————————————————————————————————————————— ## +## PENALTIES FOR AVERAGE FISHING MORTALITY RATE FOR EACH GEAR +## ———————————————————————————————————————————————————————————————————————————————————— ## +## Trap Trawl NMFS BSFRF +## Mean_F STD_PHZ1 STD_PHZ2 PHZ + 0.20 0.10 1.10 1 + 0.10 0.10 1.10 1 + 0.00 2.00 2.00 -1 + 0.00 2.00 2.00 -1 +## ———————————————————————————————————————————————————————————————————————————————————— ## + +## ———————————————————————————————————————————————————————————————————————————————————— ## +## OPTIONS FOR SIZE COMPOSTION DATA (COLUMN FOR EACH MATRIX) +## LIKELIHOOD OPTIONS: +## -1) multinomial with estimated/fixed sample size +## -2) robust_multi. Robust approximation to multinomial +## -3) logistic normal (NIY) +## -4) multivariate-t (NIY) +## AUTOTAIL COMPRESSION: +## - pmin is the cumulative proportion used in tail compression. +## ———————————————————————————————————————————————————————————————————————————————————— ## + 2 2 2 2 2 2 2 2 2 # Type of likelihood. + 0 0 0 0 0 0 0 0 0 # Auto tail compression (pmin) +-4 -4 -4 -4 -4 -4 -4 -4 -4 # Phz for estimating effective sample size (if appl.) +## ———————————————————————————————————————————————————————————————————————————————————— ## + +## ———————————————————————————————————————————————————————————————————————————————————— ## +## TIME VARYING NATURAL MORTALIIY RATES ## +## ———————————————————————————————————————————————————————————————————————————————————— ## +## TYPE: +## 0 = constant natural mortality +## 1 = Random walk (deviates constrained by variance in M) +## 2 = Cubic Spline (deviates constrined by nodes & node-placement) + 2 +## Phase of estimation + 3 +## STDEV in m_dev for Random walk + 0.01 +## Number of nodes for cubic spline + 6 +## Year position of the knots (vector must be equal to the number of nodes) + 1975 1982 1985 1991 2002 2013 + + + +## ———————————————————————————————————————————————————————————————————————————————————— ## +## OTHER CONTROLS +## ———————————————————————————————————————————————————————————————————————————————————— ## + 3 # Estimated rec_dev phase + 0 # VERBOSE FLAG (0 = off, 1 = on, 2 = objective func) + 0 # INITIALIZE MODEL AT UNFISHED RECRUITS (0=FALSE, 1=TRUE) + 1984 # First year for average recruitment for Bspr calculation. + 2013 # Last year for average recruitment for Bspr calculation. + 0.35 # Target SPR ratio for Bmsy proxy. + 1 # Gear index for SPR calculations (i.e., directed fishery). + 1 # Lambda (proportion of mature male biomass for SPR reference points.) + +## EOF +9999 + + + + + + + +# Time-varying natural mortality blocks +# 75 76 77 78 79 80 81 82 83 84 85 86 87 88 89 90 91 92 93 94 95 96 97 98 99 00 01 02 03 04 05 06 07 08 09 10 11 12 13 + 1 3 3 3 3 2 2 2 2 2 3 3 3 3 3 3 3 3 3 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 + +# Specifications for Madd parameters +# Init, Lower, Upper, Phase +0.585 0 1 2 +0.0001 0 1 2 + +1 # Form of stock-recruitment relationship (placeholder) +1 # Lag to recruitment (placeholder) + +# Specifications for the growth transition matrix +# Time-varying growth (one line per sex) one pattern in this case +# 75 76 77 78 79 80 81 82 83 84 85 86 87 88 89 90 91 92 93 94 95 96 97 98 99 00 01 02 03 04 05 06 07 08 09 10 11 12 13 + 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 + 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 + #2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 + +# Type of growth estimation (1 = simple parameter-per-class, 2 = linear growth increment, gamma distribution about mean) +# Pattern, GrowthType, OffsetType + 1 2 0 +#2 2 0 + +# Growth parameters for growthtyp 1, specified for each model size class minus one +# Init, Lower, Upper, Phase +#4.36 -20 50 5 # Parameter-per-class +# 0.12 -20 50 5 +# 0.95 -20 50 5 +# 1.86 -20 50 5 + +# 4.36 -20 50 5 # Parameter-per-class +# 0.12 -20 50 5 +# 0.95 -20 50 5 +# 1.86 -20 50 5 + +# Growth parameters for GrowthType 2 + 0.39 0.1 2 5 # Linear growth increment a + 0.93 0.1 2 5 # Linear growth increment b + 0.75 0.0 1 -5 # Gamma distribution beta + +# 0.37 0.1 1 -5 # Linear growth increment a +# 0.93 0.1 2 -5 # Linear growth increment b +# 0.75 0.0 1 -5 # Gamma distribution beta + +# Time-varying molting probability, one for each sex +# 75 76 77 78 79 80 81 82 83 84 85 86 87 88 89 90 91 92 93 94 95 96 97 98 99 00 01 02 03 04 05 06 07 08 09 10 11 12 13 + 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 + 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 + +# Molting types +1 1 0 + +# Specifications for the molting probability +# Init, Lower, Upper, Phase + 110 70 130 -3 + 160 135 175 -3 + +4 # Form of initial numbers (1 = estimate initial size structure, 2 = estimate early recruitment, build from R0, 3 = as with 2 but build from N0, 4 = as with 2 but use dummy growth trans matrix) +15 # Number of initial recruitments to estimate (conditional) + +# Specifications for the initial numbers parameters +# Init, Lower, Upper, Phase + 0.8133 -10 10 -2 + 0.8133 -10 10 -2 + 1.1774 -10 10 -2 + 1.1774 -10 10 -2 + 0.1239 -10 10 -2 + 0.1239 -10 10 -2 + -0.840 -10 10 -2 + -0.840 -10 10 -2 + -1.020 -10 10 -2 + -1.02 -10 10 -2 + +## TOBE DEPRECATED +# Time-varying fishery selectivity blocks (one row per active fleet) +# 75 76 77 78 79 80 81 82 83 84 85 86 87 88 89 90 91 92 93 94 95 96 97 98 99 0 1 2 3 4 5 6 7 8 9 10 11 12 13 + 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 + 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 + +## TOBE DEPRECATED +# Time-varying survey selectivity blocks (one row per survey) +# 75 76 77 78 79 80 81 82 83 84 85 86 87 88 89 90 91 92 93 94 95 96 97 98 99 0 1 2 3 4 5 6 7 8 9 10 11 12 13 14 + 3 3 3 3 3 3 3 4 4 4 4 4 4 4 4 4 4 4 4 4 4 4 4 4 4 4 4 4 4 4 4 4 4 4 4 4 4 4 4 4 + 5 5 5 5 5 5 5 5 5 5 5 5 5 5 5 5 5 5 5 5 5 5 5 5 5 5 5 5 5 5 5 5 5 5 5 5 5 5 5 5 + +## TOBE DEPRECATED +# Selectivity types +# Pattern, SelType, Offset +1 1 0 +2 1 0 +3 1 0 +4 1 0 +5 2 0 + +## ———————————————————————————————————————————————————————————————————————————————————— ## +## SELECTIVITY CONTROLS ## +## LEGEND sel_type:1=coefficients,2=logistic,3=logistic95 ## +## ———————————————————————————————————————————————————————————————————————————————————— ## +## ivector for number of year blocks or nodes ## +## Gear-1 Gear-2 Gear-3 Gear-4 Gear-5 + 1 1 1 1 1 +## ———————————————————————————————————————————————————————————————————————————————————— ## +## sel sel sel size year phz ## +## Index type mu sd nodes nodes mirror lam1 lam2 lam3 | blocks ## +## ———————————————————————————————————————————————————————————————————————————————————— ## + 1 1 80 10 1 1 2 12.5 12.5 12.5 1975 + 1 1 80 10 1 1 2 12.5 12.5 12.5 1975 + 1 1 80 10 1 1 2 12.5 12.5 12.5 1975 + 1 1 80 10 1 1 2 12.5 12.5 12.5 1975 + 1 2 80 10 1 1 2 12.5 12.5 12.5 1975 +## ———————————————————————————————————————————————————————————————————————————————————— ## + + +## TOBE DEPRECATED +# Specifications for Selectivity (Fishing Fleets) parameters +# Init, Lower, Upper, Phase +# # Block 1: 1973+ for Fleet 1 +# 110 50 120 2 +# 155 120 180 -2 +# # Block 2: 1968+ for Fleet 2 +# 122 90 135 3 +# 155 135 180 -3 + +# Block 1: 1973+ for Fleet 1 +46.0517019 -100 1000 -1 +46.0517019 -100 1000 1 +2.743604047 -100 1000 2 +2.743604047 -100 1000 2 +0.967349593 -100 1000 2 +0.967349593 -100 1000 2 +-1.965728316 -100 1000 2 +-1.965728316 -100 1000 2 +-4.5951199 -100 1000 1 +-4.5951199 -100 1000 -1 +# Block 2: 1968+ for Fleet 2 +3.171179741 -100 1000 1 +3.171179741 -100 1000 1 +2.699082027 -100 1000 3 +2.699082027 -100 1000 3 +0.957124967 -100 1000 3 +0.957124967 -100 1000 3 +-1.472148417 -100 1000 3 +-1.472148417 -100 1000 3 +-4.5951199 -100 1000 1 +-4.5951199 -100 1000 -1 + +# Specifications for Selectivity (Surveys) parameters +# Init, Lower, Upper, Phase +# Block 3: 1973-81 for Survey 1 +4.349913701 -1000 1000 2 +4.847710171 -1000 1000 2 +4.158845167 -1000 1000 2 +3.529600754 -1000 1000 2 +2.828326513 -1000 1000 2 +2.146152441 -1000 1000 2 +1.394673774 -1000 1000 2 +0.606391491 -1000 1000 2 +-0.057781571 -1000 1000 2 +-2.295824329 -1000 1000 2 +# Block 4: 1982+ for Survey 1 +2.999196037 -1000 1000 3 +2.632337643 -1000 1000 3 +2.10814007 -1000 1000 3 +1.607167023 -1000 1000 3 +1.031093859 -1000 1000 3 +0.185767284 -1000 1000 3 +-0.723790681 -1000 1000 3 +-1.641429316 -1000 1000 3 +-0.733155126 -1000 1000 3 +0.154878154 -1000 1000 3 +# Block 5: 1968+ for Survey 2 +117 110 120 -3 +123 121 130 -3 + +# Time-varying fishery retention (one row per directed fleet) +# 75 76 77 78 79 80 81 82 83 84 85 86 87 88 89 90 91 92 93 94 95 96 97 98 99 00 01 02 03 04 05 06 07 08 09 10 11 12 13 + 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 + +# Retention types (option 1: one parm per size-class, option 2: 2 parameter logistic [s50, s95]) +1 2 0 + +# Specifications for the retained probability +# Init, Lower, Upper, Phase +135 130 140 3 +145 141 155 4 + +# Time-varying Q +# 75 76 77 78 79 80 81 82 83 84 85 86 87 88 89 90 91 92 93 94 95 96 97 98 99 0 1 2 3 4 5 6 7 8 9 10 11 12 13 14 + 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 + 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 + +# Number of survey fleets which are in a sub-area of the main survey +0 # Number of cases + +# Specifications for survey Q parameters +# Init, Lower, Upper, Phase, Prior, Pmean, Psd +-0.10981487 -50 1 -4 1 0.896 0.03 + 0.0 -50 1 -1 1 0 -100 + +# Objective Fn weights +# (1) Priors +# F Devs + 0.00001 100.000 +# Rec_devs + 1.0000 +# Parameters (Growth, Selex, Reten) + 0.1001 0.1001 0.1001 +# Survey q + 1.000 1.000 +# Prior on M + 1.000 +# 2nd Derviative Penalty on Selex Parms + 1.000 + +# Objective Fn weights +# (2) Data +# Catch: PotRet, PotDisc, Trawl + 10.00 100.00 10.00 +# LF: PotRet, PotDisc, Trawl + 0.100 1.000 0.100 +# Effort: PotRet, Trawl + 0.000 0.000 +# Survey: NMFS, BSFRF + 1.000 1.000 +# Survey-LF: NMFS, BSFRF + 1.00 1.00 + +#======================================================================================================== +#EOF +999 + diff --git a/examples/demo/bbrkc.dat b/examples/demo/bbrkc.dat new file mode 100644 index 00000000..b35f8878 --- /dev/null +++ b/examples/demo/bbrkc.dat @@ -0,0 +1,668 @@ +#======================================================================================================== +# Gmacs Main Data File Version 1.1: BBRKC Example +# Fisheries: 1 Pot Fishery, 2 Pot Discard, 3 Trawl by-catch +# Surveys: 1 NMFS Trawl Survey, 2 BSFRF Survey +#======================================================================================================== + +1975 # Start year +2013 # End year +1 # Time-step (years) + +4 # Number of distinct data groups (among fishing fleets and surveys) + +2 # Number of sexes +2 # Number of shell condition types +1 # Number of maturity types +20 # Number of size-classes in the model +#20 # Number of size-classes in the data + +# size_breaks (a vector giving the break points between size intervals, dim=nclass+1) +65 70 75 80 85 90 95 100 105 110 115 120 125 130 135 140 145 150 155 160 165 + +# weight-at-length allometry w_l = a•l^b +#a=0.003593,b=2.666076 female > 89mm +#a=0.000408,b=3.127956 female < 90 new shell +#a=0.000403, b=3.141334 male new shell +## a (male, female) +4.03e-7 4.08e-7 +## b (male, female) +3.141334 3.127956 + +# Male mature weight-at-length (weight * proportion mature) +0 0 0 0 0 0 0 0 0 0 0 1.432 1.625 1.835 2.063 2.31 2.576 2.862 3.169 3.7 +# Proportion mature by sex. +0 0 0 0 0 0 0 0 0 0 0 1 1 1 1 1 1 1 1 1 +0 0 0 0 0 0 0 0 0 0 0 1 1 1 1 1 1 1 1 1 + +# Fishing fleet names (delimited with ":" no spaces in names) +Pot_Fishery:Trawl_Bycatch + +# Survey names (delimited with ":" no spaces in names) +NMFS_Trawl:BSFRF + +#116 # Number of lines of catch data to read +4 # Number of catch data frames +# Number of rows in each data frame. +37 21 21 37 +#0.5 # Time between survey and fishery +## ———————————————————————————————————————————————————————————————————————————————————— ## +## CATCH DATA +## Dockside sampling is very close to the retained sampling. +## At sea sampling represents discard and retained. +## Type of catch: 1 = retained, 2 = discard, 3 = total catch (discards + retained = at sea sampling data) +## Units of catch: 1 = biomass, 2 = numbers +## for BBRKC Units are in 1000 mt for landed & million crabs for discards. +## ———————————————————————————————————————————————————————————————————————————————————— ## +## Male Retained +## year seas fleet sex obs cv type units mult effort discard_mortality + 1975 1 1 1 23.287794 0.05 1 1 1 0 0 + 1976 1 1 1 29.001814 0.05 1 1 1 0 0 + 1977 1 1 1 31.745871 0.05 1 1 1 0 0 + 1978 1 1 1 39.754219 0.05 1 1 1 0 0 + 1979 1 1 1 48.923820 0.05 1 1 1 0 0 + 1980 1 1 1 58.960299 0.05 1 1 1 0 0 + 1981 1 1 1 15.241107 0.05 1 1 1 0 0 + 1982 1 1 1 1.361705 0.05 1 1 1 0 0 + 1984 1 1 1 1.897640 0.05 1 1 1 0 0 + 1985 1 1 1 1.894283 0.05 1 1 1 0 0 + 1986 1 1 1 5.169646 0.05 1 1 1 0 0 + 1987 1 1 1 5.575816 0.05 1 1 1 0 0 + 1988 1 1 1 3.351996 0.05 1 1 1 0 0 + 1989 1 1 1 4.657350 0.05 1 1 1 0 0 + 1990 1 1 1 9.275408 0.05 1 1 1 0 0 + 1991 1 1 1 7.887477 0.05 1 1 1 0 0 + 1992 1 1 1 3.682849 0.05 1 1 1 0 0 + 1993 1 1 1 6.661524 0.05 1 1 1 0 0 + 1994 1 1 1 0.042196 0.05 1 1 1 0 0 + 1995 1 1 1 0.036297 0.05 1 1 1 0 0 + 1996 1 1 1 3.862976 0.05 1 1 1 0 0 + 1997 1 1 1 4.043284 0.05 1 1 1 0 0 + 1998 1 1 1 6.781306 0.05 1 1 1 0 0 + 1999 1 1 1 5.379310 0.05 1 1 1 0 0 + 2000 1 1 1 3.739110 0.05 1 1 1 0 0 + 2001 1 1 1 3.867059 0.05 1 1 1 0 0 + 2002 1 1 1 4.385662 0.05 1 1 1 0 0 + 2003 1 1 1 7.137477 0.05 1 1 1 0 0 + 2004 1 1 1 7.008620 0.05 1 1 1 0 0 + 2005 1 1 1 8.401996 0.05 1 1 1 0 0 + 2006 1 1 1 7.145190 0.05 1 1 1 0 0 + 2007 1 1 1 9.306578 0.05 1 1 1 0 0 + 2008 1 1 1 9.218675 0.05 1 1 1 0 0 + 2009 1 1 1 7.274523 0.05 1 1 1 0 0 + 2010 1 1 1 6.763439 0.05 1 1 1 0 0 + 2011 1 1 1 3.608112 0.05 1 1 1 0 0 + 2012 1 1 1 3.622754 0.05 1 1 1 0 0 +## Male discards Pot fishery + 1990 1 1 1 1.718800 0.05 2 2 1 0 0.20 + 1991 1 1 1 1.453700 0.05 2 2 1 0 0.20 + 1992 1 1 1 2.305600 0.05 2 2 1 0 0.20 + 1993 1 1 1 2.688000 0.05 2 2 1 0 0.20 + 1996 1 1 1 0.595000 0.05 2 2 1 0 0.20 + 1997 1 1 1 0.910000 0.05 2 2 1 0 0.20 + 1998 1 1 1 3.173000 0.05 2 2 1 0 0.20 + 1999 1 1 1 0.922000 0.05 2 2 1 0 0.20 + 2000 1 1 1 1.393000 0.05 2 2 1 0 0.20 + 2001 1 1 1 1.623500 0.05 2 2 1 0 0.20 + 2002 1 1 1 1.527000 0.05 2 2 1 0 0.20 + 2003 1 1 1 3.617000 0.05 2 2 1 0 0.20 + 2004 1 1 1 1.539000 0.05 2 2 1 0 0.20 + 2005 1 1 1 3.792300 0.05 2 2 1 0 0.20 + 2006 1 1 1 1.832000 0.05 2 2 1 0 0.20 + 2007 1 1 1 3.619800 0.05 2 2 1 0 0.20 + 2008 1 1 1 3.786757 0.05 2 2 1 0 0.20 + 2009 1 1 1 2.782675 0.05 2 2 1 0 0.20 + 2010 1 1 1 2.480059 0.05 2 2 1 0 0.20 + 2011 1 1 1 1.279960 0.05 2 2 1 0 0.20 + 2012 1 1 1 0.640960 0.05 2 2 1 0 0.20 +## Female discards Pot fishery + 1990 1 1 2 2.670800 0.05 2 2 1 0 0.20 + 1991 1 1 2 0.484600 0.05 2 2 1 0 0.20 + 1992 1 1 2 2.408600 0.05 2 2 1 0 0.20 + 1993 1 1 2 2.814500 0.05 2 2 1 0 0.20 + 1996 1 1 2 0.010000 0.05 2 2 1 0 0.20 + 1997 1 1 2 0.075000 0.05 2 2 1 0 0.20 + 1998 1 1 2 3.896500 0.05 2 2 1 0 0.20 + 1999 1 1 2 0.030300 0.05 2 2 1 0 0.20 + 2000 1 1 2 0.304000 0.05 2 2 1 0 0.20 + 2001 1 1 2 0.786100 0.05 2 2 1 0 0.20 + 2002 1 1 2 0.047600 0.05 2 2 1 0 0.20 + 2003 1 1 2 2.191200 0.05 2 2 1 0 0.20 + 2004 1 1 2 0.932000 0.05 2 2 1 0 0.20 + 2005 1 1 2 2.038700 0.05 2 2 1 0 0.20 + 2006 1 1 2 0.222200 0.05 2 2 1 0 0.20 + 2007 1 1 2 0.833890 0.05 2 2 1 0 0.20 + 2008 1 1 2 0.666098 0.05 2 2 1 0 0.20 + 2009 1 1 2 0.332340 0.05 2 2 1 0 0.20 + 2010 1 1 2 0.477993 0.05 2 2 1 0 0.20 + 2011 1 1 2 0.115860 0.05 2 2 1 0 0.20 + 2012 1 1 2 0.049933 0.05 2 2 1 0 0.20 +## Trawl fishery discards + 1976 1 2 0 0.384600 0.05 2 2 1 0 0.80 + 1977 1 2 0 0.787700 0.05 2 2 1 0 0.80 + 1978 1 2 0 0.646500 0.05 2 2 1 0 0.80 + 1979 1 2 0 0.736200 0.05 2 2 1 0 0.80 + 1980 1 2 0 1.141300 0.05 2 2 1 0 0.80 + 1981 1 2 0 0.267100 0.05 2 2 1 0 0.80 + 1982 1 2 0 0.785400 0.05 2 2 1 0 0.80 + 1983 1 2 0 0.492800 0.05 2 2 1 0 0.80 + 1984 1 2 0 1.168200 0.05 2 2 1 0 0.80 + 1985 1 2 0 0.274700 0.05 2 2 1 0 0.80 + 1986 1 2 0 0.159300 0.05 2 2 1 0 0.80 + 1987 1 2 0 0.124500 0.05 2 2 1 0 0.80 + 1988 1 2 0 0.430300 0.05 2 2 1 0 0.80 + 1989 1 2 0 0.109200 0.05 2 2 1 0 0.80 + 1990 1 2 0 0.171800 0.05 2 2 1 0 0.80 + 1991 1 2 0 0.183500 0.05 2 2 1 0 0.80 + 1992 1 2 0 0.248100 0.05 2 2 1 0 0.80 + 1993 1 2 0 0.281000 0.05 2 2 1 0 0.80 + 1994 1 2 0 0.048200 0.05 2 2 1 0 0.80 + 1995 1 2 0 0.106600 0.05 2 2 1 0 0.80 + 1996 1 2 0 0.076300 0.05 2 2 1 0 0.80 + 1997 1 2 0 0.049000 0.05 2 2 1 0 0.80 + 1998 1 2 0 0.093700 0.05 2 2 1 0 0.80 + 1999 1 2 0 0.110500 0.05 2 2 1 0 0.80 + 2000 1 2 0 0.058600 0.05 2 2 1 0 0.80 + 2001 1 2 0 0.089955 0.05 2 2 1 0 0.80 + 2002 1 2 0 0.076302 0.05 2 2 1 0 0.80 + 2003 1 2 0 0.105493 0.05 2 2 1 0 0.80 + 2004 1 2 0 0.075107 0.05 2 2 1 0 0.80 + 2005 1 2 0 0.096834 0.05 2 2 1 0 0.80 + 2006 1 2 0 0.075290 0.05 2 2 1 0 0.80 + 2007 1 2 0 0.086417 0.05 2 2 1 0 0.80 + 2008 1 2 0 0.093077 0.05 2 2 1 0 0.80 + 2009 1 2 0 0.061900 0.05 2 2 1 0 0.80 + 2010 1 2 0 0.059390 0.05 2 2 1 0 0.80 + 2011 1 2 0 0.046370 0.05 2 2 1 0 0.80 + 2012 1 2 0 0.032770 0.05 2 2 1 0 0.80 + + +## ———————————————————————————————————————————————————————————————————————————————————— ## +## RELATIVE ABUNDANCE DATA +## Units of Abundance: 1 = biomass, 2 = numbers +## for BBRKC Units are in million crabs for Abundance. +## ———————————————————————————————————————————————————————————————————————————————————— ## +## Number of relative abundance indicies +2 +## Number of rows in each index +39 2 +# Survey data (abundance indices, units are millions of crabs) +# Year, Seas, Fleet, Sex, Abundance, CV units + 1975 1 3 0 250.4392 0.188 2 + 1976 1 3 0 309.8005 0.169 2 + 1977 1 3 0 339.1646 0.141 2 + 1978 1 3 0 305.5044 0.155 2 + 1979 1 3 0 201.6936 0.133 2 + 1980 1 3 0 212.6459 0.221 2 + 1981 1 3 0 125.343 0.121 2 + 1982 1 3 0 224.5556 0.259 2 + 1983 1 3 0 71.1642 0.216 2 + 1984 1 3 0 277.9271 0.678 2 + 1985 1 3 0 36.7171 0.158 2 + 1986 1 3 0 41.0401 0.428 2 + 1987 1 3 0 72.4004 0.209 2 + 1988 1 3 0 44.4455 0.217 2 + 1989 1 3 0 41.7301 0.214 2 + 1990 1 3 0 43.8329 0.214 2 + 1991 1 3 0 53.1139 0.441 2 + 1992 1 3 0 27.8487 0.174 2 + 1993 1 3 0 37.3032 0.174 2 + 1994 1 3 0 19.2967 0.173 2 + 1995 1 3 0 31.6429 0.276 2 + 1996 1 3 0 44.4464 0.201 2 + 1997 1 3 0 70.8614 0.263 2 + 1998 1 3 0 67.9181 0.178 2 + 1999 1 3 0 44.2432 0.161 2 + 2000 1 3 0 51.1263 0.178 2 + 2001 1 3 0 43.5622 0.178 2 + 2002 1 3 0 66.23 0.203 2 + 2003 1 3 0 76.3463 0.164 2 + 2004 1 3 0 85.224 0.163 2 + 2005 1 3 0 101.9823 0.173 2 + 2006 1 3 0 80.2091 0.122 2 + 2007 1 3 0 75.6192 0.135 2 + 2008 1 3 0 81.6687 0.104 2 + 2009 1 3 0 62.4014 0.287 2 + 2010 1 3 0 53.6617 0.15 2 + 2011 1 3 0 48.5909 0.141 2 + 2012 1 3 0 43.705 0.162 2 + 2013 1 3 0 36.0499 0.245 2 + 2007 1 4 0 102.9622 0.1164 2 + 2008 1 4 0 83.5895 0.0939 2 + + + + + +## # Discard mortalities per fishery +## 1.0 # Pot Landings (Retained) +## 1.0 # Pot Discards +## 0.8 # Trawl Bycatch +## +## # Fishery high-grading rates (rescaling of retention values (retention maximum of 1 becomes 1-hg) +## # 75 76 77 78 79 80 81 82 83 84 85 86 87 88 89 90 91 92 93 94 95 96 97 98 99 00 01 02 03 04 2005 2006 2007 2008 09 10 11 12 13 +## 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0.2785 0.0440 0.0197 0.019875 0 0 0 0 0 +## +## # Fishery timing (as fraction of year) +## # 1975 1976 1977 1978 1979 1980 1981 1982 1983 1984 1985 1986 1987 1988 1989 1990 1991 1992 1993 1994 1995 1996 1997 1998 1999 2000 2001 2002 2003 2004 2005 2006 2007 2008 2009 2010 2011 2012 2013 +## 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 +## 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 0.5 +## +## # Effort (by fishery) +## # 1975 1976 1977 1978 1979 1980 1981 1982 1983 1984 1985 1986 1987 1988 1989 1990 1991 1992 1993 1994 1995 1996 1997 1998 1999 2000 2001 2002 2003 2004 2005 2006 2007 2008 2009 2010 2011 2012 2013 +## 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 0.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 0.0 0.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 +## 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 1.0 +## +## # Use effort to compute F (by fishery) +## 0 1900 1900 1900 1900 +## 0 1900 1900 1900 1900 + +## Number of length frequency matrixes +9 +## Number of rows in each matrix +35 21 21 36 36 +39 39 39 4 +## Number of bins in each matrix (columns of size data) +20 20 20 20 20 +20 20 20 20 + +## SIZE COMPOSITION DATA FOR ALL FLEETS +## ———————————————————————————————————————————————————————————————————————————————————— ## +## SIZE COMP LEGEND +## Sex: 1 = male, 2 = female, 0 = both sexes combined +## Type of composition: 1 = retained, 2 = discard, 0 = selectivity +## Maturity state: 1 = immature, 2 = mature, 0 = both states combined +## Shell condition: 1 = new shell, 2 = old shell, 0 = both shell types combined +## ———————————————————————————————————————————————————————————————————————————————————— ## +##length proportions of retained males +##Year, Seas, Fleet, Sex, Type, Shell, Maturity, Nsamp, DataVec + 1975 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0 0.0071 0.0741 0.1721 0.2239 0.2122 0.1464 0.0858 0.0785 + 1976 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0 0.0016 0.029 0.1418 0.2316 0.2199 0.1635 0.1071 0.1055 + 1977 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0 0.0017 0.0192 0.1382 0.2442 0.2226 0.1605 0.104 0.1096 + 1978 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0 0.0012 0.0209 0.1441 0.2588 0.2401 0.1673 0.0966 0.0711 + 1979 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0 0.0013 0.0119 0.0747 0.1649 0.1998 0.2004 0.1556 0.1914 + 1980 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0 0.0008 0.0138 0.0919 0.1771 0.195 0.1792 0.1404 0.2019 + 1981 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0 0.0006 0.0225 0.1164 0.1743 0.1711 0.1584 0.1284 0.2283 + 1982 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0 0 0.0544 0.2576 0.2802 0.1667 0.0837 0.0508 0.1067 + 1984 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0.0003 0.0023 0.0654 0.311 0.3135 0.1763 0.0846 0.0321 0.0145 + 1985 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0.0005 0.0044 0.079 0.2869 0.3098 0.1898 0.086 0.0306 0.0129 + 1986 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0 0.0016 0.0531 0.2613 0.3289 0.2084 0.0978 0.0352 0.0137 + 1987 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0 0.0013 0.0284 0.1895 0.3045 0.2522 0.1421 0.0565 0.0255 + 1988 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0 0 0.0202 0.1294 0.2646 0.2471 0.1876 0.1033 0.0477 + 1989 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0 0.0005 0.0187 0.1211 0.2209 0.219 0.1908 0.1197 0.1094 + 1990 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0.0003 0 0.0146 0.0887 0.1801 0.1707 0.1728 0.1431 0.2297 + 1991 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0.0001 0.0005 0.0141 0.0848 0.1651 0.179 0.1739 0.1432 0.2392 + 1992 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0.0003 0.0002 0.0005 0.0095 0.0638 0.1317 0.1673 0.1747 0.1636 0.2886 + 1993 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0 0.0014 0.0138 0.094 0.1789 0.1739 0.1596 0.1331 0.2453 + 1996 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0.0006 0.0006 0.0129 0.0779 0.1407 0.162 0.1771 0.1671 0.2612 + 1997 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0.0004 0.0003 0.0138 0.0899 0.1486 0.1603 0.1699 0.1588 0.258 + 1998 1 1 1 1 0 0 100 0 0 0 0 0 0 0.0001 0.0001 0.0001 0.0001 0.0004 0.0002 0.0008 0.0225 0.1187 0.1596 0.149 0.1432 0.1394 0.266 + 1999 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0.0001 0 0.0001 0.0147 0.1313 0.2575 0.2292 0.1624 0.0961 0.1087 + 2000 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0.0001 0.0001 0 0.0001 0.0003 0.0111 0.0931 0.1945 0.2111 0.1822 0.1247 0.1826 + 2001 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0.0001 0.0001 0.0001 0.0002 0.0002 0.0012 0.0181 0.0836 0.1681 0.1986 0.1953 0.1506 0.1838 + 2002 1 1 1 1 0 0 100 0 0 0 0 0 0 0.0001 0 0.0001 0.0001 0.0001 0 0.0002 0.0151 0.108 0.1884 0.1915 0.1683 0.1334 0.1948 + 2003 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0.0001 0.0001 0.0002 0.0009 0.0243 0.1464 0.232 0.1871 0.1497 0.0994 0.1597 + 2004 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0 0.0002 0.0064 0.0514 0.1302 0.1702 0.1971 0.1632 0.2812 + 2005 1 1 1 1 0 0 100 0 0 0 0 0 0 0.0001 0 0 0 0.0001 0.0001 0.0008 0.015 0.0859 0.1543 0.1661 0.1783 0.1516 0.2475 + 2006 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0.0001 0.0001 0.0004 0.0102 0.0739 0.1905 0.2203 0.1887 0.137 0.1787 + 2007 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0.0002 0.0003 0.0067 0.0871 0.1833 0.1934 0.1846 0.1472 0.1973 + 2008 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0.0001 0.0002 0.01 0.0746 0.1457 0.1619 0.179 0.1625 0.2659 + 2009 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0 0.0002 0.0108 0.1152 0.2215 0.1968 0.1588 0.1084 0.1882 + 2010 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0 0 0.0003 0.0091 0.0986 0.2244 0.2238 0.1861 0.1144 0.1433 + 2011 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0 0 0.0003 0.0001 0.0003 0.0114 0.118 0.2436 0.2292 0.1725 0.1077 0.1169 + 2012 1 1 1 1 0 0 100 0 0 0 0 0 0 0 0 0.0001 0 0.0001 0 0 0.0044 0.0499 0.1249 0.173 0.1886 0.1654 0.2937 +##length proportions of pot discarded males +##Year, Seas, Fleet, Sex, Type, Shell, Maturity, Nsamp, DataVec + 1990 1 1 1 2 0 0 100 0.0011 0 0.0011 0.008 0.0046 0.0126 0.0069 0.0378 0.0504 0.0767 0.1226 0.1523 0.1867 0.244 0.0859 0.0092 0 0 0 0 + 1991 1 1 1 2 0 0 100 0.0033 0.0101 0.0197 0.0214 0.0242 0.0394 0.0326 0.063 0.0624 0.0692 0.0641 0.1125 0.1586 0.2154 0.0939 0.0101 0 0 0 0 + 1992 1 1 1 2 0 0 100 0 0.0009 0.0012 0.0111 0.0222 0.0549 0.0869 0.1143 0.1183 0.123 0.118 0.1251 0.1112 0.0807 0.0293 0.0028 0 0 0 0 + 1993 1 1 1 2 0 0 100 0.0019 0.0045 0.0057 0.005 0.0062 0.0122 0.0312 0.0571 0.0778 0.108 0.1334 0.1544 0.1518 0.1705 0.0747 0.0055 0 0 0 0 + 1996 1 1 1 2 0 0 100 0 0 0 0.0131 0.0524 0.083 0.0742 0.0306 0.048 0.0699 0.0611 0.1004 0.1485 0.2009 0.1048 0.0131 0 0 0 0 + 1997 1 1 1 2 0 0 100 0 0.0002 0.0005 0.0007 0.0015 0.0197 0.0553 0.109 0.1268 0.1304 0.1031 0.1002 0.1275 0.1424 0.0751 0.0076 0 0 0 0 + 1998 1 1 1 2 0 0 100 0.0002 0.0005 0.0008 0.0044 0.007 0.01 0.0104 0.0175 0.0391 0.097 0.1402 0.2062 0.2047 0.1811 0.0714 0.0097 0 0 0 0 + 1999 1 1 1 2 0 0 100 0 0 0 0.0086 0.0086 0.0029 0.0076 0.0086 0.0143 0.0286 0.063 0.126 0.2118 0.3244 0.188 0.0076 0 0 0 0 + 2000 1 1 1 2 0 0 100 0.0003 0.0051 0.0192 0.0483 0.0613 0.0576 0.0595 0.0581 0.0532 0.0558 0.0712 0.1059 0.1497 0.1554 0.0895 0.0097 0 0 0 0 + 2001 1 1 1 2 0 0 100 0.0016 0.0057 0.0093 0.0115 0.0155 0.0302 0.0568 0.0866 0.1009 0.1196 0.1239 0.1411 0.1319 0.1128 0.0481 0.0045 0 0 0 0 + 2002 1 1 1 2 0 0 100 0.0012 0.0061 0.006 0.0091 0.0065 0.0104 0.0133 0.0335 0.063 0.1142 0.1543 0.1705 0.1642 0.1582 0.0803 0.0093 0 0 0 0 + 2003 1 1 1 2 0 0 100 0.0081 0.0119 0.0146 0.0317 0.0552 0.0666 0.072 0.067 0.0642 0.0599 0.0655 0.0958 0.1322 0.1708 0.0781 0.0064 0 0 0 0 + 2004 1 1 1 2 0 0 100 0.0004 0.0074 0.0177 0.0403 0.051 0.0483 0.0615 0.1087 0.1384 0.1452 0.1102 0.0849 0.07 0.0688 0.0404 0.0059 0.0008 0 0 0 + 2005 1 1 1 2 0 0 100 0.0002 0.0008 0.0015 0.0029 0.0076 0.022 0.0343 0.0418 0.0454 0.0658 0.0956 0.1376 0.1381 0.1385 0.0729 0.0262 0.0246 0.0349 0.0345 0.075 + 2006 1 1 1 2 0 0 100 0.0003 0.0013 0.0044 0.015 0.0312 0.0377 0.0368 0.0346 0.0452 0.0766 0.0929 0.1144 0.1377 0.1764 0.1275 0.0284 0.0105 0.0085 0.0075 0.0132 + 2007 1 1 1 2 0 0 100 0.0012 0.0042 0.0068 0.0098 0.0171 0.0366 0.0658 0.085 0.0928 0.0857 0.0819 0.0987 0.1291 0.1651 0.0956 0.0126 0.0032 0.0028 0.0022 0.0037 + 2008 1 1 1 2 0 0 100 0.0001 0.0003 0.0012 0.0046 0.0108 0.0141 0.0159 0.0214 0.0441 0.0808 0.1269 0.1793 0.1988 0.1838 0.0983 0.0099 0.0014 0.0018 0.0018 0.0045 + 2009 1 1 1 2 0 0 100 0.0004 0.001 0.0018 0.0032 0.0041 0.0073 0.0178 0.0402 0.0631 0.0705 0.0798 0.118 0.1809 0.2413 0.1455 0.0149 0.0021 0.0016 0.0022 0.0043 + 2010 1 1 1 2 0 0 100 0.0007 0.0011 0.0025 0.0055 0.0085 0.0119 0.0148 0.0218 0.0341 0.0541 0.0962 0.1517 0.2017 0.2373 0.135 0.0137 0.0017 0.0018 0.0016 0.0042 + 2011 1 1 1 2 0 0 100 0.0017 0.0066 0.0112 0.0199 0.0204 0.0188 0.0272 0.0309 0.0409 0.056 0.0756 0.1176 0.1698 0.221 0.1565 0.018 0.0026 0.0017 0.0009 0.0025 + 2012 1 1 1 2 0 0 100 0.0006 0.0008 0.0024 0.0042 0.0111 0.0262 0.0416 0.0563 0.0534 0.057 0.0704 0.106 0.1521 0.2072 0.1468 0.0248 0.0054 0.0085 0.0069 0.0182 +##length proportions of pot discarded females +##Year, Seas, Fleet, Sex, Type, Shell, Maturity, Nsamp, DataVec + 1990 1 1 2 2 0 0 50 0 0.0014 0.0029 0.0029 0.0057 0.0072 0.0143 0.0672 0.1016 0.1731 0.1688 0.2132 0.1359 0.0715 0.0243 0.01 0 0 0 0 + 1991 1 1 2 2 0 0 50 0.0054 0.0239 0.0612 0.0957 0.133 0.1596 0.1223 0.0718 0.0691 0.0559 0.0691 0.0798 0.0346 0.0106 0.0053 0.0027 0 0 0 0 + 1992 1 1 2 2 0 0 50 0.0008 0.0013 0.0029 0.0176 0.0799 0.1757 0.1941 0.1694 0.0958 0.0816 0.0577 0.0406 0.0406 0.0259 0.0117 0.0046 0 0 0 0 + 1993 1 1 2 2 0 0 50 0.0015 0.0024 0.0044 0.0059 0.013 0.0326 0.1011 0.1597 0.1444 0.1137 0.0905 0.0853 0.0835 0.074 0.0434 0.0446 0 0 0 0 + 1996 1 1 2 2 0 0 50 0 0 0 0.0909 0.6364 0.2727 0 0 0 0 0 0 0 0 0 0 0 0 0 0 + 1997 1 1 2 2 0 0 50 0 0 0.0011 0.0011 0.0099 0.0265 0.0364 0.0464 0.0695 0.1391 0.1667 0.1435 0.117 0.1082 0.0607 0.074 0 0 0 0 + 1998 1 1 2 2 0 0 50 0.0002 0.0004 0.001 0.0026 0.0064 0.018 0.057 0.1813 0.2307 0.1527 0.0828 0.0855 0.0578 0.0514 0.0337 0.0386 0 0 0 0 + 1999 1 1 2 2 0 0 50 0 0 0 0.0278 0.0278 0.0278 0.0556 0 0 0.1111 0.1389 0.0833 0.1111 0.1111 0.0833 0.2222 0 0 0 0 + 2000 1 1 2 2 0 0 50 0 0.0175 0.1036 0.2234 0.2093 0.1319 0.0774 0.0323 0.0209 0.0316 0.0451 0.0518 0.0229 0.0141 0.0047 0.0135 0 0 0 0 + 2001 1 1 2 2 0 0 50 0.0027 0.005 0.0151 0.033 0.0588 0.0866 0.097 0.0866 0.0575 0.0525 0.0874 0.1392 0.1421 0.0649 0.0291 0.0426 0 0 0 0 + 2002 1 1 2 2 0 0 50 0.0258 0.1194 0.1452 0.1548 0.1161 0.0645 0.0258 0.0226 0.0548 0.0419 0.0355 0.0258 0.0323 0.0355 0.0323 0.0678 0 0 0 0 + 2003 1 1 2 2 0 0 50 0.0141 0.0187 0.0255 0.0719 0.1116 0.1157 0.0743 0.0476 0.0661 0.0902 0.1012 0.0628 0.0497 0.0504 0.046 0.054 0 0 0 0 + 2004 1 1 2 2 0 0 50 0.0005 0.0075 0.0306 0.0596 0.0754 0.09 0.1425 0.1333 0.0883 0.0484 0.0574 0.0584 0.0511 0.0394 0.0389 0.0788 0 0 0 0 + 2005 1 1 2 2 0 0 50 0.0004 0.0013 0.0022 0.005 0.0146 0.0499 0.0788 0.0931 0.1233 0.1211 0.0871 0.1021 0.0958 0.0885 0.0519 0.0848 0 0 0 0 + 2006 1 1 2 2 0 0 50 0.0003 0.0044 0.0248 0.1218 0.1937 0.1603 0.072 0.0558 0.0722 0.0778 0.0614 0.0401 0.034 0.0282 0.0199 0.0333 0 0 0 0 + 2007 1 1 2 2 0 0 50 0.003 0.0126 0.0214 0.0223 0.0436 0.0854 0.1105 0.0828 0.0558 0.0744 0.102 0.1165 0.0954 0.0684 0.0444 0.0614 0 0 0 0 + 2008 1 1 2 2 0 0 50 0.0004 0.0018 0.0097 0.0364 0.0768 0.0661 0.0469 0.0773 0.107 0.0868 0.0954 0.1265 0.1257 0.0672 0.0392 0.0369 0 0 0 0 + 2009 1 1 2 2 0 0 50 0.0037 0.008 0.01 0.0144 0.0164 0.0277 0.0647 0.0863 0.0803 0.0913 0.0858 0.09 0.1144 0.1308 0.088 0.0881 0 0 0 0 + 2010 1 1 2 2 0 0 50 0.0037 0.0051 0.0051 0.0199 0.0276 0.029 0.0271 0.0443 0.0882 0.1138 0.1322 0.1427 0.1007 0.0915 0.0879 0.0813 0 0 0 0 + 2011 1 1 2 2 0 0 50 0.0132 0.0373 0.0653 0.1089 0.0814 0.0734 0.0619 0.0436 0.0281 0.0373 0.0717 0.0896 0.0748 0.0587 0.061 0.0938 0 0 0 0 + 2012 1 1 2 2 0 0 50 0.0089 0.0107 0.0125 0.0339 0.0606 0.1159 0.0945 0.0392 0.0178 0.0125 0.041 0.0392 0.1658 0.1515 0.1105 0.0856 0 0 0 0 +#length proportions of trawl male bycatch +##Year, Seas, Fleet, Sex, Type, Shell, Maturity, Nsamp, DataVec + 1976 1 2 1 0 0 0 50 0 0 0 0 0 0.013 0.0087 0.0043 0.0216 0.0087 0.026 0.039 0.0433 0.0649 0.0996 0.0866 0.0736 0.0909 0.0649 0.1299 + 1977 1 2 1 0 0 0 50 0.0036 0.0009 0.0009 0.0009 0.0026 0.0035 0.0079 0.0097 0.0317 0.0485 0.0599 0.0996 0.1084 0.1251 0.104 0.1057 0.1004 0.0634 0.0326 0.0441 + 1978 1 2 1 0 0 0 50 0 0 0 0 0 0 0 0.0025 0.0012 0.0025 0.0149 0.0274 0.0511 0.0872 0.1245 0.1158 0.0797 0.0984 0.0672 0.188 + 1979 1 2 1 0 0 0 50 0.0178 0.0013 0.0025 0.0013 0.0025 0.0076 0.0038 0.0025 0.0013 0.0063 0.0051 0.0114 0.0228 0.0556 0.0582 0.0708 0.0898 0.086 0.0809 0.1858 + 1980 1 2 1 0 0 0 50 0.0531 0.0207 0.0096 0.0135 0.0142 0.0163 0.0274 0.0263 0.038 0.0375 0.0422 0.0394 0.0368 0.0377 0.0313 0.0231 0.0207 0.0142 0.0131 0.0265 + 1981 1 2 1 0 0 0 50 0.0262 0.0028 0.0045 0.0066 0.0112 0.0175 0.0279 0.0349 0.0386 0.0504 0.0434 0.048 0.0287 0.0334 0.0241 0.0212 0.0112 0.0064 0.0051 0.0087 + 1982 1 2 1 0 0 0 50 0.0701 0.0268 0.0247 0.0326 0.0356 0.0443 0.0409 0.0403 0.0401 0.0475 0.0426 0.0479 0.0405 0.0326 0.0218 0.0153 0.0084 0.0052 0.0038 0.0099 + 1983 1 2 1 0 0 0 50 0.0231 0.0214 0.0336 0.0344 0.0311 0.0319 0.0377 0.0445 0.0473 0.0471 0.0457 0.0437 0.0409 0.0414 0.0371 0.0283 0.0204 0.0129 0.0096 0.018 + 1984 1 2 1 0 0 0 50 0.0366 0.0156 0.0147 0.0199 0.027 0.0342 0.0399 0.0407 0.0431 0.0476 0.0511 0.0596 0.0594 0.0563 0.0473 0.0355 0.0264 0.017 0.0109 0.0146 + 1985 1 2 1 0 0 0 50 0.0051 0.0014 0.0034 0.0059 0.01 0.0164 0.0256 0.0396 0.0357 0.0446 0.0538 0.0636 0.0843 0.0862 0.0883 0.0843 0.0638 0.0455 0.0299 0.0578 + 1986 1 2 1 0 0 0 50 0.0139 0.0028 0.008 0.0106 0.0159 0.0199 0.0237 0.0263 0.0245 0.0316 0.0393 0.0532 0.0739 0.0772 0.0803 0.0706 0.0604 0.0396 0.0327 0.0401 + 1987 1 2 1 0 0 0 50 0.0017 0.0024 0.0056 0.0076 0.0115 0.017 0.0231 0.0293 0.0331 0.0349 0.0471 0.0506 0.0543 0.062 0.0646 0.0613 0.0581 0.0356 0.0231 0.0259 + 1988 1 2 1 0 0 0 50 0.0228 0.001 0.0013 0.0023 0.0045 0.0095 0.0156 0.0214 0.0251 0.028 0.0291 0.0333 0.039 0.0471 0.0604 0.0697 0.0768 0.0634 0.043 0.0393 + 1989 1 2 1 0 0 0 50 0.001 0.001 0.0012 0.0012 0.0024 0.0036 0.0084 0.0105 0.0153 0.0229 0.03 0.0473 0.0505 0.0613 0.0784 0.0849 0.0806 0.0772 0.0645 0.0919 + 1990 1 2 1 0 0 0 50 0.024 0.006 0.009 0.003 0.0105 0.0075 0.0299 0.0165 0.0329 0.0359 0.024 0.0314 0.0314 0.0434 0.0689 0.0749 0.0763 0.0644 0.0344 0.0689 + 1991 1 2 1 0 0 0 50 0.0481 0.0289 0.0225 0.0064 0.0225 0.0129 0.0161 0.0161 0.0386 0.0225 0.0418 0.0322 0.0322 0.0225 0.0322 0.074 0.0354 0.0514 0.0514 0.1479 + 1992 1 2 1 0 0 0 50 0 0 0 0 0 0.0068 0 0 0 0.0136 0.0169 0.0203 0.0407 0.0373 0.0407 0.0373 0.0271 0.0237 0.0068 0.0305 + 1994 1 2 1 0 0 0 50 0.0061 0.0061 0.0061 0.0076 0.0015 0 0 0.0015 0.0015 0.0031 0.0015 0.0031 0.0092 0.0137 0.0198 0.0427 0.0412 0.0534 0.0794 0.2885 + 1995 1 2 1 0 0 0 50 0.0193 0.0016 0.0082 0.0065 0.0033 0.0082 0.0163 0.0163 0.0098 0.0163 0.0147 0.0065 0.0114 0.0098 0.0098 0.0163 0.0245 0.0196 0.0033 0.0114 + 1996 1 2 1 0 0 0 50 0 0.0004 0.0011 0.0019 0.0088 0.0191 0.0314 0.0413 0.0452 0.0463 0.0459 0.0467 0.0387 0.0521 0.0333 0.0417 0.0379 0.0459 0.0448 0.1413 + 1997 1 2 1 0 0 0 50 0.0009 0.0009 0 0 0.0009 0.0009 0.0009 0.0044 0.0035 0.0185 0.0334 0.0439 0.0483 0.0501 0.0641 0.0571 0.0501 0.0545 0.0439 0.1344 + 1998 1 2 1 0 0 0 50 0.0023 0.0004 0.0011 0.0004 0.0004 0.0007 0.0026 0.0022 0.0056 0.0071 0.0161 0.0217 0.0446 0.067 0.076 0.0906 0.0869 0.0831 0.067 0.1476 + 1999 1 2 1 0 0 0 50 0.0054 0.0006 0.0006 0.0006 0.0012 0.0006 0.003 0.0018 0.0048 0.0083 0.0143 0.0386 0.0671 0.0837 0.1116 0.1099 0.095 0.0641 0.0523 0.0998 + 2000 1 2 1 0 0 0 50 0.0008 0 0.0005 0.0003 0.0005 0.0046 0.0065 0.0153 0.0243 0.0289 0.0289 0.0346 0.0376 0.0417 0.0444 0.0646 0.0777 0.0837 0.0733 0.2076 + 2001 1 2 1 0 0 0 50 0.0005 0.0002 0.001 0.0005 0.0025 0.0062 0.0064 0.0084 0.0155 0.0192 0.0236 0.0231 0.0266 0.0327 0.0396 0.0447 0.0595 0.058 0.0631 0.1994 + 2002 1 2 1 0 0 0 50 0.0006 0.0006 0.002 0.0068 0.009 0.0107 0.0121 0.0059 0.0059 0.0068 0.0121 0.0229 0.0274 0.0333 0.0503 0.0539 0.0553 0.0497 0.048 0.1081 + 2003 1 2 1 0 0 0 50 0.0017 0.0017 0.0068 0.0102 0.0255 0.0221 0.0272 0.0102 0.0051 0.017 0.0051 0.017 0.0187 0.0187 0.0408 0.0493 0.0425 0.0289 0.0255 0.1037 + 2004 1 2 1 0 0 0 50 0.0039 0.0039 0.0117 0.0039 0.0039 0.0117 0.035 0.0272 0.0233 0.0389 0.0233 0.0233 0.0117 0.0117 0.0233 0.0233 0.0739 0.0389 0.0389 0.1012 + 2005 1 2 1 0 0 0 50 0.0032 0 0.0097 0.0032 0.0032 0.0032 0.0032 0.0355 0.0194 0.0194 0.0323 0.0194 0.0484 0.0484 0.0194 0.0323 0.0516 0.0323 0.0323 0.1839 + 2006 1 2 1 0 0 0 50 0.0026 0.0026 0.0026 0.0078 0.0026 0.0156 0.0208 0.0234 0.0078 0.0442 0.0338 0.0571 0.0545 0.0494 0.0545 0.039 0.0416 0.026 0.0156 0.0623 + 2007 1 2 1 0 0 0 50 0 0 0 0.0002 0.0006 0.0012 0.0033 0.007 0.0107 0.0146 0.0173 0.0206 0.0177 0.0278 0.0358 0.0366 0.0379 0.0362 0.0426 0.0968 + 2008 1 2 1 0 0 0 50 0 0 0.0012 0.0006 0.0024 0.0042 0.0042 0.0089 0.0089 0.0142 0.0196 0.0219 0.0338 0.038 0.0504 0.035 0.0415 0.0534 0.0647 0.1981 + 2009 1 2 1 0 0 0 50 0 0 0 0 0.0019 0.0016 0.0016 0.0054 0.014 0.0194 0.0202 0.0427 0.0539 0.0613 0.0698 0.0741 0.0694 0.0597 0.0512 0.1194 + 2010 1 2 1 0 0 0 50 0 0 0.0017 0.0012 0.0017 0.0046 0.0041 0.0081 0.0133 0.0122 0.0145 0.0307 0.0359 0.0417 0.0557 0.0493 0.0487 0.0354 0.0307 0.0899 + 2011 1 2 1 0 0 0 50 0 0 0.0022 0.0066 0.0109 0.0109 0.0022 0.0066 0.0131 0.0087 0.0066 0.0066 0.0218 0.0284 0.048 0.059 0.059 0.059 0.0437 0.1266 + 2012 1 2 1 0 0 0 50 0 0.0037 0 0 0 0.0037 0.0037 0.0037 0.0037 0.0037 0.0111 0.0074 0.0295 0.0369 0.0517 0.0332 0.0517 0.0554 0.0554 0.1697 +##length proportions of trawl female bycatch +##Year, Seas, Fleet, Sex, Type, Shell, Maturity, Nsamp, DataVec + 1976 1 2 2 0 0 0 50 0 0 0 0 0 0 0.013 0.0087 0.0216 0.026 0.0303 0.0563 0.013 0.026 0.0043 0.026 0 0 0 0 + 1977 1 2 2 0 0 0 50 0 0.0009 0.0009 0 0 0.0009 0.0026 0.0053 0.007 0.0088 0.0062 0.0053 0.0044 0.0026 0.0009 0.0009 0 0 0 0 + 1978 1 2 2 0 0 0 50 0 0 0 0 0 0 0 0 0 0 0.0075 0.005 0.0075 0.0262 0.0324 0.061 0 0 0 0 + 1979 1 2 2 0 0 0 50 0.013 0.0013 0 0 0.0063 0.0038 0.0152 0.0468 0.0354 0.0392 0.0544 0.0215 0.0164 0.0177 0.0013 0.0139 0 0 0 0 + 1980 1 2 2 0 0 0 50 0.0433 0.016 0.0096 0.0189 0.0281 0.0409 0.0497 0.0472 0.0489 0.0525 0.0362 0.0265 0.0134 0.0081 0.0039 0.004 0 0 0 0 + 1981 1 2 2 0 0 0 50 0.0612 0.0245 0.0245 0.0437 0.054 0.0608 0.0525 0.0425 0.0315 0.0383 0.0312 0.0267 0.024 0.0158 0.0093 0.0086 0 0 0 0 + 1982 1 2 2 0 0 0 50 0.0631 0.0235 0.0237 0.0285 0.0379 0.0413 0.0332 0.0246 0.019 0.0177 0.0156 0.0144 0.0104 0.008 0.0034 0.0049 0 0 0 0 + 1983 1 2 2 0 0 0 50 0.0281 0.0233 0.0351 0.0363 0.0358 0.0407 0.0392 0.0316 0.0222 0.0154 0.01 0.0087 0.0065 0.0042 0.003 0.0041 0 0 0 0 + 1984 1 2 2 0 0 0 50 0.04 0.0156 0.0155 0.0211 0.0298 0.0344 0.0399 0.0359 0.0287 0.0151 0.0085 0.006 0.0042 0.0031 0.0019 0.0029 0 0 0 0 + 1985 1 2 2 0 0 0 50 0.0034 0.0013 0.0024 0.0046 0.0096 0.0171 0.0195 0.0193 0.0163 0.0128 0.0119 0.0111 0.0108 0.0057 0.0025 0.0066 0 0 0 0 + 1986 1 2 2 0 0 0 50 0.0144 0.0052 0.0083 0.0132 0.0245 0.0297 0.0388 0.0333 0.0308 0.0203 0.014 0.0069 0.0055 0.0029 0.0023 0.0054 0 0 0 0 + 1987 1 2 2 0 0 0 50 0.0029 0.0015 0.0117 0.0253 0.0271 0.0409 0.0546 0.0479 0.0436 0.0299 0.0221 0.0165 0.0089 0.0047 0.0028 0.0108 0 0 0 0 + 1988 1 2 2 0 0 0 50 0.0239 0.0035 0.0061 0.0111 0.0218 0.0368 0.052 0.0446 0.0464 0.0435 0.0316 0.0179 0.0115 0.0062 0.0026 0.0078 0 0 0 0 + 1989 1 2 2 0 0 0 50 0.001 0.0004 0.0006 0.0024 0.0082 0.0125 0.0151 0.032 0.033 0.0348 0.0302 0.0255 0.0221 0.0167 0.009 0.0225 0 0 0 0 + 1990 1 2 2 0 0 0 50 0.0015 0.0045 0.0105 0.009 0.009 0.0105 0.0254 0.0284 0.0494 0.0404 0.0404 0.0329 0.018 0.009 0.0015 0.0165 0 0 0 0 + 1991 1 2 2 0 0 0 50 0.0096 0.0032 0.0064 0.0032 0 0.0064 0.0032 0.0064 0.0257 0.0129 0.0161 0.0257 0.0161 0.0257 0.0032 0.0804 0 0 0 0 + 1992 1 2 2 0 0 0 50 0 0 0 0.0034 0.0475 0.0712 0.0542 0.0542 0.0508 0.0542 0.0712 0.078 0.0542 0.0508 0.0441 0.0644 0 0 0 0 + 1994 1 2 2 0 0 0 50 0.0306 0.0031 0.0076 0.026 0.029 0.0397 0.026 0.0595 0.0397 0.0153 0.0122 0.0107 0.0137 0.0183 0.0183 0.0641 0 0 0 0 + 1995 1 2 2 0 0 0 50 0.0213 0.0016 0.0065 0.0098 0.0163 0.0082 0.0228 0.0408 0.0555 0.0718 0.1289 0.1109 0.075 0.0685 0.0538 0.0734 0 0 0 0 + 1996 1 2 2 0 0 0 50 0 0 0.0008 0.0042 0.013 0.023 0.0245 0.0234 0.0283 0.0291 0.0257 0.0218 0.0207 0.0165 0.0103 0.0348 0 0 0 0 + 1997 1 2 2 0 0 0 50 0 0 0 0 0.0009 0 0.0132 0.022 0.029 0.0457 0.0343 0.0308 0.0413 0.029 0.0299 0.1134 0 0 0 0 + 1998 1 2 2 0 0 0 50 0 0 0.0004 0.0004 0.0007 0.0022 0.0109 0.0322 0.0386 0.027 0.024 0.0161 0.0187 0.0199 0.0243 0.061 0 0 0 0 + 1999 1 2 2 0 0 0 50 0 0 0 0.0018 0.0012 0.0006 0.0018 0.0018 0.0071 0.0143 0.0208 0.0273 0.041 0.0321 0.0208 0.0665 0 0 0 0 + 2000 1 2 2 0 0 0 50 0.001 0.0003 0.0003 0.0011 0.0005 0.0035 0.0079 0.012 0.0076 0.0125 0.0267 0.039 0.0313 0.0218 0.0158 0.0428 0 0 0 0 + 2001 1 2 2 0 0 0 50 0.0008 0.0002 0.0007 0.001 0.004 0.0062 0.0116 0.0159 0.0172 0.0196 0.0334 0.0577 0.0514 0.0336 0.0275 0.0882 0 0 0 0 + 2002 1 2 2 0 0 0 50 0 0.0008 0.0011 0.0056 0.011 0.0099 0.0085 0.0141 0.0265 0.0285 0.0285 0.0432 0.0536 0.057 0.0559 0.1341 0 0 0 0 + 2003 1 2 2 0 0 0 50 0 0.0017 0.0051 0.0238 0.0357 0.0102 0.0102 0.0289 0.0595 0.0408 0.0289 0.0255 0.0476 0.0391 0.0476 0.1173 0 0 0 0 + 2004 1 2 2 0 0 0 50 0.0039 0.0039 0.0039 0.0039 0.0039 0.0039 0.0117 0.0272 0.0389 0.0506 0.0389 0.0389 0.0467 0.0584 0.0389 0.0934 0 0 0 0 + 2005 1 2 2 0 0 0 50 0 0 0 0.0032 0.0032 0.0129 0.0097 0.0484 0.0516 0.0194 0.0323 0.0323 0.0323 0.0323 0.0323 0.0903 0 0 0 0 + 2006 1 2 2 0 0 0 50 0.0026 0.0078 0.0078 0.0078 0.0078 0.0156 0.0078 0.026 0.0545 0.039 0.026 0.039 0.0545 0.0156 0.039 0.0857 0 0 0 0 + 2007 1 2 2 0 0 0 50 0 0 0.001 0.0002 0.0023 0.0058 0.0124 0.028 0.0519 0.0813 0.0807 0.0774 0.0634 0.0502 0.0397 0.0986 0 0 0 0 + 2008 1 2 2 0 0 0 50 0 0 0.0006 0.0012 0.0047 0.0136 0.0208 0.0308 0.0255 0.0326 0.0403 0.051 0.0344 0.0332 0.0261 0.0842 0 0 0 0 + 2009 1 2 2 0 0 0 50 0 0 0 0.0004 0.0031 0.0031 0.0081 0.0198 0.0345 0.0271 0.0364 0.0415 0.0473 0.031 0.0213 0.0609 0 0 0 0 + 2010 1 2 2 0 0 0 50 0 0 0 0.0012 0.0029 0.0145 0.0313 0.0441 0.0464 0.0412 0.0522 0.0429 0.0638 0.0545 0.0394 0.0864 0 0 0 0 + 2011 1 2 2 0 0 0 50 0 0 0.0066 0.0175 0.0131 0.0131 0.0262 0.0109 0.0218 0.0262 0.0415 0.0437 0.0524 0.0306 0.0393 0.1376 0 0 0 0 + 2012 1 2 2 0 0 0 50 0 0 0 0 0.0037 0.0332 0.0221 0.0443 0.0148 0.0369 0.0295 0.0295 0.059 0.048 0.0332 0.1218 0 0 0 0 +##length proportions of survey newshell males +##Year, Seas, Fleet, Sex, Type, Shell, Maturity, Nsamp, DataVec + 1975 1 3 1 1 1 0 200 0.03433 0.06119 0.03631 0.03701 0.03626 0.02684 0.02746 0.02043 0.02199 0.02522 0.02323 0.02322 0.02484 0.02294 0.01909 0.0197 0.0162 0.00957 0.00661 0.01009 + 1976 1 3 1 1 1 0 200 0.00232 0.01279 0.02937 0.05077 0.06104 0.04581 0.04776 0.03559 0.03199 0.02832 0.02984 0.02996 0.02334 0.02354 0.0206 0.01457 0.01294 0.00852 0.00591 0.00568 + 1977 1 3 1 1 1 0 200 0.00722 0.00558 0.00666 0.01007 0.0195 0.037 0.04363 0.04307 0.04013 0.04302 0.03906 0.03772 0.02788 0.02964 0.02865 0.02252 0.0144 0.01024 0.00661 0.00905 + 1978 1 3 1 1 1 0 200 0.00415 0.0114 0.01313 0.02219 0.01618 0.0153 0.0153 0.02585 0.02749 0.02795 0.02833 0.02739 0.02477 0.0294 0.02988 0.02505 0.02385 0.01579 0.00971 0.00755 + 1979 1 3 1 1 1 0 200 0.00801 0.008 0.01059 0.01598 0.01392 0.01592 0.01244 0.01397 0.01354 0.0178 0.02471 0.03399 0.03477 0.03788 0.03207 0.03339 0.02893 0.02384 0.01446 0.02128 + 1980 1 3 1 1 1 0 200 0.00713 0.01445 0.02854 0.0319 0.03189 0.03189 0.02635 0.02638 0.02288 0.01971 0.02217 0.01609 0.02291 0.02541 0.0251 0.0303 0.02546 0.02432 0.02153 0.02725 + 1981 1 3 1 1 1 0 200 0.03277 0.0196 0.01678 0.0252 0.03727 0.03277 0.03133 0.0292 0.02759 0.02966 0.01907 0.01635 0.01061 0.00937 0.00747 0.00654 0.00401 0.00357 0.00143 0.00509 + 1982 1 3 1 1 1 0 200 0.07924 0.08112 0.06821 0.02812 0.02304 0.03021 0.03407 0.02807 0.01868 0.01581 0.0181 0.01276 0.00951 0.00694 0.00436 0.0034 0.00225 0.00053 0.00041 0.00082 + 1983 1 3 1 1 1 0 200 0.03252 0.03556 0.0497 0.06649 0.07859 0.07774 0.05655 0.04214 0.03545 0.03417 0.02308 0.02137 0.01351 0.00898 0.00777 0.00183 0.00084 0 0 0 + 1984 1 3 1 1 1 0 200 0.01493 0.0625 0.13306 0.14261 0.06919 0.03343 0.01442 0.01346 0.0133 0.00938 0.00949 0.00565 0.00568 0.00336 0.00416 0.00175 0.00077 0.00041 0.00002 0.00016 + 1985 1 3 1 1 1 0 200 0.00261 0.01279 0.02442 0.03954 0.0589 0.05817 0.04235 0.04026 0.05909 0.06049 0.05132 0.05049 0.04397 0.04183 0.02443 0.02289 0.00176 0.00319 0.00415 0 + 1986 1 3 1 1 1 0 200 0.01118 0.01788 0.0248 0.0201 0.02318 0.01475 0.03917 0.04 0.05364 0.04764 0.06284 0.06696 0.05865 0.06369 0.04877 0.03519 0.02325 0.00733 0.00143 0.00072 + 1987 1 3 1 1 1 0 200 0.00151 0.00715 0.03314 0.0523 0.04666 0.03193 0.02963 0.02928 0.03029 0.02445 0.03113 0.02335 0.03004 0.02375 0.02059 0.01754 0.01411 0.0133 0.00347 0.00237 + 1988 1 3 1 1 1 0 200 0.00132 0.00098 0.00662 0.01068 0.01094 0.02158 0.04663 0.04339 0.03932 0.03771 0.02571 0.02768 0.01467 0.02865 0.02359 0.03421 0.02539 0.0189 0.00946 0.00793 + 1989 1 3 1 1 1 0 200 0.00151 0.00009 0 0.00228 0.01414 0.032 0.01664 0.03469 0.02244 0.03796 0.0373 0.03601 0.04465 0.05129 0.0334 0.03221 0.02538 0.02108 0.01328 0.01964 + 1990 1 3 1 1 1 0 200 0.00132 0.01104 0.01571 0.03616 0.03285 0.01009 0.0075 0.00623 0.01313 0.02143 0.01949 0.02053 0.02075 0.0213 0.01671 0.02223 0.01615 0.01075 0.01072 0.01925 + 1991 1 3 1 1 1 0 200 0.00103 0.00876 0.0213 0.01581 0.02487 0.01952 0.01114 0.02291 0.02011 0.01171 0.00363 0.01729 0.02907 0.03294 0.04485 0.05331 0.0515 0.04094 0.03382 0.06686 + 1992 1 3 1 1 1 0 200 0.001 0 0.00202 0.01106 0.0252 0.03333 0.05097 0.04886 0.03395 0.03348 0.02591 0.03451 0.02322 0.0146 0.01108 0.01594 0.01162 0.01399 0.01176 0.02854 + 1993 1 3 1 1 1 0 200 0.00208 0.01094 0.01291 0.00906 0.00804 0.01357 0.01066 0.01917 0.01955 0.03344 0.02444 0.04147 0.02119 0.01732 0.00967 0.00822 0.00732 0.00891 0.00577 0.00787 + 1994 1 3 1 1 1 0 200 0.00162 0 0.00309 0.02093 0.01757 0.01239 0.01098 0.01082 0.01688 0.03227 0.03069 0.02792 0.03848 0.05112 0.02013 0.02458 0.02607 0.01992 0.01064 0.01519 + 1995 1 3 1 1 1 0 200 0.02826 0.06829 0.05574 0.02203 0.01101 0.01592 0.02133 0.02355 0.02568 0.02873 0.02066 0.02201 0.02408 0.02322 0.035 0.02166 0.01749 0.01473 0.00622 0.01125 + 1996 1 3 1 1 1 0 200 0.02719 0.01292 0.02918 0.05291 0.06042 0.05874 0.02691 0.01981 0.01098 0.01462 0.01337 0.01035 0.00912 0.00319 0.00622 0.00716 0.00659 0.00938 0.0111 0.01276 + 1997 1 3 1 1 1 0 200 0 0.00357 0.00221 0.00519 0.0127 0.05636 0.09427 0.10657 0.09022 0.05071 0.02796 0.0136 0.01212 0.00935 0.01131 0.01348 0.01555 0.0103 0.00979 0.02598 + 1998 1 3 1 1 1 0 200 0.02085 0.01739 0.01031 0.01272 0.012 0.01014 0.01345 0.01472 0.02013 0.04373 0.04263 0.03912 0.03466 0.01846 0.00647 0.00737 0.00442 0.0029 0.00124 0.00345 + 1999 1 3 1 1 1 0 200 0.05825 0.02444 0.01335 0.01038 0.01196 0.01036 0.00963 0.01225 0.00326 0.00664 0.01252 0.02202 0.04148 0.0395 0.05441 0.05623 0.02925 0.01972 0.01072 0.0114 + 2000 1 3 1 1 1 0 200 0.00175 0.00473 0.01944 0.03949 0.03095 0.01993 0.02272 0.01626 0.01888 0.01404 0.01099 0.02078 0.01298 0.02074 0.01385 0.0111 0.01148 0.00855 0.00427 0.0067 + 2001 1 3 1 1 1 0 200 0.00689 0.00496 0.01061 0.0149 0.0156 0.04136 0.03572 0.05159 0.03394 0.01999 0.02186 0.0132 0.00984 0.01223 0.00775 0.00551 0.01066 0.01006 0.01014 0.0124 + 2002 1 3 1 1 1 0 200 0.05335 0.06381 0.0436 0.02682 0.01193 0.00793 0.00606 0.00736 0.01535 0.01781 0.02124 0.02041 0.01045 0.00875 0.00999 0.00631 0.00525 0.00883 0.00623 0.00503 + 2003 1 3 1 1 1 0 200 0.01604 0.0074 0.0154 0.02495 0.04249 0.0342 0.03247 0.018 0.00959 0.01396 0.01125 0.02279 0.01875 0.02908 0.02324 0.02414 0.01482 0.00971 0.00796 0.02164 + 2004 1 3 1 1 1 0 200 0.04684 0.03651 0.03383 0.02365 0.02226 0.01926 0.02833 0.04015 0.03578 0.0352 0.0264 0.02019 0.01236 0.01273 0.0128 0.01815 0.01566 0.02153 0.01193 0.025 + 2005 1 3 1 1 1 0 200 0.03525 0.05861 0.04185 0.01599 0.00976 0.02277 0.02344 0.02146 0.01842 0.01622 0.02073 0.02207 0.01265 0.01714 0.00954 0.01168 0.00648 0.00646 0.00805 0.01227 + 2006 1 3 1 1 1 0 200 0.01329 0.01976 0.01658 0.02765 0.02838 0.03548 0.01857 0.02076 0.01179 0.017 0.0105 0.01205 0.01881 0.01862 0.02997 0.02605 0.02056 0.01732 0.01059 0.01291 + 2007 1 3 1 1 1 0 200 0.00172 0.00246 0.00532 0.00837 0.01967 0.02715 0.03091 0.04028 0.03332 0.02419 0.01566 0.01804 0.01517 0.02261 0.01747 0.01805 0.0179 0.01359 0.01535 0.01691 + 2008 1 3 1 1 1 0 200 0 0.00076 0.00363 0.00577 0.01395 0.01669 0.01814 0.0223 0.03342 0.04313 0.03802 0.02547 0.02337 0.01707 0.01364 0.01039 0.01454 0.01071 0.00832 0.01802 + 2009 1 3 1 1 1 0 200 0.00095 0.00048 0.0037 0.00527 0.00532 0.01039 0.00965 0.02253 0.03192 0.02616 0.0236 0.02484 0.02844 0.04127 0.02429 0.02658 0.01436 0.01032 0.00775 0.0067 + 2010 1 3 1 1 1 0 200 0 0.00334 0.00803 0.00943 0.00774 0.00538 0.01608 0.01344 0.01295 0.01526 0.02418 0.03048 0.02201 0.0223 0.02723 0.02567 0.0316 0.01894 0.01048 0.0095 + 2011 1 3 1 1 1 0 200 0.00362 0.00438 0.0125 0.02044 0.01569 0.01317 0.01676 0.01505 0.01822 0.01195 0.01613 0.0164 0.01359 0.0199 0.01732 0.01617 0.01904 0.01323 0.00578 0.00808 + 2012 1 3 1 1 1 0 200 0.00247 0.00398 0.01202 0.01593 0.01281 0.0227 0.03362 0.02474 0.01742 0.01742 0.01461 0.01733 0.01843 0.01958 0.01581 0.01519 0.01481 0.01651 0.00795 0.02737 + 2013 1 3 1 1 1 0 200 0.00082 0.00253 0.01232 0.01451 0.01006 0.01741 0.01341 0.02352 0.02798 0.02607 0.03135 0.02742 0.02114 0.01964 0.01842 0.01501 0.01278 0.01693 0.0211 0.03167 +##length proportions of survey oldshell males +##Year, Seas, Fleet, Sex, Type, Shell, Maturity, Nsamp, DataVec + 1975 1 3 1 0 2 0 200 0 0.00011 0 0.00022 0 0.00011 0 0.00085 0.00065 0.0015 0.00086 0.00138 0.00171 0.00137 0.00195 0.00362 0.00184 0.00198 0.00188 0.00076 + 1976 1 3 1 0 2 0 200 0 0 0 0.00004 0.00004 0 0 0.00002 0.00052 0.00042 0.00093 0.00365 0.00268 0.00508 0.00529 0.00393 0.00422 0.00497 0.00294 0.00151 + 1977 1 3 1 0 2 0 200 0 0 0 0 0 0.00041 0.00065 0.00018 0.00068 0.00083 0.00118 0.0024 0.00243 0.00212 0.00307 0.00309 0.00184 0.00341 0.00157 0.00302 + 1978 1 3 1 0 2 0 200 0.00014 0.00055 0.00048 0.00182 0.00106 0.00376 0.00253 0.00205 0.00207 0.00181 0.00171 0.00297 0.00421 0.00726 0.00476 0.00321 0.00216 0.00149 0.00113 0.00156 + 1979 1 3 1 0 2 0 200 0.00015 0.00093 0.00064 0.00022 0.00073 0.00111 0.00024 0.00039 0.00039 0.00087 0.00105 0.00202 0.00181 0.00378 0.0043 0.00378 0.00524 0.0044 0.00132 0.00393 + 1980 1 3 1 0 2 0 200 0 0 0 0 0 0.00045 0.0003 0 0 0.00016 0.00038 0.00045 0.00097 0.00121 0.0018 0.00285 0.00174 0.00295 0.00104 0.00401 + 1981 1 3 1 0 2 0 200 0.00016 0 0.00061 0 0.001 0.00073 0.00059 0.00247 0.00146 0.00418 0.00419 0.00537 0.00795 0.00898 0.00711 0.00801 0.0066 0.00669 0.00476 0.00952 + 1982 1 3 1 0 2 0 200 0 0 0 0.00055 0.00095 0.00079 0.0012 0.00065 0.00105 0.00129 0.00173 0.00135 0.00355 0.00097 0.00222 0.00093 0.00169 0 0 0.00094 + 1983 1 3 1 0 2 0 200 0 0 0 0 0.00146 0.00051 0.00342 0.00467 0.00427 0.00572 0.00909 0.00952 0.0055 0.00294 0.0029 0.00185 0.00166 0.00123 0 0 + 1984 1 3 1 0 2 0 200 0 0.00012 0.00014 0.00003 0.00017 0.00004 0.00044 0.00027 0.00024 0.00267 0.00045 0.00024 0.00082 0.00085 0.00249 0.00063 0.00002 0.00051 0 0.00013 + 1985 1 3 1 0 2 0 200 0 0 0 0 0 0 0 0 0.00106 0.0009 0 0.00182 0.00573 0 0.00351 0.00085 0 0.00191 0 0 + 1986 1 3 1 0 2 0 200 0 0 0 0 0 0.00088 0.00162 0 0.00224 0.00088 0.00462 0.00643 0.01135 0.01506 0.00757 0.00329 0.0042 0 0.0015 0.0016 + 1987 1 3 1 0 2 0 200 0 0 0 0 0.00039 0.00039 0 0.00041 0.00082 0.00119 0.00226 0.0036 0.00689 0.01094 0.00869 0.01119 0.00436 0.00251 0.00038 0.00161 + 1988 1 3 1 0 2 0 200 0 0 0 0 0.00205 0 0 0 0 0 0.0008 0.00288 0.00569 0.00855 0.00952 0.01509 0.01151 0.00793 0 0.00135 + 1989 1 3 1 0 2 0 200 0 0 0.00081 0 0 0 0 0.00009 0.00146 0.00516 0.0015 0.00074 0.00748 0.00942 0.0216 0.03086 0.02302 0.02473 0.01384 0.00653 + 1990 1 3 1 0 2 0 200 0 0 0 0 0.00072 0 0.00072 0.00071 0.00255 0.00453 0.00316 0.00923 0.01085 0.01496 0.01888 0.01774 0.0133 0.02177 0.00869 0.01368 + 1991 1 3 1 0 2 0 200 0 0 0.00058 0.00059 0.00112 0.0017 0.0023 0.0039 0.00156 0.00516 0.00215 0.00336 0.00581 0.00497 0.01474 0.01452 0.01304 0.00898 0.00688 0.01173 + 1992 1 3 1 0 2 0 200 0 0 0 0.00165 0 0.00217 0.00423 0.00391 0.00423 0.00645 0.00318 0.0033 0.01161 0.01343 0.01228 0.00739 0.01026 0.01666 0.00509 0.02109 + 1993 1 3 1 0 2 0 200 0 0 0.00069 0.00137 0.00145 0.00203 0.00344 0.00422 0.01136 0.01032 0.01999 0.02171 0.0285 0.02464 0.02295 0.02012 0.02286 0.01946 0.01823 0.03231 + 1994 1 3 1 0 2 0 200 0 0 0 0.00277 0.00591 0.00277 0.00138 0.00651 0.00443 0.0031 0.01053 0.01238 0.02425 0.03959 0.02727 0.02154 0.02073 0.01281 0.0123 0.03521 + 1995 1 3 1 0 2 0 200 0 0 0 0 0 0.00099 0.00086 0.00198 0.0018 0.00173 0.0056 0.00478 0.01026 0.01699 0.01402 0.02162 0.01481 0.00904 0.00454 0.0149 + 1996 1 3 1 0 2 0 200 0.00062 0.00062 0.00062 0 0.00274 0.00064 0.00065 0.00268 0.00072 0.00324 0.00066 0.00466 0.00482 0.00979 0.01555 0.00931 0.01244 0.00776 0.00717 0.01245 + 1997 1 3 1 0 2 0 200 0 0 0 0 0 0 0 0.00041 0.00075 0.00083 0.00216 0.00257 0.00276 0.00386 0.00289 0.00335 0.00782 0.00651 0.00752 0.01417 + 1998 1 3 1 0 2 0 200 0 0 0 0 0 0 0 0.00217 0.0025 0.00293 0.00589 0.0132 0.01047 0.01061 0.01185 0.00788 0.01513 0.01058 0.00671 0.02105 + 1999 1 3 1 0 2 0 200 0 0 0 0 0 0.00062 0.0025 0.00253 0.00142 0.00658 0.00563 0.00129 0.01054 0.01416 0.01567 0.01262 0.01435 0.01064 0.01136 0.01386 + 2000 1 3 1 0 2 0 200 0 0 0 0 0 0 0 0 0.00112 0.00061 0.00239 0.00876 0.01636 0.02809 0.02766 0.02479 0.02271 0.01431 0.0042 0.01289 + 2001 1 3 1 0 2 0 200 0 0 0 0 0 0.00073 0.00143 0.00075 0.00067 0 0.00347 0.00344 0.00412 0.00794 0.00542 0.00565 0.01123 0.00906 0.00907 0.02029 + 2002 1 3 1 0 2 0 200 0 0 0 0.00041 0 0.00114 0.00154 0.00326 0.00757 0.0088 0.0135 0.00862 0.0098 0.01641 0.00701 0.01303 0.01423 0.01333 0.01792 0.02237 + 2003 1 3 1 0 2 0 200 0 0 0 0.0004 0 0.00037 0.00077 0.00039 0.00188 0.00155 0.00156 0.0036 0.00356 0.0062 0.00894 0.00726 0.00734 0.00652 0.00595 0.01452 + 2004 1 3 1 0 2 0 200 0 0 0 0 0 0.00062 0.00051 0.00014 0.00032 0.00034 0 0.00034 0.00007 0.00044 0.0037 0.00377 0.00384 0.00503 0.0037 0.01012 + 2005 1 3 1 0 2 0 200 0 0 0 0 0 0 0 0 0 0.00091 0.00113 0.00119 0.00323 0.00177 0.00295 0.00415 0.00385 0.00899 0.00632 0.01294 + 2006 1 3 1 0 2 0 200 0 0 0.00071 0 0.00073 0.00144 0.00241 0 0.00111 0.00175 0.0011 0.00076 0.00473 0.00186 0.00289 0.00183 0.00646 0.00255 0.00377 0.01163 + 2007 1 3 1 0 2 0 200 0 0 0 0 0 0 0.00369 0.00339 0.00527 0.00455 0.00307 0.00526 0.00834 0.00878 0.00976 0.01062 0.00969 0.01252 0.00746 0.01193 + 2008 1 3 1 0 2 0 200 0 0 0 0.00074 0.00037 0.00148 0.00074 0.00075 0.00203 0.00037 0.0024 0.00393 0.00599 0.00862 0.00625 0.00585 0.00539 0.00811 0.00765 0.01503 + 2009 1 3 1 0 2 0 200 0 0 0 0 0 0 0 0 0.00101 0.00386 0.00786 0.00793 0.00778 0.0066 0.00689 0.00625 0.00537 0.00593 0.00704 0.01014 + 2010 1 3 1 0 2 0 200 0 0 0 0 0 0 0 0 0 0 0.00278 0.00578 0.00817 0.01021 0.00947 0.00903 0.01066 0.00728 0.00404 0.01046 + 2011 1 3 1 0 2 0 200 0 0 0 0 0.00118 0.00061 0 0 0 0.00123 0.00193 0.00385 0.00252 0.00962 0.0101 0.00952 0.00507 0.00714 0.00576 0.0083 + 2012 1 3 1 0 2 0 200 0 0 0 0 0 0 0 0 0 0 0.00071 0.00222 0.00326 0.00686 0.0076 0.00575 0.00834 0.0116 0.00523 0.01605 + 2013 1 3 1 0 2 0 200 0 0 0 0 0 0 0 0 0 0 0.00091 0.0074 0.00914 0.01228 0.01594 0.01743 0.02119 0.02615 0.01835 0.04324 +##length proportions of survey females +##Year, Seas, Fleet, Sex, Type, Shell, Maturity, Nsamp, DataVec + 1975 1 3 2 0 0 0 200 0.04788 0.05622 0.05339 0.04732 0.05296 0.04081 0.03821 0.03823 0.02918 0.02491 0.01409 0.01364 0.00998 0.00433 0.00262 0.00294 0 0 0 0 + 1976 1 3 2 0 0 0 200 0.00315 0.00913 0.03175 0.05824 0.06924 0.05738 0.04759 0.03476 0.02941 0.03378 0.02521 0.0225 0.01076 0.00545 0.00156 0.0032 0 0 0 0 + 1977 1 3 2 0 0 0 200 0.00826 0.01119 0.00883 0.01951 0.03371 0.06967 0.07991 0.0704 0.04434 0.04203 0.03962 0.03103 0.01504 0.01006 0.00333 0.00453 0 0 0 0 + 1978 1 3 2 0 0 0 200 0.0061 0.01111 0.01869 0.02009 0.02332 0.04185 0.09213 0.12133 0.07873 0.04417 0.02995 0.02681 0.01751 0.00895 0.00449 0.00738 0 0 0 0 + 1979 1 3 2 0 0 0 200 0.00979 0.00667 0.00959 0.01791 0.02392 0.02895 0.04936 0.08023 0.09823 0.09691 0.05231 0.02985 0.02374 0.01009 0.00388 0.00579 0 0 0 0 + 1980 1 3 2 0 0 0 200 0.00515 0.0223 0.03324 0.02637 0.06062 0.08389 0.04983 0.055 0.05537 0.04177 0.03098 0.01355 0.01011 0.00621 0.00361 0.00202 0 0 0 0 + 1981 1 3 2 0 0 0 200 0.04661 0.02629 0.01855 0.02254 0.03911 0.04364 0.04209 0.0438 0.05581 0.06796 0.06691 0.04072 0.02115 0.01261 0.00301 0.00313 0 0 0 0 + 1982 1 3 2 0 0 0 200 0.05357 0.09537 0.06029 0.03784 0.04226 0.04818 0.03978 0.02321 0.01896 0.02571 0.02813 0.02027 0.01141 0.00625 0.00238 0.00086 0 0 0 0 + 1983 1 3 2 0 0 0 200 0.01741 0.0383 0.04749 0.06292 0.06466 0.03981 0.03406 0.01518 0.01068 0.00422 0.00904 0.00563 0.00605 0.00222 0.00129 0 0 0 0 0 + 1984 1 3 2 0 0 0 200 0.01229 0.05937 0.13213 0.12041 0.06624 0.03177 0.01564 0.00745 0.00409 0.00158 0.00031 0.00044 0.0001 0.00014 0.00002 0 0 0 0 0 + 1985 1 3 2 0 0 0 200 0.00086 0.01548 0.03765 0.05212 0.0643 0.05553 0.05156 0.03973 0.01606 0.00681 0 0 0.00149 0 0 0 0 0 0 0 + 1986 1 3 2 0 0 0 200 0.01237 0.02244 0.03547 0.02742 0.02628 0.03133 0.03617 0.03878 0.0274 0.01125 0.00715 0.00079 0 0 0.00076 0 0 0 0 0 + 1987 1 3 2 0 0 0 200 0.00134 0.01191 0.05107 0.08877 0.07579 0.04682 0.04501 0.05784 0.04186 0.02982 0.01808 0.00781 0.00185 0.00041 0 0 0 0 0 0 + 1988 1 3 2 0 0 0 200 0.00059 0.00766 0.00646 0.00618 0.01397 0.06959 0.09121 0.09804 0.07011 0.06092 0.04076 0.0184 0.00772 0.00767 0 0 0 0 0 0 + 1989 1 3 2 0 0 0 200 0.0015 0 0.00165 0.00775 0.02771 0.06879 0.06155 0.06435 0.05136 0.0367 0.02865 0.01741 0.00523 0.00405 0 0.00009 0 0 0 0 + 1990 1 3 2 0 0 0 200 0.00421 0.00542 0.02448 0.05339 0.05461 0.00738 0.02722 0.06038 0.07596 0.07194 0.06366 0.04198 0.02071 0.00609 0.00386 0.00387 0 0 0 0 + 1991 1 3 2 0 0 0 200 0.00406 0.01126 0.01915 0.03128 0.02134 0.0337 0.03354 0.0303 0.03586 0.03225 0.02769 0.0422 0.02274 0.01081 0.00674 0.00263 0 0 0 0 + 1992 1 3 2 0 0 0 200 0 0.00534 0.00737 0.01974 0.03642 0.04139 0.06251 0.04481 0.03529 0.02733 0.04503 0.04068 0.02651 0.02118 0.01619 0.01224 0 0 0 0 + 1993 1 3 2 0 0 0 200 0.00652 0.00796 0.01742 0.00845 0.01303 0.0247 0.04349 0.06393 0.06356 0.02673 0.02981 0.02663 0.02696 0.04427 0.01746 0.02183 0 0 0 0 + 1994 1 3 2 0 0 0 200 0 0.0016 0.00443 0.00296 0.01685 0.00917 0.0124 0.02131 0.04312 0.0416 0.03619 0.02802 0.03953 0.04689 0.02916 0.03206 0 0 0 0 + 1995 1 3 2 0 0 0 200 0.02942 0.04821 0.03155 0.01453 0.01391 0.01824 0.01628 0.02535 0.02343 0.03343 0.02724 0.02335 0.02398 0.0145 0.02031 0.01547 0 0 0 0 + 1996 1 3 2 0 0 0 200 0.02595 0.02186 0.04362 0.0794 0.07958 0.04357 0.02255 0.02176 0.02451 0.02017 0.01611 0.02847 0.02443 0.01563 0.00871 0.02361 0 0 0 0 + 1997 1 3 2 0 0 0 200 0.00043 0.00367 0.00162 0.00201 0.0146 0.07907 0.09694 0.06164 0.02119 0.01367 0.00948 0.01455 0.01427 0.01092 0.00836 0.02076 0 0 0 0 + 1998 1 3 2 0 0 0 200 0.0145 0.0196 0.01006 0.00876 0.01112 0.01163 0.03034 0.10415 0.11502 0.05893 0.03058 0.02523 0.02254 0.02353 0.02321 0.03365 0 0 0 0 + 1999 1 3 2 0 0 0 200 0.0243 0.01694 0.0125 0.01147 0.00435 0.00547 0.00924 0.01639 0.05112 0.07986 0.05821 0.03575 0.03393 0.01986 0.01225 0.0268 0 0 0 0 + 2000 1 3 2 0 0 0 200 0.00174 0.00673 0.02683 0.04024 0.03574 0.02719 0.02547 0.02268 0.03591 0.05249 0.06775 0.06047 0.04205 0.02091 0.01677 0.04352 0 0 0 0 + 2001 1 3 2 0 0 0 200 0.0056 0.01683 0.01951 0.01361 0.02585 0.05984 0.07787 0.05792 0.03945 0.03981 0.02909 0.06914 0.056 0.02621 0.01028 0.02048 0 0 0 0 + 2002 1 3 2 0 0 0 200 0.05063 0.07685 0.04852 0.02466 0.02215 0.01761 0.02247 0.05199 0.0399 0.02964 0.0163 0.02059 0.02046 0.02206 0.00712 0.0136 0 0 0 0 + 2003 1 3 2 0 0 0 200 0.01765 0.00633 0.01547 0.03393 0.04499 0.04991 0.02591 0.03122 0.03807 0.05789 0.05706 0.03868 0.02395 0.02881 0.02356 0.03786 0 0 0 0 + 2004 1 3 2 0 0 0 200 0.03521 0.04131 0.02444 0.01455 0.02211 0.03202 0.04847 0.05039 0.03417 0.02504 0.02492 0.02855 0.02271 0.02044 0.01579 0.02838 0 0 0 0 + 2005 1 3 2 0 0 0 200 0.04054 0.0561 0.04573 0.01155 0.00988 0.0336 0.03861 0.05206 0.05668 0.04675 0.03355 0.03825 0.03468 0.02272 0.01648 0.02455 0 0 0 0 + 2006 1 3 2 0 0 0 200 0.0143 0.01389 0.01982 0.04253 0.06161 0.04627 0.02545 0.02591 0.04813 0.06561 0.06191 0.0415 0.03015 0.03523 0.01667 0.01864 0 0 0 0 + 2007 1 3 2 0 0 0 200 0.00152 0.00228 0.00642 0.00783 0.01548 0.03569 0.05746 0.05611 0.03252 0.05702 0.06142 0.06418 0.04593 0.03432 0.02105 0.0323 0 0 0 0 + 2008 1 3 2 0 0 0 200 0 0.00256 0.00517 0.01305 0.01121 0.0161 0.02938 0.05671 0.07231 0.06068 0.06833 0.07969 0.07628 0.04659 0.02644 0.0224 0 0 0 0 + 2009 1 3 2 0 0 0 200 0.00046 0.0019 0.00504 0.00551 0.00817 0.0122 0.02058 0.04661 0.0657 0.08682 0.06453 0.06031 0.05223 0.07044 0.05132 0.04699 0 0 0 0 + 2010 1 3 2 0 0 0 200 0.00184 0.00058 0.00374 0.00481 0.00686 0.01164 0.02132 0.03646 0.05652 0.09273 0.09553 0.07009 0.0509 0.04972 0.05077 0.05456 0 0 0 0 + 2011 1 3 2 0 0 0 200 0.00576 0.00845 0.0092 0.01413 0.02844 0.03101 0.03837 0.04841 0.02992 0.05297 0.06375 0.09059 0.0635 0.05717 0.04306 0.07101 0 0 0 0 + 2012 1 3 2 0 0 0 200 0.02925 0.01803 0.0191 0.02495 0.02805 0.04611 0.03514 0.02198 0.03313 0.03551 0.03653 0.04609 0.06625 0.05206 0.04621 0.06328 0 0 0 0 + 2013 1 3 2 0 0 0 200 0.00081 0.00269 0.00929 0.01117 0.00669 0.01248 0.02018 0.03841 0.04287 0.04496 0.03041 0.03016 0.04553 0.04914 0.04049 0.07861 0 0 0 0 +##Year, Seas, Fleet, Sex, Type, Shell, Maturity, Nsamp, DataVec + 2007 1 4 1 0 0 0 628 0.0045 0.0074 0.0103 0.0155 0.0198 0.0321 0.0532 0.0491 0.0443 0.0354 0.0268 0.0231 0.0236 0.0256 0.0223 0.032 0.0246 0.0218 0.017 0.0278 + 2008 1 4 1 0 0 0 907 0.0017 0.001 0.0093 0.0119 0.0175 0.0279 0.0267 0.0348 0.0428 0.0596 0.0581 0.0455 0.0371 0.0284 0.0218 0.0211 0.0156 0.0157 0.0202 0.0294 + 2007 1 4 2 0 0 0 623 0.0007 0.0016 0.0044 0.0198 0.0302 0.0705 0.0563 0.0345 0.0364 0.0493 0.0501 0.0448 0.0272 0.0183 0.0152 0.0243 0 0 0 0 + 2008 1 4 2 0 0 0 796 0.0004 0.0013 0.0088 0.0142 0.0286 0.0483 0.0754 0.0687 0.0463 0.0386 0.0411 0.0357 0.021 0.0179 0.0126 0.015 0 0 0 0 +## Growth data (increment) +# nobs_growth +80 +# Note these are the values set as fixed in the BBRKC model +# Premolt_size Sex Increment CV +67.5 2 13.8 0.05 +72.5 2 12.2 0.05 +77.5 2 10.5 0.05 +82.5 2 8.4 0.05 +87.5 2 7.5 0.05 +92.5 2 7 0.05 +97.5 2 6.6 0.05 +102.5 2 6.1 0.05 +107.5 2 5.6 0.05 +112.5 2 5.1 0.05 +117.5 2 4.6 0.05 +122.5 2 4.1 0.05 +127.5 2 3.6 0.05 +132.5 2 3.2 0.05 +137.5 2 2.7 0.05 +142.5 2 2.2 0.05 +147.5 2 1.7 0.05 +152.5 2 1.2 0.05 +157.5 2 0.7 0.05 +162.5 2 0.4 0.05 +67.5 2 15.4 0.05 +72.5 2 13.8 0.05 +77.5 2 12.2 0.05 +82.5 2 10.5 0.05 +87.5 2 8.9 0.05 +92.5 2 7.9 0.05 +97.5 2 7.2 0.05 +102.5 2 6.6 0.05 +107.5 2 6.1 0.05 +112.5 2 5.6 0.05 +117.5 2 5.1 0.05 +122.5 2 4.6 0.05 +127.5 2 4.1 0.05 +132.5 2 3.6 0.05 +137.5 2 3.2 0.05 +142.5 2 2.7 0.05 +147.5 2 2.2 0.05 +152.5 2 1.7 0.05 +157.5 2 1.2 0.05 +162.5 2 0.7 0.05 +67.5 2 15.1 0.05 +72.5 2 14 0.05 +77.5 2 12.9 0.05 +82.5 2 11.8 0.05 +87.5 2 10.6 0.05 +92.5 2 8.7 0.05 +97.5 2 7.4 0.05 +102.5 2 6.6 0.05 +107.5 2 6.1 0.05 +112.5 2 5.6 0.05 +117.5 2 5.1 0.05 +122.5 2 4.6 0.05 +127.5 2 4.1 0.05 +132.5 2 3.6 0.05 +137.5 2 3.2 0.05 +142.5 2 2.7 0.05 +147.5 2 2.2 0.05 +152.5 2 1.7 0.05 +157.5 2 1.2 0.05 +162.5 2 0.7 0.05 +67.5 1 16.5 0.05 +72.5 1 16.5 0.05 +77.5 1 16.4 0.05 +82.5 1 16.3 0.05 +87.5 1 16.3 0.05 +92.5 1 16.2 0.05 +97.5 1 16.2 0.05 +102.5 1 16.1 0.05 +107.5 1 16.1 0.05 +112.5 1 16 0.05 +117.5 1 16 0.05 +122.5 1 15.9 0.05 +127.5 1 15.8 0.05 +132.5 1 15.8 0.05 +137.5 1 15.7 0.05 +142.5 1 15.7 0.05 +147.5 1 15.6 0.05 +152.5 1 15.6 0.05 +157.5 1 15.5 0.05 +162.5 1 15.5 0.05 +## eof +9999 + + +# Size bin-width +5 + +# Midpoint of size bins (vector length = nclass) +67.5 72.5 77.5 82.5 87.5 92.5 97.5 102.5 107.5 112.5 117.5 122.5 127.5 132.5 137.5 142.5 147.5 152.5 157.5 162.5 + +# Mean-weight vector (vector length = nclass, males then females) +0.22478 0.28135 0.34692 0.42221 0.50793 0.6048 0.71356 0.83495 0.9697 1.11856 1.28229 1.46163 1.65736 1.87023 2.10101 2.35048 2.61942 2.90861 3.21882 3.90595 +0.2151 0.26898 0.33137 0.40294 0.48437 0.62711 0.7216 0.82452 0.93615 1.05678 1.18669 1.32613 1.47539 1.63473 1.80441 2.18315 2.18315 2.18315 2.18315 2.18315 + + +0 # Number of lines of capture data to read +0 # Number of lines of mark data to read +0 # Number of lines of recapture data to read + + +999 # EOF check. diff --git a/examples/demo/gmacs.dat b/examples/demo/gmacs.dat new file mode 100644 index 00000000..73fd0934 --- /dev/null +++ b/examples/demo/gmacs.dat @@ -0,0 +1,2 @@ +bbrkc.dat +bbrkc.ctl \ No newline at end of file diff --git a/examples/demo/run.bat b/examples/demo/run.bat new file mode 100644 index 00000000..68ef9c23 --- /dev/null +++ b/examples/demo/run.bat @@ -0,0 +1,5 @@ +@echo off +set exec=..\..\src\build\release\gmacs.exe +:: if EXIST %exec% (mklink /D %exec% gmacs.exe ) ELSE echo "file missing, compile source code in gmacs\src directory " +if EXIST %exec% (copy %exec% gmacs.exe ) ELSE echo "file missing, compile source code in gmacs\src directory " +gmacs -nox %1 %2 %3 %4 %5 %6 diff --git a/examples/demo/rundebug.bat b/examples/demo/rundebug.bat new file mode 100644 index 00000000..1c69f0d6 --- /dev/null +++ b/examples/demo/rundebug.bat @@ -0,0 +1,4 @@ +@echo off +set exec=..\..\src\build\debug\gmacs.exe +if EXIST %exec% (copy %exec% ) ELSE echo "file missing, compile source code in gmacs\src directory " +gmacs -nox %1 %2 %3 %4 %5 %6 diff --git a/examples/equilibrium/equilib.cpp b/examples/equilibrium/equilib.cpp new file mode 100644 index 00000000..28ec14a8 --- /dev/null +++ b/examples/equilibrium/equilib.cpp @@ -0,0 +1,124 @@ +#include +/* + + A little program to show how to calculate the initial + equilbriubrium population. For fun fish are allowed to shrink a bit. + the recruitment is normalized to 1 fish spread out over the first 5 + length intervals + + Change n to a number larger than 10 to increase the number of intervals. + +*/ + +#undef COUT +#define COUT(object) cout << #object "\n" << setw(6) \ +<< setprecision(3) << setfixed() << object << endl; + + +int main(int charc, char * argv[]) +{ + int n=10; + double m = 0.3; + + dmatrix At(1,n,1,n); // At is the transpose of the matrix A + // caus' easier to work with. + dmatrix Id=identity_matrix(1,n); + dvector x(1,n); + dvector r(1,n); + dvector p(1,n); // probability of molting. + dvector os(1,n); // oldshell + dvector ns(1,n); // newshell + x.initialize(); + r.initialize(); + p.initialize(); + At.initialize(); + dvector bin(1,n); + bin.fill_seqadd(1,1); + + // recruitment is like a litte normal bump over the first 5 intervals + r(1)=1.0; + r(2)=2.0; + r(3)=3.0; + r(4)=2.0; + r(5)=1.0; + + r/=sum(r); // normalize to a total recruitment of 1 + + // probability of not molting + p = 1.0 / (1.0+exp(-(bin-3.0)/1.85)); + COUT(p); + + for (int i=1;i<=n;i++) + { + for (int j=i;j<=n;j++) // permit a bit of shrinkage + { + if ( j>i && j<=n ) + At(i,j)=(1.0/j); + + if ( j == i) + At(j,j) = p(i); + } + At(i)/=1.00*sum(At(i)); + // At(i)/=sum(At(i)); + } + + // Replace diagonal of size transition matrix with the probability of molting. + // for (int i = 1; i <= n; ++i) + // { + // At(i,i) = p(i); + // } + + COUT(colsum(trans(At))); + + dmatrix A=trans(At); // now transpose to get A + dmatrix G=trans(At); + COUT(A); + + //dvector lx(1,n); + for(int i=1;i<=n;i++) + { + //lx(i) = exp(-m*(i-1.0)); + A(i) *= exp(-m); + //if(i==n) A(i)/=(1.-exp(-m)); + } + + // numerical soln. + int count = 500; + dvector N(1,n); + N.initialize(); + for(int iter = 1; iter <= count; iter++ ) + { + N = A*N + r; + } + + COUT(A); + cout << endl; + + COUT(rowsum(A)); + COUT(colsum(A)); + + COUT(r); + cout << endl; + + + x=-solve(A-Id,r); + + ns = elem_prod(1.-diagonal(G),x); + os = elem_prod(diagonal(G),x); + + cout << endl; + COUT(N); + COUT(x) + COUT(A*x+r); + COUT(os); + COUT(ns); + COUT(sum(os+ns)); + + COUT(sum(N)); + COUT(sum(x)); + cout << endl; + cout << "||A*x+r-x||^2" << endl; + cout << "The next number should equal 0.0 it actually equals " << norm2(A*x+r-x) << endl; + +} + diff --git a/examples/equilibrium/equilib.obj b/examples/equilibrium/equilib.obj new file mode 100644 index 00000000..0587c46d Binary files /dev/null and b/examples/equilibrium/equilib.obj differ diff --git a/examples/equilibrium/equilib.pdf b/examples/equilibrium/equilib.pdf new file mode 100644 index 00000000..4554903a Binary files /dev/null and b/examples/equilibrium/equilib.pdf differ diff --git a/examples/nsrkc/nsrkc.ctl b/examples/nsrkc/nsrkc.ctl new file mode 100644 index 00000000..2b3e441b --- /dev/null +++ b/examples/nsrkc/nsrkc.ctl @@ -0,0 +1,135 @@ +# +# —————————————————————————————————————————————————————————————————————————————————————— # +# Controls for leading parameter vector theta +# LEGEND FOR PRIOR: +# 0 -> uniform +# 1 -> normal +# 2 -> lognormal +# 3 -> beta +# 4 -> gamma +# —————————————————————————————————————————————————————————————————————————————————————— # +# ntheta +7 +# —————————————————————————————————————————————————————————————————————————————————————— # +# ival lb ub phz prior p1 p2 # parameter # +# —————————————————————————————————————————————————————————————————————————————————————— # + 0.18 0.01 1 5 2 0.18 0.04 # M + 7.0 -10 20 -1 1 3.0 5.0 # logR0 + 7.0 -10 20 2 1 3.0 5.0 # logR1 + 7.0 -10 20 2 1 3.0 5.0 # logRbar + 72.5 65 150 4 1 72.5 7.25 # Recruitment mBeta + 1.50 0.1 5 4 0 0.1 5 # Recruitment m50 + -0.51 -10 0.75 -4 0 -10 0.75 # ln(sigma_R) +## ———————————————————————————————————————————————————————————————————————————————————— ## + +## ———————————————————————————————————————————————————————————————————————————————————— ## +## GROWTH PARAM CONTROLS ## +# nGrwth +## ## +## Two lines for each parameter if split sex, one line if not ## +## ———————————————————————————————————————————————————————————————————————————————————— ## +# ival lb ub phz prior p1 p2 # parameter # +# —————————————————————————————————————————————————————————————————————————————————————— # + 17.5 10.0 30.0 3 0 0.0 20.0 # alpha males or combined + 0.10 0.0 0.5 3 0 0.0 10.0 # beta males or combined + 6.0 1.0 30.0 3 0 0.0 3.0 # gscale males or combined + 115. 65.0 165.0 2 0 0.0 3.0 # molt_mu males or combined + 0.2 0.0 1.0 3 0 0.0 3.0 # molt_cv males or combined +# ———————————————————————————————————————————————————————————————————————————————————— ## +## ———————————————————————————————————————————————————————————————————————————————————— ## +## SELECTIVITY CONTROLS ## +## -Each gear must have a selectivity and a retention selectivity ## +## LEGEND sel_type:1=coefficients 2=logistic 3=logistic95 ## +## Index: use #NAME? for selectivity #NAME? for retention +## ———————————————————————————————————————————————————————————————————————————————————— ## +## ivector for number of year blocks or nodes ## +## Gear-1 Gear-2 Gear-3 ... + 1 1 1 1 1 1 #Selectivity blocks + 1 0 0 0 0 0 #Retention blocks + 1 0 0 0 0 0 #male retention flag (0 -> no, 1 -> yes) +## ———————————————————————————————————————————————————————————————————————————————————— ## +## sel sel sel sex size year phz start end ## +## Index type mu sd dep nodes nodes mirror lam1 lam2 lam3 | block block ## +## ———————————————————————————————————————————————————————————————————————————————————— ## +## Selectivity P(capture of all sizes) + 1 2 180 10 0 1 1 2 12.5 12.5 12.5 1976 2014 + 2 2 90 10 0 1 1 2 12.5 12.5 12.5 1976 2014 + 3 2 90 10 0 1 1 2 12.5 12.5 12.5 1976 2014 + 4 2 90 10 0 1 1 2 12.5 12.5 12.5 1976 2014 + 5 2 90 10 0 1 1 2 12.5 12.5 12.5 1976 2014 + 6 2 90 10 0 1 1 2 12.5 12.5 12.5 1976 2014 +## +## +## Retained +## + -1 2 180 10 0 1 1 2 12.5 12.5 12.5 1976 2014 + -2 2 90 10 0 1 1 2 12.5 12.5 12.5 1976 2014 + -3 2 90 10 0 1 1 2 12.5 12.5 12.5 1976 2014 + -4 2 90 10 0 1 1 2 12.5 12.5 12.5 1976 2014 + -5 2 90 10 0 1 1 2 12.5 12.5 12.5 1976 2014 + -6 2 90 10 0 1 1 2 12.5 12.5 12.5 1976 2014 +## +## ———————————————————————————————————————————————————————————————————————————————————— ## +## PRIORS FOR CATCHABILITY +## TYPE: 0 = UNINFORMATIVE, 1 - NORMAL (log-space), 2 = time-varying (nyi) +## ———————————————————————————————————————————————————————————————————————————————————— ## +## SURVEYS/INDICES ONLY +## NMFS_Trawl:ADFG:STCPUE +## TYPE Mean_q SD_q + 1 0.896 0.23 + 1 0.896 10.23 +## ———————————————————————————————————————————————————————————————————————————————————— ## + +## ———————————————————————————————————————————————————————————————————————————————————— ## +## PENALTIES FOR AVERAGE FISHING MORTALITY RATE FOR EACH GEAR +## ———————————————————————————————————————————————————————————————————————————————————— ## +## Trap Trawl NMFS BSFRF +## Mean_F STD_PHZ1 STD_PHZ2 PHZ + 0.2 0.1 1.1 1 + 0.1 0.1 1.1 1 + 0.01 2 2 1 + 0.01 2 2 1 + 0.01 2 2 -1 + 0.01 2 2 -1 +## ———————————————————————————————————————————————————————————————————————————————————— ## +## OPTIONS FOR SIZE COMPOSTION DATA (COLUMN FOR EACH MATRIX) +## LIKELIHOOD OPTIONS: +## -1) multinomial with estimated/fixed sample size +## -2) logistic normal +## -3) multivariate-t +## AUTOTAIL COMPRESSION: +## - pmin is the cumulative proportion used in tail compression. +## ———————————————————————————————————————————————————————————————————————————————————— ## + 1 1 1 1 # 1 1 #1 1 1 # Type of likelihood. + 0 0 0 0 # 0 0 #0 0 0 # Auto tail compression (pmin) + 4 4 4 4 # 4 4 #4 4 4 # Phz for estimating effective sample size (if appl.) +## ———————————————————————————————————————————————————————————————————————————————————— ## +## TIME VARYING NATURAL MORTALIIY RATES ## +## ———————————————————————————————————————————————————————————————————————————————————— ## +## TYPE: +## 0 = constant natural mortality +## 1 = Random walk (deviates constrained by variance in M) +## 2 = Cubic Spline (deviates constrined by nodes & node-placement) + 0 +## Phase of estimation +-3 +## STDEV in m_dev for Random walk + 0.01 +## Number of nodes for cubic spline + 6 +## Year position of the knots (vector must be equal to the number of nodes) + 1976 1982 1985 1991 2002 2014 +## ———————————————————————————————————————————————————————————————————————————————————— ## +## OTHER CONTROLS +## ———————————————————————————————————————————————————————————————————————————————————— ## + 3 # Estimated rec_dev phase + 0 # VERBOSE FLAG (0 = off 1 = on 2 = objective func) + 0 # INITIALIZE MODEL AT UNFISHED RECRUITS (0=FALSE 1=TRUE) + 1984 # First year for average recruitment for Bspr calculation. + 2013 # Last year for average recruitment for Bspr calculation. + 0.35 # Target SPR ratio for Bmsy proxy. + 1 # Gear index for SPR calculations (i.e. directed fishery). + 1 # Lambda (proportion of mature male biomass for SPR reference points.) + 1 # Lambda (proportion of mature male biomass for SPR reference points.) +## EOF +9999 diff --git a/examples/nsrkc/nsrkc.dat b/examples/nsrkc/nsrkc.dat new file mode 100644 index 00000000..6a1e661b --- /dev/null +++ b/examples/nsrkc/nsrkc.dat @@ -0,0 +1,475 @@ +#======================================================================================================== +# Gmacs Main Data File Version 1.1: BBRKC Example +# Fisheries: 1 Pot Fishery, 2 Pot Discard, 3 Trawl by-catch +# Surveys: 1 NMFS Trawl Survey, 2 BSFRF Survey +#======================================================================================================== +1976 # Start year +2014 # End year +1 # Time-step (years) +6 # Number of distinct data groups (among fishing fleets and surveys) +1 # Number of sexes +2 # Number of shell condition types +1 # Number of maturity types +6 # Number of size-classes in the model +# size_breaks (a vector giving the break points between size intervals, dim=nclass+1) +74 84 94 104 114 124 134 +# weight-at-length allometry w_l = a•l^b +## a (male, female) +1.24E-04 +## b (male, female) +2.89 +# Male mature weight-at-length (weight * proportion mature) +0 0 1.652 2.187 2.825 3.697 +# Proportion mature by sex. +0 0 1 1 1 1 +# Fishing fleet names (delimited with : no spaces in names) +Summer:Winter_COM:Winter_Sub:Winter_Discard +# Survey names (delimited with : no spaces in names) +# NMFS_Trawl:ADFG:STCPUE +NMFS_Trawl:ADFG +4 # Number of catch data frames +# Number of rows in each data frame. +37 37 37 31 +## ———————————————————————————————————————————————————————————————————————————————————— ## +## CATCH DATA +## Type of catch: 1 = retained, 2 = discard, 3 = +## Units of catch: 1 = biomass, 2 = numbers +## for NSRKC Units are in 1000 crabs +## ———————————————————————————————————————————————————————————————————————————————————— ## +## year seas fleet sex obs cv type units mult effort discard_mortality +## Male Retained + 1977 1 1 1 195.877 0.05 1 2 1 5457 0 + 1978 1 1 1 660.829 0.05 1 2 1 10817 0 + 1979 1 1 1 970.962 0.05 1 2 1 34773 0 + 1980 1 1 1 329.778 0.05 1 2 1 11199 0 + 1981 1 1 1 376.313 0.05 1 2 1 33745 0 + 1982 1 1 1 63.949 0.05 1 2 1 11230 0 + 1983 1 1 1 132.205 0.05 1 2 1 11195 0 + 1984 1 1 1 139.759 0.05 1 2 1 9706 0 + 1985 1 1 1 146.669 0.05 1 2 1 13209 0 + 1986 1 1 1 162.438 0.05 1 2 1 4284 0 + 1987 1 1 1 103.338 0.05 1 2 1 10258 0 + 1988 1 1 1 76.148 0.05 1 2 1 2350 0 + 1989 1 1 1 79.116 0.05 1 2 1 5149 0 + 1990 1 1 1 59.132 0.05 1 2 1 3172 0 + 1992 1 1 1 24.902 0.05 1 2 1 5746 0 + 1993 1 1 1 115.913 0.05 1 2 1 7063 0 + 1994 1 1 1 108.824 0.05 1 2 1 11729 0 + 1995 1 1 1 105.967 0.05 1 2 1 18782 0 + 1996 1 1 1 74.752 0.05 1 2 1 10453 0 + 1997 1 1 1 32.606 0.05 1 2 1 2982 0 + 1998 1 1 1 10.661 0.05 1 2 1 1639 0 + 1999 1 1 1 8.734 0.05 1 2 1 1630 0 + 2000 1 1 1 111.728 0.05 1 2 1 6345 0 + 2001 1 1 1 98.321 0.05 1 2 1 11928 0 + 2002 1 1 1 86.666 0.05 1 2 1 6491 0 + 2003 1 1 1 93.638 0.05 1 2 1 8494 0 + 2004 1 1 1 120.289 0.05 1 2 1 8066 0 + 2005 1 1 1 138.926 0.05 1 2 1 8867 0 + 2006 1 1 1 150.358 0.05 1 2 1 8695 0 + 2007 1 1 1 110.344 0.05 1 2 1 9118 0 + 2008 1 1 1 143.337 0.05 1 2 1 8721 0 + 2009 1 1 1 143.485 0.05 1 2 1 11934 0 + 2010 1 1 1 149.822 0.05 1 2 1 9698 0 + 2011 1 1 1 141.626 0.05 1 2 1 6808 0 + 2012 1 1 1 161.113 0.05 1 2 1 10041 0 + 2013 1 1 1 130.603 0.05 1 2 1 15058 0 + 2014 1 1 1 129.656 0.05 1 2 1 10127 0 +## Winter Commercial + 1978 1 2 1 9.625 0.05 1 2 1 0 0 + 1979 1 2 1 0.221 0.05 1 2 1 0 0 + 1980 1 2 1 0.022 0.05 1 2 1 0 0 + 1981 1 2 1 0 0.05 1 2 1 0 0 + 1982 1 2 1 0.017 0.05 1 2 1 0 0 + 1983 1 2 1 0.549 0.05 1 2 1 0 0 + 1984 1 2 1 0.856 0.05 1 2 1 0 0 + 1985 1 2 1 1.168 0.05 1 2 1 0 0 + 1986 1 2 1 2.168 0.05 1 2 1 0 0 + 1987 1 2 1 1.04 0.05 1 2 1 0 0 + 1988 1 2 1 0.425 0.05 1 2 1 0 0 + 1989 1 2 1 0.403 0.05 1 2 1 0 0 + 1990 1 2 1 3.626 0.05 1 2 1 0 0 + 1991 1 2 1 3.8 0.05 1 2 1 0 0 + 1992 1 2 1 7.478 0.05 1 2 1 0 0 + 1993 1 2 1 1.788 0.05 1 2 1 0 0 + 1994 1 2 1 5.753 0.05 1 2 1 0 0 + 1995 1 2 1 7.538 0.05 1 2 1 0 0 + 1996 1 2 1 1.778 0.05 1 2 1 0 0 + 1997 1 2 1 0.083 0.05 1 2 1 0 0 + 1998 1 2 1 0.984 0.05 1 2 1 0 0 + 1999 1 2 1 2.714 0.05 1 2 1 0 0 + 2000 1 2 1 3.045 0.05 1 2 1 0 0 + 2001 1 2 1 1.098 0.05 1 2 1 0 0 + 2002 1 2 1 2.591 0.05 1 2 1 0 0 + 2003 1 2 1 6.853 0.05 1 2 1 0 0 + 2004 1 2 1 0.522 0.05 1 2 1 0 0 + 2005 1 2 1 2.121 0.05 1 2 1 0 0 + 2006 1 2 1 0.075 0.05 1 2 1 0 0 + 2007 1 2 1 3.313 0.05 1 2 1 0 0 + 2008 1 2 1 5.796 0.05 1 2 1 0 0 + 2009 1 2 1 4.951 0.05 1 2 1 0 0 + 2010 1 2 1 4.834 0.05 1 2 1 0 0 + 2011 1 2 1 3.365 0.05 1 2 1 0 0 + 2012 1 2 1 9.157 0.05 1 2 1 0 0 + 2013 1 2 1 22.639 0.05 1 2 1 0 0 + 2014 1 2 1 14.986 0.05 1 2 1 0 0 +## Winter Subsistence retained + 1978 1 3 1 12.506 0.05 1 2 1 0 0 + 1979 1 3 1 0.224 0.05 1 2 1 0 0 + 1980 1 3 1 0.213 0.05 1 2 1 0 0 + 1981 1 3 1 0.36 0.05 1 2 1 0 0 + 1982 1 3 1 1.288 0.05 1 2 1 0 0 + 1983 1 3 1 10.432 0.05 1 2 1 0 0 + 1984 1 3 1 11.22 0.05 1 2 1 0 0 + 1985 1 3 1 8.377 0.05 1 2 1 0 0 + 1986 1 3 1 7.052 0.05 1 2 1 0 0 + 1987 1 3 1 5.772 0.05 1 2 1 0 0 + 1988 1 3 1 2.724 0.05 1 2 1 0 0 + 1989 1 3 1 6.126 0.05 1 2 1 0 0 + 1990 1 3 1 12.152 0.05 1 2 1 0 0 + 1991 1 3 1 7.366 0.05 1 2 1 0 0 + 1992 1 3 1 11.736 0.05 1 2 1 0 0 + 1993 1 3 1 1.097 0.05 1 2 1 0 0 + 1994 1 3 1 4.113 0.05 1 2 1 0 0 + 1995 1 3 1 5.426 0.05 1 2 1 0 0 + 1996 1 3 1 1.679 0.05 1 2 1 0 0 + 1997 1 3 1 0.745 0.05 1 2 1 0 0 + 1998 1 3 1 8.622 0.05 1 2 1 0 0 + 1999 1 3 1 7.533 0.05 1 2 1 0 0 + 2000 1 3 1 5.723 0.05 1 2 1 0 0 + 2001 1 3 1 0.256 0.05 1 2 1 0 0 + 2002 1 3 1 2.177 0.05 1 2 1 0 0 + 2003 1 3 1 4.14 0.05 1 2 1 0 0 + 2004 1 3 1 1.181 0.05 1 2 1 0 0 + 2005 1 3 1 3.973 0.05 1 2 1 0 0 + 2006 1 3 1 1.239 0.05 1 2 1 0 0 + 2007 1 3 1 10.69 0.05 1 2 1 0 0 + 2008 1 3 1 9.485 0.05 1 2 1 0 0 + 2009 1 3 1 4.752 0.05 1 2 1 0 0 + 2010 1 3 1 7.044 0.05 1 2 1 0 0 + 2011 1 3 1 6.64 0.05 1 2 1 0 0 + 2012 1 3 1 7.311 0.05 1 2 1 0 0 + 2013 1 3 1 7.622 0.05 1 2 1 0 0 + 2014 1 3 1 3.252 0.05 1 2 1 0 0 +## Winter Subsistence discards + 1984 2 4 1 4.703 0.05 1 2 1 0 0.2 + 1985 2 4 1 2.38 0.05 1 2 1 0 0.2 + 1986 2 4 1 3.699 0.05 1 2 1 0 0.2 + 1987 2 4 1 1.634 0.05 1 2 1 0 0.2 + 1988 2 4 1 0.849 0.05 1 2 1 0 0.2 + 1989 2 4 1 1.819 0.05 1 2 1 0 0.2 + 1990 2 4 1 4.483 0.05 1 2 1 0 0.2 + 1991 2 4 1 1.929 0.05 1 2 1 0 0.2 + 1992 2 4 1 3.315 0.05 1 2 1 0 0.2 + 1993 2 4 1 0.096 0.05 1 2 1 0 0.2 + 1994 2 4 1 0.781 0.05 1 2 1 0 0.2 + 1995 2 4 1 2.351 0.05 1 2 1 0 0.2 + 1996 2 4 1 1.257 0.05 1 2 1 0 0.2 + 1997 2 4 1 0.872 0.05 1 2 1 0 0.2 + 1998 2 4 1 11.705 0.05 1 2 1 0 0.2 + 1999 2 4 1 3.118 0.05 1 2 1 0 0.2 + 2000 2 4 1 4.093 0.05 1 2 1 0 0.2 + 2001 2 4 1 0.11 0.05 1 2 1 0 0.2 + 2002 2 4 1 2.942 0.05 1 2 1 0 0.2 + 2003 2 4 1 4.912 0.05 1 2 1 0 0.2 + 2004 2 4 1 0.594 0.05 1 2 1 0 0.2 + 2005 2 4 1 2.511 0.05 1 2 1 0 0.2 + 2006 2 4 1 0.844 0.05 1 2 1 0 0.2 + 2007 2 4 1 10.754 0.05 1 2 1 0 0.2 + 2008 2 4 1 9.136 0.05 1 2 1 0 0.2 + 2009 2 4 1 2.219 0.05 1 2 1 0 0.2 + 2010 2 4 1 1.96 0.05 1 2 1 0 0.2 + 2011 2 4 1 2.543 0.05 1 2 1 0 0.2 + 2012 2 4 1 4.03 0.05 1 2 1 0 0.2 + 2013 2 4 1 13.902 0.05 1 2 1 0 0.2 + 2014 2 4 1 2.169 0.05 1 2 1 0 0.2 +## ———————————————————————————————————————————————————————————————————————————————————— ## +## RELATIVE ABUNDANCE DATA +## Units of Abundance: 1 = biomass, 2 = numbers +## for BBRKC Units are in million crabs for Abundance. +## ———————————————————————————————————————————————————————————————————————————————————— ## +## Number of relative abundance indicies +2 +## Number of rows in each index +14 37 +# Survey data (abundance indices, units are 1000 of crabs) +# Year Seas Fleet Sex Abundance CV units + 1976 1 5 1 4247.462 0.311 2 + 1979 1 5 1 1417.215 0.204 2 + 1982 1 5 1 2791.733 0.289 2 + 1985 1 5 1 2306.321 0.254 2 + 1988 1 5 1 2263.353 0.288 2 + 1991 1 5 1 3132.508 0.428 2 + 2010 1 5 1 2041.02 0.455 2 + 1996 1 5 1 1264.691 0.317 2 + 1999 1 5 1 2276.095 0.194 2 + 2002 1 5 1 1747.581 0.125 2 + 2006 1 5 1 2549.726 0.288 2 + 2008 1 5 1 2707.083 0.164 2 + 2011 1 5 1 2701.708 0.133 2 + 2014 1 5 1 5481.5 0.486 2 +# Catch CPUE data (abundance indices, units are catch CPUE crabs) +# Year Seas Fleet Sex Abundance CV units + 1977 1 6 1 3.437762237 0.34197571 2 + 1978 1 6 1 2.822551719 0.225481204 2 + 1979 1 6 1 2.595617932 0.173994077 2 + 1980 1 6 1 2.434575754 0.249767972 2 + 1981 1 6 1 0.744464703 0.170823698 2 + 1982 1 6 1 0.131656914 0.250528818 2 + 1983 1 6 1 0.902523322 0.215670389 2 + 1984 1 6 1 1.08782846 0.228990399 2 + 1985 1 6 1 0.366410635 0.210401513 2 + 1986 1 6 1 0.996600918 0.426212113 2 + 1987 1 6 1 0.631410987 0.322875239 2 + 1988 1 6 1 1.511219841 0.704880904 2 + 1989 1 6 1 1.611476557 0.332485206 2 + 1990 1 6 1 1.182279915 0.415432361 2 + 1992 1 6 1 0.25529254 0.314335609 2 + 1993 1 6 1 0.906423386 0.079866709 2 + 1994 1 6 1 0.810282647 0.049349507 2 + 1995 1 6 1 0.482184482 0.044931912 2 + 1996 1 6 1 0.447705464 0.057769037 2 + 1997 1 6 1 0.861633103 0.084132537 2 + 1998 1 6 1 0.746831692 0.120462202 2 + 1999 1 6 1 0.779001577 0.115230595 2 + 2000 1 6 1 1.279663493 0.060869919 2 + 2001 1 6 1 0.713441815 0.045087684 2 + 2002 1 6 1 1.231829138 0.057274111 2 + 2003 1 6 1 0.906911328 0.048849717 2 + 2004 1 6 1 1.396939227 0.050112896 2 + 2005 1 6 1 1.321496477 0.047858937 2 + 2006 1 6 1 1.460213643 0.04742779 2 + 2007 1 6 1 1.153505118 0.048796872 2 + 2008 1 6 1 1.50293962 0.049353333 2 + 2009 1 6 1 0.935329967 0.043093615 2 + 2010 1 6 1 1.349240406 0.045271873 2 + 2011 1 6 1 1.660502064 0.053410468 2 + 2012 1 6 1 1.415665457 0.044196782 2 + 2013 1 6 1 0.723348001 0.039107405 2 + 2014 1 6 1 1.230130348 0.046386349 2 +## Number of length frequency matrixes +4 +## Number of rows in each matrix +37 14 27 9 +## Number of bins in each matrix (columns of size data) +6 6 6 6 +## SIZE COMPOSITION DATA FOR ALL FLEETS +## ———————————————————————————————————————————————————————————————————————————————————— ## +## SIZE COMP LEGEND +## Sex: 1 = male, 2 = female, 0 = both sexes combined +## Type of composition: 1 = retained, 2 = discard, 0 = selectivity +## Maturity state: 1 = immature, 2 = mature, 0 = both states combined +## Shell condition: 1 = new shell, 2 = old shell, 0 = both shell types combined +## ———————————————————————————————————————————————————————————————————————————————————— ## +##length proportions of Summer Commercial Catches males +## Year Seas Fleet Sex Type Shell Maturity Nsamp DataVec + 1977 1 1 1 1 0 0 100 0 0 0.0032 0.4196 0.3422 0.122 + 1977 1 1 1 1 0 0 100 0 0 0 0.0626 0.04 0.0103 + 1978 1 1 1 1 0 0 100 0 0 0.0103 0.1851 0.473 0.3059 + 1978 1 1 1 1 0 0 100 0 0 0 0.0051 0.0103 0.0103 + 1979 1 1 1 1 0 0 100 0 0 0.0253 0.2325 0.3831 0.3217 + 1979 1 1 1 1 0 0 100 0 0 0 0.0253 0.0006 0.0114 + 1980 1 1 1 1 0 0 100 0 0 0.0037 0.0983 0.3062 0.5543 + 1980 1 1 1 1 0 0 100 0 0 0 0.0028 0.0112 0.0234 + 1981 1 1 1 1 0 0 100 0 0 0.0039 0.0734 0.1541 0.509 + 1981 1 1 1 1 0 0 100 0 0 0 0.0045 0.0504 0.2046 + 1982 1 1 1 1 0 0 100 0 0 0.0421 0.1921 0.1647 0.505 + 1982 1 1 1 1 0 0 100 0 0 0.0037 0.0128 0.022 0.0576 + 1983 1 1 1 1 0 0 100 0 0 0.0387 0.4127 0.3579 0.0973 + 1983 1 1 1 1 0 0 100 0 0 0.0037 0.0362 0.01 0.0436 + 1984 1 1 1 1 0 0 100 0 0 0.0966 0.4195 0.2804 0.0717 + 1984 1 1 1 1 0 0 100 0 0 0.0104 0.0654 0.0488 0.0073 + 1985 1 1 1 1 0 0 100 0 0.0004 0.0643 0.3122 0.3716 0.1747 + 1985 1 1 1 1 0 0 100 0 0 0.0026 0.0334 0.0312 0.0097 + 1986 1 1 1 1 0 0 100 0 0 0.029 0.3559 0.3937 0.1353 + 1986 1 1 1 1 0 0 100 0 0 0.0018 0.0202 0.0378 0.0264 + 1987 1 1 1 1 0 0 100 0 0 0.0166 0.1788 0.2912 0.3798 + 1987 1 1 1 1 0 0 100 0 0 0.0025 0.0267 0.065 0.0393 + 1988 1 1 1 1 0 0 100 0.0007 0 0.0237 0.2004 0.3003 0.2181 + 1988 1 1 1 1 0 0 100 0.0007 0 0.0059 0.0644 0.0972 0.0894 + 1989 1 1 1 1 0 0 100 0 0 0.0127 0.1643 0.3185 0.2148 + 1989 1 1 1 1 0 0 100 0 0 0.0042 0.0555 0.1215 0.1084 + 1990 1 1 1 1 0 0 100 0 0 0.0147 0.1435 0.3468 0.3251 + 1990 1 1 1 1 0 0 100 0 0 0.0008 0.0372 0.0737 0.0582 + 1992 1 1 1 1 0 0 100 0 0 0.0172 0.201 0.2662 0.2244 + 1992 1 1 1 1 0 0 100 0 0 0.0027 0.0792 0.1292 0.08 + 1993 1 1 1 1 0 0 100 0 0 0.0142 0.2312 0.3939 0.263 + 1993 1 1 1 1 0 0 100 0 0 0.0004 0.0173 0.0437 0.0362 + 1994 1 1 1 1 0 0 100 0 0 0.0248 0.0941 0.0817 0.0891 + 1994 1 1 1 1 0 0 100 0 0 0.0248 0.1881 0.25 0.2475 + 1995 1 1 1 1 0 0 100 0 0 0.0392 0.2615 0.2853 0.207 + 1995 1 1 1 1 0 0 100 0 0 0.0077 0.0486 0.0741 0.0767 + 1996 1 1 1 1 0 0 100 0 0 0.0318 0.2236 0.2389 0.141 + 1996 1 1 1 1 0 0 100 0 0 0.014 0.1194 0.136 0.0953 + 1997 1 1 1 1 0 0 100 0 0 0.0292 0.3656 0.3414 0.1244 + 1997 1 1 1 1 0 0 100 0 0 0.0033 0.0559 0.0417 0.0384 + 1998 1 1 1 1 0 0 100 0 0 0.0284 0.2332 0.2427 0.1071 + 1998 1 1 1 1 0 0 100 0 0 0.0218 0.1118 0.1431 0.1118 + 1999 1 1 1 1 0 0 100 0 0 0.0026 0.2434 0.2698 0.3836 + 1999 1 1 1 1 0 0 100 0 0 0 0 0.0423 0.0582 + 2000 1 1 1 1 0 0 100 0 0 0.0194 0.2991 0.3917 0.1249 + 2000 1 1 1 1 0 0 100 0 0 0.0028 0.0531 0.0654 0.0436 + 2001 1 1 1 1 0 0 100 0 0 0.0243 0.2232 0.3691 0.2781 + 2001 1 1 1 1 0 0 100 0 0 0.0008 0.0241 0.0497 0.0304 + 2002 1 1 1 1 0 0 100 0 0 0.0442 0.2341 0.2814 0.3253 + 2002 1 1 1 1 0 0 100 0 0 0.0046 0.0282 0.0419 0.0402 + 2003 1 1 1 1 0 0 100 0 0 0.0232 0.368 0.3197 0.1523 + 2003 1 1 1 1 0 0 100 0 0 0.0011 0.0218 0.0465 0.0674 + 2004 1 1 1 1 0 0 100 0 0 0.0087 0.3811 0.388 0.1395 + 2004 1 1 1 1 0 0 100 0 0 0.0004 0.0255 0.0347 0.0221 + 2005 1 1 1 1 0 0 100 0 0 0.0022 0.2539 0.4709 0.1823 + 2005 1 1 1 1 0 0 100 0 0 0 0.0205 0.0451 0.025 + 2006 1 1 1 1 0 0 100 0 0 0.0021 0.1822 0.3484 0.199 + 2006 1 1 1 1 0 0 100 0 0 0.0003 0.0498 0.1375 0.0807 + 2007 1 1 1 1 0 0 100 0 0 0.0111 0.3574 0.3407 0.1714 + 2007 1 1 1 1 0 0 100 0 0 0.0008 0.0247 0.0573 0.0366 + 2008 1 1 1 1 0 0 100 0 0 0.0047 0.3512 0.3476 0.0668 + 2008 1 1 1 1 0 0 100 0 0 0.0014 0.0895 0.0928 0.0461 + 2009 1 1 1 1 0 0 100 0 0 0.0105 0.3445 0.3294 0.1339 + 2009 1 1 1 1 0 0 100 0 0 0.0012 0.0768 0.0795 0.0242 + 2010 1 1 1 1 0 0 100 0 0 0.0053 0.3855 0.3617 0.1095 + 2010 1 1 1 1 0 0 100 0 0 0.0019 0.0546 0.0546 0.0271 + 2011 1 1 1 1 0 0 100 0 0 0.0043 0.317 0.3969 0.1387 + 2011 1 1 1 1 0 0 100 0 0 0.002 0.0611 0.0588 0.0212 + 2012 1 1 1 1 0 0 100 0 0 0.0026 0.2421 0.462 0.2067 + 2012 1 1 1 1 0 0 100 0 0 0.0002 0.0259 0.0423 0.0182 + 2013 1 1 1 1 0 0 100 0 0 0.0044 0.2388 0.371 0.302 + 2013 1 1 1 1 0 0 100 0 0 0.0003 0.014 0.0422 0.0272 + 2014 1 1 1 1 0 0 100 0 0 0.0085 0.2828 0.236 0.2565 + 2014 1 1 1 1 0 0 100 0 0 0.0002 0.0412 0.0865 0.0882 +##length proportions of Trawl Survey Male +## Year Seas Fleet Sex Type Shell Maturity + 1976 1 5 1 1 0 0 100 0.0214 0.1053 0.1915 0.3455 0.1831 0.029 + 1976 1 5 1 1 0 0 100 0.0214 0.0114 0.0252 0.032 0.0366 0.0145 + 1979 1 5 1 1 0 0 100 0.0151 0.0075 0.0301 0.0752 0.0827 0.0602 + 1979 1 5 1 1 0 0 100 0.0151 0.0075 0.0301 0.1203 0.3835 0.188 + 1982 1 5 1 1 0 0 100 0.0898 0.2031 0.2891 0.2109 0.0352 0.0078 + 1982 1 5 1 1 0 0 100 0.0898 0.0156 0.0195 0.043 0.0234 0.0625 + 1985 1 5 1 1 0 0 100 0.119 0.2122 0.1865 0.1768 0.0643 0.0193 + 1985 1 5 1 1 0 0 100 0.119 0 0.0193 0.0514 0.0868 0.0643 + 1988 1 5 1 1 0 0 100 0.2255 0.1405 0.1536 0.1275 0.0686 0.0392 + 1988 1 5 1 1 0 0 100 0.2255 0.0065 0.0131 0.0392 0.0882 0.098 + 1991 1 5 1 1 0 0 100 0.0967 0.0223 0.0372 0.0743 0.0409 0.0223 + 1991 1 5 1 1 0 0 100 0.0967 0.0297 0.0967 0.197 0.1747 0.1375 + 2010 1 5 1 1 0 0 100 0.2959 0.1786 0.1224 0.0816 0.0051 0.0153 + 2010 1 5 1 1 0 0 100 0.2959 0.0357 0.0459 0.0612 0.0612 0.0918 + 1996 1 5 1 1 0 0 100 0.0109 0.1058 0.2993 0.2701 0.1314 0.0401 + 1996 1 5 1 1 0 0 100 0.0109 0.0036 0.0292 0.0511 0.0401 0.0182 + 1999 1 5 1 1 0 0 100 0.1261 0.1435 0.1565 0.0304 0.0348 0.0348 + 1999 1 5 1 1 0 0 100 0.1261 0.0739 0.1087 0.0957 0.0913 0.0739 + 2002 1 5 1 1 0 0 100 0.3235 0.2614 0.1405 0.0752 0.0458 0.0294 + 2002 1 5 1 1 0 0 100 0.3235 0 0.0196 0.0458 0.0458 0.0131 + 2006 1 5 1 1 0 0 100 0.1743 0.2407 0.1286 0.112 0.0332 0.029 + 2006 1 5 1 1 0 0 100 0.1743 0.0498 0.0705 0.0954 0.0125 0.0456 + 2008 1 5 1 1 0 0 100 0.1202 0.1366 0.2077 0.1257 0.1093 0.0437 + 2008 1 5 1 1 0 0 100 0.1202 0.0328 0.082 0.071 0.0383 0.0219 + 2011 1 5 1 1 0 0 100 0.1282 0.0989 0.1282 0.2051 0.1612 0.0476 + 2011 1 5 1 1 0 0 100 0.1282 0.0147 0.0256 0.0989 0.0513 0.0366 + 2014 1 5 1 1 0 0 100 0.1607 0.2576 0.1939 0.0997 0.0166 0.0233 + 2014 1 5 1 1 0 0 100 0.1607 0.0277 0.1053 0.0554 0.0471 0.0139 +##length proportions of Winter Pot Survey +## Year Seas Fleet Sex Type Shell Maturity Nsamp DataVec + 1982 1 6 1 1 0 0 100 0.1481 0.3374 0.3169 0.1029 0.0288 0.0247 + 1982 1 6 1 1 0 0 100 0.1481 0 0.0041 0.0082 0.0082 0.0206 + 1983 1 6 1 1 0 0 100 0.0855 0.2824 0.2854 0.2155 0.0706 0.0085 + 1983 1 6 1 1 0 0 100 0.0855 0 0.004 0.0194 0.0097 0.0189 + 1984 1 6 1 1 0 0 100 0.1638 0.2626 0.2291 0.1502 0.0601 0.0057 + 1984 1 6 1 1 0 0 100 0.1638 0 0.0178 0.065 0.0329 0.0127 + 1985 1 6 1 1 0 0 100 0.0932 0.2589 0.3618 0.1586 0.057 0.0097 + 1985 1 6 1 1 0 0 100 0.0932 0 0.0065 0.0291 0.0239 0.0013 + 1986 1 6 1 1 0 0 100 0.1276 0.1831 0.2553 0.2025 0.0863 0.0132 + 1986 1 6 1 1 0 0 100 0.1276 0 0.015 0.0607 0.044 0.0123 + 1987 1 6 1 1 0 0 100 0.0556 0.1597 0.1944 0.0694 0.0417 0 + 1987 1 6 1 1 0 0 100 0.0556 0 0.0417 0.2986 0.1111 0.0278 + 1989 1 6 1 1 0 0 100 0.1341 0.1514 0.1352 0.1941 0.1758 0.0346 + 1989 1 6 1 1 0 0 100 0.1341 0 0.002 0.0528 0.0854 0.0346 + 1990 1 6 1 1 0 0 100 0.0495 0.2075 0.2616 0.1795 0.1221 0.0726 + 1990 1 6 1 1 0 0 100 0.0495 0 0.001 0.0263 0.056 0.0239 + 1991 1 6 1 1 0 0 100 0.0125 0.0921 0.2857 0.2678 0.096 0.0109 + 1991 1 6 1 1 0 0 100 0.0125 0 0.0039 0.0265 0.1163 0.0882 + 1993 1 6 1 1 0 0 100 0.0055 0.0331 0.0552 0.1271 0.116 0.0276 + 1993 1 6 1 1 0 0 100 0.0055 0 0.0166 0.1934 0.2707 0.1547 + 1995 1 6 1 1 0 0 100 0.0588 0.08 0.0988 0.2576 0.2341 0.0847 + 1995 1 6 1 1 0 0 100 0.0588 0 0.0035 0.0329 0.0718 0.0776 + 1996 1 6 1 1 0 0 100 0.1214 0.1835 0.1733 0.1022 0.0599 0.0265 + 1996 1 6 1 1 0 0 100 0.1214 0 0.0181 0.1214 0.1242 0.0695 + 1997 1 6 1 1 0 0 100 0.2297 0.2351 0.1189 0.1568 0.1216 0.0676 + 1997 1 6 1 1 0 0 100 0.2297 0 0 0.0189 0.027 0.0243 + 1998 1 6 1 1 0 0 100 0.1395 0.4136 0.2653 0.0544 0.0236 0.0034 + 1998 1 6 1 1 0 0 100 0.1395 0 0.0238 0.0317 0.017 0.0272 + 1999 1 6 1 1 0 0 100 0.0192 0.1168 0.3566 0.3605 0.0838 0.0154 + 1999 1 6 1 1 0 0 100 0.0192 0 0.01 0.0223 0.0069 0.0085 + 2000 1 6 1 1 0 0 100 0.0885 0.1062 0.1646 0.3345 0.1788 0.0372 + 2000 1 6 1 1 0 0 100 0.0885 0 0.0018 0.0513 0.023 0.0142 + 2002 1 6 1 1 0 0 100 0.3136 0.2763 0.1761 0.0681 0.0668 0.0501 + 2002 1 6 1 1 0 0 100 0.3136 0 0.0077 0.0051 0.0154 0.0064 + 2003 1 6 1 1 0 0 100 0.0994 0.2236 0.2994 0.1801 0.0559 0.0261 + 2003 1 6 1 1 0 0 100 0.0994 0 0.0224 0.0273 0.0261 0.0273 + 2004 1 6 1 1 0 0 100 0.0175 0.1643 0.2622 0.3462 0.1119 0.0105 + 2004 1 6 1 1 0 0 100 0.0175 0 0.0175 0.021 0.014 0.0245 + 2005 1 6 1 1 0 0 100 0.0741 0.1407 0.1827 0.2173 0.1852 0.0765 + 2005 1 6 1 1 0 0 100 0.0741 0 0.0025 0.0395 0.0593 0.0173 + 2006 1 6 1 1 0 0 100 0.1406 0.2266 0.209 0.1563 0.0547 0.0215 + 2006 1 6 1 1 0 0 100 0.1406 0 0.0176 0.043 0.0742 0.0352 + 2007 1 6 1 1 0 0 100 0.1486 0.2095 0.3784 0.1419 0.0473 0 + 2007 1 6 1 1 0 0 100 0.1486 0 0.0068 0.0203 0.0405 0 + 2008 1 6 1 1 0 0 100 0.1898 0.3219 0.1703 0.1479 0.0672 0.0083 + 2008 1 6 1 1 0 0 100 0.1898 0 0.0359 0.0339 0.0155 0.0092 + 2009 1 6 1 1 0 0 100 0.0706 0.1336 0.3511 0.2023 0.084 0.0134 + 2009 1 6 1 1 0 0 100 0.0706 0 0.0019 0.0382 0.0992 0.0057 + 2010 1 6 1 1 0 0 100 0.047 0.1357 0.2157 0.2452 0.113 0.0191 + 2010 1 6 1 1 0 0 100 0.047 0 0.0591 0.1009 0.0539 0.0104 + 2011 1 6 1 1 0 0 100 0.0786 0.1368 0.2103 0.1744 0.1333 0.0513 + 2011 1 6 1 1 0 0 100 0.0786 0.012 0.0325 0.1128 0.0462 0.012 + 2012 1 6 1 1 0 0 100 0.1155 0.234 0.1945 0.1246 0.1292 0.0456 + 2012 1 6 1 1 0 0 100 0.1155 0.003 0.0912 0.0532 0.0532 0.035 +#length proportions of Comercial male Discards +## Year Seas Fleet Sex Type Shell Maturity Nsamp DataVec + 1987 1 4 1 2 0 0 100 0.2026 0.3625 0.3522 0.0344 0 0 + 1987 1 4 1 2 0 0 100 0.2026 0 0.0437 0.0046 0 0 + 1988 1 4 1 2 0 0 100 0.052 0.184 0.4831 0.139 0 0 + 1988 1 4 1 2 0 0 100 0.052 0 0.0969 0.0449 0 0 + 1989 1 4 1 2 0 0 100 0.2492 0.3392 0.2371 0.0274 0 0 + 1989 1 4 1 2 0 0 100 0.2492 0 0.1196 0.0274 0 0 + 1990 1 4 1 2 0 0 100 0.2702 0.3203 0.3028 0.0414 0 0 + 1990 1 4 1 2 0 0 100 0.2702 0 0.0588 0.0065 0 0 + 1992 1 4 1 2 0 0 100 0.2175 0.3592 0.332 0.0369 0 0 + 1992 1 4 1 2 0 0 100 0.2175 0 0.0447 0.0097 0 0 + 1994 1 4 1 2 0 0 100 0.1556 0.303 0.1736 0.0262 0 0 + 1994 1 4 1 2 0 0 100 0.1556 0 0.2824 0.0592 0 0 + 2012 1 4 1 2 0 0 100 0.1396 0.2398 0.4106 0.1314 0.0122 0 + 2012 1 4 1 2 0 0 100 0.1396 0.0027 0.0298 0.0285 0.0014 0.0014 + 2013 1 4 1 2 0 0 100 0.4379 0.2352 0.252 0.0639 0.0029 0.0012 + 2013 1 4 1 2 0 0 100 0.4379 0.0006 0.0035 0.0012 0.0006 0.0006 + 2014 1 4 1 2 0 0 100 0.1045 0.2746 0.4322 0.1236 0.0078 0.0024 + 2014 1 4 1 2 0 0 100 0.1045 0.009 0.023 0.0113 0.0018 0.0006 +## Growth data (increment) +# nobs_growth +20 +## Note SM used loewss regression for males BBRKC data +## and cubic spine to interpolate 3 sets of female BBRKC data +# MidPoint Sex Increment CV + 67.5 1 16.510674 0.2 + 72.5 1 16.454438 0.2 + 77.5 1 16.398615 0.2 + 82.5 1 16.343118 0.2 + 87.5 1 16.287715 0.2 + 92.5 1 16.23213 0.2 + 97.5 1 16.176368 0.2 + 102.5 1 16.123732 0.2 + 107.5 1 16.069744 0.2 + 112.5 1 16.013906 0.2 + 117.5 1 15.957058 0.2 + 122.5 1 15.900084 0.2 + 127.5 1 15.843143 0.2 + 132.5 1 15.786395 0.2 + 137.5 1 15.732966 0.2 + 142.5 1 15.68064 0.2 + 147.5 1 15.628775 0.2 + 152.5 1 15.577259 0.2 + 157.5 1 15.526092 0.2 + 162.5 1 15.475241 0.2 +## eof +9999 +## eof +9999 diff --git a/examples/nsrkc/readme.md b/examples/nsrkc/readme.md new file mode 100644 index 00000000..b919b7b7 --- /dev/null +++ b/examples/nsrkc/readme.md @@ -0,0 +1,9 @@ +# Setup for comparing Norton Sound red king crab models + +## to do list + + go through datafiles + +## Files + + * Script for running alternative model configurations diff --git a/ignore.gitignore b/ignore.gitignore deleted file mode 100644 index f78d955f..00000000 --- a/ignore.gitignore +++ /dev/null @@ -1,25 +0,0 @@ -# Compiled Object files -*.slo -*.lo -*.o -*.obj -*.htp - -# Compiled Dynamic libraries -*.so -*.dylib -*.dll - -# Compiled Static libraries -*.lai -*.la -*.a -*.lib - -# Executables -*.exe -*.out -*.app - -# Links -*.lnk \ No newline at end of file diff --git a/scripts/gmacs.r b/scripts/gmacs.r deleted file mode 100644 index ee819669..00000000 --- a/scripts/gmacs.r +++ /dev/null @@ -1,94 +0,0 @@ -#========================================================================================================= -# -# Gmacs.r : Version 1.0 (January 2014) -# R script: Import content from Gmacs model output; produce plots. -# Authors: Athol R. Whitten, James N. Ianelli -# Updated: January 2014 -# -# Acknowledgements: 'Read' functions based on code developed for ADMB by Steve Martell -# Some plotting functions based on code developed for Stock Synthesis by Ian Taylor (r4ss). -# -# Returns: A list containing elements of gmacs_r.rep -# Plots: Various fits to data, summary statistics. -# -#========================================================================================================= - -# Remove previous R console objects; load required packages: -rm(list=ls()) - -#======================================= -# Set and load directories/files -#======================================= -source('reptoRlist.r') -windows(record=TRUE) -#layout(matrix(1:8, 4, 2, byrow = TRUE)) - -# Read and assign gmacs_r.rep output file: -gmout <- reptoRlist('gmacs_r.rep') -names(gmout) -summary(gmout) -# -------------------------------------------------------------------------------------------------------- - -# Plot fits to catch data (main fisheries): -plot(1, type="n", main="Fit to Catch Data (Retained Pot Fishery)", xlab="Years", ylab ="Catch (tonnes)", xlim=(c(min(gmout$years),max(gmout$years)+1)), ylim=c(0,max(gmout$catch_biom_obs[2, ])), cex.main=1.2) -nfleet_ret <- 2 -for(ifleet in nfleet_ret) - { - abline(h=0) - lines(gmout$years, gmout$catch_biom_obs[ifleet, ], type="p", pch=20, col=2, cex=1.2) - lines(gmout$years, gmout$catch_biom_pred[ifleet, ], type= "l", col=4, lwd=2) - legend("topright", legend=c("Observed","Predicted"), pch=20, col=c(2,4), bty="n") - } - -# Plot fits to catch data (main fisheries): -plot(1, type="n", main="Fit to Catch Data (Trawl Bycatch)", xlab="Years", ylab ="Catch (tonnes)", xlim=(c(min(gmout$years),max(gmout$years)+1)), ylim=c(0,max(gmout$catch_biom_obs[3, ])), cex.main=1.2) -nfleet_ret <- 3 -for(ifleet in nfleet_ret) -{ - abline(h=0) - lines(gmout$years, gmout$catch_biom_obs[ifleet, ], type="p", pch=20, col=2, cex=1.2) - lines(gmout$years, gmout$catch_biom_pred[ifleet, ], type= "l", col=4, lwd=2) - legend("topright", legend=c("Observed","Predicted"), pch=20, col=c(2,4), bty="n") -} - -# Plot fits to survey data: -plot(1, type="n", main="Fit to survey data", xlab="Years", ylab ="Survey Observation", xlim=(c(min(gmout$years),max(gmout$years)+1)), ylim=c(0,max(c(gmout$survey_num_pred[1, ],gmout$survey_num_obs[1, ]))), cex.main=1.2) - -# Survey 1 (NMFS) -nsurvey <- 1 -for(isrv in 1:nsurvey) -{ - lines(gmout$yr_survey[isrv,], gmout$survey_num_obs[isrv, ], type="p", pch=20, col=isrv, cex=1.2) - lines(gmout$yr_survey[isrv,], gmout$survey_num_pred[isrv, ], type= "l", col=isrv+2, lwd=2) - legend("topright", legend=c("Observed","Predicted"), pch=20, col=c(isrv,isrv+2), bty='n') -} - -# Survey 2 (BRSF) -nsurvey <- 2 -for(isrv in 1:nsurvey) -{ - lines(gmout$yr_survey[isrv,], gmout$survey_num_obs[isrv, ], type="p", pch=20, col=isrv, cex=1.2) - lines(gmout$yr_survey[isrv,], gmout$survey_num_pred[isrv, ], type= "l", col=isrv+2, lwd=2) - legend("topright", legend=c("Observed","Predicted"), pch=20, col=c(isrv,isrv+2), bty='n') -} - -# Plot Selectivity -plot(1:5,gmout$select_fish_2[43,2:6], type="b", main="Selectivity", xlab="Size Class", ylab ="Selectivity" , pch=19,col="blue",cex.main=1.2) -for(i in 1:43) -{ -# lines(1:5, gmout$select_fish_2[i,2:6]) - lines(1:5, gmout$select_fish_1[i,2:6],col="salmon") - lines(1:5, gmout$select_fish_3[i,2:6],col="grey") -} - -# Plot Natural mortality -plot(gmout$years,gmout$M, type="b", main="Time-varying Natural Mortality (M)", xlab="Years", ylab ="M", xlim=(c(min(gmout$years),max(gmout$years)+1)), ylim=c(0,max(gmout$M)), pch=19,col="blue",cex.main=1.2) - -# Plot Recruitment -plot(gmout$years,gmout$recruits, type="b", main="Yearly Recruitment", xlab="Years", ylab ="No. of Recruits", xlim=(c(min(gmout$years),max(gmout$years)+1)), ylim=c(0,max(gmout$recruits)), pch=19,col="blue",cex.main=1.2) - -# Plot Fishing Mortality Rate -plot(gmout$exp_rate_2[,1], gmout$exp_rate_2[,2], type="b", main="Exploitation Rate (F)", xlab="Years", ylab ="Rate", xlim=(c(min(gmout$years),max(gmout$years)+1)), ylim=c(0,max(gmout$exp_rate_2[,2])), pch=19,col="red",cex.main=1.2) - -#========================================================================================================= -# EOF diff --git a/scripts/reptoRlist.r b/scripts/reptoRlist.r deleted file mode 100644 index ec2c48f7..00000000 --- a/scripts/reptoRlist.r +++ /dev/null @@ -1,48 +0,0 @@ -reptoRlist = function(fn) -{ - # Function to read a report file with file name fn - # Example: - # fn <-("~/admb/simple.rep") - # A <- reptoRlist(fn) - # - # Then the 'A' object contains a list structure - # with all the elemements in the report file. - # In the REPORT_SECTION of the AMDB template use - # the following format to output objects: - # report<<"object \n"<2) dum=as.matrix(read.table(fn,skip=ir,nrow=irr-ir-1,fill=T)) - - if(is.numeric(dum))#Logical test to ensure dealing with numbers - { - A[[vnam[i]]]=dum - } - } -return(A) -} \ No newline at end of file diff --git a/src/gmacs.tpl b/src/gmacs.tpl index 945583eb..fd3daf65 100644 --- a/src/gmacs.tpl +++ b/src/gmacs.tpl @@ -1,1859 +1,2677 @@ -// ========================================================================================================= -// Gmacs: Generalized Modelling for Alaskan Crab Stocks. +/// ==================================================================================== // +// Gmacs: A generalized size-structured stock assessment modeling framework. // -// Authors: Athol Whitten, University of Washington -// Jim Ianelli, NOAA Alaskan Fisheries Science Centre +// Authors: Athol Whitten and Jim Ianelli +// University of Washington, Seattle +// and Alaska Fisheries Science Centre, Seattle // -// Info: https://github.com/awhitten/gmacs or write to whittena@uw.edu -// Copyright (c) 2014. All rights reserved. +// Info: https://github.com/seacode/gmacs Copyright (C) 2014. All rights reserved. // -// Acknowledgement: The format of this code, and many of the details, -// were adapted from code developed for the NPFMC by Andre Punt (2012), -// and on the 'LSMR' model by Steven Martell (2011). -// -// TO DO LIST: -// - Look at numbers-at-length matrix...dimensioned by year, maturity, shell condition, sex, size bin -// - Add routine to calculate reference points -// - Add forecast routine -// - Add warning section: use macro for warning(object,text) -// - Add section to write new data/control files (enable easy labelling after first model attempt) -// - Add simulation option, see LSMR model for demonstration -// ========================================================================================================= - -// ========================================================================================================= -GLOBALS_SECTION - #include - #include - #include - - time_t start,finish; - long hour,minute,second; - double elapsed_time; - - // Define objects for report file, echoinput, etc. - /** - \def report(object) - Prints name and value of \a object on ADMB report %ofstream file. - */ - #undef REPORT - #define REPORT(object) report << #object "\n" << object << endl; - - /** - \def echo(object) - Prints name and value of \a object on echoinput %ofstream file. - */ - #define echo(object) echoinput << #object << "\n" << object << endl; - #define echotxt(object,text) echoinput << object << "\t" << text << endl; - - /** - \def writeR(object) - Prints name and value of \a object on R_out (gmacs_r.rep) %ofstream file. - */ - #define writeR(object) R_out << #object << "\n" << object << endl; - - /** - \def check(object) - Prints name and value of \a object on checkfile %ofstream output file. - */ - #define check(object) checkfile << #object << "\n" << object << endl; - - // Open output files using ofstream - ofstream echoinput("echoinput.gm"); - ofstream checkfile("checkfile.gm"); - ofstream warning("warning.gm"); - ofstream R_out("gmacs_r.rep"); - - // Define some adstring variables for use in output files: - adstring version; - adstring version_short; - adstring_array fleet_names; - adstring_array survey_names; - adstring_array like_names; - adstring_array prior_names; - - -// ========================================================================================================= -TOP_OF_MAIN_SECTION - time(&start); - arrmblsize = 50000000; - gradient_structure::set_GRADSTACK_BUFFER_SIZE(1.e7); - gradient_structure::set_CMPDIF_BUFFER_SIZE(1.e7); - gradient_structure::set_MAX_NVAR_OFFSET(5000); - gradient_structure::set_NUM_DEPENDENT_VARIABLES(5000); - -// ========================================================================================================= +// INDEXES: +// g = group +// h = sex +// i = year +// j = time step (years) +// k = gear or fleet +// l = index for length class +// m = index for maturity state +// o = index for shell condition. + +// ==================================================================================== // + +/// +///@file gmacs.tpl +///@authors Steve Martell, Jim Ianelli, Athol Whitten +/// + DATA_SECTION - // Create strings with version information: - !!version+="Gmacs_V1.03_2014/01/02_by_Athol_Whitten_and_Jim_Ianelli_using_ADMB_11.1"; - !!version_short+="Gmacs V1.03"; - !! echoinput << version << endl; - !! echoinput << ctime(&start) << endl; - - // Declare global increment values for likelihoods calculations: - number incc - number incd - !! incc = 0.00001; ///< Constant for likelihoods - !! incd = 0.0001; ///< Constant for likelihoods - -// --------------------------------------------------------------------------------------------------------- -// STARTER FILE - // Open Starter file (starter.gm) - !! ad_comm::change_datafile_name("starter.gm"); - !! cout << " Reading information from starter file" << endl; - !! echoinput << " Start reading starter file" << endl; - - // Read data, control, and size transition file names, then echo: - init_adstring data_file; - init_adstring control_file; - init_adstring size_trans_file; - - !! echotxt(data_file, "data file"); - !! echotxt(control_file, "control file"); - - // Read various option values, then echo: - init_int verbose; // Display detail to screen (option 1/0) - init_int final_phase; // Stop estimation after this phase - init_int use_pin; // Use a .pin file to get initial parameters (option 1/0) - init_int read_growth; // Read growth transition matrix file (option 1/0) - - !! echotxt(verbose, " display detail"); - !! echotxt(final_phase, " final phase"); - !! echotxt(use_pin, " use parameter in file (*.pin)"); - !! echotxt(read_growth, " read growth transition matrix data file"); - - // Print EOF confirmation to screen and echoinput, warn otherwise: - init_int eof_starter; - - !! if(eof_starter!=999) {cerr << " Error reading starter file \n EOF = "<< eof_starter << endl; exit(1);} - !! cout << " Finished reading starter file \n" << endl; - !! echotxt(eof_starter," EOF: finished reading starter file \n"); - -// --------------------------------------------------------------------------------------------------------- -// DATA FILE (MAIN) - // Open main data file (*.dat): - !! ad_comm::change_datafile_name(data_file); - !! cout << " Reading main data file" << endl; - !! echoinput << " Start reading main data file" << endl; - - //Initialize some counters: - int i; - int j; - int iyr; - int iclass; - int jclass; - int ifleet; - int isurvey; - int last; - - // Read input from main data file: - init_int styr; ///< Start year - init_int endyr; ///< End year - init_number tstep; ///< Time-step - - !! echotxt(styr, " Start year"); - !! echotxt(endyr, " End year"); - !! echotxt(tstep, " Time-step"); - - init_int nsex; ///< Number of sexes - init_int nfleet; ///< Number of fishing fleets - init_int nsurvey; ///< Number of surveys - init_int nclass; ///< Number of size classes - init_int ndclass; ///< Number of size classes (in the data) - - imatrix iname_flt(1,nfleet,1,2); - imatrix iname_srv(1,nfleet,1,2); - init_adstring name_read_flt; - init_adstring name_read_srv; - LOCAL_CALCS - // Convert read in strings of fishery and survey names to a string array (so they can be indexed): - // TODO: Create way to return an error if not formatted properly. - int k; - for(k=1;k<=nfleet;k++) - { - iname_flt(k,1)=1; - iname_flt(k,2)=1; - } - // Set whole array equal to 1 in case not enough names are read: - adstring_array CRLF; // Blank to terminate lines (not sure why this is needed...) - CRLF+=""; - k=1; - for(i=1;i<=strlen(name_read_flt);i++) - { - if(adstring(name_read_flt(i))==adstring(":")) - { - iname_flt(k,2)=i-1; - k++; - iname_flt(k,1)=i+1; - } - } - iname_flt(nfleet,2)=strlen(name_read_flt); - for(k=1;k<=nfleet;k++) - { - fleet_names += name_read_flt(iname_flt(k,1),iname_flt(k,2))+CRLF(1); - } - for(k=1;k<=nsurvey;k++) - { - iname_srv(k,1)=1; - iname_srv(k,2)=1; - } - // Set whole array equal to 1 in case not enough names are read - // Read in survey names - k=1; - for(i=1;i<=strlen(name_read_srv);i++) - { - if(adstring(name_read_srv(i))==adstring(":")) - { - iname_srv(k,2) =i-1; - k++; - iname_srv(k,1) =i+1; - } - } - iname_srv(nsurvey,2)=strlen(name_read_srv); - for(k=1;k<=nsurvey;k++) - { - survey_names += name_read_srv(iname_srv(k,1),iname_srv(k,2))+CRLF(1); - } - // TODO: Macro doesn't work perfectly for printing these out...unsure why. Test and fix. - echotxt(fleet_names, "Fleetnames"); - echotxt(survey_names, "Surveynames"); - END_CALCS - - init_imatrix class_link(1,nclass,1,2); ///< Link between data size-classes and model size-classs - - !! echotxt(nsex, " Number of sexes"); - !! echotxt(nfleet, " Number of fleets"); - !! echotxt(nsurvey, " Number of surveys") - !! echotxt(nclass, " Number of size classes"); - !! echotxt(ndclass, " Number of size classes for data"); - - !! echo(class_link); - - init_vector catch_units(1,nfleet); ///< Catch units (pot discards; + other fleets) [1=biomass (tons);2=numbers] - init_vector catch_multi(1,nfleet); ///< Additional catch scaling multipliers [1 for no effect] - init_vector survey_units(1,nsurvey); ///< Survey units [1=biomass (tons);2=numbers] - init_vector survey_multi(1,nsurvey); ///< Additional survey scaling multipliers [1 for no effect] - init_int ncatch_obs; ///< Number of catch lines to read - init_int nsurvey_obs; ///< Number of survey lines to read - init_number survey_time; ///< Time between survey and fishery (for projections) - - !! echotxt(catch_units, " Catch units"); - !! echotxt(catch_multi, " Catch multipliers"); - !! echotxt(survey_units, " Survey units"); - !! echotxt(survey_multi, " Survey multipliers") - !! echotxt(ncatch_obs, " Number of lines of catch data"); - !! echotxt(nsurvey_obs, " Number of lines of survey data") - !! echotxt(survey_time, " Time between survey and fishery"); - - // Read fleet specifications and determine number with catch retained or discarded etc: - init_imatrix fleet_control(1,nfleet,1,2); ///< Fleet control matrix - - int nfleet_ret; ///< Number of fleets for retained catch data - int nfleet_dis; ///< Number of fleets for discarded catch data (with link to above retained catch) - int nfleet_byc; ///< Number of fleets for bycatch data only - int nfleet_act; ///< Number of active distinct fleets - - LOCAL_CALCS - nfleet_ret = 0; - nfleet_dis = 0; - nfleet_byc = 0; - - for (ifleet=1; ifleet<=nfleet; ifleet++) - { - switch (fleet_control(ifleet,1)) - { - case 1 : - nfleet_ret += 1; - break; - case 2 : - nfleet_dis += 1; - break; - case 3 : - nfleet_byc += 1; - break; - } - } - nfleet_act = nfleet_ret + nfleet_byc; ///< Determine number of active distinct fleets - END_CALCS - - ivector fleet_ind_act(1,nfleet_act); ///< Fleet index to map active fleet to all fleets - !! int iact=0;for (int i=1;i<=nfleet;i++) if(fleet_control(i,1)!=2) {iact++;fleet_ind_act(iact)=i;} - !! echo(fleet_control); - - init_matrix catch_data(1,ncatch_obs,1,5); ///< Catch data matrix, one line per ncatch_obs, requires year, season, fleet, observation - matrix catch_biom_obs(1,nfleet,styr,endyr) ; - matrix catch_num_obs(1,nfleet,styr,endyr) ; - - init_matrix survey_data(1,nsurvey_obs,1,6); ///< Survey data matrix, one line per nsurvey_obs, requires year, season, survey, observation, and error - ivector nobs_survey(1,nsurvey); - - !! echo(catch_data); - !! echo(survey_data); - - LOC_CALCS - // Fishery data - catch_biom_obs.initialize(); - catch_num_obs.initialize(); - for (int i=1;i<=ncatch_obs;i++) - { - catch_biom_obs(catch_data(i,3),catch_data(i,1)) = catch_data(i,5); - catch_num_obs(catch_data(i,3),catch_data(i,1)) = catch_data(i,5); - } - // survey data - nobs_survey.initialize(); - for (int i=1;i<=nsurvey_obs;i++) - nobs_survey(survey_data(i,3))++; - check(nobs_survey); - - END_CALCS - imatrix yr_survey(1,nsurvey,1,nobs_survey) ; - matrix survey_biom_obs(1,nsurvey,1,nobs_survey) ; - matrix survey_num_obs(1,nsurvey,1,nobs_survey) ; - matrix survey_var(1,nsurvey,1,nobs_survey) ; - LOC_CALCS - survey_var.initialize(); - survey_biom_obs.initialize(); - survey_num_obs.initialize(); - ivector iobs_sv(1,nsurvey); ///< Counter for number of obs within each survey - iobs_sv.initialize(); - for (int i=1;i<=nsurvey_obs;i++) - { - int isrv=survey_data(i,3); - iobs_sv(isrv)++; - yr_survey(isrv,iobs_sv(isrv)) = survey_data(i,1); - if (survey_units(isrv)==1) - survey_biom_obs(isrv,iobs_sv(isrv)) = survey_data(i,5); - else - survey_num_obs(isrv,iobs_sv(isrv)) = survey_data(i,5); - survey_var(isrv,iobs_sv(isrv)) = log(1+square(survey_data(i,6))); // For likelihood, compute input variance here, assumes input as CV. - } - - for (isurvey=1; isurvey<=nsurvey; isurvey++) - { - for (int i=1; i<=nobs_survey(isurvey); i++) - { - survey_biom_obs(isurvey,i) *= survey_multi(isurvey); - survey_num_obs(isurvey,i) *= survey_multi(isurvey); - } - } - check(survey_var); - check(survey_num_obs); - check(survey_var); - END_CALCS - - init_vector discard_mort(1,nfleet); ///< Discard mortality (per fishery) - init_vector hg(styr,endyr); ///< Retention value for each year (highgrading) - init_matrix catch_time(1,nfleet_act,styr,endyr); ///< Timing of each fishery (as fraction of time-step) - init_matrix effort(1,nfleet_act,styr,endyr); ///< Effort by fishery - init_imatrix f_new(1,nfleet_act,1,5); ///< Alternative f estimators (overwrite others) - - LOC_CALCS - echo(discard_mort); - echo(hg); - echo(catch_time); - echo(effort); - echo(f_new); - check(catch_biom_obs); - check(catch_num_obs); - for (ifleet=1; ifleet<=nfleet; ifleet++) - { - for (iyr=styr; iyr<=endyr; iyr++) - { - catch_biom_obs(ifleet,iyr) *= discard_mort(ifleet) * catch_multi(ifleet); - catch_num_obs(ifleet,iyr) *= discard_mort(ifleet) * catch_multi(ifleet); - } - } - END_CALCS - - // Determine which F values will be computed using effort (f_new) if applicable: - ivector ncatch_f(1,nfleet_act); - - LOCAL_CALCS - for (ifleet=1; ifleet<=nfleet_act; ifleet++) - { - ncatch_f(ifleet) = 0; - for (iyr=styr; iyr<=endyr; iyr++) - if (effort(ifleet,iyr) > 0) - { - if (f_new(ifleet,1) == 0 || iyr < f_new(ifleet,2) || iyr > f_new(ifleet,3)) - ncatch_f(ifleet) += 1; - } - } - END_CALCS - - !! echotxt(ncatch_f, " Number of F's (calculated)") - - // Read in the length frequency data: - init_int nlf_obs; ///< Number of length frequency lines to read for fishing fleets - init_matrix lf_data(1,nlf_obs,1,ndclass+7); ///< Length frequency data, one line per nlf_obs, requires year, season, fleet, sex, maturity, shell cond., effective sample size, then data vector - ivector nlf_fleet(1,nfleet); ///< Number of years of lf data per fleet - - LOC_CALCS - nlf_fleet.initialize(); - for (int i=1; i<=nlf_obs; i++) - { - nlf_fleet(int(lf_data(i,3)))++ ; - } - END_CALCS - - imatrix yr_fleet_lf(1,nfleet,1,nlf_fleet); ///< Years with lf data, by fleet - matrix ss_fleet_lf(1,nfleet,1,nlf_fleet); ///< Effective sample sizes, by fleet - 3darray fleet_lf(1,nfleet,1,nlf_fleet,1,ndclass); ///< Length-frequency data (ndclass), by fleet (can be ragged array) - 3darray fleet_lf_obs(1,nfleet,1,nlf_fleet,1,nclass); ///< Length-frequency data (nclass), by fleet (can be ragged array) - - LOC_CALCS - ivector iobs_fl(1,nfleet); ///< Counter for number of obs within each fleet - iobs_fl.initialize(); - for (int i=1; i<=nlf_obs; i++) - { - ifleet = int(lf_data(i,3)); - iobs_fl(ifleet)++; - yr_fleet_lf(ifleet,iobs_fl(ifleet)) = (lf_data(i,1)); - ss_fleet_lf(ifleet,iobs_fl(ifleet)) = lf_data(i,7); - - if(nclass!=ndclass) - { - for (iclass=1; iclass<=nclass; iclass++) - fleet_lf_obs(ifleet,iobs_fl(ifleet),iclass) = sum(lf_data(i)(7+class_link(iclass,1),7+class_link(iclass,2))); - } - else - fleet_lf_obs(ifleet,iobs_fl(ifleet)) = lf_data(i)(8,7+ndclass).shift(1); - - fleet_lf_obs(ifleet,iobs_fl(ifleet)) /= sum(fleet_lf_obs(ifleet,iobs_fl(ifleet)) ); // normalize LF to sum to 1 - } - END_CALCS - - // NOTE: Simple.tpl down-weighted sample sizes w/in the code. Check this. - - !! echotxt(nlf_obs, " Number of length freq lines to read"); - !! echo(lf_data); - !! echo(nlf_fleet); - !! echo(yr_fleet_lf); - !! echo(ss_fleet_lf); - !! echo(fleet_lf_obs); - - // Read in survey length frequency data: - init_int nlfs_obs; ///< Number of survey length frequency lines to read - init_matrix lfs_data(1,nlfs_obs,1,ndclass+5); ///< Survey length frequency data, one line per nlfs_obs, requires year, season, survey, sex, effective sample size, then data vector - ivector nlf_survey(1,nsurvey); ///< Number of years of survey lf data per survey - - LOC_CALCS - nlf_survey.initialize(); - for (int i=1; i<=nlfs_obs; i++) - { - nlf_survey(int(lfs_data(i,3)))++ ; - } - END_CALCS - - imatrix yr_survey_lf(1,nsurvey,1,nlf_survey); ///< Years with lf data, by survey - matrix ss_survey_lf(1,nsurvey,1,nlf_survey); ///< Effective sample sizes, by survey - 3darray survey_lf(1,nsurvey,1,nlf_survey,1,ndclass); ///< Length-frequency data (ndclass), by survey (can be ragged array) - 3darray survey_lf_obs(1,nsurvey,1,nlf_survey,1,nclass); ///< Length-frequency data (nclass), by survey (can be ragged array) - - LOC_CALCS - iobs_sv.initialize(); - for (int i=1; i<=nlfs_obs; i++) - { - isurvey = int(lfs_data(i,3)); - iobs_sv(isurvey)++; - yr_survey_lf(isurvey,iobs_sv(isurvey)) = (lfs_data(i,1)); - ss_survey_lf(isurvey,iobs_sv(isurvey)) = lfs_data(i,5); - - if(nclass!=ndclass) - { - for (iclass=1; iclass<=nclass; iclass++) - { - survey_lf_obs(isurvey,iobs_sv(isurvey),iclass) = sum(lfs_data(i)(5+class_link(iclass,1),5+class_link(iclass,2))); - } - } - else - { - survey_lf_obs(isurvey,iobs_sv(isurvey)) = lfs_data(i)(6,5+ndclass).shift(1); - } - survey_lf_obs(isurvey,iobs_sv(isurvey)) /= sum(survey_lf_obs(isurvey,iobs_sv(isurvey))); // normalize to sum to 1 - survey_lf(isurvey,iobs_sv(isurvey)) = lfs_data(i)(6,(ndclass+5)).shift(1); // Retain full dimension for length and weight calcs - } - END_CALCS - - !! echotxt(nlfs_obs, " Number of survey length freq lines to read"); - !! echo(lfs_data); - !! echo(nlf_survey); - !! echo(yr_survey_lf); - !! echo(ss_survey_lf); - !! echo(survey_lf_obs); - - // Read in length, weight, fecundity vectors, then calculate equivalent vectors with nclass number of size-classes: - init_vector mean_length(1,ndclass); ///< Mean length vector input - init_vector mean_weight(1,ndclass); ///< Mean weight vector input - init_vector fecundity_inp(1,ndclass); ///< Fecundity vector input - - !! echo(mean_length); - !! echo(mean_weight); - !! echo(fecundity_inp); - - // Format length, weight, and fecundity vectors to model size-classes: - vector length(1,nclass); ///< Length vector (mm) for model - vector weight(1,nclass); ///< Weight (kg) vector for model - vector fecundity(1,nclass); ///< Fecundity (kg) vector for model - - vector surv_lf_store(1,ndclass); ///< Survey lf total by data class - - !! checkfile << "Class-specific length, weight, and fecundity" << endl; - - // TODO: Check surv_lf_store loop over nlfs_obs; only loops over first survey in simple.tpl (only first survey has data). - LOCAL_CALCS - if(nclass!=ndclass) - { - int total; - total = 0; - for (iclass=1; iclass<=ndclass; iclass++) - { - surv_lf_store(iclass) = 0; - for (iyr=1; iyr<=nlfs_obs; iyr++) surv_lf_store(iclass) += survey_lf(1,iyr,iclass); - total += surv_lf_store(iclass); - } - if (verbose == 1) cout << "Survey sample sizes stored" << endl; // CHECK: ? Not storing sample sizes. - - for (iclass=1; iclass<=nclass; iclass++) - { - length(iclass) = 0; - weight(iclass) = 0; - fecundity(iclass) = 0; - total = 0; - for (jclass=class_link(iclass,1); jclass<=class_link(iclass,2); jclass++) - { - length(iclass) += mean_length(jclass)*surv_lf_store(jclass); - weight(iclass) += mean_weight(jclass)*surv_lf_store(jclass); - fecundity(iclass) += fecundity_inp(jclass)*surv_lf_store(jclass); - total += surv_lf_store(jclass); - } - length(iclass) /= total; - weight(iclass) /= total; - fecundity(iclass) /= total; - checkfile << iclass << " " << length(iclass) << " " << weight(iclass) << " " << fecundity(iclass) << endl; - } - if (verbose == 1) cout << " Lengths, weights, and fecundity recalculated" << endl; - } - else - { - length = mean_length; - weight = mean_weight; - fecundity = fecundity_inp; - check(length); - check(weight); - check(fecundity); - } - END_CALCS - - // Read in capture, mark, recapture data: - init_int ncapture_obs; ///< Number of capture data lines to read - init_int nmark_obs; ///< Number of mark data lines to read - init_int nrecapture_obs; ///< Number of recapture data lines to read - - init_matrix capture_data(1,ncapture_obs,1,ndclass+3); ///< Capture data, one line per ncapture_obs, requires years, fleet, sex, then data vector - init_matrix mark_data(1,nmark_obs,1,ndclass+3); ///< Mark data, one line per nmark_obs, requires years, fleet, sex, then data vector - init_matrix recapture_data(1,nrecapture_obs,1,ndclass+3); ///< Recapture data, one line per nrecapture_obs, requires years, fleet, sex, then data vector - - !! echotxt(ncapture_obs, " Number of capture data lines"); - !! echotxt(nmark_obs, " Number of mark data lines"); - !! echotxt(nrecapture_obs, " Number of recapture data lines") - - // Echo capture, mark, recapture data when appropriate: - LOCAL_CALCS - if(ncapture_obs > 0) - { - echo(capture_data); - echo(mark_data); - echo(recapture_data); - } - END_CALCS - - // Print EOF confirmation to screen and echoinput, warn otherwise: - init_int eof_data; - - !! if(eof_data!=999) {cout << " Error reading main data file \n EOF = "<< eof_data << endl; exit(1);} - !! cout << " Finished reading main data file \n" << endl; - !! echotxt(eof_data," EOF: finished reading main data file \n"); - - -// --------------------------------------------------------------------------------------------------------- -// DATA FILE (GROWTH) -// This section is conditional on starter file flag (read growth matrix data file). - - // Declare objects to read in from growth data file: - int styr_growth; ///< Start year for growth data - int endyr_growth; ///< End year for growth data - int ndclass_growth; ///< Number of data classes for growth data - - !! ndclass_growth = 0; - - LOCAL_CALCS - if(read_growth==1) - { - // Open size transition file (*.dat) // - ad_comm::change_datafile_name(size_trans_file); - cout << " Reading size transition file" << endl; - echoinput << " Start reading size transition file" << endl; - // Read input from growth data file: - *(ad_comm::global_datafile) >> styr_growth; - *(ad_comm::global_datafile) >> endyr_growth; - *(ad_comm::global_datafile) >> ndclass_growth; - - echotxt(styr_growth, " Start year for growth data"); - echotxt(endyr_growth, " End year for growth data"); - echotxt(ndclass_growth, " Number of growth data classes"); - } - else // Set to some values so as not to cause allocation issues for public variables: - { - ndclass_growth = ndclass; - styr_growth = styr; - endyr_growth = endyr; - } - END_CALCS - - // Declare objects dependent on previous objects: needs some defaults - ivector growth_bins(1,ndclass_growth); ///< Vector of growth data bins (lower length of each bin) - 3darray growth_data(styr_growth,endyr_growth,1,ndclass_growth-1,1,ndclass_growth-1); ///< Array of year specific growth transition matrices - - int eof_growth; // Declare EOF check - - LOCAL_CALCS - if(read_growth==1) - { - *(ad_comm::global_datafile) >> growth_bins; - *(ad_comm::global_datafile) >> growth_data; - - echo(growth_bins); - echo(growth_data); - - *(ad_comm::global_datafile) >> eof_growth; - - // Print EOF confirmation to screen and echoinput, warn otherwise: - if(eof_growth!=999) {cout << " Error reading size transition file\n EOF = " << eof_growth << endl; exit(1);} - cout << " Finished reading size transition file \n" << endl; - echotxt(eof_growth," EOF: finished reading size transition file \n"); - } - END_CALCS - -// --------------------------------------------------------------------------------------------------------- -// CONTROL FILE - - // Open control file (*.ctl) // - !! ad_comm::change_datafile_name(control_file); - !! cout << " Reading control file" << endl; - !! echoinput << " Start reading control file" << endl; - - // Specifiy number of general parameters to be read in: - int ntheta; - !! ntheta = 2; - - // Read general input from control file: - init_matrix theta_control(1,ntheta,1,13); ///< General parameter matrix, with specifications - matrix trans_theta_control(1,13,1,ntheta); ///< Transpose of general parameter matrix - vector theta_init(1,ntheta); ///< Vector of general parameter specs - initial values - vector theta_lbnd(1,ntheta); ///< Vector of general parameter specs - lower bound values - vector theta_ubnd(1,ntheta); ///< Vector of general parameter specs - upper bound values - ivector theta_phz(1,ntheta); ///< Vector of general parameter specs - phase values - ivector theta_prior(1,ntheta); ///< Vector of general parameter specs - prior type - vector theta_pmean(1,ntheta); ///< Vector of general parameter specs - prior mean values - vector theta_psd(1,ntheta); ///< Vector of general parameter specs - prior s.d. values - ivector theta_cov(1,ntheta); ///< Vector of general parameter specs - covariate type - ivector theta_dev(1,ntheta); ///< Vector of general parameter specs - deviation type - vector theta_dsd(1,ntheta); ///< Vector of general parameter specs - deviation s.d. - ivector theta_dmin(1,ntheta); ///< Vector of general parameter specs - deviation min. year - ivector theta_dmax(1,ntheta); ///< Vector of general parameter specs - deviation max. year - ivector theta_blk(1,ntheta); ///< Vector of general parameter specs - block number (for time-varying paramters) - - !! echo(theta_control); - - // Fill matrices and vectors created above: - LOC_CALCS - trans_theta_control = trans(theta_control); - theta_init = trans_theta_control(1); - theta_lbnd = trans_theta_control(2); - theta_ubnd = trans_theta_control(3); - theta_phz = ivector(trans_theta_control(4)); - theta_prior = ivector(trans_theta_control(5)); - theta_pmean = trans_theta_control(6); - theta_psd = trans_theta_control(7); - theta_cov = ivector(trans_theta_control(8)); - theta_dev = ivector(trans_theta_control(9)); - theta_dsd = trans_theta_control(10); - theta_dmin = ivector(trans_theta_control(11)); - theta_dmax = ivector(trans_theta_control(12)); - theta_blk = ivector(trans_theta_control(13)); - END_CALCS - - // Read in specifications relating to recruitment: - init_int sr_lag; ///< Lag to recruitment - init_int sr_type; ///< Form of stock recruitment relationship - - !! echotxt(sr_lag, " Lag to recruitment (years)"); - !! echotxt(sr_type, " Form of stock-recruitment relationship"); - - // Read in pointers for time-varying natural mortality: - vector M_pnt(styr,endyr); ///< Pointers to blocks for time-varying natural mortality - int nMadd_parms; ///< Number of M additional parameters - LOC_CALCS - M_pnt.initialize(); - if (theta_blk(2)>0) - { - *(ad_comm::global_datafile) >> M_pnt ; - M_pnt -= 1; - nMadd_parms = max(M_pnt) ; - } - else - nMadd_parms = 1; // just to have some value (will be unestimated) - - echo(M_pnt); - echotxt(nMadd_parms, " Number of additional natural mortality parameters"); - END_CALCS - - // Read in naturaly mortality parameter specifications: - matrix madd_control(1,nMadd_parms,1,4); ///< Natural mort. parameter matrix, with speciifications - // init_matrix madd_control(1,nMadd_parms,1,4); ///< Natural mort. parameter matrix, with speciifications - matrix trans_madd_control(1,4,1,nMadd_parms); ///< Transponse of natural mort. parameter matrix - vector madd_init(1,nMadd_parms); ///< Vector of natural mort. parameter specs - initial values - vector madd_lbnd(1,nMadd_parms); ///< Vector of natural mort. parameter specs - lower bounds - vector madd_ubnd(1,nMadd_parms); ///< Vector of natural mort. parameter specs - upper bounds - ivector madd_phz(1,nMadd_parms); ///< Vector of natural mort. parameter specs - phase values - - - // Fill matrices and vectors created above: - LOCAL_CALCS - if (theta_blk(2)>0) - { - for (int i=1;i<=nMadd_parms;i++) *(ad_comm::global_datafile) >> madd_control(i) ; - trans_madd_control = trans(madd_control); - madd_init = trans_madd_control(1); - madd_lbnd = trans_madd_control(2); - madd_ubnd = trans_madd_control(3); - madd_phz = ivector(trans_madd_control(4)); - } - else - { - nMadd_parms = 1; - madd_lbnd = 0.; - madd_ubnd = 1.; - madd_phz = -1; - madd_init = 0.0; - madd_control.initialize(); - } - echo(madd_control); - echo(madd_init); - echo(madd_ubnd); - echo(madd_lbnd); - echo(madd_phz); - END_CALCS - - // Read in pointers for time-varying fishery and survey selectivity: - init_imatrix selex_fleet_pnt(1,nfleet_act,styr,endyr); ///< Pointers to blocks for time-varying fishing selectivity - init_imatrix selex_survey_pnt(1,nsurvey,styr,endyr+1); ///< Pointers to blocks for time-varying survey selectivity - - !! echo(selex_fleet_pnt); - !! echo(selex_survey_pnt); - - // Determine number of different selectivity functions/patterns to estimate: - int nselex; - int nselex_pats; - int nselex_pars; - - !! nselex_pats = max(selex_survey_pnt); - !! echotxt(nselex_pats, " Total number of selectivity patterns"); - - // TODO: For selex types, check AEP BBRKC document for what each type is. - // Read in specifications for each selectivity pattern and determine number of parameters to estimate: - matrix selex_type(1,nselex_pats,1,4); ///< Selectivity types for each fleet/survey by time-block - - // TODO: The selex_type matrix can probably be read in directly, then the loop over the columns should work the same. - LOCAL_CALCS - nselex = 0; - for (int i=1; i<=nselex_pats; i++) - { - *(ad_comm::global_datafile) >> selex_type(i,1) >> selex_type(i,2) >> selex_type(i,3); - if (selex_type(i,2) == 1) nselex += 2; - if (selex_type(i,2) == 2) nselex += nclass; - if (selex_type(i,2) == 3) nselex += 1; - } - nselex_pars = nselex; - echo(selex_type); - echotxt(nselex_pars, " Total number of selectivity parameters"); - - // Fill last column of selex_type matrix, for use in Set_selex function. - int i = 0; - for (j=1; j<=nselex_pats; j++) - { - selex_type(j,4) = i; - if (selex_type(j,2)==1) last = 2; - if (selex_type(j,2)==2) last = nclass; - if (selex_type(j,2)==3) last = 1; - i += last; - } - check(selex_type); - END_CALCS - - //TODO: Add more selectivity options above as necessary for next example models. See LSMR code for example. - - // Read in selectivity parameter specifications: - init_matrix selex_control(1,nselex_pars,1,4); ///< Selectivity parameter matrix, with specifications - matrix trans_selex_control(1,4,1,nselex_pars); ///< Transpose of selectivity parameter matrix - vector selex_init(1,nselex_pars); ///< Vector of selex parameter specs - initial values - vector selex_lbnd(1,nselex_pars); ///< Vector of selex parameter specs - lower bounds - vector selex_ubnd(1,nselex_pars); ///< Vector of selex parameter specs - upper bounds - ivector selex_phz(1,nselex_pars); ///< Vector of selex parameter specs - phase values - - !! echo(selex_control); - - // Fill matrices and vectors created above: - LOCAL_CALCS - trans_selex_control = trans(selex_control); - selex_init = trans_selex_control(1); - selex_lbnd = trans_selex_control(2); - selex_ubnd = trans_selex_control(3); - selex_phz = ivector(trans_selex_control(4)); - echo(selex_phz); - END_CALCS - - // Read in pointers for time-varying fishery retention: - int nreten_pars; - init_imatrix reten_fleet_pnt(1,nfleet_ret,styr,endyr); - - !! nreten_pars = max(reten_fleet_pnt); - !! nreten_pars *= nclass; - - //TODO: This code assumes only one type of retention function at the moment. Update as necessary. - - !! echotxt(nreten_pars, " Total number of retention parameters"); - - // Read in retention parameter specifications: - init_matrix reten_control(1,nreten_pars,1,4); ///< Retention parameter matrix, with speciifications - matrix trans_reten_control(1,4,1,nreten_pars); ///< Transponse of retention parameter matrix - vector reten_init(1,nreten_pars); ///< Vector of retention parameter specs - initial values - vector reten_lbnd(1,nreten_pars); ///< Vector of retention parameter specs - lower bounds - vector reten_ubnd(1,nreten_pars); ///< Vector of retention parameter specs - upper bounds - ivector reten_phz(1,nreten_pars); ///< Vector of retention parameter specs - phase values - - !! echo(reten_control); - - // Fill matrices and vectors created above: - LOCAL_CALCS - trans_reten_control = trans(reten_control); - reten_init = trans_reten_control(1); - reten_lbnd = trans_reten_control(2); - reten_ubnd = trans_reten_control(3); - reten_phz = ivector(trans_reten_control(4)); - END_CALCS - - // Read in pointers for time-varying survey catchability: - int nsurveyq_pars; - init_imatrix surveyq_pnt(1,nsurvey,styr,endyr+1); - - !! nsurveyq_pars = max(surveyq_pnt); - - !! echo(surveyq_pnt); - !! echotxt(nsurveyq_pars, " Total number of survey Q patterns"); - - // Read in flag for number of surveys in a sub-area of the main survey area: - init_int nsubsurvey; - init_imatrix subsurvey(1,nsubsurvey,1,2); - - !! echotxt(nsubsurvey, " Number of sub-surveys"); - !! if(nsubsurvey > 0) echo(subsurvey); - - // Read in survey catchability parameter specifications: - init_matrix surveyq_control(1,nsurveyq_pars,1,7); ///< Survey Q parameter matrix, with speciifications - matrix trans_surveyq_control(1,7,1,nsurveyq_pars); ///< Transponse of survey Q parameter matrix - vector surveyq_init(1,nsurveyq_pars); ///< Vector of survey Q parameter specs - initial values - vector surveyq_lbnd(1,nsurveyq_pars); ///< Vector of survey Q parameter specs - lower bounds - vector surveyq_ubnd(1,nsurveyq_pars); ///< Vector of survey Q parameter specs - upper bounds - ivector surveyq_phz(1,nsurveyq_pars); ///< Vector of survey Q parameter specs - phase values - ivector surveyq_prior(1,nsurveyq_pars); ///< Vector of survey Q parameter specs - prior types - vector surveyq_pmean(1,nsurveyq_pars); ///< Vector of survey Q parameter specs - prior mean values - vector surveyq_psd(1,nsurveyq_pars); ///< Vector of survey Q parameter specs - prior s.d. values - - !! echo(surveyq_control); - - // Fill matrices and vectors created above: - LOCAL_CALCS - trans_surveyq_control = trans(surveyq_control); - surveyq_init = trans_surveyq_control(1); - surveyq_lbnd = trans_surveyq_control(2); - surveyq_ubnd = trans_surveyq_control(3); - surveyq_phz = ivector(trans_surveyq_control(4)); - surveyq_prior = ivector(trans_surveyq_control(5)); - surveyq_pmean = trans_surveyq_control(6); - surveyq_psd = trans_surveyq_control(7); - END_CALCS - - // Read in initial N parameter specifications: - init_matrix lognin_control(1,nclass,1,4); ///< Initial N parameter matrix, with specifications - matrix trans_lognin_control(1,4,1,nclass); ///< Transpose of initial N parameter matrix - vector lognin_init(1,nclass); ///< Vector of initial N parameter specs - initial values - vector lognin_lbnd(1,nclass); ///< Vector of initial N parameter specs - lower bounds - vector lognin_ubnd(1,nclass); ///< Vector of initial N parameter specs - upper bounds - ivector lognin_phz(1,nclass); ///< Vector of initial N parameter specs - phase values - - !! echo(lognin_control); - - // Fill matrices and vectors created above: - LOCAL_CALCS - trans_lognin_control = trans(lognin_control); - lognin_init = trans_lognin_control(1); - lognin_lbnd = trans_lognin_control(2); - lognin_ubnd = trans_lognin_control(3); - lognin_phz = ivector(trans_lognin_control(4)); - END_CALCS - - // Read in selectivity parameter specifications: - init_matrix gtrans_control(1,nclass-1,1,4); ///< Growth transition parameter matrix, with specifications - matrix trans_gtrans_control(1,4,1,nclass-1); ///< Transpose of initial N parameter matrix - vector gtrans_init(1,nclass-1); ///< Vector of growth trans. parameter specs - initial values - vector gtrans_lbnd(1,nclass-1); ///< Vector of growth trans. parameter specs - lower bounds - vector gtrans_ubnd(1,nclass-1); ///< Vector of growth trans. parameter specs - upper bounds - ivector gtrans_phz(1,nclass-1); ///< Vector of growth trans. parameter specs - phase values - - !! echo(gtrans_control); - - int nprior_terms; ///< Number of terms in the prior components - int nlike_terms; ///< Number of terms in the likelihood components - // Determine number of prior terms, and create objects to hold these values: - !! nprior_terms = (nfleet_act) + 1 + 3 + nsurveyq_pars + 1 + 1; - !! nlike_terms = (nfleet)*2+ (nfleet_act) + (nsurvey)*2; - vector mn_offset(1,nlike_terms); ///< Offset for multinomial calculations - - // Fill matrices and vectors created above: - LOCAL_CALCS - trans_gtrans_control = trans(gtrans_control); - gtrans_init = trans_gtrans_control(1); - gtrans_lbnd = trans_gtrans_control(2); - gtrans_ubnd = trans_gtrans_control(3); - gtrans_phz = ivector(trans_gtrans_control(4)); - - for (int ifl=1;ifl<=nfleet_act;ifl++) - prior_names += fleet_names(fleet_ind_act(ifl))+"_Fpen"+CRLF(1); - prior_names += "rec_devs" +CRLF(1); - prior_names += "trans_parms" +CRLF(1); - prior_names += "Selex"+CRLF(1); - prior_names += "reten_parms" +CRLF(1); - for (int ifl=1;ifl<=nsurveyq_pars;ifl++) - prior_names += "Survey_q_parms" +CRLF(1); - prior_names += "M" +CRLF(1); - prior_names += "SelPen" +CRLF(1); - - // TODO: Check this section works in the general sense when applying to other species. - echotxt(nprior_terms, " Number of prior terms"); - echotxt(nlike_terms, " Number of likelihood terms"); - mn_offset.initialize(); - - // Fill in names of likelihood and prior components: - int ilike=0; - for (int ifl=1;ifl<=nfleet;ifl++) - { - ilike++; - like_names += fleet_names(ifl)+"_catch"+CRLF(1); - } - // Catch LFs - for (int ifl=1;ifl<=nfleet;ifl++) - { - ilike++; - for (int i=1;i<=nlf_fleet(ifl);i++) - { - dvector pobs = incd + fleet_lf_obs(ifl,i); - pobs /= sum(pobs); - mn_offset(ilike) -= ss_fleet_lf(ifl,i)*pobs*log(pobs); - } - like_names += fleet_names(ifl)+"_LF"+CRLF(1); - } - // Effort indices - for (int ifl=1;ifl<=nfleet_act;ifl++) - { - ilike++; ///< Increment the likelihood index - like_names += "Fish_effort"+CRLF(1); - } - // Survey indices - for (int isrv=1;isrv<=nsurvey;isrv++) - { - ilike++; ///< Increment the likelihood index - like_names += survey_names(isrv)+"_Index"+CRLF(1); - ilike++; - like_names += survey_names(isrv)+"_LF"+CRLF(1); - // Survey LF - for (int i=1;i<=nlf_survey(isrv);i++) - { - dvector pobs = incd + survey_lf_obs(isrv,i); - pobs /= sum(pobs); - mn_offset(ilike) -= ss_survey_lf(isrv,i)*pobs*log(pobs); - } - } - check(mn_offset); - echo(mn_offset); - echo(nlike_terms); - echo(nprior_terms); - - END_CALCS - - // Read in prior and data re-weighting values: - init_vector prior_weight(1,nprior_terms); ///< Weights on the priors - init_vector like_weight(1,nlike_terms); ///< Weights on the data - - !! echo(prior_weight); - !! echo(like_weight); - - // Print EOF confirmation to screen and echoinput, warn otherwise: - init_int eof_control; - - !! if(eof_control!=999) {cout << " Error reading control file\n EOF = " << eof_control << endl; exit(1);} - !! cout << " Finished reading control file \n" << endl; - !! echotxt(eof_data," EOF: finished reading control file \n"); - - // TODO: Check these extra objects below, and make them Gmacs format if required. - - //3darray FleetObsLF(1,nfleet,1,maxFleetLF,1,nclass) // Catch/bycatch Lfs (by model classes) - //3darray SurveyObsLF(1,nsurvey,1,maxSurveyLF,1,nclass) // Survey Lfs (by model classes) - - // Objects related to the SR relationship: - int IsB0; // Constant recruitment? - int SR_rel; // Form of SR_Relationship - -// --------------------------------------------------------------------------------------------------------- -// FORECAST FILE - - // Open forecast file (forecast.gm): - !! ad_comm::change_datafile_name("forecast.gm"); - !! cout << " Reading forecast file" << endl; - !! echoinput << " Start reading forecast file" << endl; - - init_int bmsy_start; - init_int bmsy_end; - - !! echotxt(bmsy_start, " BMSY start year"); - !! echotxt(bmsy_end, " BMSY end year"); - - // Print EOF confirmation to screen and echoinput, warn otherwise: - init_int eof_forecast; - - !! if(eof_forecast!=999) {cout << " Error reading forecast file\n EOF = " << eof_forecast << endl; exit(1);} - !! cout << " Finished reading forecast file \n" << endl; - !! echotxt(eof_data," EOF: finished reading forecast file \n"); - - !! cout << " Successfully read all input files. \n" << endl; - -// ========================================================================================================= -// GENERAL CALCS SECTION - - // Create count of active parameters and derived quantities: - int par_count; - int active_count; - int active_parms; - ivector active_parm(0,ntheta); ///< Pointer from active list to the element of the full parameter list to get label. - // TODO: Add active_parm pointer list for labelling active parameters in report file. - - // Adjust the phases to negative if beyond final_phase and find resultant max_phase: - int max_phase; - - LOC_CALCS - cout << " Count parameters and get max phase, adjust phases if required" << endl; - max_phase=1; - active_count=0; - par_count=0; - active_parm(0,ntheta)=0; - - for(int i=1; i<=ntheta; i++) - { - par_count++; - if(theta_phz(i) > final_phase) theta_phz(i)=-1; - if(theta_phz(i) > max_phase) max_phase=theta_phz(i); - if(theta_phz(i) >= 0) - active_count++; active_parm(active_count)=par_count; - } - active_parms=active_count; - cout << " Number of active parameters is " << active_parms << endl; - cout << " Maximum phase for estimation is " << max_phase << "\n" << endl; - - check (theta_phz); - check (ntheta); - check (par_count); - check (active_parm); - check (active_parms); - END_CALCS - // TODO: Adjust this section to include other parameters not specified in the general paramter matrix 'theta'. - -// ========================================================================================================= + + // |---------------------| + // | SIMULATION CONTROLS | + // |---------------------| + int simflag; + int rseed + LOC_CALCS + simflag = 0; + rseed = 0; + int opt,on; + if((on=option_match(ad_comm::argc,ad_comm::argv,"-sim",opt))>-1) + { + simflag = 1; + rseed = atoi(ad_comm::argv[on+1]); + } + + if((on=option_match(ad_comm::argc,ad_comm::argv,"-i",opt))>-1) + { + cout<<" |----------------------------------------------------------|\n"; + cout<<" | CONTRIBUTIONS (Code and intellectual) |\n"; + cout<<" |----------------------------------------------------------|\n"; + cout<<" | Name: Organization: |\n"; + cout<<" | Steven Martell, IPHC |\n"; + cout<<" | James Ianelli, NOAA-NMFS |\n"; + cout<<" | Jack Turnock, NOAA-NMFS |\n"; + cout<<" | Jie Zheng, ADF&G |\n"; + cout<<" | Hamachan Hamazaki, ADF&G |\n"; + cout<<" | Athol Whitten, University of Washington |\n"; + cout<<" | Andre Punt, University of Washington |\n"; + cout<<" | Dave Fournier, Otter Research |\n"; + cout<<" | John Levitt, Mathemetician |\n"; + cout<<" |----------------------------------------------------------|\n"; + + cout<<"\n"; + cout<<" |----------------------------------------------------------|\n"; + cout<<" | FINANCIAL SUPPORT |\n"; + cout<<" |----------------------------------------------------------|\n"; + cout<<" | Financial support for this project was provided by the |\n"; + cout<<" | National Marine Fisheries Service, the Bering Sea |\n"; + cout<<" | Fisheries Research Foundation,.... |\n"; + cout<<" |----------------------------------------------------------|\n"; + cout<<"\n"; + + cout<<"\n"; + cout<<" |----------------------------------------------------------|\n"; + cout<<" | DOCUMENTATION |\n"; + cout<<" |----------------------------------------------------------|\n"; + cout<<" | online api: http://seacode.github.io/gmacs/index.html |\n"; + cout<<" |----------------------------------------------------------|\n"; + + cout<<"\n"; + exit(1); + } + END_CALCS + + // |------------------------| + // | DATA AND CONTROL FILES | + // |------------------------| + init_adstring datafile; + init_adstring controlfile; + + + !! ad_comm::change_datafile_name(datafile); ECHO(datafile);ECHO(controlfile); + + // |------------------| + // | MODEL DIMENSIONS | + // |------------------| + init_int syr; ///> initial year + init_int nyr; ///> terminal year + init_number jstep; ///> time step (years) + init_int nfleet; ///> number of gears + init_int nsex; ///> number of sexes + init_int nshell; ///> number of shell conditions + init_int nmature; ///> number of maturity types + init_int nclass; ///> number of size-classes + int n_grp; ///> number of sex/newshell/oldshell groups + !! n_grp = nsex * nshell * nmature; + int nlikes + // 1 2 3 4 5 + !! nlikes = 5; // (catch, cpue, sizecomps, recruits, molt_increment data) + + // Set up index pointers + ivector isex(1,n_grp); + ivector ishell(1,n_grp); + ivector imature(1,n_grp); + 3darray pntr_hmo(1,nsex,1,nmature,1,nshell); + LOC_CALCS + int h,m,o; + int hmo=1; + for( h = 1; h <= nsex; h++ ) + { + for( m = 1; m <= nmature; m++ ) + { + for( o = 1; o <= nshell; o++ ) + { + isex(hmo) = h; + ishell(hmo) = o; + imature(hmo) = m; + pntr_hmo(h,m,o) = hmo++; + } + } + } + COUT(isex); + COUT(pntr_hmo); + END_CALCS + + + + init_vector size_breaks(1,nclass+1); + vector mid_points(1,nclass); + !! mid_points = size_breaks(1,nclass) + 0.5 * first_difference(size_breaks); + !! ECHO(syr); ECHO(nyr); ECHO(nfleet); ECHO(nsex); ECHO(nshell);ECHO(nmature); ECHO(nclass); ECHO(size_breaks); + + // |-----------| + // | ALLOMETRY | + // |-----------| + init_vector lw_alfa(1,nsex); + init_vector lw_beta(1,nsex); + matrix mean_wt(1,nsex,1,nclass); + LOC_CALCS + for(int h = 1; h <= nsex; h++ ) + { + mean_wt(h) = lw_alfa(h) * pow(mid_points,lw_beta(h)); + } + END_CALCS + !! ECHO(lw_alfa); ECHO(lw_beta); ECHO(mean_wt); + + // |-------------------------------| + // | FECUNDITY FOR MMB CALCULATION | + // |-------------------------------| + init_vector fecundity(1,nclass); + init_matrix maturity(1,nsex,1,nclass); + !! ECHO(fecundity); ECHO(maturity); + + // |-------------| + // | FLEET NAMES | + // |-------------| + init_adstring name_read_flt; + init_adstring name_read_srv; + !! ECHO(name_read_srv); ECHO(name_read_flt); + + // |--------------| + // | CATCH SERIES | + // |--------------| + //init_int nCatchRows; // number of rows in dCatchData + init_int nCatchDF; + init_ivector nCatchRows(1,nCatchDF); + init_3darray dCatchData(1,nCatchDF,1,nCatchRows,1,11); // array of catch data + matrix obs_catch(1,nCatchDF,1,nCatchRows); + matrix catch_cv(1,nCatchDF,1,nCatchRows); + matrix catch_dm(1,nCatchDF,1,nCatchRows); + LOC_CALCS + for(int k = 1; k <= nCatchDF; k++ ) + { + obs_catch(k) = column(dCatchData(k),5); + catch_cv(k) = column(dCatchData(k),6); + catch_dm(k) = column(dCatchData(k),11); + } + ECHO(nCatchDF); ECHO(nCatchRows); ECHO(dCatchData); + END_CALCS + //!! ECHO(obs_catch); ECHO(catch_cv); + + // From the catch series determine the number of fishing mortality + // rate parameters that need to be estimated. Note that there is + // a number of combinations which require a F to be estimated. The + // ivector nFparams is the number of deviations required for each + // fleet, and nYparams is the number of deviations for female Fs. + ivector nFparams(1,nfleet); + ivector nYparams(1,nfleet); + ivector foff_phz(1,nfleet); + imatrix fhit(syr,nyr,1,nfleet); + imatrix yhit(syr,nyr,1,nfleet); + matrix dmr(syr,nyr,1,nfleet); + + + LOC_CALCS + nFparams.initialize(); + nYparams.initialize(); + fhit.initialize(); + yhit.initialize(); + dmr.initialize(); + foff_phz = -1; + for(int k = 1; k <= nCatchDF; k++ ) + { + for(int i = 1; i <= nCatchRows(k); i++ ) + { + int g = dCatchData(k)(i,3); + int y = dCatchData(k)(i,1); + int h = dCatchData(k)(i,4); + if(!fhit(y,g)) + { + fhit(y,g) ++; + nFparams(g) ++; + dmr(y,g) = catch_dm(k)(i); + } + if(!yhit(y,g) && h == 2) + { + yhit(y,g) ++; + nYparams(g) ++; + foff_phz(g) = 1; + dmr(y,g) = catch_dm(k)(i); + } + } + } + END_CALCS + + + // |----------------------------| + // | RELATIVE ABUNDANCE INDICES | + // |----------------------------| + init_int nSurveys; + init_ivector nSurveyRows(1,nSurveys); + init_3darray dSurveyData(1,nSurveys,1,nSurveyRows,1,7); + matrix obs_cpue(1,nSurveys,1,nSurveyRows); + matrix cpue_cv(1,nSurveys,1,nSurveyRows); + LOC_CALCS + for(int k = 1; k <= nSurveys; k++ ) + { + obs_cpue(k) = column(dSurveyData(k),5); + cpue_cv(k) = column(dSurveyData(k),6); + } + ECHO(nSurveys);ECHO(nSurveyRows);ECHO(dSurveyData); ECHO(obs_cpue); ECHO(cpue_cv); + END_CALCS + + + // |-----------------------| + // | SIZE COMPOSITION DATA | + // |-----------------------| + init_int nSizeComps; + init_ivector nSizeCompRows(1,nSizeComps); + init_ivector nSizeCompCols(1,nSizeComps); + init_3darray d3_SizeComps(1,nSizeComps,1,nSizeCompRows,-7,nSizeCompCols); + 3darray d3_obs_size_comps(1,nSizeComps,1,nSizeCompRows,1,nSizeCompCols); + 3darray d3_res_size_comps(1,nSizeComps,1,nSizeCompRows,1,nSizeCompCols); + matrix size_comp_sample_size(1,nSizeComps,1,nSizeCompRows); + LOC_CALCS + for(int k = 1; k <= nSizeComps; k++ ) + { + dmatrix tmp = trans(d3_SizeComps(k)).sub(1,nSizeCompCols(k)); + d3_obs_size_comps(k) = trans(tmp); + // NOTE This normalizes all observations by row--may be incorrect if shell condition + for (int i=1;i<=nSizeCompRows(k);i++) + d3_obs_size_comps(k,i) /= sum(d3_obs_size_comps(k,i)); + size_comp_sample_size(k) = column(d3_SizeComps(k),0); + } + ECHO(nSizeComps);ECHO(nSizeCompRows); ECHO(nSizeCompCols); ECHO(d3_SizeComps); ECHO(d3_obs_size_comps); + END_CALCS + ivector ilike_vector(1,nlikes) + LOC_CALCS + ilike_vector(1) = nCatchDF; + ilike_vector(2) = nSurveys; + ilike_vector(3) = nSizeComps; + ilike_vector(4) = 1; + ilike_vector(5) = 1; + END_CALCS + + + + // |-----------------------| + // | Growth increment data | + // |-----------------------| + init_int nGrowthObs; + init_matrix dGrowthData(1,nGrowthObs,1,4); + vector dPreMoltSize(1,nGrowthObs); + ivector iMoltIncSex(1,nGrowthObs); + vector dMoltInc(1,nGrowthObs); + vector dMoltIncCV(1,nGrowthObs); + vector mle_alpha(1,nsex); + vector mle_beta(1,nsex); + LOC_CALCS + dPreMoltSize = column(dGrowthData,1); + iMoltIncSex = ivector(column(dGrowthData,2)); + dMoltInc = column(dGrowthData,3); + dMoltIncCV = column(dGrowthData,4); + + dvector xybar(1,nsex); + dvector xx(1,nsex); + dvector xbar(1,nsex); + dvector ybar(1,nsex); + ivector nh(1,nsex); + + nh.initialize(); + xybar.initialize(); + xbar.initialize(); + ybar.initialize(); + xx.initialize(); + + // come up with mle estimates for alpha and beta + // for the linear growth increment model. + if(nGrowthObs) + { + for(int i = 1; i <= nGrowthObs; i++ ) + { + int h = iMoltIncSex(i); + + nh(h)++; + xybar(h) += dPreMoltSize(i) * dMoltInc(i); + xbar(h) += dPreMoltSize(i); + ybar(h) += dMoltInc(i); + xx(h) += square(dPreMoltSize(i)); + } + for( h = 1; h <= nsex; h++ ) + { + xybar(h) /= nh(h); + xbar(h) /= nh(h); + ybar(h) /= nh(h); + xx(h) /= nh(h); + + double slp = (xybar(h) - xbar(h)*ybar(h)) / (xx(h) - square(xbar(h))); + double alp = ybar(h) - slp*xbar(h); + mle_alpha(h) = alp; + mle_beta(h) = -slp; + } + + } + ECHO(nGrowthObs); ECHO(dGrowthData); ECHO(dPreMoltSize); ECHO(iMoltIncSex); ECHO(dMoltInc); ECHO(dMoltIncCV); + END_CALCS + + // |------------------| + // | END OF DATA FILE | + // |------------------| + init_int eof; + !! if (eof != 9999) {cout<<"Error reading data"< Estimated rec_dev phase + int verbose; ///> Flag to print to screen + int bInitializeUnfished; ///> Flag to initialize at unfished conditions + int spr_syr; + int spr_nyr; + number spr_target; + int spr_fleet; + number spr_lambda; + int bUseEmpiricalGrowth; + LOC_CALCS + rdv_phz = int(model_controls(1)); + verbose = int(model_controls(2)); + bInitializeUnfished = int(model_controls(3)); + spr_syr = int(model_controls(4)); + spr_nyr = int(model_controls(5)); + spr_target = model_controls(6); + spr_fleet = int(model_controls(7)); + spr_lambda = model_controls(8); + bUseEmpiricalGrowth = int(model_controls(9)); + ECHO(model_controls); + END_CALCS + + init_int eof_ctl; + !! ECHO(model_controls); if(eof_ctl!=9999){cout<<"Error reading control file"< Male mean fishing mortality + init_vector_vector log_fdev(1,nfleet,1,nFparams,f_phz); ///> Male f devs + init_number_vector log_foff(1,nfleet,foff_phz); ///> Female F offset to Male F + init_vector_vector log_fdov(1,nfleet,1,nYparams,foff_phz); ///> Female F offset to Male F + + // Recruitment deviation parameters + init_bounded_dev_vector rec_ini(1,nclass,-7.0,7.0,rdv_phz); ///> initial size devs + init_bounded_dev_vector rec_dev(syr+1,nyr,-7.0,7.0,rdv_phz);///> recruitment deviations + + // Time-varying natural mortality rate devs. + init_bounded_dev_vector m_dev(1,nMdev,-3.0,3.0,Mdev_phz); + + // Effective sample size parameter for multinomial + init_number_vector log_vn(1,nSizeComps,nvn_phz); + + + matrix nloglike(1,nlikes,1,ilike_vector); + vector nlogPenalty(1,4); + vector priorDensity(1,ntheta+nGrwth+nSurveys); + + objective_function_value objfun; + + number fpen; + number M0; ///> natural mortality rate + number logR0; ///> logarithm of unfished recruits. + number logRbar; ///> logarithm of average recruits(syr+1,nyr) + number logRini; ///> logarithm of initial recruitment(syr). + number ra; ///> Expected value of recruitment distribution + number rbeta; ///> rate parameter for recruitment distribution + number logSigmaR; ///> standard deviation of recruitment deviations. + + vector alpha(1,nsex); ///> intercept for linear growth increment model. + vector beta(1,nsex); ///> slope for the linear growth increment model. + vector gscale(1,nsex); ///> scale parameter for the gamma distribution. + + vector molt_mu(1,nsex); ///> 50% probability of molting at length each year. + vector molt_cv(1,nsex); ///> CV in molting probabilility. + + vector rec_sdd(1,nclass); ///> recruitment size_density_distribution + vector recruits(syr,nyr); ///> vector of estimated recruits + vector survey_q(1,nSurveys); ///> scalers for relative abundance indices (q) + + matrix pre_catch(1,nCatchDF,1,nCatchRows); ///> predicted catch (Baranov eq) + matrix res_catch(1,nCatchDF,1,nCatchRows); ///> catch residuals in log-space + + matrix pre_cpue(1,nSurveys,1,nSurveyRows); ///> predicted relative abundance index + matrix res_cpue(1,nSurveys,1,nSurveyRows); ///> relative abundance residuals + + matrix molt_increment(1,nsex,1,nclass); ///> linear molt increment + matrix molt_probability(1,nsex,1,nclass); ///> probability of molting + + 3darray growth_transition(1,nsex,1,nclass,1,nclass); + 3darray M(1,nsex,syr,nyr,1,nclass); ///> Natural mortality + 3darray Z(1,nsex,syr,nyr,1,nclass); ///> Total mortality + 3darray F(1,nsex,syr,nyr,1,nclass); ///> Fishing mortality + 3darray P(1,nsex,1,nclass,1,nclass); ///> Diagonal matrix of molt probabilities + + //3darray N(1,nsex,syr,nyr+1,1,nclass); ///> Numbers-at-length + 3darray d3_N(1,n_grp,syr,nyr+1,1,nclass); ///> Numbers-at-sex/mature/shell/length. + 3darray ft(1,nfleet,1,nsex,syr,nyr); ///> Fishing mortality by gear + 3darray d3_newShell(1,nsex,syr,nyr+1,1,nclass); ///> New shell crabs-at-length. + 3darray d3_oldShell(1,nsex,syr,nyr+1,1,nclass); ///> Old shell crabs-at-length. + 3darray d3_pre_size_comps(1,nSizeComps,1,nSizeCompRows,1,nSizeCompCols); + 3darray d3_res_size_comps(1,nSizeComps,1,nSizeCompRows,1,nSizeCompCols); + + 4darray S(1,nsex,syr,nyr,1,nclass,1,nclass); ///> Surival Rate (S=exp(-Z)) + 4darray log_slx_capture(1,nfleet,1,nsex,syr,nyr,1,nclass); + 4darray log_slx_retaind(1,nfleet,1,nsex,syr,nyr,1,nclass); + 4darray log_slx_discard(1,nfleet,1,nsex,syr,nyr,1,nclass); + + sdreport_vector sd_log_recruits(syr,nyr); + sdreport_vector sd_log_mmb(syr,nyr); + + +PRELIMINARY_CALCS_SECTION + if( simflag ) + { + if(!global_parfile) + { + cerr << "Must have a gmacs.pin file to use the -sim command line option"< nclass) l=1; + } + } + + + -// ========================================================================================================= PROCEDURE_SECTION - logRbar = theta_parms(1); - M0 = theta_parms(2); - Set_effort(); - Set_selectivity(); - Set_survival(); - Initial_size_structure(); - Set_growth(); - Update_population(); - Get_Survey(); - Get_Catch_Pred(); - Get_ObjFunction(); - if (last_phase()) - Get_Dependent_Vars(); - -// -------------------------------------------------------------------- -FUNCTION Set_effort - f_all.initialize(); // Initialize all Fs to zero - // Convert to Fs - int count, ifl, iyear; - dvariable ratio, ratio_2, delta; - - for (ifl=1; ifl<=nfleet_act; ifl++) - { - count = 0; - for (iyear=styr; iyear<=endyr; iyear++) - { - if (effort(ifl,iyear) > 0) - { - if (f_new(ifl,1) == 0 || iyear < f_new(ifl,2) || iyear > f_new(ifl,3)) - { - count++; - f_all(ifl,iyear) = f_est(ifl,count); - } - else - f_all(ifl,iyear) = -100; // not sure why this is needed? - } - } - } - - // Fill in missing values using a ratio estimator: - for (ifl=1; ifl<=nfleet_act; ifl++) - { - if (f_new(ifl,1) > 0) // Not used for BBRKC case... - { - ratio = 0; ratio_2 = 0; - for (iyear=f_new(ifl,4); iyear<=f_new(ifl,5); iyear++) - { - if (effort(ifl,iyear) > 0) - { - ratio += -log(1.0-f_all(ifl,iyear))/effort(ifl,iyear); - ratio_2 += 1; - } - } - delta = ratio/ratio_2; - for (iyear=f_new(ifl,2); iyear<=f_new(ifl,3); iyear++) - f_all(ifl,iyear) = 1.0-mfexp(-delta*effort(ifl,iyear)); - } - } - -// -------------------------------------------------------------------- -FUNCTION Set_growth - int iclass, jclass; - dvariable total; - strans.initialize(); - for (iclass=1; iclass0) // TODO Check to see the logic here - M(iyr) += Madd_parms(M_pnt(iyr)); - - for (iyr=styr; iyr<=endyr; iyr++) - { - S(iyr) = mfexp(-M(iyr)); - for (ifl=1; ifl<=nfleet_act; ifl++) - { - S_fleet(ifl,iyr) = (1.-selex_fleet(ifl,iyr)*f_all(ifl,iyr)); - exp_rate(ifl,iyr) = f_all(ifl,iyr); - S(iyr) = elem_prod(S(iyr),S_fleet(ifl,iyr)); - } - } -// -------------------------------------------------------------------- -FUNCTION Update_population - for (int iyr=styr; iyr<=endyr; iyr++) - { - // Grow individuals for one time-step: - for (int iclass=1; iclass<=nclass; iclass++) - for (int jclass=1; jclass<=nclass; jclass++) - N(iyr+1,iclass) += strans(jclass,iclass)*N(iyr,jclass)*S(iyr,jclass); - - // Add recruitment for next year: - recruits(iyr) = mfexp(logRbar+recdev(iyr)); - N(iyr+1,1) += recruits(iyr); - } - -// --------------------------------------------------------------------------------------------------------- -FUNCTION Get_Dependent_Vars - // TODO: Check why only selex_fleet(1) is used for mbio_calc. - // TODO: Check 2/12 here in mbio calculation, is this a timing fraction that needs to be generalised? - mbio.initialize(); - for (int iyr=styr; iyr<=endyr; iyr++) - mbio(iyr) += N(iyr)*elem_prod(fecundity,(1-selex_fleet(1,iyr)*f_all(1,iyr))) * - mfexp(-(catch_time(1,iyr)+2/12)*M(iyr)); - -// --------------------------------------------------------------------------------------------------------- -FUNCTION Get_ObjFunction - Get_Likes(); - Get_Priors(); - ObjFun = like_weight*like_val + prior_weight * prior_val; - -// --------------------------------------------------------------------------------------------------------- -FUNCTION Get_Likes - like_val.initialize(); - int ilike=0; - // Likelihood for Catch biomass (or number) - for (int ifl=1;ifl<=nfleet;ifl++) - { - ilike++; ///< Increment the likelihood index - for (int iyr=styr;iyr<=endyr;iyr++) - { - if (catch_biom_obs(ifl,iyr)>0.) - { - if(catch_units(ifl) == 1) - like_val(ilike) += square(log(catch_biom_pred(ifl,iyr)+incd)-log(catch_biom_obs(ifl,iyr)+incd)); - else - like_val(ilike) += square(log(catch_num_pred(ifl,iyr)+incd)-log(catch_num_obs(ifl,iyr)+incd)); - } - } - } - - // Likelihood for catch LFs - for (int ifl=1;ifl<=nfleet;ifl++) - { - ilike++; ///< Increment the likelihood index - for (int i=1;i<=nlf_fleet(ifl);i++) - { - int iyr = yr_fleet_lf(ifl,i); - dvar_vector phat(1,nclass); - phat = incd + fleet_lf_pred(ifl,iyr); - phat /= sum(phat); - dvector pobs(1,nclass); - pobs = incd + fleet_lf_obs(ifl,i); - pobs /= sum(pobs); - like_val(ilike) -= ss_fleet_lf(ifl,i)*pobs*log(phat); - } - like_val(ilike) -= mn_offset(ilike); - } - - // Likelihood for effort indices - q_effort.initialize(); - for (int ifl=1;ifl<=nfleet_act;ifl++) - { - ilike++; ///< Increment the likelihood index - double nn= 0; - - for (iyr=styr;iyr<=endyr;iyr++) - if (effort(ifl,iyr) > 0) - { - if (f_new(ifl,1) == 0 || iyrf_new(ifl,3)) - { - nn++ ; - q_effort(ifl) += log((effort(ifl,iyr)+incd)/(exp_rate(ifl,iyr)+incd)); - } - } - q_effort(ifl) = mfexp(q_effort(ifl)/nn); - for (iyr=styr;iyr<=endyr;iyr++) - if (effort(ifl,iyr) > 0) - if (f_new(ifl,1) == 0 || iyr f_new(ifl,3)) - like_val(ilike) += square(log((effort(ifl,iyr)+incd)/(q_effort(ifl)*(exp_rate(ifl,iyr)+incd)))); - } - - // Likelihood for survey indices - for (int isrv=1;isrv<=nsurvey;isrv++) - { - ilike++; ///< Increment the likelihood index - for (int i=1;i<=nobs_survey(isrv);i++) - { - if(survey_units(isrv) == 1) - like_val(ilike) += 0.5*square(log((survey_biom_obs(isrv,i)+incd)/(survey_biom_pred(isrv,i)+incd))) /survey_var(isrv,i); - else - like_val(ilike) += 0.5*square(log((survey_num_obs(isrv,i)+incd)/(survey_num_pred(isrv,i)+incd))) /survey_var(isrv,i); - } - - // Likelihood for survey LF - ilike++; - for (int i=1;i<=nlf_survey(isrv);i++) - { - dvar_vector phat(1,nclass); - phat = incd + survey_lf_pred(isrv,i); - phat /= sum(phat); - dvector pobs(1,nclass); - pobs = incd + survey_lf_obs(isrv,i); - pobs /= sum(pobs); - like_val(ilike) -= ss_survey_lf(isrv,i)*pobs*log(phat); - /* for(Iclass=1;Iclass<=Nclass;Iclass++) if (SurveyObsLF(isrv,Icnt,Iclass) > 0) // Jim says this seems to imply that a zero means no data...UNTRUE{ Error = (PredSurvey(isrv,iyr,Iclass)+Incc)/(SurveyObsLF(isrv,Icnt,Iclass)+Incc); like_val(ilike) += -1*SSSurveyLF(isrv,Icnt)*SurveyObsLF(isrv,Icnt,Iclass)*log(Error); } */ - } - like_val(ilike) -= mn_offset(ilike); - } - -// --------------------------------------------------------------------------------------------------------- -FUNCTION Get_Priors - prior_val.initialize(); - int iprior = 0; - double nn = 0; - dvariable mean_F=0; - // Prior on F-devs - for (int ifl=1;ifl<=nfleet_act;ifl++) - { - iprior++; - mean_F = 0; nn = 0; - for (iyr=styr;iyr<=endyr;iyr++) - { - if (effort(ifl,iyr) > 0) - { - mean_F += f_all(ifl,iyr); - nn++; - } - mean_F /= nn; - } - for (iyr=styr;iyr<=endyr;iyr++) - if (effort(ifl,iyr) > 0) - prior_val(iprior) += square(f_all(ifl,iyr)-mean_F); - } - iprior++; - // Prior on Rec Devs - prior_val(iprior) = norm2(recdev); - - iprior++; - // Penalties on parameters - prior_val(iprior) = sum(square(gtrans_parms)); - iprior++; - for (int i=1;i<=nselex_pars;i++) - if (selex_phz(i) > 0) - prior_val(iprior) += square(selex_parms(i)); - iprior++; - prior_val(iprior) = sum(square(reten_parms)); - iprior++; - - // Prior on Catchability (q) - for (int isrv=1;isrv<=nsurveyq_pars;isrv++) - { - if (surveyq_psd(isrv) > 0) - { - prior_val(iprior) = square(mfexp(surveyq_parms(isrv))-surveyq_pmean(isrv))/(2.0*square(surveyq_psd(isrv))); - } - iprior++; - } - // M-prior - prior_val(iprior) = square(M0-theta_pmean(2))/(2.0*square(theta_psd(2))); - - // 2nd derivative penalty - iprior++; - dvariable penal = 0.; - for (int isel=1;isel<=nselex_pats;isel++) - if (selex_type(isel,1) == 2) - for (iclass=2;iclass<=nclass-1;iclass++) - penal += square(selex_all(isel,iclass-1)-2.0*selex_all(isel,iclass)+selex_all(isel,iclass+1)); - prior_val(iprior) = penal; - -// --------------------------------------------------------------------------------------------------------- -FUNCTION Get_Catch_Pred; - dvar_vector S1(1,nclass); - dvar_vector N_tmp(1,nclass); ///< Numbers per fishery (temporary accumulator) - int ifl_act; - - fleet_lf_pred.initialize(); - catch_biom_pred.initialize(); - catch_num_pred.initialize(); - N_tmp.initialize(); - - for (int iyr=styr;iyr<=endyr;iyr++) - { - // TODO: Need to loop over number of directed fisheries (presently fixed at 1) fleet control matrix - N_tmp = N(iyr)*mfexp(-catch_time(1,iyr)*M(iyr)); - for (int ifl=1;ifl<=nfleet;ifl++) - { - switch (fleet_control(ifl,1)) - { - case 1 : // Main retained fishery - ifl_act = fleet_control(ifl,2); - S1 = S_fleet(ifl_act,iyr); - fleet_lf_pred(ifl,iyr) = elem_prod(N_tmp , elem_prod((1.-S1),reten(iyr))); - break; - case 2 : // Discard fishery - ifl_act = fleet_control(ifl,2); - S1 = S_fleet(ifl_act,iyr); - fleet_lf_pred(ifl,iyr) = elem_prod(N_tmp , elem_prod((1.-S1),(1.-reten(iyr)))); - break; - case 3 : // Fishery w/ no discard component (can be a bycatch fishery) - ifl_act = fleet_control(ifl,2); - S1 = S_fleet(ifl_act,iyr); - fleet_lf_pred(ifl,iyr) = elem_prod(N_tmp , (1.-S1)); - break; - } - N_tmp = elem_prod(N_tmp,S1); - // Accumulate totals - catch_biom_pred(ifl,iyr) = fleet_lf_pred(ifl,iyr) * weight; - catch_num_pred(ifl,iyr) = sum(fleet_lf_pred(ifl,iyr) ); - if (catch_num_pred(ifl,iyr) >0.) - fleet_lf_pred(ifl,iyr) /= catch_num_pred(ifl,iyr) ; - } - } - -// --------------------------------------------------------------------------------------------------------- -FUNCTION Get_Survey - survey_lf_pred.initialize(); - survey_biom_pred.initialize(); - survey_num_pred.initialize(); - for (int isrv=1;isrv<=nsurvey;isrv++) - { - for (int i=1;i<=nlf_survey(isrv);i++) - { - int iyr = yr_survey_lf(isrv,i); - survey_lf_pred(isrv,i) = elem_prod(N(iyr),selex_survey(isrv,iyr)); // note use if iyr here...t - survey_lf_pred(isrv,i) /= sum(survey_lf_pred(isrv,i)); - } - for (int i=1;i<=nobs_survey(isrv);i++) - { - int iyr = yr_survey(isrv,i); - dvar_vector N_tmp = elem_prod(N(iyr),selex_survey(isrv,iyr)); // note use if iyr here...t - survey_biom_pred(isrv,i) = N_tmp * weight; - survey_num_pred(isrv,i) = sum(N_tmp); - } - } - -// ========================================================================================================= + // Initialize model parameters + initialize_model_parameters(); + if( verbose ) cout<<"Ok after initializing model parameters ..."< *pSLX[slx_rows(k)-1]; + for( j = 0; j < slx_rows(k); j++ ) + { + switch (slx_type(k)) + { + case 1: //coefficients + pv = mfexp(log_slx_pars(k)(block)); + pSLX[j] = new cstar::SelectivityCoefficients(pv); + break; + + case 2: //logistic + p1 = mfexp(log_slx_pars(k,block,1)); + p2 = mfexp(log_slx_pars(k,block,2)); + pSLX[j] = new cstar::LogisticCurve(p1,p2); + break; + + case 3: // logistic95 + p1 = mfexp(log_slx_pars(k,block,1)); + p2 = mfexp(log_slx_pars(k,block,2)); + pSLX[j] = new cstar::LogisticCurve95(p1,p2); + break; + } + block ++; + } + + // fill array with selectivity coefficients + j = 0; + for( h = 1; h <= nsex; h++ ) + { + for( i = slx_styr(k); i <= slx_edyr(k); i++ ) + { + int kk = fabs(slx_indx(k)); // gear index + + if(slx_indx(k) > 0) + { + log_slx_capture(kk)(h)(i) = pSLX[j]->logSelectivity(mid_points); + } + else + { + log_slx_retaind(kk)(h)(i) = pSLX[j]->logSelectivity(mid_points); + log_slx_discard(kk)(h)(i) = log(1.0 - exp(log_slx_retaind(kk)(h)(i))); + } + } + + // Increment counter if sex-specific selectivity curves are defined. + if(slx_bsex(k)) j++; + } + + delete *pSLX; + } + + + + /** + * @brief Calculate fishing mortality rates for each fleet. + * @details For each fleet estimate scaler log_fbar and deviates (f_devs). + * + * In the event that there is effort data and catch data, then it's possible + * to estimate a catchability coefficient and predict the catch for the + * period of missing catch/discard data. Best option for this would be + * to use F = q*E, where q = F/E. Then in the objective function, minimize + * the variance in the estimates of q, and use the mean q to predict catch. + * Or minimize the first difference and assume a random walk in q. + * + * Note that this function calculates the fishing mortality rate including + * deaths due to discards. Where lambda is the discard mortality rate. + * + * Note also that Jie estimates F for retained fishery, f for male discards and + * f for female discards. Not recommended to have separate F' for retained and + * discard fisheries, but might be ok to have sex-specific F's. + * + * TODO + * -[ ] fix discard mortality rate. + */ +FUNCTION calc_fishing_mortality + int h,i,k,ik,yk; + double lambda; // discard mortality rate + F.initialize(); + ft.initialize(); + dvariable log_ftmp; + dvar_vector sel(1,nclass); + dvar_vector ret(1,nclass); + dvar_vector tmp(1,nclass); + + for( k = 1; k <= nfleet; k++ ) + { + for( h = 1; h <= nsex; h++ ) + { + ik=1; yk=1; + for( i = syr; i <= nyr; i++ ) + { + if(fhit(i,k)) + { + log_ftmp = log_fbar(k) + log_fdev(k,ik++); + + if(yhit(i,k)) + { + log_ftmp += (h-1) * (log_foff(k) + log_fdov(k,yk++)); + } + ft(k)(h)(i) = mfexp(log_ftmp); + + lambda = dmr(i,k); + + sel = exp(log_slx_capture(k)(h)(i)); + ret = exp(log_slx_retaind(k)(h)(i)) * slx_nret(h,k); + tmp = elem_prod(sel,ret + (1.0 - ret) * lambda); + + F(h)(i) += ft(k,h,i) * tmp; + } + } + } + } + + + + + /** + * @brief Compute growth increments + * @details Presently based on liner form + * + * @param vSizes is a vector of size data from which to compute predicted values + * @param iSex is an integer vector indexing sex (1 = male, 2 = female ) + * @return dvar_vector of predicted growth increments + */ +FUNCTION dvar_vector calc_growth_increments(const dvector vSizes, const ivector iSex) + { + if( vSizes.indexmin() != iSex.indexmin() || vSizes.indexmax() != iSex.indexmax() ) + { + cerr<<"indices don't match..."< syr ) + { + recruits(i) *= mfexp(rec_dev(i)); + } + rt = (0.5 * recruits(i)) * rec_sdd; + + for( ig = 1; ig <= n_grp; ig++ ) + { + h = isex(ig); + m = imature(ig); + o = ishell(ig); + + if( o == 1 ) // newshell + { + A = growth_transition(h) * S(h)(i); + x = d3_N(ig)(i); + d3_N(ig)(i+1) = elem_prod(x,diagonal(P(h))) * A + rt; + + } + + if( o == 2 ) // oldshell + { + x = d3_N(ig)(i); + y = d3_N(ig-1)(i); + t1 = (Id - P(h)) * S(h)(i); + + // add oldshell non-terminal molts to newshell + d3_N(ig-1)(i+1) += elem_prod(x,diagonal(P(h))) * A; + + // oldshell + d3_N(ig)(i+1) = (x+d3_N(ig-1)(i)) * t1; + } + + if ( o == 1 && m == 2 ) // terminal molt to new shell. + { + + } + + if ( o == 2 && m == 2 ) // terminal molt newshell to oldshell. + { + + } + + } + + + // TO BE DEPRECATED +// for( h = 1; h <= nsex; h++ ) +// { +// At = growth_transition(h) * S(h)(i); +// //for( l = 1; l <= nclass; l++ ) +// //{ +// // At(l) *= S(h)(i)(l); +// //} +// +// // New-shell Old-shell accounting +// dvar_vector tmpNew = elem_prod(molt_probability(h),N(h)(i)); +// dvar_vector tmpOld = N(h)(i) - tmpNew; +// d3_newShell(h)(i+1) = tmpNew * At; +// d3_oldShell(h)(i+1) = elem_prod(tmpOld,diagonal(S(h)(i))); +// +// N(h)(i+1) = (0.5 * recruits(i)) * rec_sdd; +// N(h)(i+1) += d3_newShell(h)(i+1) + d3_oldShell(h)(i+1); +// +// // d3_newShell(h)(i+1) = elem_prod(1.0-diagonal(growth_transition(h)) , N(h)(i+1)); +// // d3_oldShell(h)(i+1) = elem_prod(diagonal(growth_transition(h)) , N(h)(i+1)); +// } + } + + + if(verbose) COUT(d3_N(1)+d3_N(2)); + + + + + /** + * @brief Calculate predicted catch observations + * @details The function uses the Baranov catch equation to predict the retained + * and discarded catch. + * + * Assumptions: + * 1) retained (landed catch) is assume to be newshell male only. + * 2) discards are all females (new and old) and male only crab. + * 3) Natural and fishing mortality occur simultaneously. + * 4) discard is the total number of crab caught and discarded. + * + * + * @param [description] + * @return NULL + */ +FUNCTION calc_predicted_catch + int h,i,j,k,ig; + int type,unit; + pre_catch.initialize(); + dvariable tmp_ft; + dvar_vector sel(1,nclass); + dvar_vector nal(1,nclass); // numbers or biomass at length. + + + for(int kk = 1; kk <= nCatchDF; kk++ ) + { + for( j = 1; j <= nCatchRows(kk); j++ ) + { + i = dCatchData(kk)(j,1); // year index + k = dCatchData(kk)(j,3); // gear index + h = dCatchData(kk)(j,4); // sex index + + // Type of catch (retained = 1, discard = 2) + type = int(dCatchData(kk)(j,7)); + + // Units of catch equation (1 = biomass, 2 = numbers) + unit = int(dCatchData(kk)(j,8)); + + // Total catch + if(h) // sex specific + { + nal.initialize(); + sel = log_slx_capture(k)(h)(i); + switch(type) + { + case 1: // retained catch + // Question here about what the retained catch is. + // Should probably include shell condition here as well. + // Now assuming both old and new shell are retained. + sel = exp( sel + log_slx_retaind(k)(h)(i) ); + for(int m = 1; m <= nmature; m++ ) + { + for(int o = 1; o <= nshell; o++ ) + { + ig = pntr_hmo(h,m,o); + nal += d3_N(ig)(i); + } + } + break; + + case 2: // discard catch + sel = elem_prod(exp(sel),1.0 - exp( log_slx_retaind(k)(h)(i) )); + for(int m = 1; m <= nmature; m++ ) + { + for(int o = 1; o <= nshell; o++ ) + { + ig = pntr_hmo(h,m,o); + nal += d3_N(ig)(i); + } + } + break; + } + tmp_ft = ft(k)(h)(i); + nal = (unit==1) ? elem_prod(nal,mean_wt(h)) : nal; + + pre_catch(kk)(j) = nal + * elem_div(elem_prod(tmp_ft*sel,1.0-exp(-Z(h)(i))),Z(h)(i)); + } + else // sexes combibed + { + for( h = 1; h <= nsex; h++ ) + { + nal.initialize(); + sel = log_slx_capture(k)(h)(i); + switch(type) + { + case 1: // retained catch + sel = exp( sel + log_slx_retaind(k)(h)(i) ); + for(int m = 1; m <= nmature; m++ ) + { + ig = pntr_hmo(h,m,1); //indexes new shell. + nal += d3_N(ig)(i); + } + break; + + case 2: // discard catch + sel = + elem_prod(exp(sel),1.0 - exp( log_slx_retaind(k)(h)(i) )); + for(int m = 1; m <= nmature; m++ ) + { + for(int o = 1; o <= nshell; o++ ) + { + ig = pntr_hmo(h,m,o); + nal += d3_N(ig)(i); + } + } + break; + } + tmp_ft = ft(k)(h)(i); + nal = (unit==1) ? elem_prod(nal,mean_wt(h)) : nal; + + pre_catch(kk)(j) += nal + * elem_div(elem_prod(tmp_ft*sel,1.0-exp(-Z(h)(i))),Z(h)(i)); + } + } + } + // Catch residuals + res_catch(kk) = log(obs_catch(kk)) - log(pre_catch(kk)); + if(verbose)COUT(pre_catch(kk)(1)); + } + + + + + + + + + + /** + * @brief Calculate predicted relative abundance and residuals + * @author Steve Martell + * + * @details This function uses the conditional mle for q to scale + * the population to the relative abundance index. Assumed errors in + * relative abundance are lognormal. Currently assumes that the CPUE + * index is made up of both retained and discarded crabs. + * + * Question regarding use of shell condition in the relative abundance index. + * Currenlty there is no shell condition information in the CPUE data, should + * there be? Similarly, there is no mature immature information, should there be? + * + */ +FUNCTION calc_relative_abundance + int g,h,i,j,k,ig; + int unit; + dvar_vector nal(1,nclass); // numbers at length + dvar_vector sel(1,nclass); // selectivity at length + + + for( k = 1; k <= nSurveys; k++ ) + { + dvar_vector V(1,nSurveyRows(k)); + V.initialize(); + for( j = 1; j <= nSurveyRows(k); j++ ) + { + nal.initialize(); + i = dSurveyData(k)(j)(1); // year index + g = dSurveyData(k)(j)(3); // gear index + h = dSurveyData(k)(j)(4); // sex index + unit = dSurveyData(k)(j)(7); // units 1==biomass 2==Numbers + + if(h) + { + sel = exp(log_slx_capture(g)(h)(i)); + for(int m = 1; m <= nmature; m++ ) + { + for(int o = 1; o <= nshell; o++ ) + { + ig = pntr_hmo(h,m,o); + nal += (unit==1)? + elem_prod(d3_N(ig)(i),mean_wt(h)): + d3_N(ig)(i); + } + } + + // switch(unit) + // { + // case 1: + // nal=elem_prod(N(h)(i),mean_wt(h)); + // break; + // case 2: + // nal=N(h)(i); + // break; + // } + V(j) = nal * sel; + } + else + { + for( h = 1; h <= nsex; h++ ) + { + sel = exp(log_slx_capture(g)(h)(i)); + for(int m = 1; m <= nmature; m++ ) + { + for(int o = 1; o <= nshell; o++ ) + { + ig = pntr_hmo(h,m,o); + nal += (unit==1)? + elem_prod(d3_N(ig)(i),mean_wt(h)): + d3_N(ig)(i); + } + } + + // switch(unit) + // { + // case 1: + // nal=elem_prod(N(h)(i),mean_wt(h)); + // break; + // case 2: + // nal=N(h)(i); + // break; + // } + V(j) += nal * sel; + } + } + } // nSurveyRows(k) + dvar_vector zt = log(obs_cpue(k)) - log(V); + dvariable zbar = mean(zt); + res_cpue(k) = zt - zbar; + survey_q(k) = mfexp(zbar); + pre_cpue(k) = survey_q(k) * V; + } + + + + + + /** + * @brief Calculate predicted size composition data. + * @details Predicted size composition data are given in proportions. + * Size composition strata: + * - sex + * - type (retained or discard) + * - shell condition + * - mature or immature + * + * NB Sitting in a campground on the Orgeon Coast writing this code, + * with baby Tabitha sleeping on my back. + * + * TODO: + * - add pointers for shell type. DONE + * - add pointers for maturity state. DONE + * + * Jan 5, 2015. + * Size compostion data can come in a number of forms. + * Given sex, maturity and 3 shell conditions, there are 12 possible + * combinations for adding up the numbers at length (nal). + * Shell + * Sex Maturity condition Description + * _____________________________________________________________ + * Male 0 1 immature, new shell + * ! Male 0 2 immature, old shell + * ! Male 0 0 immature, new & old shell 1 Male, immature, new shell + * Male 1 1 mature, new shell + * Male 1 2 mature, old shell + * Male 1 0 mature, new & old shell + * Female 0 1 immature, new shell + * !Female 0 2 immature, old shell + * !Female 0 0 immature, new & old shell + * Female 1 1 mature, new shell + * Female 1 2 mature, old shell + * Female 1 0 mature, new & old shell + * _____________________________________________________________ + * + * Call function to get the appropriate numbers-at-length. + * + * TODO: + * [x] Check to ensure new shell old shell is working. + * [ ] Add maturity component for data sets with mature old and mature new. + * [ ] Issue 53, comps/total(sex,shell cond) + */ +FUNCTION calc_predicted_composition + int h,i,j,k,ig; + int type,shell,bmature ; + d3_pre_size_comps.initialize(); + dvar_vector dNtmp(1,nclass); + dvar_vector dNtot(1,nclass); + dvar_vector nal(1,nclass); + + for(int ii = 1; ii <= nSizeComps; ii++ ) + { + for(int jj = 1; jj <= nSizeCompRows(ii); jj++ ) + { + dNtmp.initialize(); + dNtot.initialize(); + nal.initialize(); + i = d3_SizeComps(ii)(jj,-7); // year + j = d3_SizeComps(ii)(jj,-6); // seas + k = d3_SizeComps(ii)(jj,-5); // gear + h = d3_SizeComps(ii)(jj,-4); // sex + type = d3_SizeComps(ii)(jj,-3); // retained or discard + shell = d3_SizeComps(ii)(jj,-2); // shell condition + bmature = d3_SizeComps(ii)(jj,-1); // boolean for maturity + + + if(h) // sex specific + { + dvar_vector sel = exp(log_slx_capture(k)(h)(i)); + dvar_vector ret = exp(log_slx_retaind(k)(h)(i)); + dvar_vector dis = exp(log_slx_discard(k)(h)(i)); + // dvar_vector tmp = N(h)(i); + + for(int m = 1; m <= nmature; m++ ) + { + for(int o = 1; o <= nshell; o++ ) + { + ig = pntr_hmo(h,m,o); + if(shell == 0) nal += d3_N(ig)(i); + if(shell == o) nal += d3_N(ig)(i); + } + } + dvar_vector tmp = nal; + + switch (type) + { + case 1: // retained + dNtmp = elem_prod(tmp,elem_prod(sel,ret)); + break; + case 2: // discarded + dNtmp = elem_prod(tmp,elem_prod(sel,dis)); + break; + default: // both retained and discarded + dNtmp = elem_prod(tmp,sel); + break; + } + + } + else // sexes combined in the observations + { + for( h = 1; h <= nsex; h++ ) + { + dvar_vector sel = exp(log_slx_capture(k)(h)(i)); + dvar_vector ret = exp(log_slx_retaind(k)(h)(i)); + dvar_vector dis = exp(log_slx_discard(k)(h)(i)); + // dvar_vector tmp = N(h)(i); + + for(int m = 1; m <= nmature; m++ ) + { + for(int o = 1; o <= nshell; o++ ) + { + ig = pntr_hmo(h,m,o); + if(shell == 0) nal += d3_N(ig)(i); + if(shell == o) nal += d3_N(ig)(i); + } + } + dvar_vector tmp = nal; + + switch (type) + { + case 1: + dNtmp += elem_prod(tmp,ret); + break; + case 2: + dNtmp += elem_prod(tmp,dis); + break; + default: + dNtmp += elem_prod(tmp,sel); + break; + } + } + } + d3_pre_size_comps(ii)(jj) = dNtmp / sum(dNtmp); + } + + } + + + /** + * @brief Calculate prior density functions for leading parameters. + * @details + * - case 0 is a uniform density between the lower and upper bounds. + * - case 1 is a normal density with mean = p1 and sd = p2 + * - case 2 is a lognormal density with mean = log(p1) and sd = p2 + * - case 3 is a beta density bounded between lb-ub with p1 and p2 as alpha & beta + * - case 4 is a gamma density with parameters p1 and p2. + * + * TODO + * Make this a generic function. + * Agrs would be vector of parameters, and matrix of controls + * @param theta a vector of parameters + * @param C matrix of controls (priorType, p1, p2, lb, ub) + * @return vector of prior densities for each parameter + * + */ +FUNCTION calculate_prior_densities + double p1,p2; + double lb,ub; + priorDensity.initialize(); + + for(int i = 1; i <= ntheta; i++ ) + { + // for(int j = 1; j <= ipar_vector(i); j++ ) + { + int priorType = int(theta_control(i,5)); + p1 = theta_control(i,6); + p2 = theta_control(i,7); + switch(priorType) + { + // uniform + case 0: + priorDensity(i) = -log(1.0 / (p2-p1)); + break; + + // normal + case 1: + priorDensity(i) = dnorm(theta(i),p1,p2); + break; + + // lognormal + case 2: + priorDensity(i) = dlnorm(theta(i),log(p1),p2); + break; + + // beta + case 3: + lb = theta_control(i,2); + ub = theta_control(i,3); + priorDensity(i) = dbeta((theta(i)-lb)/(ub-lb),p1,p2); + break; + + // gamma + case 4: + priorDensity(i) = dgamma(theta(i),p1,p2); + break; + } + } + } + + // ---Continue with catchability priors----------------------- + int iprior = ntheta + 1; + for (int i=1;i<=nSurveys;i++) + { + int itype = int(prior_qtype(i)); + switch(itype) + { + // Analytical soln, no prior (uniform, uniformative) + case 0: + break; + // Prior on analytical soln, log-normal + case 1: + priorDensity(iprior) = dnorm(log(survey_q(i)),log(prior_qbar(i)),prior_qsd(i)); + break; + } + iprior++; + } + + + + + + + + + + /** + * @brief calculate objective function + * @details + * + * Likelihood components + * -# likelihood of the catch data (assume lognormal error) + * -# likelihood of relative abundance data + * -# likelihood of size composition data + * + * Penalty components + * -# Penalty on log_fdev to ensure they sum to zero. + * -# Penalty to regularize values of log_fbar. + * -# Penalty to constrain random walk in natural mortaliy rates + * + */ +FUNCTION calc_objective_function + + // |---------------------------------------------------------------------------------| + // | NEGATIVE LOGLIKELIHOOD COMPONENTS FOR THE OBJECTIVE FUNCTION | + // |---------------------------------------------------------------------------------| + nloglike.initialize(); + + // 1) Likelihood of the catch data. + if(verbose) COUT(res_catch(1)); + for(int k = 1; k <= nCatchDF; k++ ) + { + dvector catch_sd = sqrt( log( 1.0+square(catch_cv(k)) ) ); + nloglike(1,k) += dnorm(res_catch(k),catch_sd); + } + + + + + // 2) Likelihood of the relative abundance data. + if(verbose) COUT(res_cpue(1)); + for(int k = 1; k <= nSurveys; k++ ) + { + dvector cpue_sd = sqrt(log(1.0 + square(cpue_cv(k)))); + nloglike(2,k) += dnorm(res_cpue(k),cpue_sd(k)); + } + + + + + // 3) Likelihood for size composition data. + for(int ii = 1; ii <= nSizeComps; ii++) + { + dmatrix O = d3_obs_size_comps(ii); + dvar_matrix P = d3_pre_size_comps(ii); + dvar_vector log_effn = log(exp(log_vn(ii)) * size_comp_sample_size(ii)); + + bool bCmp = bTailCompression(ii); + acl::negativeLogLikelihood *ploglike; + + switch(nAgeCompType(ii)) + { + case 1: // multinomial with fixed or estimated n + ploglike = new acl::multinomial(O,bCmp); + break; + + case 2: // robust approximation to the multinomial + if( current_phase() <= 3 || !last_phase() ) + ploglike = new acl::multinomial(O,bCmp); + else + ploglike = new acl::robust_multi(O,bCmp); + break; + } + // Compute residuals in the last phase. + if(last_phase()) + { + d3_res_size_comps(ii) = ploglike->residual(log_effn,P); + } + + // now compute the likelihood. + nloglike(3,ii) += ploglike->nloglike(log_effn,P); + + + } + + + // 4) Likelihood for recruitment deviations. + dvariable sigR = mfexp(logSigmaR); + nloglike(4,1) = dnorm(rec_dev,sigR); + + + // 5) Likelihood for growth increment data + if( !bUseEmpiricalGrowth && ( active(theta(7)) || active(theta(8)) ) ) + { + dvar_vector MoltIncPred = calc_growth_increments(dPreMoltSize, iMoltIncSex); + nloglike(5,1) = dnorm(log(dMoltInc) - log(MoltIncPred),dMoltIncCV); + } + + + // |---------------------------------------------------------------------------------| + // | PENALTIES AND CONSTRAINTS | + // |---------------------------------------------------------------------------------| + nlogPenalty.initialize(); + + // 1) Penalty on log_fdev to ensure they sum to zero + for(int k = 1; k <= nfleet; k++ ) + { + dvariable s = mean(log_fdev(k)); + nlogPenalty(1) += 10000.0*s*s; + } + + + // 2) Penalty on mean F to regularize the solution. + int irow=1; + if(last_phase()) irow=2; + dvariable fbar; + for(int k = 1; k <= nfleet; k++ ) + { + fbar = mean(ft(k)); + nlogPenalty(2) += dnorm(fbar,pen_fbar(k),pen_fstd(irow,k)); + } + + + // 3) Penalty to constrain M in random walk + if( active(m_dev) ) + { + nlogPenalty(3) = dnorm(m_dev,m_stdev); + } + + + objfun = sum(nloglike) + sum(nlogPenalty) + sum(priorDensity); + if( verbose==2 ) + { + COUT(objfun); + COUT(nloglike); + COUT(nlogPenalty); + COUT(priorDensity); + } + + /** + * @brief Simulation model + * @details Uses many of the same routines as the assessment + * model, over-writes the observed data in memory with simulated + * data. + * + */ +FUNCTION simulation_model + // random number generator + random_number_generator rng(rseed); + + // Initialize model parameters + initialize_model_parameters(); + + // Fishing fleet dynamics ... + calc_selectivities(); + calc_fishing_mortality(); + + + dvector drec_dev(syr+1,nyr); + drec_dev.fill_randn(rng); + rec_dev = exp(logSigmaR) * drec_dev; + + // Population dynamics ... + calc_growth_increments(); + calc_molting_probability(); + calc_growth_transition(); + calc_natural_mortality(); + calc_total_mortality(); + calc_recruitment_size_distribution(); + calc_initial_numbers_at_length(); + update_population_numbers_at_length(); + + // observation models ... + calc_predicted_catch(); + calc_relative_abundance(); + calc_predicted_composition(); + + + // add observation errors to catch. + dmatrix err_catch(1,nCatchDF,1,nCatchRows); + err_catch.fill_randn(rng); + dmatrix catch_sd(1,nCatchDF,1,nCatchRows); + for(int k = 1; k <= nCatchDF; k++ ) + { + catch_sd(k) = sqrt(log(1.0 + square(catch_cv(k)))); + obs_catch(k) = value(pre_catch(k)); + err_catch(k) = elem_prod(catch_sd(k),err_catch(k)) - 0.5*square(catch_sd(k)); + obs_catch(k) = elem_prod(obs_catch(k),exp(err_catch(k))); + } + + + // add observation errors to cpue. & fill in dSurveyData column 5 + dmatrix err_cpue(1,nSurveys,1,nSurveyRows); + dmatrix cpue_sd = sqrt(log(1.0 + square(cpue_cv))); + err_cpue.fill_randn(rng); + obs_cpue = value(pre_cpue); + err_cpue = elem_prod(cpue_sd,err_cpue) - 0.5*square(cpue_sd); + obs_cpue = elem_prod(obs_cpue,exp(err_cpue)); + for(int k = 1; k <= nSurveys; k++ ) + { + for(int i = 1; i <= nSurveyRows(k); i++ ) + { + dSurveyData(k)(i,5) = obs_cpue(k,i); + } + } + + + // add sampling errors to size-composition. + // 3darray d3_obs_size_comps(1,nSizeComps,1,nSizeCompRows,1,nSizeCompCols); + double tau; + for(int k = 1; k <= nSizeComps; k++ ) + { + for(int i = 1; i <= nSizeCompRows(k); i++ ) + { + tau = sqrt(1.0 / size_comp_sample_size(k)(i)); + dvector p = value(d3_pre_size_comps(k)(i)); + d3_obs_size_comps(k)(i) = rmvlogistic(p,tau,rseed+k+i); + } + } + // COUT(d3_pre_size_comps(1)(1)); + // COUT(d3_obs_size_comps(1)(1)); + REPORT_SECTION - cout << "-----End of phase "< matrix to get distribution of size at say, nclass "ages" (meaning years since initial recruitment) + dvar3_array growth_matrix(1,nsex,1,nclass,1,nclass); + for (int isex=1;isex<=nsex;isex++) + { + int iage=1; + // Set the initial size frequency + growth_matrix(isex,iage) = growth_transition(isex,iage); + mean_size(isex,iage) = growth_matrix(isex,iage) * mid_points /sum(growth_matrix(isex,iage)); + for (iage=2;iage<=nclass;iage++) + { + growth_matrix(isex,iage) = growth_matrix(isex,iage-1)*growth_transition(isex); + mean_size(isex,iage) = growth_matrix(isex,iage) * mid_points / sum(growth_matrix(isex,iage)); + } + } + REPORT(growth_matrix); + REPORT(mean_size); + for(int ii = 1; ii <= nSizeComps; ii++) + { + // Set final sample-size for composition data for comparisons + size_comp_sample_size(ii) = value(exp(log_vn(ii))) * size_comp_sample_size(ii); + } + REPORT(size_comp_sample_size); + } + // Print total numbers at length + dvar_matrix N_len(syr,nyr+1,1,nclass); + dvar_matrix N_mm(syr,nyr+1,1,nclass); + dvar_matrix N_males(syr,nyr+1,1,nclass); + dvar_matrix N_males_old(syr,nyr+1,1,nclass); + N_len.initialize(); + N_males.initialize(); + N_mm.initialize(); + N_males_old.initialize(); + for (int i=syr;i<=nyr+1;i++) + for (int j=1;j<=nclass;j++) + for (int k=1;k<=n_grp;k++) + { + if (isex(k)==1) + { + N_males(i,j) += d3_N(k,i,j); + if (ishell(k)==2) + N_males_old(i,j) += d3_N(k,i,j); + if (imature(k)==1) + N_mm(i,j) += d3_N(k,i,j); + } + N_len(i,j) += d3_N(k,i,j); + } + + REPORT(N_len); + REPORT(N_mm); + REPORT(N_males); + REPORT(N_males_old); + REPORT(molt_increment); + REPORT(dPreMoltSize); + REPORT(iMoltIncSex); + REPORT(dMoltInc); + if(bUseEmpiricalGrowth) + { + dvector pMoltInc = dMoltInc; + REPORT(pMoltInc); + } + else + { + dvar_vector pMoltInc = calc_growth_increments(dPreMoltSize,iMoltIncSex); + REPORT(pMoltInc); + } + REPORT(survey_q); + REPORT(P); + REPORT(growth_transition); + dmatrix size_transition_M(1,nclass,1,nclass); + dmatrix size_transition_F(1,nclass,1,nclass); + + size_transition_M = value(P(1) * growth_transition(1)); + for (int i=1;i<=nclass;i++) + size_transition_M(i,i) += value(1.-P(1,i,i)); + + REPORT(size_transition_M); + + if (nsex==2) + { + size_transition_F = value(P(2) * growth_transition(2)); + for (int i=1;i<=nclass;i++) + size_transition_M(i,i) += value(1.-P(2,i,i)); + REPORT(size_transition_F); + } + + /** + * @brief Calculate mature male biomass + + * + * + * TODO correct for timing of when the MMB is calculated + * + * @return dvar_vector + */ +FUNCTION dvar_vector calc_mmb() + dvar_vector mmb(syr,nyr); + mmb.initialize(); + int ig,m,o; + int h = 1; // males + for(int i = syr; i <= nyr; i++ ) + { + if( nmature == 1 ) // continous molt + { + m = 1; + } + else if( nmature == 2 ) // terminal molt males only + { + m = 2; + } + for( o = 1; o <= nshell; o++ ) + { + ig = pntr_hmo(h,m,o); + mmb(i) += d3_N(ig)(i) * elem_prod(mean_wt(h),maturity(h)); + } + } + return(mmb); + + +// To be deprecated? +//FUNCTION dvariable robust_multi(const dmatrix O, const dvar_matrix P, const dvar_vector lnN) +// /** +// * @brief Robustified Multinomial likleihood for composition data. +// * @details Follows Fournier's approach +// * +// * @param lnN The assumed log of sample size +// * @return returns the negative log likelihood. +// * +// * TO BE Deprecated, now lives in robust_multi.cpp +// */ +// if( lnN.indexmin() != O.rowmin() || lnN.indexmax() != O.rowmax() ) +// { +// cerr<<"Sample size index do not match row index in\ +// observed size composition matrix."<get_fspr(ifleet,spr_target,_fhk,_sel,_ret,_dmr); + spr_bspr = ptrSPR->get_bspr(); + + // OFL Calculations + dvector mmb = value(calc_mmb()); + double cuttoff = 0.1; + double limit = 0.25; + spr_fofl = ptrSPR->get_fofl(cuttoff,limit,mmb(nyr)); + spr_cofl = ptrSPR->get_cofl(_N); + + + + + + + + RUNTIME_SECTION - maximum_function_evaluations 500,1500,2500,25000,25000 - convergence_criteria 0.01,1.e-4,1.e-5,1.e-5 - \ No newline at end of file + maximum_function_evaluations 500, 500, 1500, 25000, 25000 + convergence_criteria 1.e-4, 1.e-4, 1.e-4, 1.e-4, 1.e-4, + + +GLOBALS_SECTION + #include + #include + //#include + #if defined __APPLE__ || defined __linux + #include "./include/libgmacs.h" + #endif + + #if defined _WIN32 || defined _WIN64 + #include "include\libgmacs.h" + #endif + + + + + time_t start,finish; + long hour,minute,second; + double elapsed_time; + + // Define objects for report file, echoinput, etc. + /** + \def report(object) + Prints name and value of \a object on ADMB report %ofstream file. + */ + #undef REPORT + #define REPORT(object) report << #object "\n" << setw(8) \ + << setprecision(4) << setfixed() << object << endl; + + /** + * + * \def COUT(object) + * Prints object to screen during runtime. + * cout < + +#ifndef NLOGLIKE_H +#define NLOGLIKE_H + +#define TINY 1.e-08 + + + + + + + +namespace acl +{ + + + /** + * Base class for negative loglikelihoods used in composition data. + * @details This class has two virtual methods: nloglike and residual. + * + */ + class negativeLogLikelihood + { + private: + int r1,r2; + int c1,c2; + ivector m_jmin; + ivector m_jmax; + dmatrix m_O; + dmatrix m_Or; + + public: + //virtual const dvariable nloglike(const dmatrix& _O) const = 0; + //virtual const dmatrix residual(const dmatrix& _O) const = 0; + + virtual const dvariable nloglike(const dvar_vector& _n, const dvar_matrix& _P) const = 0; + virtual const dmatrix residual(const dvar_vector& _n, const dvar_matrix& _P) const = 0; + + negativeLogLikelihood(){} + negativeLogLikelihood(const dmatrix& _O) + :m_O(_O) + { + r1 = m_O.rowmin(); + r2 = m_O.rowmax(); + c1 = m_O.colmin(); + c2 = m_O.colmax(); + } + ~negativeLogLikelihood(){} + + dmatrix get_O() const{ return m_O; } + void set_O(dmatrix _O){ this->m_O = _O;} + + dmatrix get_Or() const{ return m_Or; } + void set_Or(dmatrix _O){ this->m_Or = _O;} + + const ivector get_jmin() const { return m_jmin; } + const ivector get_jmax() const { return m_jmax; } + + void tail_compression(); ///> get indexes for ragged objects + + template + inline + const T compress(const T& _M) const; ///> make ragged objects + + }; + + + template + inline + const T acl::negativeLogLikelihood::compress(const T& _M) const + { + // cout<<"In compress"<m_vn = _n;} + + // dvar_matrix get_P() const { return m_P; } + // void set_P(dvar_matrix _P) { this->m_P = _P;} + + + // // negative log likelihood + // const dvariable nloglike(const dvector& _vn, const dvar_matrix& _P) const + // { + // if(m_bCompress) + // { + // dmatrix Or = compress(this->get_O()); + // dvar_matrix Pr = compress(_P); + // return dmultinom(_vn,Or,Pr); + // } + // else + // { + // return dmultinom(_vn,this->get_O(),_P); + // } + // } + + // // pearson residuals + // const dmatrix residual(const dvector& _n, const dvar_matrix& _P) const + // { + // return pearson_residuals(_n,this->get_O(),_P); + // } + + + // const dvariable dmultinom(const dvector& log_vn, + // const dmatrix& o, + // const dvar_matrix& p) const; + + // const dmatrix pearson_residuals(const dvector& log_vn, + // const dmatrix& o, + // const dvar_matrix p) const; + // }; + + /** + * @brief Class for multinomial negative loglikelihood. + * @details This is a derived class which inherits the virtual methods + * in negativeLogLikelihood. + * + */ + class multinomial: public negativeLogLikelihood + { + private: + bool m_bCompress; + dvariable m_log_vn; + dvar_matrix m_P; + + public: + + multinomial(const dmatrix &_O,const bool bCompress=false) + : negativeLogLikelihood(_O),m_bCompress(bCompress) + { + if(m_bCompress) tail_compression(); + } + + ~multinomial(); + + + dvariable get_n() const { return m_log_vn; } + void set_n(dvariable _n){ this->m_log_vn = _n;} + + dvar_matrix get_P() const { return m_P; } + void set_P(dvar_matrix _P) { this->m_P = _P;} + + + // negative log likelihood + const dvariable nloglike(const dvar_vector& log_vn, const dvar_matrix& _P) const + { + if(m_bCompress) + { + dmatrix Or = compress(this->get_O()); + dvar_matrix Pr = compress(_P); + return dmultinom(log_vn,Or,Pr); + } + else + { + return dmultinom(log_vn,this->get_O(),_P); + } + } + + // pearson residuals + const dmatrix residual(const dvar_vector& _n, const dvar_matrix& _P) const + { + return pearson_residuals(_n,this->get_O(),_P); + } + + + const dvariable dmultinom(const dvar_vector& log_vn, + const dmatrix& o, + const dvar_matrix& p) const; + + const dmatrix pearson_residuals(const dvar_vector& log_vn, + const dmatrix& o, + const dvar_matrix p) const; + }; + + + class robust_multi: public negativeLogLikelihood + { + private: + bool m_bCompress; + dvariable m_log_vn; + dvar_matrix m_P; + + public: + + robust_multi(const dmatrix &_O,const bool bCompress=false) + : negativeLogLikelihood(_O),m_bCompress(bCompress) + { + if(m_bCompress) tail_compression(); + } + + ~robust_multi(); + + dvariable get_n() const { return m_log_vn; } + void set_n(dvariable _n){ this->m_log_vn = _n;} + + dvar_matrix get_P() const { return m_P; } + void set_P(dvar_matrix _P) { this->m_P = _P;} + + + // negative log likelihood + const dvariable nloglike(const dvar_vector& log_vn, const dvar_matrix& _P) const + { + if(m_bCompress) + { + dmatrix Or = compress(this->get_O()); + dvar_matrix Pr = compress(_P); + return pdf(Or,Pr,log_vn); + } + else + { + return pdf(this->get_O(),_P,log_vn); + } + } + + // pearson residuals + const dmatrix residual(const dvar_vector& _n, const dvar_matrix& _P) const + { + return pearson_residuals(this->get_O(),_P,_n); + } + + const dvariable pdf(const dmatrix& O, + const dvar_matrix& P, + const dvar_vector& lnN) const; + + + const dmatrix pearson_residuals(const dmatrix& o, + const dvar_matrix p, + const dvar_vector& log_vn) const; + + }; + + +} // end of acl namespace + + + +#endif + diff --git a/src/include/selex.hpp b/src/include/selex.hpp new file mode 100644 index 00000000..bfb0246c --- /dev/null +++ b/src/include/selex.hpp @@ -0,0 +1,355 @@ + +#ifndef SELEX_HPP +#define SELEX_HPP + +#include +// #include "cstar.h" + +/** + * @defgroup Selectivities + * @Selectivities Alternative selectivity functions in the cstar namespace are + * derived from the cstar::Selex base class. + * + * @file selex.hpp + * + * @author Steven Martell + * @date Feb 10, 2014 + * + *
Available Selectivity options are:

+ *
Selectivity FUNCTIONS Class name + *
Logistic plogis LogisticCurve + *
Nonparametric nonparametric SelectivityCoefficients + *
+ */ + +namespace cstar { + +// ========================================================================================================= +// Selex: Defined Base Class for Selectivity Functions +// ========================================================================================================= + + /** + * @ingroup Selectivities + * @brief An abstract class for Selectivity functions. + * @details Classes that derive from this class overload the pure virtual functions:

+ * const T Selectivity(const T &x) const
+ * + * @tparam x Independent variable (ie. age or size) for calculating selectivity. + */ + + template + class Selex + { + private: + T m_x; + + public: + virtual const T Selectivity(const T &x) const = 0; + + virtual const T logSelectivity(const T &x) const = 0; + + virtual const T logSelexMeanOne(const T &x) const = 0; + + virtual ~Selex(){} + + void Set_x(T & x) { this-> m_x = x; } + T Get_x() const{ return m_x; } + }; + +// ========================================================================================================= +// plogis: Base functions for logistic-based selectivity functions +// ========================================================================================================= + + /* Traits for the vonBertalaffy template function*/ + template + class logisticTrait; + + template<> + class logisticTrait { + public: + typedef dvector plogisT; + }; + + template<> + class logisticTrait { + public: + typedef dvar_vector plogisT; + }; + + + /** + * @brief Logistic function + * @details Basic two parameter logistic function with mean and standard deviation + * + * @param x Independent variable (e.g. age or size) + * @tparam T data vector or dvar vector + * @tparam T2 double or dvariable for mean and standard deviation of the logistic curve + * + * template + inline + typename vonBtrait::vonBT vonBertalanffy(const T &lmin, const T &lmax, const T &rho, const T1 &age) + { + typedef typename vonBtrait::vonBT vonBT; + */ + + //typename logisticTrait::plogisT plogis(const T &x, const T2 &mean, const T2 &sd) + template + inline + const T plogis(const T &x, const T2 &mean, const T2 &sd) + { + //typedef typename logisticTrait::plogisT plogisT; + T selex = T2(1.0)/(T2(1.0)+mfexp(-(x-mean)/sd)); + return selex; + } + + + template + inline + const T plogis95(const T &x, const T2 &s50, const T2 &s95) + { + T selex = T2(1.0)/(T2(1.0)+(exp(-log(19)*((x-s50)/(s95-s50))))); + selex /= selex(selex.indexmax()); + return selex; + } + +// ========================================================================================================= +// LogisticCurve: Logistic-based selectivity function with options +// ========================================================================================================= + + /** + * @brief Logistic curve + * @details Uses the logistic curve (plogis) for a two parameter function + * + * @tparam T data vector or dvar vector + * @tparam T2 double or dvariable for mean and standard deviation of the logistic curve + */ + + template + class LogisticCurve: public Selex + { + private: + T2 m_mean; + T2 m_std; + + public: + LogisticCurve(T2 mean = T2(0), T2 std = T2(1)) + : m_mean(mean), m_std(std) {} + + T2 GetMean() const { return m_mean; } + T2 GetStd() const { return m_std; } + + void SetMean(T2 mean) { this->m_mean = mean;} + void SetStd(T2 std) { this->m_std = std; } + + const T Selectivity(const T &x) const + { + return cstar::plogis(x, this->GetMean(), this->GetStd()); + } + + const T logSelectivity(const T &x) const + { + return log(cstar::plogis(x, this->GetMean(), this->GetStd())); + } + + const T logSelexMeanOne(const T &x) const + { + T y = log(cstar::plogis(x, this->GetMean(), this->GetStd())); + y -= log(mean(mfexp(y))); + return y; + } + + }; + +// ========================================================================================================= +// LogisticCurve95: Logistic-based selectivity function with options +// ========================================================================================================= + + /** + * @brief Logistic curve parameterised with 5% and 95% selectivity + * @details Uses the logistic curve (plogis95) for a two parameter function + * + * @tparam T data vector or dvar vector + * @tparam T2 double or dvariable for size at 5% and 95% selectivity + */ + + template + class LogisticCurve95: public Selex + { + private: + T2 m_s50; + T2 m_s95; + + public: + LogisticCurve95(T2 s50 = T2(1), T2 s95 = T2(1)) + : m_s50(s50), m_s95(s95) {} + + T2 GetS50() const { return m_s50; } + T2 GetS95() const { return m_s95; } + + void SetS50(T2 s50) { this->m_s50 = s50; } + void SetS95(T2 s95) { this->m_s95 = s95; } + + const T Selectivity(const T &x) const + { + return cstar::plogis95(x, this->GetS50(), this->GetS95()); + } + + const T logSelectivity(const T &x) const + { + return log(cstar::plogis95(x, this->GetS50(), this->GetS95())); + } + + const T logSelexMeanOne(const T &x) const + { + T y = log(cstar::plogis95(x, this->GetS50(), this->GetS95())); + y -= log(mean(mfexp(y))); + return y; + } + + }; + +// ========================================================================================================= +// coefficients: Base function for non-parametric selectivity cooefficients +// ========================================================================================================= + + /** + * @brief Nonparametric selectivity coefficients + * @details Assumes that the last age/size class has the same selectivity coefficient + * as the terminal sel_coeffs. + * + * @param x Independent variable + * @param sel_coeffs Vector of estimated selectivity coefficients. + * @return Selectivity coefficients. + */ + template + const T coefficients(const T &x, const T &sel_coeffs) + { + int x1 = x.indexmin(); + int x2 = x.indexmax(); + int y2 = sel_coeffs.indexmax(); + T y(x1,x2); + for(int i = x1; i < y2; i++ ) + { + y(i) = sel_coeffs(i); + } + y(y2,x2) = sel_coeffs(y2); + return y; + } + +// ========================================================================================================= +// SelectivityCoefficients: Age/size-specific selectivity coefficients for n-1 age/size classes +// ========================================================================================================= + + /** + * @brief Selectivity coefficients + * @details Age or size-specific selectivity coefficients for n-1 age/size classes + * + * @tparam T vector of coefficients + */ + template + class SelectivityCoefficients: public Selex + { + private: + T m_sel_coeffs; + + public: + SelectivityCoefficients(T params = T(1)) + :m_sel_coeffs(params) {} + + T GetSelCoeffs() const { return m_sel_coeffs; } + void SetSelCoeffs(T x) { this->m_sel_coeffs = x; } + + const T Selectivity(const T &x) const + { + // Call the age/size specific function + return cstar::coefficients(x, this->GetSelCoeffs()); + } + + const T logSelectivity(const T &x) const + { + // Call the age/size specific function + return log(cstar::coefficients(x, this->GetSelCoeffs())); + } + + const T logSelexMeanOne(const T &x) const + { + T y = log(cstar::coefficients(x, this->GetSelCoeffs())); + y -= log(mean(mfexp(y))); + return y; + } + }; + +// ========================================================================================================= +// nonparametric: Base function for parametric selectivity option +// ========================================================================================================= + + /** + * @brief Nonparametric selectivity function + * @details Estimate one parameter per age/size class, and rescale to maximum of one. + * + * @param x Independent variable (number of classes) + * @param selparms Vector of selectivity parameters (initial values). + * @return Selectivity values. + */ + template + const T nonparametric(const T &x, const T &selparms) + { + int x2 = x.indexmax(); + dvar_vector selex(1,x2); + for (int i=1; i<=x2; i++) + selex(i) = (1.0)/(1.0+mfexp(selparms(i))); + dvariable temp = selex(x2); + selex /= temp; + return selex; + } + +// ========================================================================================================= +// ParameterPerClass: One age/size-specific selectivity parameter for each age/size class +// ========================================================================================================= + + /** + * @brief Parametric selectivity function + * @details One age or size-specific selectivity parameter for each age/size class. + * + * @tparam T vector of parameters (initial values) + */ + template + class ParameterPerClass: public Selex + { + private: + T m_selparms; + + public: + ParameterPerClass(T selparms = T(1)) + :m_selparms(selparms) {} + + T GetSelparms() const { return m_selparms; } + void SetSelparms(T selparms) { this->m_selparms = selparms; } + + const T Selectivity(const T &x) const + { + // Call the age/size specific function + return cstar::nonparametric(x, this->GetSelparms()); + } + + const T logSelectivity(const T &x) const + { + // Call the age/size specific function + return log(cstar::nonparametric(x, this->GetSelparms())); + } + + const T logSelexMeanOne(const T &x) const + { + T y = log(cstar::nonparametric(x, this->GetSelparms())); + //y -= log(mean(mfexp(y))); + return y; + } + }; + +}//cstar + + +#endif /* SELEX_HPP */ + +// EOF. +// ========================================================================================================= \ No newline at end of file diff --git a/src/include/spr.h b/src/include/spr.h new file mode 100644 index 00000000..9b58c74c --- /dev/null +++ b/src/include/spr.h @@ -0,0 +1,112 @@ + +/** + * \file spr.h + * \author Steve Martell + */ + +#include + +#ifndef _SPR_H_ +#define _SPR_H_ + +#define MAXIT 100 +#define TOL 1.e-4 + +#undef COUT +#define COUT(object) cout << #object "\n" << setw(6) \ +<< setprecision(3) << setfixed() << object << endl; + + +class spr +{ +private: + int m_nsex; + int m_nshell; + int m_nfleet; + int m_nclass; + int m_ifleet; + + double m_rbar; + double m_lambda; + double m_ssb0; + double m_ssb; + double m_spr; + double m_fspr; + double m_bspr; + double m_fofl; + double m_cofl; + + dvector m_rx; + dvector m_dmr; + + dmatrix m_wa; + dmatrix m_fref; + + + d3_array m_M; + d3_array m_A; + d3_array m_P; // molting probability + d3_array m_sel; + d3_array m_ret; +public: + // constructors + spr(); + + + /** + * @brief constructor for SPR class + * @details Constructor for SRR class + * + * @param _r equilibrium recruitment + * @param _lambda fraction of females that contribute to the Spawning potential ratio + * @param _rx size distribution of new recruits + * @param _M natural mortality at size by sex + * @param _wa weight-at-length interval + * @param _A size-transition matrix + */ + spr(const double& _r, + const double& _lambda, + const dvector& _rx, + const dmatrix& _wa, + const d3_array& _M, + const d3_array& _A); + + // constructor where nshell == 2 & continous molting + spr(const double& _r, + const double & _lambda, + const dvector& _rx, + const dmatrix& _wa, + const d3_array& _M, + const d3_array& _P, + const d3_array& _A); + + // destructor + ~spr(); + + // getters + double get_fspr(const int& ifleet, + const double& spr_target, + const dmatrix& _fhk, + const d3_array _sel, + const d3_array _ret, + const dvector _dmr); + + double get_bspr() {return m_bspr;} + + + double get_fofl(const double& alpha, const double& limit, const double& ssb); + double get_cofl(const dmatrix& N); + + + void calc_equilibrium(dvector& n, + dvector& o, + const dmatrix& A, + const dmatrix& S, + const dmatrix& P, + const dvector& r); + dvector calc_equilibrium(const dmatrix& M, const int& sex); + +}; + + +#endif \ No newline at end of file diff --git a/src/lib/Makefile b/src/lib/Makefile new file mode 100644 index 00000000..030c8405 --- /dev/null +++ b/src/lib/Makefile @@ -0,0 +1,106 @@ +# Name of archive. +OUTPUT:=libgmacs.a + +# Portable makefiles (http://skramm.blogspot.com/2013/04/writing-portable-makefiles.html) +# Windows users: download http://gnuwin32.sourceforge.net/packages/make.htm +ifdef ComSpec + RM=del /F /Q +else + RM=rm -rf +endif + +# Global source files from current dir. +SRCS:=$(wildcard *.cpp *.c *.cc *.cxx ) + +# Path to ADMB distribution directory +# export ADMB_HOME=/Users/stevenmartell1/admb-trunk/bin/dist + +# Compiler +CXX:=clang++ + +# Compiler and linker flags. +CXXFLAGS:=-g -Wall -D__GNUDOS__ -Dlinux -DUSE_LAPLACE \ + -I. \ + -I$(ADMB_HOME)/include \ + -I/usr/include/libxml2 +LDFLAGS:= + +# Release specific flags. +RELEASE_CXXFLAGS:=-O3 -DOPT_LIB +RELEASE_LDFLAGS:= $(ADMB_HOME)/lib/libadmb-contribo.a -lxml2 + +# Debug specific flags. +DEBUG_CXXFLAGS:=-O0 -DSAFE_ALL +DEBUG_LDFLAGS:= $(ADMB_HOME)/lib/libadmb-contrib.a -lxml2 + + +# ======================= END OF CONFIGURABLE THINGS =========================== +# Create debug & release list of object files as well as dep files. +BASEFILES:=$(basename $(SRCS)) +DEBUG_OBJS:=$(addprefix bin/debug/,$(addsuffix .o,$(BASEFILES))) +RELEASE_OBJS:=$(addprefix bin/release/,$(addsuffix .o,$(BASEFILES))) +DEPFILES:=$(addprefix bin/deps/,$(addsuffix .d,$(BASEFILES))) + +# Default to release bin. +all: debug release + + +# Directory targets +bin/debug: + @echo creating debug directory + @mkdir -p bin/debug bin/deps + +bin/release: + @echo creating release directory + @mkdir -p bin/release bin/deps + +# Debug route. +.PHONY: debug +debug: CXXFLAGS+= $(DEBUG_CXXFLAGS) +debug: LDFLAGS+= $(DEBUG_LDFLAGS) +debug: bin/debug/$(OUTPUT) + +bin/debug/$(OUTPUT): bin/debug $(DEBUG_OBJS) + @echo 'linking ' bin/debug/$(OUTPUT) + $(AR) -rs $@ $(DEBUG_OBJS) + # @$(CXX) -o bin/debug/$(OUTPUT) $(DEBUG_OBJS) $(LDFLAGS) + +-include $(DEPFILES) + +bin/debug/%.o : %.cpp + @echo 'compiling ' $< + @$(CXX) -c $(CXXFLAGS) $< -o $@ + @$(CXX) -MM $(CXXFLAGS) $< -o bin/deps/$*.d + @mv -f bin/deps/$*.d bin/deps/$*.d.tmp + @sed -e 's|.*:|bin/debug/$*.o:|' < bin/deps/$*.d.tmp \ + > bin/deps/$*.d + @sed -e 's/.*://' -e 's/\\$$//' < bin/deps/$*.d.tmp | fmt -1 \ + | sed -e 's/^ *//' -e 's/$$/:/' >> bin/deps/$*.d + @$(RM) -f bin/deps/$*.d.tmp + +# Release route. +.PHONY: release +release: CXXFLAGS+= $(RELEASE_CXXFLAGS) +release: LDFLAGS+= $(RELEASE_LDFLAGS) +release: bin/release/$(OUTPUT) + +bin/release/$(OUTPUT): bin/release $(RELEASE_OBJS) + @echo 'linking ' bin/release/$(OUTPUT) + $(AR) -rs $@ $(RELEASE_OBJS) + # @$(CXX) -o bin/release/$(OUTPUT) $(RELEASE_OBJS) $(LDFLAGS) + +bin/release/%.o : %.cpp + @echo 'compiling ' $< + @$(CXX) -c $(CXXFLAGS) $< -o $@ + @$(CXX) -MM $(CXXFLAGS) $< -o bin/deps/$*.d + @mv -f bin/deps/$*.d bin/deps/$*.d.tmp + @sed -e 's|.*:|bin/release/$*.o:|' < bin/deps/$*.d.tmp \ + > bin/deps/$*.d + @sed -e 's/.*://' -e 's/\\$$//' < bin/deps/$*.d.tmp | fmt -1 | \ + sed -e 's/^ *//' -e 's/$$/:/' >> bin/deps/$*.d + @$(RM) -f bin/deps/$*.d.tmp + +.PHONY: clean +clean: + @echo 'removing bin directory' + @$(RM) -rf bin \ No newline at end of file diff --git a/src/lib/equilibrium.cpp b/src/lib/equilibrium.cpp new file mode 100644 index 00000000..f8e1716e --- /dev/null +++ b/src/lib/equilibrium.cpp @@ -0,0 +1,125 @@ +/** + * \file equilibrium.cpp + * \author Steve Martell + * @defgroup GMACS + * + */ + + +#include +#if defined __APPLE__ || defined __linux + #include "../include/libgmacs.h" +#endif +#if defined _WIN32 || defined _WIN64 + #include "include\libgmacs.h" +#endif + + + +/** + * @ingroup GMACS + * @brief Calculate equilibrium vector n given A, S and r + * @details Solving a matrix equation for the equilibrium number + * of crabs in length interval. + * + * + * + * @param[out] n vector of numbers at length + * @param[in] A size transition matrix + * @param[in] S diagonal matrix of length specific survival rates + * @param[in] r vector of new recruits at length. + */ +void calc_equilibrium(dvar_vector& n, + const dvar_matrix& A, + const dvar_matrix& S, + const dvar_vector r) +{ + int nclass = n.indexmax(); + dmatrix Id = identity_matrix(1,nclass); + dvar_matrix At(1,nclass,1,nclass); + + At = trans(A*S); + n = -solve(At-Id,r); + +} + + + +/** + * @brief Get initial vector of new shell and oldshell crabs at equilibrium + * @ingroup GMACS + * @authors Steve Martell and John Levitt + * @date Jan 3, 2015. + * + * @param[out] n vector of numbers at length in new shell condition + * @param[out] o vector of numbers of old shell crabs at length + * @param[in] A size transition matrix + * @param[in] S diagonal matrix of length specific survival rates + * @param[in] P diagonal matrix of length specific molting probabilities + * @param[in] r vector of new recruits at length. + * + * @details + * Jan 3, 2015. Working with John Levitt on analytical solution instead of the + * numerical approach. Think we have a soln. + * + * Notation: \n + * \f$n\f$ = vector of newshell crabs \n + * \f$o\f$ = vector of oldshell crabs \n + * \f$P\f$ = diagonal matrix of molting probabilities by size \n + * \f$S\f$ = diagonal matrix of survival rates by size \n + * \f$A\f$ = Size transition matrix \n + * \f$r\f$ = vector of new recruits (newshell) \n + * \f$I\f$ = identity matrix. \n + * + * + * The following equations represent the dynamics of newshell \a n and oldshell crabs. + * \f{align*}{ + * n &= nSPA + oSPA + r \\ + * o &= oS(I-P) + nS(I-P) + * \f} + * Objective is to solve the above equations for \f$n\f$ and \f$o\f$ repsectively. + * First, lets solve the second equation for \f$o\f$: + * \f{align*}{ + * o &= n(I-P)S[I-(I-P)S]^{-1} + * \f} + * next substitute the above expression into first equation above and solve for \f$n\f$ + * \f{align*}{ + * n &= nPSA + n(I-P)S[I-(I-P)S]^{-1}PSA + r \\ + * \mbox{let} \quad \beta& = [I-(I-P)S]^{-1}, \\ + * r &= n - nPSA - n(I-P)S \beta PSA \\ + * r &= n(I - PSA - (I-P)S \beta PSA) \\ + * \mbox{let} \quad C& = (I - PSA - (I-P)S \beta PSA), \\ + * n &= (C)^{-1} (r) + * \f} + * Note that \f$C\f$ must be invertable to solve for the equilibrium solution for \f$n\f$. + * So the diagonal elements of \f$P\f$ and \f$S\f$ must be positive non-zero numbers. + * + * + */ +void calc_equilibrium(dvar_vector& n, + dvar_vector& o, + const dvar_matrix& A, + const dvar_matrix& S, + const dvar_matrix& P, + const dvar_vector& r) +{ + int nclass = n.indexmax(); + dmatrix Id = identity_matrix(1,nclass); + dvar_matrix B(1,nclass,1,nclass); + dvar_matrix C(1,nclass,1,nclass); + dvar_matrix D(1,nclass,1,nclass); + + + + B = inv(Id - (Id-P)*S); + C = P * S * A; + D = trans(Id - C - (Id-P)*S*B*C); + + // COUT(A); + // COUT(inv(D)*r); + + n = solve(D,r); // newshell + o = n*((Id-P)*S*B); // oldshell + +} + diff --git a/src/lib/moltIncrement.cpp b/src/lib/moltIncrement.cpp new file mode 100644 index 00000000..2d69366c --- /dev/null +++ b/src/lib/moltIncrement.cpp @@ -0,0 +1,68 @@ +#include +#if defined __APPLE__ || defined __linux + #include "../include/libgmacs.h" +#endif +#if defined _WIN32 || defined _WIN64 + #include "include\libgmacs.h" +#endif + + +/** + * @brief Return molt increment matrix based on empirical data + * @details Fit's a cubic spline to the empirical data. + * Note that the spline function strictly requires increasing + * values for each of the knots. + * + * @param data [description] + * @return dmatrix of molt increments by sex for each size bin + */ +dmatrix get_empirical_molt_increment(const dvector& bin, const dmatrix& data) +{ + cout<<"In get_empirical_molt_increment"< +#if defined __APPLE__ || defined __linux + #include "../include/nloglike.h" +#endif +#if defined _WIN32 || defined _WIN64 + #include "include\nloglike.h" +#endif + + + +/** + * @brief multinomial desity function with estimated effective sample size. + * @details Negative log likelihood using the multinomial distribution. + * @author Dave Fournier + * @param log_vn log of effective sample size. + * @param o observed proportions. + * @param p predicted proportions + * @return negative loglikelihood. + */ +const dvariable acl::multinomial::dmultinom(const dvar_vector& log_vn, + const dmatrix& o, + const dvar_matrix& p) const +{ + if(o.colsize()!=p.colsize() || o.rowsize()!=p.rowsize()) + { + cerr<<"Error in dmultinom, " + " observed and predicted matrixes" + " are not the same size"< 0.0 ) + ff += gammln(sobs(j)); + } + ff -= sobs * log(TINY + p(i)); + } + + return ff; +} + + +const dmatrix acl::multinomial::pearson_residuals(const dvar_vector& log_vn, + const dmatrix& o, + const dvar_matrix p) const +{ + dvector vn = value(mfexp(log_vn)); + dmatrix res = o - value(p); + // dmatrix var = value(elem_prod(p,1.0-p)) / vn; + for(int i = o.rowmin(); i <= o.rowmax(); i++ ) + { + dvector var = value(elem_prod(p(i),1.0-p(i))) / vn(i); + res(i) = elem_div(res(i),sqrt(var+TINY)); + } + return res; +} + + + diff --git a/src/lib/nloglike.cpp b/src/lib/nloglike.cpp new file mode 100644 index 00000000..55956605 --- /dev/null +++ b/src/lib/nloglike.cpp @@ -0,0 +1,171 @@ +#include +#if defined __APPLE__ || defined __linux + #include "../include/nloglike.h" +#endif +#if defined _WIN32 || defined _WIN64 + #include "include\nloglike.h" +#endif +// using namespace likelihoods; + + +// nloglike::nloglike(const dmatrix& _O, const dvar_matrix& _P) +// :m_O(_O),m_P(_P) +// { +// r1 = m_O.rowmin(); +// r2 = m_O.rowmax(); +// c1 = m_O.colmin(); +// c2 = m_O.colmax(); +// tail_compression(); +// m_residual.allocate(r1,r2,c1,c2); +// } + +// nloglike::~nloglike() +// { + +// } + +// /** +// * @brief Multivariate logistic likelihood +// * @details This is a modified version of the dmvlogistic negative log likelihood +// where proportions at age less than minp are pooled into the consecutive +// age-classes. See last paragraph in Appendix A of Richards, Schnute and +// Olsen 1997. +// * @return negative log likelihood. +// */ +// dvariable nloglike::dmvlogistic() +// { + +// int n = 0; +// dvariable nll = 0; +// dvar_matrix nu; +// nu.allocate(m_Pr); +// nu.initialize(); + + +// for(int i = r1; i <= r2; i++ ) +// { +// if(min(m_Pr(i))==0) {cout<<"Deal with zeros"< +#if defined __APPLE__ || defined __linux + #include "../include/nloglike.h" +#endif +#if defined _WIN32 || defined _WIN64 + #include "include\nloglike.h" +#endif + + + +/** + * @brief robust multinomial desity function with estimated effective sample size. + * @details Robustified Multinomia likelihood for composition data following Fournier's approach. + * @author Dave Fournier & Jim Ianelli + * @param log_vn log of effective sample size. + * @param o observed proportions. + * @param p predicted proportions + * @return negative loglikelihood. + */ +const dvariable acl::robust_multi::pdf(const dmatrix& O, + const dvar_matrix& P, + const dvar_vector& lnN) const + { + if( lnN.indexmin() != O.rowmin() || lnN.indexmax() != O.rowmax() ) + { + cerr<<"Sample size index do not match row index in\ + observed size composition matrix."< +#if defined __APPLE__ || defined __linux + #include "../include/spr.h" +#endif +#if defined _WIN32 || defined _WIN64 + #include "include\spr.h" +#endif + + + +/** + * \brief constructor for SPR class + * \details Constructor for SRR class + * + * \param _r equilibrium recruitment + * \param _lambda fraction of females that contribute to the Spawning potential ratio + * \param _rx size distribution of new recruits + * \param _M natural mortality at size by sex + * \param _wa weight-at-length interval + * \param _A size-transition matrix + */ +spr::spr(const double& _r, + const double& _lambda, + const dvector& _rx, + const dmatrix& _wa, + const d3_array& _M, + const d3_array& _A) +:m_rbar(_r),m_lambda(_lambda),m_rx(_rx),m_wa(_wa),m_M(_M),m_A(_A) +{ + m_nshell = 1; + m_nsex = m_M.slicemax(); + m_nclass = m_rx.indexmax(); + dmatrix S(1,m_nclass,1,m_nclass); + S.initialize(); + + // get unfished mature male biomass per recruit. + m_ssb0 = 0.0; + for(int h = 1; h <= m_nsex; h++ ) + { + for (int l = 1; l <= m_nclass; ++l) + { + S(l,l) = exp(-m_M(h)(l,l)); + } + dvector x = calc_equilibrium(S,h); + + double lam; + h <= 1 ? lam=m_lambda: lam=(1.-m_lambda); + m_ssb0 += lam * x * m_wa(h); + } + +} + +/** + * @brief constructor for SPR class + * @details Constructor for SRR class + * + * @param _r equilibrium recruitment + * @param _lambda fraction of females that contribute to the Spawning potential ratio + * @param _rx size distribution of new recruits + * @param _M natural mortality at size by sex + * @param _wa weight-at-length interval + * @param _A size-transition matrix + */ +spr::spr(const double& _r, + const double& _lambda, + const dvector& _rx, + const dmatrix& _wa, + const d3_array& _M, + const d3_array& _P, + const d3_array& _A) +:m_rbar(_r),m_lambda(_lambda),m_rx(_rx),m_wa(_wa),m_M(_M),m_A(_A),m_P(_P) +{ + m_nshell = 2; + m_nsex = m_M.slicemax(); + m_nclass = m_rx.indexmax(); + dvector n(1,m_nclass); + dvector o(1,m_nclass); + dmatrix S(1,m_nclass,1,m_nclass); + S.initialize(); + + cout<<"inside Constructor"< 0) + { + fa = fc; + } + else + { + fb = fc; + } + cout<<"iter = "< 1.0 ) + { + m_fofl = m_fspr; + } + + if( limit < depletion && depletion <= 1.0 ) + { + m_fofl = m_fspr * (depletion - alpha)/(1.0-alpha); + } + + + return m_fofl; +} + + +/** + * @brief Calculate OFL + * @details Calculates the OFL based on harvest control rule + * and estimate of Fspr% + * + * @param N [description] + * @return [description] + */ +double spr::get_cofl(const dmatrix& N) +{ + cout<<"Get OFL"< + #if defined __APPLE__ || defined __linux + #include "../include/nloglike.h" + #endif + #if defined _WIN32 || defined _WIN64 + #include "include\nloglike.h" + #endif + + +/** + * @brief Determine non-zero array elements for tail compression. + * @details This routine fills the member variables m_jmin and m_jmax + * with the array indexes that correpsond to the cumulative sum that is + * greater than pmin, and 1-pmin respectively. This is then later + * used to construct ragged objects to be used in the likelihood functions. + * @return [description] + * @author Steve Martell + */ + + +void acl::negativeLogLikelihood::tail_compression() +{ + // cout<<"Running tail compression"< build/deps/$*.d + @sed -e 's/.*://' -e 's/\\$$//' < build/deps/$*.d.tmp | fmt -1 \ + | sed -e 's/^ *//' -e 's/$$/:/' >> build/deps/$*.d + @rm -f build/deps/$*.d.tmp + +# Release route. +.PHONY: release +release: CXXFLAGS+= $(RELEASE_CXXFLAGS) +release: LDFLAGS+= $(RELEASE_LDFLAGS) +release: build/release/$(OUTPUT) + +build/release/$(OUTPUT): build/release $(RELEASE_OBJS) + @echo 'linking ' build/release/$(OUTPUT) + @$(CXX) -o build/release/$(OUTPUT) $(RELEASE_OBJS) $(LDFLAGS) + +build/release/%.o : %.cpp + @echo 'compiling ' $< + @$(CXX) -c $(CXXFLAGS) $< -o $@ + @$(CXX) -MM $(CXXFLAGS) $< -o build/deps/$*.d + @mv -f build/deps/$*.d build/deps/$*.d.tmp + @sed -e 's|.*:|build/release/$*.o:|' < build/deps/$*.d.tmp \ + > build/deps/$*.d + @sed -e 's/.*://' -e 's/\\$$//' < build/deps/$*.d.tmp | fmt -1 | \ + sed -e 's/^ *//' -e 's/$$/:/' >> build/deps/$*.d + @rm -f build/deps/$*.d.tmp + +.PHONY: clean +clean: + @echo 'removing build directory' + @$(RM) -rf build diff --git a/src/makefile.orig b/src/makefile.orig new file mode 100644 index 00000000..2188a1f4 --- /dev/null +++ b/src/makefile.orig @@ -0,0 +1,116 @@ +# Name of executable. +OUTPUT:=gmacs +LIBINCLUDE = lib/bin +# Global source files from current dir. +LIBS:=$(wildcard ./lib/*.cpp) +SRCS:=$(wildcard *.cpp *.c *.cc *.cxx ) + + +# Path to ADMB distribution directory +# export ADMB_HOME=/Users/stevenmartell1/admb-trunk/build/dist +export ADMB_HOME=/Users/jim/admb/build/dist + +# Compiler +CXX:=clang++ + +# Compiler and linker flags. +CXXFLAGS:=-g -Wall -D__GNUDOS__ -Dlinux -DUSE_LAPLACE \ + -I. \ + -I$(ADMB_HOME)/include \ + -I$(ADMB_HOME)/contrib/include \ + -I$(LIBINCLUDE) \ + -I/usr/include/libxml2 \ + -std=c++11 \ + -stdlib=libc++ +LDFLAGS:= + +# Release specific flags. +RELEASE_CXXFLAGS:=-O3 -DOPT_LIB +RELEASE_LDFLAGS:= $(ADMB_HOME)/lib/libadmb-contribo.a \ + $(LIBINCLUDE)/release/libgmacs.a \ + lib/bin/release/libgmacs.a \ + -lxml2 + +# Debug specific flags. +DEBUG_CXXFLAGS:=-O0 -DSAFE_ALL +DEBUG_LDFLAGS:= $(ADMB_HOME)/lib/libadmb-contrib.a \ + $(LIBINCLUDE)/debug/libgmacs.a \ + lib/bin/debug/libgmacs.a \ + -lxml2 + +# Name of text file containing build number. +BUILD_NUMBER_FILE=build-number.txt + +# ======================= END OF CONFIGURABLE THINGS =========================== +# Create debug & release list of object files as well as dep files. +BASEFILES:=$(basename $(SRCS)) +DEBUG_OBJS:=$(addprefix build/debug/,$(addsuffix .o,$(BASEFILES))) +RELEASE_OBJS:=$(addprefix build/release/,$(addsuffix .o,$(BASEFILES))) +DEPFILES:=$(addprefix build/deps/,$(addsuffix .d,$(BASEFILES))) + +# Default to release build. +all: $(OUTPUT).cpp library debug release + +library: $(LIBS) + @$(MAKE) --directory=./lib + +$(OUTPUT).cpp: $(OUTPUT).tpl + $(ADMB_HOME)/bin/tpl2cpp $(OUTPUT) + +# Directory targets +build/debug: + @echo creating debug directory + @mkdir -p build/debug build/deps + +build/release: + @echo creating release directory + @mkdir -p build/release build/deps + +# Debug route. +.PHONY: debug +debug: CXXFLAGS+= $(DEBUG_CXXFLAGS) +debug: LDFLAGS+= $(DEBUG_LDFLAGS) +debug: build/debug/$(OUTPUT) + +build/debug/$(OUTPUT): build/debug $(DEBUG_OBJS) + @echo 'linking ' build/debug/$(OUTPUT) + @$(CXX) -o build/debug/$(OUTPUT) $(DEBUG_OBJS) $(LDFLAGS) + +-include $(DEPFILES) + +build/debug/%.o : %.cpp + @echo 'compiling ' $< + @$(CXX) -c $(CXXFLAGS) $< -o $@ + @$(CXX) -MM $(CXXFLAGS) $< -o build/deps/$*.d + @mv -f build/deps/$*.d build/deps/$*.d.tmp + @sed -e 's|.*:|build/debug/$*.o:|' < build/deps/$*.d.tmp \ + > build/deps/$*.d + @sed -e 's/.*://' -e 's/\\$$//' < build/deps/$*.d.tmp | fmt -1 \ + | sed -e 's/^ *//' -e 's/$$/:/' >> build/deps/$*.d + @rm -f build/deps/$*.d.tmp + +# Release route. +.PHONY: release +release: CXXFLAGS+= $(RELEASE_CXXFLAGS) +release: LDFLAGS+= $(RELEASE_LDFLAGS) +release: build/release/$(OUTPUT) + +build/release/$(OUTPUT): build/release $(RELEASE_OBJS) + @echo 'linking ' build/release/$(OUTPUT) + @$(CXX) -o build/release/$(OUTPUT) $(RELEASE_OBJS) $(LDFLAGS) + +build/release/%.o : %.cpp + @echo 'compiling ' $< + @$(CXX) -c $(CXXFLAGS) $< -o $@ + @$(CXX) -MM $(CXXFLAGS) $< -o build/deps/$*.d + @mv -f build/deps/$*.d build/deps/$*.d.tmp + @sed -e 's|.*:|build/release/$*.o:|' < build/deps/$*.d.tmp \ + > build/deps/$*.d + @sed -e 's/.*://' -e 's/\\$$//' < build/deps/$*.d.tmp | fmt -1 | \ + sed -e 's/^ *//' -e 's/$$/:/' >> build/deps/$*.d + @rm -f build/deps/$*.d.tmp + +.PHONY: clean +clean: + @echo 'removing build directory' + @rm -rf build