# HG changeset patch # User ecology # Date 1595325651 14400 # Node ID 0778efa9eb2e6b9a1d2b9123a884879ad67bb074 "planemo upload for repository https://github.com/ColineRoyaux/PAMPA-Galaxy commit 07f1028cc764f920b1e6419c151f04ab4e3600fa" diff -r 000000000000 -r 0778efa9eb2e FunctExeCalcGLMSpGalaxy.r --- /dev/null Thu Jan 01 00:00:00 1970 +0000 +++ b/FunctExeCalcGLMSpGalaxy.r Tue Jul 21 06:00:51 2020 -0400 @@ -0,0 +1,249 @@ +#Rscript + +##################################################################################################################### +##################################################################################################################### +################################# Compute a Generalized Linear Model from your data ################################# +##################################################################################################################### +##################################################################################################################### + +###################### Packages +#suppressMessages(library(MASS)) +suppressMessages(library(multcomp)) +suppressMessages(library(glmmTMB)) ###Version: 0.2.3 +suppressMessages(library(gap)) + +###################### Load arguments and declaring variables + +args = commandArgs(trailingOnly=TRUE) +#options(encoding = "UTF-8") + +if (length(args) < 10) { + stop("At least 4 arguments must be supplied : \n- two input dataset files (.tabular) : metrics table and unitobs table \n- Interest variable field from metrics table \n- Response variable from unitobs table.", call.=FALSE) #si pas d'arguments -> affiche erreur et quitte / if no args -> error and exit1 + +} else { + Importdata <- args[1] ###### file name : metrics table + ImportUnitobs <- args[2] ###### file name : unitobs informations + colmetric <- as.numeric(args[3]) ###### Selected interest metric for GLM + listFact <- strsplit(args [4],",")[[1]] ###### Selected response factors for GLM + listRand <- strsplit(args [5],",")[[1]] ###### Selected randomized response factors for GLM + colFactAna <- args[6] ####### (optional) Selected splitting factors for GLMs + Distrib <- args[7] ###### (optional) Selected distribution for GLM + log <- args[8] ###### (Optional) Log on interest metric ? + aggreg <- args[9] ###### Aggregation level of the data table + source(args[10]) ###### Import functions + +} +#### Data must be a dataframe with at least 3 variables : unitobs representing location and year ("observation.unit"), species code ("species.code") and abundance ("number") + + +#Import des données / Import data +obs<- read.table(Importdata,sep="\t",dec=".",header=TRUE,encoding="UTF-8") # +obs[obs == -999] <- NA +metric <- colnames(obs)[colmetric] +tabUnitobs <- read.table(ImportUnitobs,sep="\t",dec=".",header=TRUE,encoding="UTF-8") +tabUnitobs[tabUnitobs == -999] <- NA + +vars_data1<- c("species.code") +err_msg_data1<-"The input metrics dataset doesn't have the right format. It needs to have at least the following 3 variables :\n- species.code \n- observation.unit (or year and site)\n- numeric or integer metric\n" +check_file(obs,err_msg_data1,vars_data1,3) + +vars_data2 <- c(listFact,listRand) +vars_data2 <- vars_data2[vars_data2 != "None"] +err_msg_data2<-"The input unitobs dataset doesn't have the right format. It needs to have at least the following 2 variables :\n- observation.unit (or year and site)\n- factors used in GLM (habitat, year and/or site)\n" +check_file(tabUnitobs,err_msg_data2,vars_data2,2) + + +if (colFactAna != "None") +{ + FactAna <- colFactAna + if (class(obs[FactAna]) == "numeric" || FactAna == "observation.unit"){stop("Wrong chosen separation factor : Analysis can't be separated by observation unit or numeric factor")} +}else{ + FactAna <- colFactAna +} + + +#factors <- fact.det.f(Obs=obs) + +#################################################################################################### +########## Computing Generalized Linear Model ## Function : modeleLineaireWP2.unitobs.f ############ +#################################################################################################### + +modeleLineaireWP2.species.f <- function(metrique, listFact, listRand, FactAna, Distrib, log=FALSE, tabMetrics, tableMetrique, tabUnitobs, unitobs="observation.unit", outresiduals = FALSE, nbName="number") +{ + ## Purpose: Gestions des différentes étapes des modèles linéaires. + ## ---------------------------------------------------------------------- + ## Arguments: metrique : la métrique choisie. + ## factAna : le facteur de séparation des graphiques. + ## factAnaSel : la sélection de modalités pour ce dernier + ## listFact : liste du (des) facteur(s) de regroupement + ## listFactSel : liste des modalités sélectionnées pour ce(s) + ## dernier(s) + ## tabMetrics : table de métriques. + ## tableMetrique : nom de la table de métriques. + ## dataEnv : environnement de stockage des données. + ## baseEnv : environnement de l'interface. + ## ---------------------------------------------------------------------- + ## Author: Yves Reecht, Date: 18 août 2010, 15:59 + + tmpData <- tabMetrics + + if (listRand[1] != "None") + { + if (all(is.element(listFact,listRand)) || listFact[1] == "None") + { + RespFact <- paste("(1|",paste(listRand,collapse=") + (1|"),")") + listF <- NULL + listFact <- listRand + }else{ + listF <- listFact[!is.element(listFact,listRand)] + RespFact <- paste(paste(listF, collapse=" + ")," + (1|",paste(listRand,collapse=") + (1|"),")") + listFact <- c(listF,listRand) + } + }else{ + listF <- listFact + RespFact <- paste(listFact, collapse=" + ") + } + ##Creating model's expression : + #if (log == FALSE) { + exprML <- eval(parse(text=paste(metrique, "~", RespFact))) + #}else{ + # exprML <- eval(parse(text=paste("log(",metrique,")", "~", RespFact))) + #} + + ##Creating analysis table : + listFactTab <- c(listFact,FactAna) + listFactTab <- listFactTab[listFactTab != "None"] + + if (all(is.na(match(tmpData[,unitobs],tabUnitobs[,unitobs])))) {stop("Observation units doesn't match in the two input tables")} + + if(is.element("species.code",colnames(tmpData))) + { + col <- c(unitobs,metrique,FactAna) + tmpData <- cbind(tmpData[,col], tabUnitobs[match(tmpData[,unitobs],tabUnitobs[,unitobs]),listFact]) + colnames(tmpData) <- c(col,listFact) + + for (i in listFactTab) { + tmpData[,i] <- as.factor(tmpData[,i]) + } + }else{ + stop("Warning : wrong data frame, data frame should be aggregated by observation unit (year and site) and species") + } + + ## Suppression des 'levels' non utilisés : + tmpData <- dropLevels.f(tmpData) + + ## Aide au choix du type d'analyse : + if (Distrib == "None") + { + if (metrique == "pres.abs") + { + loiChoisie <- "binomial" + }else{ + switch(class(tmpData[,metrique]), + "integer"={loiChoisie <- "poisson"}, + "numeric"={loiChoisie <- "gaussian"}, + stop("Selected metric class doesn't fit, you should select an integer or a numeric variable")) + } + }else{ + loiChoisie <- Distrib + } + + ##Create results table : + lev <- unlist(lapply(listF,FUN=function(x){levels(tmpData[,x])})) + + if (listRand[1] != "None") ## if random effects + { + TabSum <- data.frame(species=levels(tmpData[,FactAna]),AIC=NA,BIC=NA,logLik=NA, deviance=NA,df.resid=NA) + colrand <- unlist(lapply(listRand, + FUN=function(x){lapply(c("Std.Dev","NbObservation","NbLevels"), + FUN=function(y){paste(x,y,collapse = ":") + }) + })) + TabSum[,colrand] <- NA + + if (! is.null(lev)) ## if fixed effects + random effects + { + colcoef <- unlist(lapply(c("(Intercept)",lev), + FUN=function(x){lapply(c("Estimate","Std.Err","Zvalue","Pvalue","signif"), + FUN=function(y){paste(x,y,collapse = ":") + }) + })) + }else{ ## if no fixed effects + colcoef <- NULL + } + + }else{ ## if no random effects + TabSum <- data.frame(species=levels(tmpData[,FactAna]),AIC=NA,Resid.deviance=NA,df.resid=NA,Null.deviance=NA,df.null=NA) + + switch(loiChoisie, + "gaussian"={colcoef <- unlist(lapply(c("(Intercept)",lev), + FUN=function(x){lapply(c("Estimate","Std.Err","Tvalue","Pvalue","signif"), + FUN=function(y){paste(x,y,collapse = ":") + }) + }))}, + "quasipoisson"={colcoef <- unlist(lapply(c("(Intercept)",lev), + FUN=function(x){lapply(c("Estimate","Std.Err","Tvalue","Pvalue","signif"), + FUN=function(y){paste(x,y,collapse = ":") + }) + }))}, + colcoef <- unlist(lapply(c("(Intercept)",lev), + FUN=function(x){lapply(c("Estimate","Std.Err","Zvalue","Pvalue","signif"), + FUN=function(y){paste(x,y,collapse = ":") + }) + }))) + + } + + TabSum[,colcoef] <- NA + + ### creating rate table + TabRate <- data.frame(species=levels(tmpData[,FactAna]), complete_plan=NA, balanced_plan=NA, NA_proportion_OK=NA, no_residual_dispersion=NA, uniform_residuals=NA, outliers_proportion_OK=NA, no_zero_inflation=NA, observation_factor_ratio_OK=NA, enough_levels_random_effect=NA, rate=NA) + + ## Compute Model(s) : + + for (sp in levels(tmpData[,FactAna])) + { + cutData <- tmpData[grep(sp,tmpData[,FactAna]),] + cutData <- dropLevels.f(cutData) + + res <-"" + + if (listRand[1] != "None") + { + res <- tryCatch(glmmTMB(exprML,family=loiChoisie, data=cutData), error=function(e){}) + }else{ + res <- tryCatch(glm(exprML,data=cutData,family=loiChoisie), error=function(e){}) + } + + ## Écriture des résultats formatés dans un fichier : + if (! is.null(res)) + { + TabSum <- sortiesLM.f(objLM=res, TabSum=TabSum, factAna=factAna, cut=sp, colAna="species", lev=lev, Data=cutData, metrique=metrique, type="espece", listFact=listFact) + + TabRate[TabRate[,"species"]==sp,c(2:11)] <- noteGLM.f(data=cutData, objLM=res, metric=metrique, listFact=listFact, details=TRUE) + + }else{ + cat("\nCannot compute GLM for species",sp,"Check if one or more factor(s) have only one level, or try with another distribution for the model in advanced settings \n\n") + } + + } + noteGLMs.f(tabRate=TabRate,exprML=exprML,objLM=res,file_out=TRUE) + + ## simple statistics and infos : + filename <- "GLMSummaryFull.txt" + + ## Save data on model : + + infoStats.f(filename=filename, Data=tmpData, agregLevel=aggreg, type="stat", + metrique=metrique, factGraph=factAna, #factGraphSel=modSel, + listFact=listFact)#, listFactSel=listFactSel) + + return(TabSum) +} + +################# Analysis + +Tab <- modeleLineaireWP2.species.f(metrique=metric, listFact=listFact, listRand=listRand, FactAna=FactAna, Distrib=Distrib, tabMetrics=obs, tableMetrique=aggreg, tabUnitobs=tabUnitobs, outresiduals=SupprOutlay, nbName="number") + +write.table(Tab,"GLMSummary.tabular", row.names=FALSE, sep="\t", dec=".",fileEncoding="UTF-8") + diff -r 000000000000 -r 0778efa9eb2e FunctPAMPAGalaxy.r --- /dev/null Thu Jan 01 00:00:00 1970 +0000 +++ b/FunctPAMPAGalaxy.r Tue Jul 21 06:00:51 2020 -0400 @@ -0,0 +1,3568 @@ +#Rscript + + +################################################################################################################################## +####################### PAMPA Galaxy tools functions : Calculate metrics, compute GLM and plot ################################# +################################################################################################################################## + +#### Based on Yves Reecht R script +#### Modified by Coline ROYAUX for integrating within Galaxy-E + +######################################### start of the function fact.def.f called by FunctExeCalcCommIndexesGalaxy.r and FunctExeCalcPresAbsGalaxy.r +####### Define the finest aggregation with the observation table + +fact.det.f <- function (Obs, + size.class="size.class", + code.especes="species.code", + unitobs="observation.unit") +{ + if (any(is.element(c(size.class), colnames(obs))) && all(! is.na(obs[, size.class]))) + { + factors <- c(unitobs, code.especes, size.class) + }else{ + factors <- c(unitobs, code.especes) + } + return(factors) +} + +######################################### end of the function fact.def.f + +######################################### start of the function def.typeobs.f called by FunctExeCalcCommIndexesGalaxy.r and FunctExeCalcPresAbsGalaxy.r +####### Define observation type from colnames + +def.typeobs.f <- function(Obs) +{ + if (any(is.element(c("rotation","rot","rotate"),colnames(obs)))) + { + ObsType <- "SVR" + }else{ + ObsType <- "other" + } + return(ObsType) +} +######################################### end of the function fact.def.f + +######################################### start of the function create.unitobs called by FunctExeCalcCommIndexesGalaxy.r and FunctExeCalcPresAbsGalaxy.r +####### Create unitobs column when inexistant +create.unitobs <- function(data,year="year",point="point", unitobs="observation.unit") +{ + if (is.element(paste(unitobs),colnames(data)) && all(grepl("[1-2][0|8|9][0-9]{2}_.*",data[,unitobs])==FALSE)) + { + unitab <- data + + }else{ + + unitab <- unite(data,col="observation.unit",c(year,point)) + } + return(unitab) +} +######################################### start of the function create.unitobs + +######################################### start of the function create.year.point called by FunctExeCalcCommIndexesGalaxy.r and FunctExeCalcPresAbsGalaxy.r +####### separate unitobs column when existant +create.year.point <- function(data,year="year",point="point", unitobs="observation.unit") +{ + if (all(grepl("[1-2][0|8|9][0-9]{2}_.*",data[,unitobs]))==TRUE) + { + tab <- separate(data,col=unitobs,into=c(year,point),sep="_") + }else{ + tab <- separate(data,col=unitobs,into=c("site1", year,"obs"),sep=c(2,4)) + tab <- unite(tab, col=point, c("site1","obs")) + + } + + tab <- cbind(tab,observation.unit = data[,unitobs]) + + return(tab) +} +######################################### start of the function create.unitobs + +######################################### start of the function check_file called by every Galaxy Rscripts + +check_file<-function(dataset,err_msg,vars,nb_vars){ + + ## Purpose: General function to check integrity of input file. Will + ## check numbers and contents of variables(colnames). + ## return an error message and exit if mismatch detected + ## ---------------------------------------------------------------------- + ## Arguments: dataset : dataset name + ## err_msg : output error + ## vars : expected name of variables + ## nb_vars : expected number of variables + ## ---------------------------------------------------------------------- + ## Author: Alan Amosse, Benjamin Yguel + + if(ncol(dataset) < nb_vars){ #checking for right number of columns in the file if not = error message + cat("\nerr nb var\n") + stop(err_msg, call.=FALSE) + } + + for(i in vars){ + if(!(i %in% names(dataset))){ #checking colnames + stop(err_msg,call.=FALSE) + } + } +} + +######################################### end of the function check_file + + +######################################### start of the function statRotationsNumber.f called by calc.numbers.f + +statRotationsNumber.f <- function(factors, obs) +{ + ## Purpose: Computing abundance statistics by rotation (max, sd) + ## on SVR data + ## ---------------------------------------------------------------------- + ## Arguments: factors : Names of aggregation factors + ## obs : observation data + ## ---------------------------------------------------------------------- + ## Author: Yves Reecht, Date: 29 oct. 2012, 16:01 modified by Coline ROYAUX 04 june 2020 + + ## Identification of valid rotations : + if (is.element("observation.unit", factors)) + { + ## valid rotations (empty must be there as well) : + rotations <- tapply(obs$rotation, + as.list(obs[ , c("observation.unit", "rotation"), drop=FALSE]), + function(x)length(x) > 0) + + ## Changing NA rotations in FALSE : + rotations[is.na(rotations)] <- FALSE + }else{ + #stop(mltext("statRotations.err.1")) + } + + ## ########################################################### + ## Abundance per rotation at chosen aggregation factors : + nombresR <- tapply(obs$number, + as.list(obs[ , c(factors, "rotation"), drop=FALSE]), + function(x,...){ifelse(all(is.na(x)), NA, sum(x,...))}, + na.rm = TRUE) + + ## If valid rotation NA are considered 0 : + nombresR <- sweep(nombresR, + match(names(dimnames(rotations)), names(dimnames(nombresR)), nomatch=NULL), + rotations, # Tableau des secteurs valides (booléens). + function(x, y) + { + x[is.na(x) & y] <- 0 # Lorsque NA et secteur valide => 0. + return(x) + }) + + ## ################################################## + ## Statistics : + + ## Means : + nombresMean <- apply(nombresR, which(is.element(names(dimnames(nombresR)), factors)), + function(x,...){ifelse(all(is.na(x)), NA, mean(x,...))}, na.rm=TRUE) + + ## Maxima : + nombresMax <- apply(nombresR, which(is.element(names(dimnames(nombresR)), factors)), + function(x,...){ifelse(all(is.na(x)), NA, max(x,...))}, na.rm=TRUE) + + ## SD : + nombresSD <- apply(nombresR, which(is.element(names(dimnames(nombresR)), factors)), + function(x,...){ifelse(all(is.na(x)), NA, sd(x,...))}, na.rm=TRUE) + + ## Valid rotations count : + nombresRotations <- apply(rotations, 1, sum, na.rm=TRUE) + + ## Results returned as list : + return(list(nombresMean=nombresMean, nombresMax=nombresMax, nombresSD=nombresSD, + nombresRotations=nombresRotations, nombresTot=nombresR)) +} + +######################################### end of the function statRotationsNumber.f + +######################################### start of the function calcNumber.default.f called by calc.numbers.f + +calcNumber.default.f <- function(obs, + factors=c("observation.unit", "species.code", "size.class"), + nbName="number") +{ + ## Purpose : Compute abundances at finest aggregation + ## --------------------------------------------------------------------- + ## Arguments: obs : observation table + ## factors : aggregation factors + ## nbName : name of abundance column. + ## + ## Output: array with ndimensions = nfactors. + ## ---------------------------------------------------------------------- + ## Author: Yves Reecht, Date: 19 déc. 2011, 13:38 modified by Coline ROYAUX 04 june 2020 + + ## Sum individuals number : + nbr <- tapply(obs[ , nbName], + as.list(obs[ , factors]), + sum, na.rm = TRUE) + + ## Absences as "true zero" : + nbr[is.na(nbr)] <- 0 + + return(nbr) +} + +######################################### end of the function calcNumber.default.f + +######################################### start of the function calc.numbers.f + +calc.numbers.f <- function(obs, ObsType="", factors=c("observation.unit", "species.code", "size.class"), nbName="number") +{ + ## Purpose: Produce data.frame used as table from output of calcNumber.default.f(). + ## ---------------------------------------------------------------------- + ## Arguments: obs : observation table + ## ObsType : Type of observation (SVR, LIT, ...) + ## factors : aggregation factors + ## nbName : name of abundance column + ## + ## Output: data.frame with (N aggregation factors + 1) columns + ## ---------------------------------------------------------------------- + ## Author: Yves Reecht, Date: 19 déc. 2011, 13:46 modified by Coline ROYAUX 04 june 2020 + + if (ObsType == "SVR") + { + ## Compute SVR abundances statistics : + statRotations <- statRotationsNumber.f(factors=factors, + obs=obs) + + ## Mean for rotating videos (3 rotations at most times) : + nbr <- statRotations[["nombresMean"]] + + }else{ + + nbr <- calcNumber.default.f(obs, factors, nbName) + } + + res <- as.data.frame(as.table(nbr), responseName=nbName) + + if (is.element("size.class", colnames(res))) + { + res$size.class[res$size.class == ""] <- NA + }else{} + + ## If integer abundances : + if (isTRUE(all.equal(res[ , nbName], as.integer(res[ , nbName])))) + { + res[ , nbName] <- as.integer(res[ , nbName]) + }else{} + + if (ObsType == "SVR") + { + ## statistics on abundances : + res$number.max <- as.vector(statRotations[["nombresMax"]]) + res$number.sd <- as.vector(statRotations[["nombresSD"]]) + + }else{} + + return(res) +} + +######################################### end of the function calc.numbers.f + +######################################### start of the function presAbs.f called by calcBiodiv.f + +presAbs.f <- function(nombres, logical=FALSE) +{ + ## Purpose: Compute presence absence from abundances + ## ---------------------------------------------------------------------- + ## Arguments: nombres : vector of individuals count. + ## logical : (boolean) results as boolean or 0/1 ? + ## ---------------------------------------------------------------------- + ## Author: Yves Reecht, Date: 29 oct. 2010, 10:20 modified by Coline ROYAUX 04 june 2020 + + if (any(nombres < 0, na.rm=TRUE)) + { + stop("Negative abundances!") + }else{} + + if (logical) + { + return(nombres > 0) + }else{ + nombres[nombres > 0] <- 1 + return(nombres) + } +} + +######################################### end of the function presAbs.f + +######################################### start of the function betterCbind called by agregations.generic.f + +betterCbind <- function(..., dfList=NULL, deparse.level = 1) +{ + ## Purpose: Apply cbind to data frame with mathcing columns but without + ## redundancies. + ## ---------------------------------------------------------------------- + ## Arguments: same as cbind... + ## dfList : data.frames list + ## ---------------------------------------------------------------------- + ## Author: Yves Reecht, Date: 17 janv. 2012, 21:10 modified by Coline ROYAUX 04 june 2020 + + if (is.null(dfList)) + { + dfList <- list(...) + }else{} + + return(do.call(cbind, + c(list(dfList[[1]][ , c(tail(colnames(dfList[[1]]), -1), + head(colnames(dfList[[1]]), 1))]), + lapply(dfList[-1], + function(x, colDel) + { + return(x[ , !is.element(colnames(x), + colDel), + drop=FALSE]) + }, + colDel=colnames(dfList[[1]])), + deparse.level=deparse.level))) +} + +######################################### end of the function betterCbind + +######################################### start of the function agregation.f called by agregations.generic.f + +agregation.f <- function(metric, Data, factors, casMetrique, + nbName="number") +{ + ## Purpose: metric aggregation + ## ---------------------------------------------------------------------- + ## Arguments: metric: colnames of chosen metric + ## Data: Unaggregated data table + ## factors: aggregation factors vector + ## casMetrique: named vector of observation types depending + ## on chosen metric + ## nbName : abundance column name + ## ---------------------------------------------------------------------- + ## Author: Yves Reecht, Date: 20 déc. 2011, 14:29 modified by Coline ROYAUX 04 june 2020 + + switch(casMetrique[metric], + "sum"={ + res <- tapply(Data[ , metric], + as.list(Data[ , factors, drop=FALSE]), + function(x) + { + ifelse(all(is.na(x)), + NA, + sum(x, na.rm=TRUE)) + }) + }, + "w.mean"={ + res <- tapply(1:nrow(Data), + as.list(Data[ , factors, drop=FALSE]), + function(ii) + { + ifelse(all(is.na(Data[ii, metric])), + NA, + weighted.mean(Data[ii, metric], + Data[ii, nbName], + na.rm=TRUE)) + }) + }, + "w.mean.colonies"={ + res <- tapply(1:nrow(Data), + as.list(Data[ , factors, drop=FALSE]), + function(ii) + { + ifelse(all(is.na(Data[ii, metric])), + NA, + weighted.mean(Data[ii, metric], + Data[ii, "colonies"], + na.rm=TRUE)) + }) + }, + "w.mean.prop"={ + res <- tapply(1:nrow(Data), + as.list(Data[ , factors, drop=FALSE]), + function(ii) + { + ifelse(all(is.na(Data[ii, metric])) || sum(Data[ii, "nombre.tot"], na.rm=TRUE) == 0, + NA, + ifelse(all(na.omit(Data[ii, metric]) == 0), # Pour ne pas avoir NaN. + 0, + (sum(Data[ii, nbName][ !is.na(Data[ii, metric])], na.rm=TRUE) / + sum(Data[ii, "nombre.tot"], na.rm=TRUE)) * + ## Correction if size class isn't an aggregation factor + ## (otherwise value divided by number of present classes) : + ifelse(is.element("size.class", factors), + 100, + 100 * length(unique(Data$size.class))))) + }) + + }, + "w.mean.prop.bio"={ + res <- tapply(1:nrow(Data), + as.list(Data[ , factors, drop=FALSE]), + function(ii) + { + ifelse(all(is.na(Data[ii, metric])) || sum(Data[ii, "tot.biomass"], na.rm=TRUE) == 0, + NA, + ifelse(all(na.omit(Data[ii, metric]) == 0), # Pour ne pas avoir NaN. + 0, + (sum(Data[ii, "biomass"][ !is.na(Data[ii, metric])], na.rm=TRUE) / + sum(Data[ii, "tot.biomass"], na.rm=TRUE)) * + ## Correction if size class isn't an aggregation factor + ## (otherwise value divided by number of present classes) : + ifelse(is.element("size.class", factors), + 100, + 100 * length(unique(Data$size.class))))) + }) + + }, + "pres"={ + res <- tapply(Data[ , metric], + as.list(Data[ , factors, drop=FALSE]), + function(x) + { + ifelse(all(is.na(x)), # When only NAs. + NA, + ifelse(any(x > 0, na.rm=TRUE), # Otherwise... + 1, # ... presence if at least one observation in the group. + 0)) + }) + }, + "nbMax"={ + ## Recuperation of raw abundances with selections : + nbTmp <- getReducedSVRdata.f(dataName=".NombresSVR", data=Data) + + ## Sum by factor cross / rotation : + nbTmp2 <- apply(nbTmp, + which(is.element(names(dimnames(nbTmp)), c(factors, "rotation"))), + function(x) + { + ifelse(all(is.na(x)), NA, sum(x, na.rm=TRUE)) + }) + + ## Sum by factor cross : + res <- as.array(apply(nbTmp2, + which(is.element(names(dimnames(nbTmp)), factors)), + function(x) + { + ifelse(all(is.na(x)), NA, max(x, na.rm=TRUE)) + })) + }, + "nbSD"={ + ## Recuperation of raw abundances with selections : + nbTmp <- getReducedSVRdata.f(dataName=".NombresSVR", data=Data) + + ## Sum by factor cross / rotation : + nbTmp2 <- apply(nbTmp, + which(is.element(names(dimnames(nbTmp)), c(factors, "rotation"))), + function(x) + { + ifelse(all(is.na(x)), NA, sum(x, na.rm=TRUE)) + }) + + ## Sum by factor cross : + res <- as.array(apply(nbTmp2, + which(is.element(names(dimnames(nbTmp)), factors)), + function(x) + { + ifelse(all(is.na(x)), NA, sd(x, na.rm=TRUE)) + })) + }, + "densMax"={ + ## Recuperation of raw abundances with selections : + densTmp <- getReducedSVRdata.f(dataName=".DensitesSVR", data=Data) + + ## Sum by factor cross / rotation : + densTmp2 <- apply(densTmp, + which(is.element(names(dimnames(densTmp)), c(factors, "rotation"))), + function(x) + { + ifelse(all(is.na(x)), NA, sum(x, na.rm=TRUE)) + }) + + ## Sum by factor cross : + res <- as.array(apply(densTmp2, + which(is.element(names(dimnames(densTmp)), factors)), + function(x) + { + ifelse(all(is.na(x)), NA, max(x, na.rm=TRUE)) + })) + }, + "densSD"={ + ## Recuperation of raw abundances with selections : + densTmp <- getReducedSVRdata.f(dataName=".DensitesSVR", data=Data) + + ## Sum by factor cross / rotation : + densTmp2 <- apply(densTmp, + which(is.element(names(dimnames(densTmp)), c(factors, "rotation"))), + function(x) + { + ifelse(all(is.na(x)), NA, sum(x, na.rm=TRUE)) + }) + + ## Sum by factor cross : + res <- as.array(apply(densTmp2, + which(is.element(names(dimnames(densTmp)), factors)), + function(x) + { + ifelse(all(is.na(x)), NA, sd(x, na.rm=TRUE)) + })) + }, + "%.nesting"={ + res <- tapply(1:nrow(Data), + as.list(Data[ , factors, drop=FALSE]), + function(ii) + { + ifelse(all(is.na(Data[ii, metric])), + NA, + weighted.mean(Data[ii, metric], + Data[ii, "readable.tracks"], + na.rm=TRUE)) + }) + }, + stop("Not implemented!") + ) + + ## dimension names + names(dimnames(res)) <- c(factors) + + ## Transformation to long format : + reslong <- as.data.frame(as.table(res), responseName=metric) + reslong <- reslong[ , c(tail(colnames(reslong), 1), head(colnames(reslong), -1))] # metric first + + return(reslong) +} + +######################################### end of the function agregation.f + +######################################### start of the function agregations.generic.f called y calcBiodiv.f in FucntExeCalcCommIndexesGalaxy.r + +agregations.generic.f <- function(Data, metrics, factors, listFact=NULL, unitSpSz=NULL, unitSp=NULL, + nbName="number") +{ + ## Purpose: Aggregate data + ## ---------------------------------------------------------------------- + ## Arguments: Data : data set + ## metrics : aggregated metric + ## factors : aggregation factors + ## listFact : other factors to aggregate and add to output + ## unitSpSz : Metrics table by unitobs/species/Size Class + ## unitSp : Metrics table by unitobs/species + ## nbName : abundance colname + ## + ## Output : aggregated data frame + ## ---------------------------------------------------------------------- + ## Author: Yves Reecht, Date: 18 oct. 2010, 15:47 modified by Coline ROYAUX 04 june 2020 + + ## trt depending on metric type : + casMetrique <- c("number"="sum", + "mean.length"="w.mean", + "taille_moy"="w.mean", + "biomass"="sum", + "Biomass"="sum", + "weight"="sum", + "mean.weight"="w.mean", + "density"="sum", + "Density"="sum", + "CPUE"="sum", + "CPUE.biomass"="sum", + "pres.abs"="pres", + "abundance.prop.SC"="w.mean.prop", # Not OK [!!!] ? + "biomass.prop.SC"="w.mean.prop.bio", # Not OK [!!!] ? + ## Benthos : + "colonies"="sum", + "coverage"="sum", + "mean.size.colonies"="w.mean.colonies", + ## SVR (expérimental) : + "number.max"="nbMax", + "number.sd"="nbSD", + "density.max"="densMax", + "density.sd"="densSD", + "biomass.max"="sum", + "spawning.success"="%.nesting", + "spawnings"="sum", + "readable.tracks"="sum", + "tracks.number"="sum") + + ## add "readable.tracks" for egg laying percentage : + if (any(casMetrique[metrics] == "%.nesting")) + { + if (is.element("size.class", colnames(Data))) + { + if (is.null(unitSpSz)) stop("unitSpSz doit être défini") + + Data <- merge(Data, + unitSpSz[ , c("species.code", "observation.unit", "size.class", "readable.tracks")], + by=c("species.code", "observation.unit", "size.class"), + suffixes=c("", ".y")) + }else{ + if (is.null(unitSp)) stop("unitSp must be defined") + + Data <- merge(Data, + unitSp[ , c("species.code", "observation.unit", "readable.tracks")], + by=c("species.code", "observation.unit"), + suffixes=c("", ".y")) + } + }else{} + + ## Add "number" field for computing ponderate means if absent : + if (any(casMetrique[metrics] == "w.mean" | casMetrique[metrics] == "w.mean.prop")) + { + if (is.element("size.class", colnames(Data))) + { + if (is.null(unitSpSz)) stop("unitSpSz must be defined") + + Data <- merge(Data, + unitSpSz[ , c("species.code", "observation.unit", "size.class", nbName)], + by=c("species.code", "observation.unit", "size.class"), + suffixes=c("", ".y")) + + ## add tot abundance / species / observation unit : + nbTot <- tapply(unitSpSz[ , nbName], + as.list(unitSpSz[ , c("species.code", "observation.unit")]), + sum, na.rm=TRUE) + + Data <- merge(Data, + as.data.frame(as.table(nbTot), responseName="nombre.tot")) + }else{ + if (is.null(unitSp)) stop("unitSp must be defined") + + Data <- merge(Data, + unitSp[ , c("species.code", "observation.unit", nbName)], # [!!!] unitSpSz ? + by=c("species.code", "observation.unit"), + suffixes=c("", ".y")) + } + }else{} + + ## Add biomass field of biomass proportion by size class : + if (any(casMetrique[metrics] == "w.mean.prop.bio")) + { + if (is.null(unitSpSz)) stop("unitSpSz doit être défini") + + Data <- merge(Data, + unitSpSz[ , c("species.code", "observation.unit", "size.class", "biomass")], + by=c("species.code", "observation.unit", "size.class"), + suffixes=c("", ".y")) + + ## add tot biomass / species / observation unit : + biomTot <- tapply(unitSpSz$biomass, + as.list(unitSpSz[ , c("species.code", "observation.unit")]), + function(x) + { + ifelse(all(is.na(x)), + NA, + sum(x, na.rm=TRUE)) + }) + + Data <- merge(Data, + as.data.frame(as.table(biomTot), responseName="tot.biomass")) + } + + ## add colony field for ponderate means pondérées if absent : + if (any(casMetrique[metrics] == "w.mean.colonies" & ! is.element("colonies", colnames(Data)))) + { + Data$colonies <- unitSp[match(apply(Data[ , c("species.code", "observation.unit")], + 1, paste, collapse="*"), + apply(unitSp[ , c("species.code", "observation.unit")], + 1, paste, collapse="*")), "colonies"] + }else{} + + + ## Aggregation of metric depending on factors : + reslong <- betterCbind(dfList=lapply(metrics, # sapply used to have names + agregation.f, + Data=Data, factors=factors, casMetrique=casMetrique, + nbName=nbName)) + + ## Aggregation and add other factors : + if ( ! (is.null(listFact) || length(listFact) == 0)) + { + reslong <- cbind(reslong, + sapply(Data[ , listFact, drop=FALSE], + function(fact) + { + tapply(fact, + as.list(Data[ , factors, drop=FALSE]), + function(x) + { + if (length(x) > 1 && length(unique(x)) > 1) # must be one modality + { + return(NULL) # otherwise it is NULL + }else{ + unique(as.character(x)) + } + }) + })) + }else{} + + ## If some factors aren't at the right class : + if (any(tmp <- sapply(reslong[ , listFact, drop=FALSE], class) != sapply(Data[ , listFact, drop=FALSE], class))) + { + for (i in which(tmp)) + { + switch(sapply(Data[ , listFact, drop=FALSE], class)[i], + "integer"={ + reslong[ , listFact[i]] <- as.integer(as.character(reslong[ , listFact[i]])) + }, + "numeric"={ + reslong[ , listFact[i]] <- as.numeric(as.character(reslong[ , listFact[i]])) + }, + reslong[ , listFact[i]] <- eval(call(paste("as", sapply(Data[ , listFact, drop=FALSE], class)[i], sep="."), + reslong[ , listFact[i]])) + ) + } + }else{} + + ## Initial order of factors levels : + reslong <- as.data.frame(sapply(colnames(reslong), + function(x) + { + if (is.factor(reslong[ , x])) + { + return(factor(reslong[ , x], levels=levels(Data[ , x]))) + }else{ + return(reslong[ , x]) + } + }, simplify=FALSE)) + + + ## Check of other aggregated factors supplémentaires. There must be no NULL elements : + if (any(sapply(reslong[ , listFact], function(x){any(is.null(unlist(x)))}))) + { + warning(paste("One of the suppl. factors is probably a subset", + " of the observations grouping factor(s).", sep="")) + return(NULL) + }else{ + return(reslong) + } +} + +######################################### end of the function agregations.generic.f + +######################################### start of the function dropLevels.f called y calcBiodiv.f in FucntExeCalcCommIndexesGalaxy.r and modeleLineaireWP2.unitobs.f in FunctExeCalcGLMGalaxy.r +dropLevels.f <- function(df, which=NULL) +{ + ## Purpose: Suppress unused levels of factors + ## ---------------------------------------------------------------------- + ## Arguments: df : a data.frame + ## which : included columns index (all by default) + ## ---------------------------------------------------------------------- + ## Author: Yves Reecht, Date: 10 août 2010, 13:29 modified by Coline ROYAUX 04 june 2020 + + if (class(df) != "data.frame") + { + stop("'df' must be a data.frame") + }else{ + if (is.null(which)) + { + x <- as.data.frame(sapply(df, function(x) + { + return(x[ ,drop=TRUE]) + }, simplify=FALSE), + stringsAsFactors=FALSE) + }else{ # Only some columns used + x <- df + + x[ , which] <- as.data.frame(sapply(df[ , which, drop=FALSE], + function(x) + { + return(x[ , drop=TRUE]) + }, simplify=FALSE), + stringsAsFactors=FALSE) + } + + return(x) + } +} +######################################### end of the function dropLevels.f + +######################################### start of the function subsetToutesTables.f called by modeleLineaireWP2.unitobs.f in FunctExeCalcGLMGalaxy.r + +subsetToutesTables.f <- function(metrique, tabMetrics, facteurs, selections, + tabUnitobs, refesp, tableMetrique="", nbName="number", ObsType = "", + exclude=NULL, add=c("species.code", "observation.unit")) +{ + ## Purpose: Extract useful data only from chosen metrics and factors + ## ---------------------------------------------------------------------- + ## Arguments: metrique : chosen metric + ## facteurs : all chosen factors + ## selections : corresponding modality selected + ## tableMetrique : metrics table name + ## exclude : factors levels to exclude + ## add : field to add to data table + ## ---------------------------------------------------------------------- + ## Author: Yves Reecht, Date: 6 août 2010, 16:46 modified by Coline ROYAUX 04 june 2020 + + ## If no metrics table available : + if (is.element(tableMetrique, c("", "TableOccurrences", "TablePresAbs"))) + { + tableMetrique <- "unitSp" + }else{} + + casTables <- c("unitSp"="unitSp", + "TablePresAbs"="unitSp", + "unitSpSz"="unitSpSz") + + ## Recuperation of metrics table : + dataMetrique <- tabMetrics + unitobs <- tabUnitobs + refesp <- refesp + + ## If no metrics available or already computed : + if (is.element(metrique, c("", "occurrence.frequency"))) + { + metrique <- "tmp" + dataMetrique$tmp <- 0 + dataMetrique$tmp[dataMetrique[ , nbName] > 0] <- 1 + }else{} + + if (!is.null(add)) + { + metriques <- c(metrique, add[is.element(add, colnames(dataMetrique))]) + }else{ + metriques <- metrique + } + + ## Subset depending on metrics table + switch(casTables[tableMetrique], + ## Observation table by unitobs and species : + unitSp={ + restmp <- cbind(dataMetrique[!is.na(dataMetrique[ , metrique]) , metriques, drop=FALSE], + unitobs[match(dataMetrique$observation.unit[!is.na(dataMetrique[ , metrique])], + unitobs$observation.unit), # ajout des colonnes sélectionnées d'unitobs + facteurs[is.element(facteurs, colnames(unitobs))], drop=FALSE], + refesp[match(dataMetrique$species.code[!is.na(dataMetrique[ , metrique])], + refesp$species.code), # ajout des colonnes sélectionnées d'especes + facteurs[is.element(facteurs, colnames(refesp))], drop=FALSE]) + }, + ## Observation table by unitobs, species and size class : + unitSpSz={ + restmp <- cbind(dataMetrique[!is.na(dataMetrique[ , metrique]) , + c(metriques, "size.class"), drop=FALSE], + unitobs[match(dataMetrique$observation.unit[!is.na(dataMetrique[ , metrique])], + unitobs$observation.unit), # ajout des colonnes sélectionnées d'unitobs + facteurs[is.element(facteurs, colnames(unitobs))], drop=FALSE], + refesp[match(dataMetrique$species.code[!is.na(dataMetrique[ , metrique])], + refesp$species.code), # ajout des colonnes sélectionnées d'especes + facteurs[is.element(facteurs, colnames(refesp))], drop=FALSE]) + }, + ## Other cases : + restmp <- cbind(dataMetrique[!is.na(dataMetrique[ , metrique]) , metriques, drop=FALSE], + unitobs[match(dataMetrique$observation.unit[!is.na(dataMetrique[ , metrique])], + unitobs$observation.unit), # ajout des colonnes sélectionnées d'unitobs. + facteurs[is.element(facteurs, colnames(unitobs))], drop=FALSE]) + ) + + selCol <- which(!is.na(selections)) + if (!is.null(exclude)) + { + selCol <- selCol[selCol != exclude] + } + + ## Particular case of size classes : + if (is.element("size.class", colnames(restmp))) + { + if (length(grep("^[[:digit:]]*[-_][[:digit:]]*$", unique(as.character(restmp$size.class)), perl=TRUE)) == + length(unique(as.character(restmp$size.class)))) + { + restmp$size.class <- + factor(as.character(restmp$size.class), + levels=unique(as.character(restmp$size.class))[ + order(as.numeric(sub("^([[:digit:]]*)[-_][[:digit:]]*$", + "\\1", + unique(as.character(restmp$size.class)), + perl=TRUE)), + na.last=FALSE)]) + }else{ + restmp$size.class <- factor(restmp$size.class) + } + }else{} + + ## Biomass and density conversion -> /100m² : + if (any(is.element(colnames(restmp), c("biomass", "density", + "biomass.max", "density.max", + "biomass.sd", "density.sd"))) && ObsType != "fishing") + { + restmp[ , is.element(colnames(restmp), + c("biomass", "density", + "biomass.max", "density.max", + "biomass.sd", "density.sd"))] <- 100 * + restmp[, is.element(colnames(restmp), + c("biomass", "density", + "biomass.max", "density.max", + "biomass.sd", "density.sd"))] + }else{} + + return(restmp) +} + +######################################### end of the function subsetToutesTables.f + + +######################################### start of the function sortiesLM.f called by modeleLineaireWP2.unitobs.f in FunctExeCalcGLMGalaxy.r +sortiesLM.f <- function(objLM, TabSum, #formule, + metrique, factAna, cut, colAna, listFact, lev = NULL, Data, + Log=FALSE, sufixe=NULL, type="espece") +{ + ## Purpose: Form GLM and LM results + ## ---------------------------------------------------------------------- + ## Arguments: objLM : lm object + ## TabSum : output summary table + ## formule : LM formula + ## metrique : Chosen metric + ## factAna : separation factor + ## cut : level of separation factor + ## colAna : colname for separation factor in output summary table + ## listFact : Analysis factors list + ## levels : Levels of analysis factors list + ## Data : Data used for analysis + ## Log : put log on metric ? (boolean) + ## sufixe : sufix for file name + ## type : analysis type + ## ---------------------------------------------------------------------- + ## Author: Yves Reecht, Date: 25 août 2010, 16:19 modified by Coline ROYAUX 04 june 2020 + + sumLM <- summary(objLM) + if (length(grep("^glmmTMB", objLM$call)) > 0) #if random effects + { + TabSum[TabSum[,colAna]==cut,"AIC"] <- sumLM$AICtab[1] + TabSum[TabSum[,colAna]==cut,"BIC"] <- sumLM$AICtab[2] + TabSum[TabSum[,colAna]==cut,"logLik"] <- sumLM$AICtab[3] + TabSum[TabSum[,colAna]==cut,"deviance"] <- sumLM$AICtab[4] + TabSum[TabSum[,colAna]==cut,"df.resid"] <- sumLM$AICtab[5] + + if (! is.null(lev)) ## if fixed effects + random effects + { + TabCoef <- as.data.frame(sumLM$coefficients$cond) + TabCoef$signif <- lapply(TabCoef[,"Pr(>|z|)"],FUN=function(x){if(!is.na(x) && x < 0.05){"yes"}else{"no"}}) + + TabSum[TabSum[,colAna]==cut,grepl("Intercept.*Zvalue",colnames(TabSum))] <- TabCoef[grepl("Intercept",rownames(TabCoef)),"z value"] + TabSum[TabSum[,colAna]==cut,grepl("Intercept.*Pvalue",colnames(TabSum))] <- TabCoef[grepl("Intercept",rownames(TabCoef)),"Pr(>|z|)"] + + TabSum[TabSum[,colAna]==cut,grepl(paste(lev,"Zvalue",collapse="|"),colnames(TabSum))] <- unlist(lapply(lev,FUN=function(x){if (length(grep(x,rownames(TabCoef))) > 0) {TabCoef[grepl(x,rownames(TabCoef)),"z value"]}else{NA}})) + TabSum[TabSum[,colAna]==cut,grepl(paste(lev,"Pvalue",collapse="|"),colnames(TabSum))] <- unlist(lapply(lev,FUN=function(x){if (length(grep(x,rownames(TabCoef))) > 0) {TabCoef[grepl(x,rownames(TabCoef)),"Pr(>|z|)"]}else{NA}})) + }else{} + + switch(as.character(length(sumLM$varcor$cond)), + "1"={StdD <- c(sumLM$varcor$cond[[1]])}, + "2"={StdD <- c(sumLM$varcor$cond[[1]],sumLM$varcor$cond[[2]])}, + StdD <- NULL) + TabSum[TabSum[,colAna]==cut,grepl(paste(listRand,"Std.Dev",collapse="|"),colnames(TabSum))] <- StdD + TabSum[TabSum[,colAna]==cut,grepl(paste(listRand,"NbObservation",collapse="|"),colnames(TabSum))] <- sumLM$nobs + TabSum[TabSum[,colAna]==cut,grepl(paste(listRand,"NbLevels",collapse="|"),colnames(TabSum))] <- unlist(lapply(listRand,FUN=function(x){nlevels(Data[,x])})) + + }else{ ## if fixed effects only + + TabSum[TabSum[,colAna]==cut,"AIC"] <- sumLM$aic + TabSum[TabSum[,colAna]==cut,"Resid.deviance"] <- sumLM$deviance + TabSum[TabSum[,colAna]==cut,"df.resid"] <- sumLM$df.residual + TabSum[TabSum[,colAna]==cut,"Null.deviance"] <- sumLM$null.deviance + TabSum[TabSum[,colAna]==cut,"df.null"] <- sumLM$df.null + TabCoef <- as.data.frame(sumLM$coefficients) + + if (sumLM$family[1] == "gaussian" || sumLM$family[1] == "quasipoisson") + { + + TabCoef$signif <- lapply(TabCoef[,"Pr(>|t|)"],FUN=function(x){if(!is.na(x) && x < 0.05){"yes"}else{"no"}}) + TabSum[TabSum[,colAna]==cut,grepl("Intercept.*Tvalue",colnames(TabSum))] <- TabCoef[grepl("Intercept",rownames(TabCoef)),"t value"] + TabSum[TabSum[,colAna]==cut,grepl("Intercept.*Pvalue",colnames(TabSum))] <- TabCoef[grepl("Intercept",rownames(TabCoef)),"Pr(>|t|)"] + + TabSum[TabSum[,colAna]==cut,grepl(paste(lev,"Tvalue",collapse="|"),colnames(TabSum))] <- unlist(lapply(lev,FUN=function(x){if (length(grep(x,rownames(TabCoef))) > 0) {TabCoef[grepl(x,rownames(TabCoef)),"t value"]}else{NA}})) + + TabSum[TabSum[,colAna]==cut,grepl(paste(lev,"Pvalue",collapse="|"),colnames(TabSum))] <- unlist(lapply(lev,FUN=function(x){if (length(grep(x,rownames(TabCoef))) > 0) {TabCoef[grepl(x,rownames(TabCoef)),"Pr(>|t|)"]}else{NA}})) + }else{ + TabCoef$signif <- lapply(TabCoef[,"Pr(>|z|)"],FUN=function(x){if(!is.na(x) && x < 0.05){"yes"}else{"no"}}) + + TabSum[TabSum[,colAna]==cut,grepl("Intercept.*Zvalue",colnames(TabSum))] <- TabCoef[grepl("Intercept",rownames(TabCoef)),"z value"] + TabSum[TabSum[,colAna]==cut,grepl("Intercept.*Pvalue",colnames(TabSum))] <- TabCoef[grepl("Intercept",rownames(TabCoef)),"Pr(>|z|)"] + + TabSum[TabSum[,colAna]==cut,grepl(paste(lev,"Zvalue",collapse="|"),colnames(TabSum))] <- unlist(lapply(lev,FUN=function(x){if (length(grep(x,rownames(TabCoef))) > 0) {TabCoef[grepl(x,rownames(TabCoef)),"z value"]}else{NA}})) + TabSum[TabSum[,colAna]==cut,grepl(paste(lev,"Pvalue",collapse="|"),colnames(TabSum))] <- unlist(lapply(lev,FUN=function(x){if (length(grep(x,rownames(TabCoef))) > 0) {TabCoef[grepl(x,rownames(TabCoef)),"Pr(>|z|)"]}else{NA}})) + } + } + + if (! is.null(lev)) ## if fixed effects + { + TabSum[TabSum[,colAna]==cut,grepl("Intercept.*Estimate",colnames(TabSum))] <- TabCoef[grepl("Intercept",rownames(TabCoef)),"Estimate"] + TabSum[TabSum[,colAna]==cut,grepl("Intercept.*Std.Err",colnames(TabSum))] <- TabCoef[grepl("Intercept",rownames(TabCoef)),"Std. Error"] + TabSum[TabSum[,colAna]==cut,grepl("Intercept.*signif",colnames(TabSum))] <- TabCoef[grepl("Intercept",rownames(TabCoef)),"signif"] + + TabSum[TabSum[,colAna]==cut,grepl(paste(lev,"Estimate",collapse="|"),colnames(TabSum))] <- unlist(lapply(lev,FUN=function(x){if (length(grep(x,rownames(TabCoef))) > 0) {TabCoef[grepl(x,rownames(TabCoef)),"Estimate"]}else{NA}})) + + TabSum[TabSum[,colAna]==cut,grepl(paste(lev,"Std.Err",collapse="|"),colnames(TabSum))] <- unlist(lapply(lev,FUN=function(x){if (length(grep(x,rownames(TabCoef))) > 0) {TabCoef[grepl(x,rownames(TabCoef)),"Std. Error"]}else{NA}})) + TabSum[TabSum[,colAna]==cut,grepl(paste(lev,"signif",collapse="|"),colnames(TabSum))] <- unlist(lapply(lev,FUN=function(x){if (length(grep(x,rownames(TabCoef))) > 0) {TabCoef[grepl(x,rownames(TabCoef)),"signif"]}else{NA}})) + }else{} + + return(TabSum) + +} + + +######################################### end of the function sortiesLM.f + +######################################### start of the function graphTitle.f called by sortiesLM.f + +graphTitle.f <- function(metrique, modGraphSel, factGraph, listFact, model=NULL, type="espece", + lang = getOption("P.lang")) +{ + ## Purpose: Automatically write a name for a graph + ## ---------------------------------------------------------------------- + ## Arguments: + ## ---------------------------------------------------------------------- + ## Author: Yves Reecht, Date: 14 oct. 2010, 15:44 modified by Coline ROYAUX 04 june 2020 + return(paste(ifelse(is.null(model), + "Values of ", + paste(model, + " for", + sep="")), + metrique, + ifelse(is.element(type, c("espece", "unitobs", "CL_espece", "unitobs(CL)")), + paste("aggregated"), + ""), + switch(type, + "espece"=" per species and station", + "CL_espece"=" per size class, species and station", + "unitobs"=" per station", + "unitobs(CL)"=" per station", + "CL_unitobs"=" per size class and station", + "biodiv"=" per station", + ""), + switch(type, + "espece"={ + ifelse(modGraphSel == "", # Only separation factor if defined + "", + paste("\nfor the field", + " '", factGraph, "' = ", modGraphSel, sep="")) + }, + "CL_espece"={ + ifelse(modGraphSel == "", # Only separation factor if defined + "", + paste("\nfor the field", + " '", factGraph, "' = ", modGraphSel, sep="")) + }, + "unitobs"={ + ifelse(modGraphSel[1] == "", # Only separation factor if defined + "\nfor all species", + paste("\nfor all species matching", + " '", factGraph, "' = (", + paste(modGraphSel, collapse=", "), ")", sep="")) + }, + "unitobs(CL)"={ + ifelse(modGraphSel[1] == "", # Only separation factor if defined + "\nfor all size classes", + paste("\nfor size classes matching", + " '", factGraph, "' = (", + paste(modGraphSel, collapse=", "), ")", sep="")) + }, + "CL_unitobs"={ + ifelse(modGraphSel[1] == "", # Only separation factor if defined + "\nfor all species", + paste("\nfor all species matching", + " '", factGraph, "' = (", + paste(modGraphSel, collapse=", "), ")", sep="")) + }, + "biodiv"={ + ifelse(modGraphSel[1] == "", # Only separation factor if defined + "", + paste("\nfor stations matching", + " '", factGraph, "' = (", + paste(modGraphSel, collapse=", "), ")", sep="")) + }, + ""), + "\n by ", + paste(sapply(listFact[length(listFact):1], + function(x)paste(c(## varNames.f(x, "article"), + "", + x, collapse="")), + collapse=" and"), + "\n", sep=""))) +} + +######################################### end of the function graphTitle.f + +######################################### start of the function noteGLM.f called by modeleLineaireWP2.species.f and modeleLineaireWP2.unitobs.f + +noteGLM.f <- function(data, objLM, metric, listFact, details = FALSE) +{ + ## Purpose: Note your GLM analysis + ## ---------------------------------------------------------------------- + ## Arguments: data : Dataframe used for analysis + ## objLM : GLM assessed + ## metric : selected metric + ## listFact : Analysis factors list + ## ---------------------------------------------------------------------- + ## Author: Coline ROYAUX, 26 june 2020 + + rate <- 0 + detres <- list(complete_plan=NA, balanced_plan=NA, NA_proportion_OK=NA, no_residual_dispersion=NA, uniform_residuals=NA, outliers_proportion_OK=NA, no_zero_inflation=NA, observation_factor_ratio_OK=NA, enough_levels_random_effect=NA, rate=NA) + + #### Data criterions #### + + ## Plan + + plan <- as.data.frame(table(data[,listFact])) + + if (nrow(plan[plan$Freq==0,]) < nrow(plan)*0.1) # +0.5 if less than 10% of possible factor's level combinations aren't represented in the sampling scheme + { + rate <- rate + 0.5 + detres$complete_plan <- TRUE + + if (summary(as.factor(plan$Freq))[1] > nrow(plan)*0.9) # +0.5 if the frequency of the most represented frequency of possible factor's levels combinations is superior to 90% of the total number of possible factor's levels combinations + { + rate <- rate + 0.5 + detres$balanced_plan <- TRUE + }else{} + + }else{ + detres$complete_plan <- FALSE + detres$balanced_plan <- FALSE + } + + if (nrow(data) - nrow(na.omit(data)) < nrow(data)*0.1) # +1 if less than 10% of the lines in the dataframe bares a NA + { + rate <- rate + 1 + detres$NA_proportion_OK <- TRUE + }else{ + detres$NA_proportion_OK <- FALSE + } + + #### Model criterions #### + + if (length(grep("quasi",objLM$family)) == 0) #DHARMa doesn't work with quasi distributions + { + + Residuals <- simulateResiduals(objLM) + + capture.output(testRes <- testResiduals(Residuals)) + testZero <- testZeroInflation(Residuals) + + ## dispersion of residuals + + if (testRes$dispersion$p.value > 0.05) # +1.5 if dispersion tests not significative + { + rate <- rate + 1.5 + detres$no_residual_dispersion <- TRUE + }else{ + detres$no_residual_dispersion <- FALSE + } + + ## uniformity of residuals + + if (testRes$uniformity$p.value > 0.05) # +1 if uniformity tests not significative + { + rate <- rate + 1.5 + detres$uniform_residuals <- TRUE + }else{ + detres$uniform_residuals <- FALSE + } + + ## residuals outliers + + if (testRes$outliers$p.value > 0.05) # +0.5 if outliers tests not significative + { + rate <- rate + 0.5 + detres$outliers_proportion_OK <- TRUE + }else{ + detres$outliers_proportion_OK <- FALSE + } + + ## Zero inflation test + + if (testZero$p.value > 0.05) # +1 if zero inflation tests not significative + { + rate <- rate + 1.5 + detres$no_zero_inflation <- TRUE + }else{ + detres$no_zero_inflation <- FALSE + } + + ## Factors/observations ratio + + if (length(listFact)/nrow(na.omit(data)) < 0.1) # +1 if quantity of factors is less than 10% of the quantity of observations + { + rate <- rate + 1 + detres$observation_factor_ratio_OK <- TRUE + }else{ + detres$observation_factor_ratio_OK <- FALSE + } + + ## less than 10 factors' level on random effect + + if (length(grep("^glmmTMB", objLM$call)) > 0) + { + nlevRand <- c() + for(fact in names(summary(objLM)$varcor$cond)) + { + nlevRand <- c(nlevRand,length(unlist(unique(data[,fact])))) + } + + if (all(nlevRand > 10)) # +1 if more than 10 levels in one random effect + { + rate <- rate + 1 + detres$enough_levels_random_effect <- TRUE + }else{ + detres$enough_levels_random_effect <- FALSE + } + }else{} + + detres$rate <- rate + + if (details) + { + return(detres) + }else{ + return(rate) + } + + }else{ + return(NA) + cat("Models with quasi distributions can't be rated for now") + } +} + +######################################### end of the function noteGLM.f + +######################################### start of the function noteGLMs.f called by modeleLineaireWP2.species.f and modeleLineaireWP2.unitobs.f + +noteGLMs.f <- function(tabRate, exprML, objLM, file_out=FALSE) +{ + ## Purpose: Note your GLM analysis + ## ---------------------------------------------------------------------- + ## Arguments: data : rates table from noteGLM.f + ## objLM : GLM assessed + ## metric : selected metric + ## listFact : Analysis factors list + ## ---------------------------------------------------------------------- + ## Author: Coline ROYAUX, 26 june 2020 + + RateM <- mean(na.omit(tabRate[,"rate"])) + sum <- summary(objLM) + + if (length(grep("^glmmTMB", objLM$call)) > 0) + { + if (median(na.omit(tabRate[,"rate"])) >= 6) # if 50% has a rate superior or equal to 6 +1 + { + RateM <- RateM + 1 + } + + if (quantile(na.omit(tabRate[,"rate"]), probs=0.9) >= 6) # if 90% has a rate superior or equal to 6 +1 + { + RateM <- RateM + 1 + } + }else{ + if (median(na.omit(tabRate[,"rate"])) >= 5) # if 50% has a rate superior or equal to 5 +1 + { + RateM <- RateM + 1 + } + + if (quantile(na.omit(tabRate[,"rate"]), probs=0.9) >= 5) # if 90% has a rate superior or equal to 5 +1 + { + RateM <- RateM + 1 + } + } + + if (file_out) + { + namefile <- "RatingGLM.txt" + + cat("###########################################################################", + "\n########################### Analysis evaluation ###########################", + "\n###########################################################################", file=namefile, fill=1,append=TRUE) + + ## Informations on model : + cat("\n\n######################################### \nFitted model:", file=namefile, fill=1,append=TRUE) + cat("\t", deparse(exprML), "\n\n", file=namefile, sep="",append=TRUE) + cat("Family: ", sum$family[[1]], + file=namefile,append=TRUE) + cat("\n\nNumber of analysis: ", nrow(tabRate), file=namefile, append=TRUE) + + ## Global rate : + cat("\n\n######################################### \nGlobal rate for all analysis:", + "\n\n", RateM, "out of 10", file=namefile, append=TRUE) + + ## details on every GLM : +#NA_proportion_OK=NA, no_residual_dispersion=NA, uniform_residuals=NA, outliers_proportion_OK=NA, no_zero_inflation=NA, observation_factor_ratio_OK=NA, enough_levels_random_effect=NA, rate=NA + cat("\n\n######################################### \nDetails on every analysis:\n\n", file=namefile, append=TRUE) + cat("Analysis\tC1\tC2\tC3\tC4\tC5\tC6\tC7\tC8\tC9\tFinal rate", file=namefile, append=TRUE) + apply(tabRate, 1, FUN=function(x) + { + + if (!is.na(x["complete_plan"]) && x["complete_plan"]==TRUE) + { + cat("\n",x[1],"\tyes", file=namefile, append=TRUE) + }else{ + cat("\n",x[1],"\tno", file=namefile, append=TRUE) + } + + for (i in c("balanced_plan","NA_proportion_OK", "no_residual_dispersion", "uniform_residuals", "outliers_proportion_OK", "no_zero_inflation", "observation_factor_ratio_OK", "enough_levels_random_effect")) + { + if (!is.na(x[i]) && x[i]==TRUE) + { + cat("\tyes", file=namefile, append=TRUE) + }else{ + cat("\tno", file=namefile, append=TRUE) + } + } + + cat("\t",x["rate"], "/ 8", file=namefile, append=TRUE) + + + }) + cat("\n\nC1: Complete plan?\nC2: Balanced plan?\nC3: Few NA?\nC4: Regular dispersion?\nC5: Uniform residuals?\nC6: Regular outliers proportion?\nC7: No zero-inflation?\nC8: Enough observations for the amount of factors?\nC9: Enough levels on random effect?", file=namefile, append=TRUE) + + ## Red flags - advice : + cat("\n\n######################################### \nRed flags - advice:\n\n", file=namefile, append=TRUE) + if (all(na.omit(tabRate["NA_proportion_OK"]) == FALSE)) + { + cat("\n","\t- More than 10% of your dataset bares NAs", file=namefile, append=TRUE) + }else{} + + if (length(grep("FALSE",tabRate["no_residual_dispersion"])) / length(na.omit(tabRate["no_residual_dispersion"])) > 0.5) + { + cat("\n","\t- More than 50% of your analyses are over- or under- dispersed : Try with another distribution family", file=namefile, append=TRUE) + }else{} + + if (length(grep("FALSE",tabRate["uniform_residuals"])) / length(na.omit(tabRate["uniform_residuals"])) > 0.5) + { + cat("\n","\t- More than 50% of your analyses haven't an uniform distribution of residuals : Try with another distribution family", file=namefile, append=TRUE) + }else{} + + if (length(grep("FALSE",tabRate["outliers_proportion_OK"])) / length(na.omit(tabRate["outliers_proportion_OK"])) > 0.5) + { + cat("\n","\t- More than 50% of your analyses have too much outliers : Try with another distribution family or try to select your data", file=namefile, append=TRUE) + }else{} + + if (length(grep("FALSE",tabRate["no_zero_inflation"])) / length(na.omit(tabRate["no_zero_inflation"])) > 0.5) + { + cat("\n","\t- More than 50% of your analyses have zero inflation : Try to select your data", file=namefile, append=TRUE) + }else{} + + if (length(grep("FALSE",tabRate["observation_factor_ratio_OK"])) / length(na.omit(tabRate["observation_factor_ratio_OK"])) > 0.5) + { + cat("\n","\t- More than 50% of your analyses have not enough observations for the amount of factors : Try to use less factors in your analysis or try to use another separation factor", file=namefile, append=TRUE) + }else{} + + if (any(tabRate["enough_levels_random_effect"] == FALSE, na.rm=TRUE) && length(grep("^glmmTMB", objLM$call)) > 0) + { + cat("\n","\t- Random effect hasn't enough levels to be robust : If it has less than ten levels remove the random effect", file=namefile, append=TRUE) + }else{} + }else{ + + return(RateM) + + } +} + +######################################### end of the function noteGLM.f + +######################################### start of the function infoStats.f called by modeleLineaireWP2.species.f and modeleLineaireWP2.unitobs.f + +infoStats.f <- function(filename, Data, agregLevel=c("species", "unitobs"), type=c("graph", "stat"), + metrique, factGraph, factGraphSel, listFact, listFactSel) +{ + ## Purpose: Écrire les infos et statistic sur les données associées à + ## un graphique ou analyse. + ## ---------------------------------------------------------------------- + ## Arguments: filename : chemin du fichier de résultats. + ## Data : données du graphique/de l'analyse. + ## agregLevel : niveau d'agrégation de la fonction appelante. + ## type : type de fonction appelante (grapique ou analyse). + ## metrique : la métrique choisie. + ## factGraph : le facteur sélection des espèces. + ## factGraphSel : la sélection de modalités pour ce dernier + ## listFact : liste du (des) facteur(s) de regroupement + ## listFactSel : liste des modalités sélectionnées pour ce(s) + ## dernier(s) + ## ---------------------------------------------------------------------- + ## Author: Yves Reecht, Date: 10 sept. 2012, 15:26 modified by Coline ROYAUX 04 june 2020 + + ## Open file : + File <- file(description=filename, + open="w", encoding="latin1") + + ## if error : + on.exit(if (exists("filename") && + tryCatch(isOpen(File), + error=function(e)return(FALSE))) close(File)) + + ## Metrics and factors infos : + printSelectionInfo.f(metrique=metrique, #factGraph=factGraph, factGraphSel=factGraphSel, + listFact=listFact, #listFactSel=listFactSel, + File=File, + agregLevel=agregLevel, type=type) + + ## statistics : + if (class(Data) == "list") + { + cat("\n###################################################", + "\nStatistics per level of splitting factor:\n", + sep="", file=File,append=TRUE) + + invisible(sapply(1:length(Data), + function(i) + { + printStats.f(Data=Data[[i]], metrique=metrique, listFact=listFact, File=File, + headline=factGraphSel[i]) + })) + }else{ + printStats.f(Data=Data, metrique=metrique, listFact=listFact, File=File, + headline=NULL) + } + + ## Close file : + close(File) + +} + +######################################### end of the function infoStats.f + + +######################################### start of the function printSelectionInfo.f called by infoStats.f + +printSelectionInfo.f <- function(metrique, listFact, + File, + agregLevel=c("species", "unitobs"), type=c("graph", "stat")) +{ + ## Purpose: Write data informations + ## ---------------------------------------------------------------------- + ## Arguments: metrique : chosen metric + ## listFact : factor's list + ## File : Results file name + ## agregLevel : aggregation level + ## type : function type + ## ---------------------------------------------------------------------- + ## Author: Yves Reecht, Date: 11 sept. 2012, 10:41 modified by Coline ROYAUX 04 june 2020 + + cat("\n##################################################\n", + "Metrics and factors (and possible units/selections):\n", + sep="", file=File,append=TRUE) + + ## metric info : + cat("\n Metrics:", metrique, + "\n", file=File,append=TRUE) + + ## aggregation level : + cat(" aggregated per ", + switch(agregLevel, + "CL_espece"=,"CL_unitobs"=,"spCL_unitobs"=,"spCL_espece"={ + "size class / " + }), + switch(agregLevel, + "CL_espece"=,"spCL_espece"=,"species"=,"spSpecies"=,"spEspece"={ + "species / " + }), + switch(agregLevel, + "spUnitobs"=,"spCL_unitobs"=,"spCL_espece"=,"spUnitobs(CL)"=,"spSpecies"=,"spEspece"={ + paste(listFact, " (mean over ", sep="") + }), + "observation units", + switch(agregLevel, + "spUnitobs"=,"spCL_unitobs"=,"spCL_espece"=,"spUnitobs(CL)"=,"spSpecies"=,"spEspece"={ + ")" + }), + ".\n", + sep="", file=File,append=TRUE) + + ## Separation factors : +# switch(agregLevel, + # "species"=,"CL_espece"=,"espece"={ # Adapté également pour les LMs. + # cat("\n", + # switch(type, + # "graph"="Graphics separation factor", + # "stat"="Analyses separation factor"), + # " : ", + # ifelse(factGraph == "", "printSelectionInfo.f.11", + # ifelse(is.na(factGraphSel[1]), + # paste(varNames.f(factGraph, "nom"), "none!"), + # paste(varNames.f(factGraph, "nom"), " (", + # paste(factGraphSel, collapse=", "), ")", sep=""))), "\n", + # sep="", file=File,append=TRUE) +# }, + # "unitobs"=,"CL_unitobs"=,"unitobs(CL)"=,"spUnitobs"={ + # cat("(warning: no selection!!!)", + # ifelse(factGraph == "", "\nSelection factor for aggregation of observations: ", + # ifelse(is.na(factGraphSel[1]), + # paste(varNames.f(factGraph, "nom"), "none (all species/size classes)!"), + # paste(varNames.f(factGraph, "nom"), " (", + # paste(factGraphSel, collapse=", "), ")", sep=""))), "\n", + # sep="", file=File,append=TRUE) + # }) + + ## Clustering factors : + if (is.element(agregLevel, c("spCL_unitobs", "spCL_espece", "spSpecies", "spEspece", + "spUnitobs", "spUnitobs(CL)"))) {type <- "spatialGraph"} + + cat(switch(type, + "graph"="\nGrouping factor(s): \n * ", + "stat"="\nAnalyses factor(s): \n * ", + "spatialGraph"="\nSpatial aggregation factor(s): \n * "), + paste(listFact,collaspe="\n * "),"\n",file=File,append=TRUE) + +# invisible(sapply(1:length(listFact), + # function(i) + # { + # cat("\n * ", + # ifelse(is.na(listFactSel[[i]][1]), + # paste(varNames.f(listFact[i], "nom"), "(no selection)"), + # paste(varNames.f(listFact[i], "nom"), " (", + # paste(listFactSel[[i]], collapse=", "), ")", sep="")), "\n", + # sep="", file=File,append=TRUE) + # })) +} + +######################################### end of the function printSelectionInfo.f + + +######################################### start of the function printStats.f called by infoStats.f + +printStats.f <- function(Data, metrique, listFact, File, headline=NULL) +{ + ## Purpose: Write general statistics table + ## ---------------------------------------------------------------------- + ## Arguments: Data : Analysis data + ## metrique : metric's name + ## listFact : Factor's list + ## File : Simple statistics file name + ## ---------------------------------------------------------------------- + ## Author: Yves Reecht, Date: 11 sept. 2012, 10:09 modified by Coline ROYAUX 04 june 2020 + + ## Header : + if ( ! is.null(headline)) + { + cat("\n", rep("#", nchar(headline) + 3), "\n", + "## ", headline, "\n", + sep="", file=File,append=TRUE) + }else{} + + cat("\n########################\nBase statistics:\n\n", file=File,append=TRUE) + + capture.output(print(summary.fr(Data[ , metrique])), file=File, append=TRUE) + + if ( ! is.null(listFact)) + { + cat("\n#########################################", + "\nStatistics per combination of factor levels:\n\n", file=File, sep="",append=TRUE) + + ## Compute summary for each existing factor's cross : + res <- with(Data, + tapply(eval(parse(text=metrique)), + INDEX=do.call(paste, + c(lapply(listFact, + function(y)eval(parse(text=y))), + sep=".")), + FUN=summary.fr)) + + ## results in table + capture.output(print(do.call(rbind, res)), + file=File, append=TRUE) + }else{} + + ## empty line : + cat("\n", file=File,append=TRUE) +} + +######################################### end of the function printStats.f + + +######################################### start of the function summary.fr called by printStats.f +summary.fr <- function(object, digits = max(3, getOption("digits") - 3),...) +{ + ## Purpose: Adding SD and N to summary + ## ---------------------------------------------------------------------- + ## Arguments: object : Object to summarise + ## ---------------------------------------------------------------------- + ## Author: Yves Reecht, Date: 13 sept. 2012, 15:47 modified by Coline ROYAUX 04 june 2020 + + if ( ! is.numeric(object)) stop("Programming error") + + ## Compute summary : + res <- c(summary(object=object, digits, ...), "sd"=signif(sd(x=object), digits=digits), "N"=length(object)) + + return(res) +} + +######################################### start of the function summary.fr + +######################################### Package DHARMa + +################ simulateResiduals.R + +#' Create simulated residuals +#' +#' The function creates scaled residuals by simulating from the fitted model. Residuals can be extracted with \code{\link{residuals.DHARMa}}. See \code{\link{testResiduals}} for an overview of residual tests, \code{\link{plot.DHARMa}} for an overview of available plots. +#' +#' @param fittedModel a fitted model of a class supported by DHARMa +#' @param n number of simulations. Default is 100. A more save value would be 250 or even 1000. The smaller the number, the higher the stochastic error on the residuals. Also, for very small n, discretization artefacts can influence the tests. +#' @param refit if FALSE, new data will be simulated and scaled residuals will be created by comparing observed data with new data. If TRUE, the model will be refit on the simulated data (parametric bootstrap), and scaled residuals will be created by comparing observed with refitted residuals. +#' @param integerResponse if TRUE, noise will be added at to the residuals to maintain a uniform expectations for integer responses (such as Poisson or Binomial). Usually, the model will automatically detect the appropriate setting, so there is no need to adjust this setting. +#' @param plot if TRUE, \code{\link{plotResiduals}} will be directly run after the residuals have been calculated +#' @param ... parameters to pass to the simulate function of the model object. An important use of this is to specify whether simulations should be conditional on the current random effect estimates, e.g. via re.form. Note that not all models support syntax to specify conditionao or unconditional simulations. See also details +#' @param seed the random seed to be used within DHARMa. The default setting, recommended for most users, is keep the random seed on a fixed value 123. This means that you will always get the same randomization and thus teh same result when running the same code. NULL = no new seed is set, but previous random state will be restored after simulation. FALSE = no seed is set, and random state will not be restored. The latter two options are only recommended for simulation experiments. See vignette for details. +#' @param method the quantile randomization method used. The two options implemented at the moment are probability integral transform (PIT-) residuals (current default), and the "traditional" randomization procedure, that was used in DHARMa until version 0.3.0. For details, see \code{\link{getQuantile}} +#' @return An S3 class of type "DHARMa", essentially a list with various elements. Implemented S3 functions include plot, print and \code{\link{residuals.DHARMa}}. Residuals returns the calculated scaled residuals. +#' +#' @details There are a number of important considerations when simulating from a more complex (hierarchical) model: +#' +#' \strong{Re-simulating random effects / hierarchical structure}: in a hierarchical model, we have several stochastic processes aligned on top of each other. Specifically, in a GLMM, we have a lower level stochastic process (random effect), whose result enters into a higher level (e.g. Poisson distribution). For other hierarchical models such as state-space models, similar considerations apply. +#' +#' In such a situation, we have to decide if we want to re-simulate all stochastic levels, or only a subset of those. For example, in a GLMM, it is common to only simulate the last stochastic level (e.g. Poisson) conditional on the fitted random effects. This is often referred to as a conditional simuation. For controlling how many levels should be re-simulated, the simulateResidual function allows to pass on parameters to the simulate function of the fitted model object. Please refer to the help of the different simulate functions (e.g. ?simulate.merMod) for details. For merMod (lme4) model objects, the relevant parameters are parameters are use.u and re.form +#' +#' If the model is correctly specified, the simulated residuals should be flat regardless how many hierarchical levels we re-simulate. The most thorough procedure would therefore be to test all possible options. If testing only one option, I would recommend to re-simulate all levels, because this essentially tests the model structure as a whole. This is the default setting in the DHARMa package. A potential drawback is that re-simulating the lower-level random effects creates more variability, which may reduce power for detecting problems in the upper-level stochastic processes. In particular dispersion tests may produce different results when switching from conditional to unconditional simulations, and often the conditional simulation is more sensitive. +#' +#' \strong{Integer responses}: a second complication is the treatment of inter responses. Imaging we have observed a 0, and we predict 30\% zeros - what is the quantile that we should display for the residual? To deal with this problem and maintain a uniform response, the option integerResponse adds a uniform noise from -0.5 to 0.5 on the simulated and observed response, which creates a uniform distribution - you can see this via hist(ecdf(runif(10000))(runif(10000))). +#' +#' DHARMa will try to automatically if the fitted model has an integer or discrete distribution via the family argument. However, in some cases the family does not allow to uniquely identify the distribution type. For example, a tweedie distribution can be inter or continuous. Therefore, DHARMa will additionally check the simulation results for repeated values, and will change the distribution type if repeated values are found (a message is displayed in this case). +#' +#' \strong{Refitting or not}: a third issue is how residuals are calculated. simulateResiduals has two options that are controlled by the refit parameter: +#' +#' 1. if refit = FALSE (default), new data is simulated from the fitted model, and residuals are calculated by comparing the observed data to the new data +#' +#' 2. if refit = TRUE, a parametric bootstrap is performed, meaning that the model is refit on the new data, and residuals are created by comparing observed residuals against refitted residuals. I advise against using this method per default (see more comments in the vignette), unless you are really sure that you need it. +#' +#' \strong{Residuals per group}: In many situations, it can be useful to look at residuals per group, e.g. to see how much the model over / underpredicts per plot, year or subject. To do this, use \code{\link{recalculateResiduals}}, together with a grouping variable (see also help) +#' +#' \strong{Transformation to other distributions}: DHARMa calculates residuals for which the theoretical expectation (assuming a correctly specified model) is uniform. To transfor this residuals to another distribution (e.g. so that a correctly specified model will have normal residuals) see \code{\link{residuals.DHARMa}}. +#' +#' @seealso \code{\link{testResiduals}}, \code{\link{plot.DHARMa}}, \code{\link{plotResiduals}}, \code{\link{print.DHARMa}}, \code{\link{residuals.DHARMa}}, \code{\link{recalculateResiduals}} +#' +#' +#' @example inst/examples/simulateResidualsHelp.R +#' @import stats +#' @export +simulateResiduals <- function(fittedModel, n = 250, refit = F, integerResponse = NULL, plot = F, seed = 123, method = c("PIT", "traditional"), ...){ + + ######## general assertions and startup calculations ########## + + if (n < 2) stop("error in DHARMa::simulateResiduals: n > 1 is required to calculate scaled residuals") + checkModel(fittedModel) + match.arg(method) + randomState <-getRandomState(seed) + on.exit({randomState$restoreCurrent()}) + ptm <- proc.time() + + ####### extract model info ############ + + out = list() + + family = family(fittedModel) + out$fittedModel = fittedModel + out$modelClass = class(fittedModel)[1] + + out$nObs = nobs(fittedModel) + out$nSim = n + out$refit = refit + out$observedResponse = getObservedResponse(fittedModel) + + if(is.null(integerResponse)){ + if (family$family %in% c("binomial", "poisson", "quasibinomial", "quasipoisson", "Negative Binom", "nbinom2", "nbinom1", "genpois", "compois", "truncated_poisson", "truncated_nbinom2", "truncated_nbinom1", "betabinomial", "Poisson", "Tpoisson", "COMPoisson", "negbin", "Tnegbin") | grepl("Negative Binomial",family$family) ) integerResponse = TRUE + else integerResponse = FALSE + } + out$integerResponse = integerResponse + + out$problems = list() + + # re-form should be set to ~0 to avoid spurious residual patterns, see https://github.com/florianhartig/DHARMa/issues/43 + + if(out$modelClass %in% c("HLfit")){ + out$fittedPredictedResponse = predict(fittedModel, type = "response", re.form = ~0)[,1L] + }else{ + out$fittedPredictedResponse = predict(fittedModel, type = "response", re.form = ~0) + } + + out$fittedFixedEffects = getFixedEffects(fittedModel) + out$fittedResiduals = residuals(fittedModel, type = "response") + + ######## refit = F ################## + + if (refit == FALSE){ + + out$simulatedResponse = getSimulations(fittedModel, nsim = n, type = "normal", ...) + + checkSimulations(out$simulatedResponse, out$nObs, out$nSim) + + out$scaledResiduals = getQuantile(simulations = out$simulatedResponse , observed = out$observedResponse , integerResponse = integerResponse, method = method) + + ######## refit = T ################## + } else { + + # Adding new outputs + + out$refittedPredictedResponse <- matrix(nrow = out$nObs, ncol = n ) + out$refittedFixedEffects <- matrix(nrow = length(out$fittedFixedEffects), ncol = n ) + #out$refittedRandomEffects <- matrix(nrow = length(out$fittedRandomEffects), ncol = n ) + out$refittedResiduals = matrix(nrow = out$nObs, ncol = n) + out$refittedPearsonResiduals = matrix(nrow = out$nObs, ncol = n) + + out$simulatedResponse = getSimulations(fittedModel, nsim = n, type = "refit", ...) + + for (i in 1:n){ + + simObserved = out$simulatedResponse[[i]] + + try({ + + # for testing + # if (i==3) stop("x") + # Note: also set silent = T for production + + refittedModel = getRefit(fittedModel, simObserved) + + out$refittedPredictedResponse[,i] = predict(refittedModel, type = "response") + out$refittedFixedEffects[,i] = getFixedEffects(refittedModel) + out$refittedResiduals[,i] = residuals(refittedModel, type = "response") + out$refittedPearsonResiduals[,i] = residuals(refittedModel, type = "pearson") + #out$refittedRandomEffects[,i] = ranef(refittedModel) + }, silent = TRUE) + } + + ######### residual checks ########### + + if(anyNA(out$refittedResiduals)) warning("DHARMa::simulateResiduals warning: on refit = TRUE, at least one of the refitted models produced an error. Inspect the refitted model values. Results may not be reliable.") + + ## check for convergence problems + + dup = sum(duplicated(out$refittedFixedEffects, MARGIN = 2)) + if (dup > 0){ + if (dup < n/3){ + warning(paste("There were", dup, "of", n ,"duplicate parameter estimates in the refitted models. This may hint towards a problem with optimizer convergence in the fitted models. Results may not be reliable. The suggested action is to not use the refitting procedure, and diagnose with tools available for the normal (not refitted) simulated residuals. If you absolutely require the refitting procedure, try changing tolerance / iterations in the optimizer settings.")) + } else { + warning(paste("There were", dup, "of", n ,"duplicate parameter estimates in the refitted models. This may hint towards a problem with optimizer convergence in the fitted models. Results are likely not reliable. The suggested action is to not use the refitting procedure, and diagnose with tools available for the normal (not refitted) simulated residuals. If you absolutely require the refitting procedure, try changing tolerance / iterations in the optimizer settings.")) + out$problems[[length(out$problems)+ 1]] = "error in refit" + } + } + + ######### residual calculations ########### + + out$scaledResiduals = getQuantile(simulations = out$refittedResiduals, observed = out$fittedResiduals, integerResponse = integerResponse, method = method) + } + + ########### Wrapup ############ + + out$time = proc.time() - ptm + out$randomState = randomState + + class(out) = "DHARMa" + + if(plot == TRUE) plot(out) + + return(out) +} + +getPossibleModels<-function()c("lm", "glm", "negbin", "lmerMod", "glmerMod", "gam", "bam", "glmmTMB", "HLfit") + + + +#' Check if the fitted model is supported by DHARMa +#' +#' The function checks if the fitted model is supported by DHARMa, and if there are other issues that could create problems +#' +#' @param fittedModel a fitted model +#' @param stop whether to throw an error if the model is not supported by DHARMa +#' +#' @details The main purpose of this function os to check if the fitted model class is supported by DHARMa. The function additionally checks for properties of the fitted model that could create problems for calculating residuals or working with the resuls in DHARMa. +#' +#' +#' @keywords internal +checkModel <- function(fittedModel, stop = F){ + + out = T + + if(!(class(fittedModel)[1] %in% getPossibleModels())){ + if(stop == FALSE) warning("DHARMa: fittedModel not in class of supported models. Absolutely no guarantee that this will work!") + else stop("DHARMa: fittedModel not in class of supported models") + } + + # if(hasNA(fittedModel)) message("It seems there were NA values in the data used for fitting the model. This can create problems if you supply additional data to DHARMa functions. See ?checkModel for details") + + # TODO: check as implemented does not work reliably, check if there is any other option to check for NA + # #' @example inst/examples/checkModelHelp.R + + # NA values in the data: checkModel will detect if there were NA values in the data frame. For NA values, most regression models will remove the entire observation from the data. This is not a problem for DHARMa - residuals are then only calculated for non-NA rows in the data. However, if you provide additional predictors to DHARMa, for example to plot residuals against a predictor, you will have to remove all NA rows that were also removed in the model. For most models, you can get the rows of the data that were actually used in the fit via rownames(model.frame(fittedModel)) + + + if (class(fittedModel)[1] == "gam" ) if (class(fittedModel$family)[1] == "extended.family") stop("It seems you are trying to fit a model from mgcv that was fit with an extended.family. Simulation functions for these families are not yet implemented in DHARMa. See issue https://github.com/florianhartig/DHARMa/issues/11 for updates about this") + +} + + + +#' Check simulated data +#' +#' The function checks if the simulated data seems fine +#' +#' @param simulatedResponse the simulated response +#' @param nObs number of observations +#' @param nSim number of simulations +#' +#' @keywords internal +checkSimulations <- function(simulatedResponse, nObs, nSim){ + + if(!inherits(simulatedResponse, "matrix")) securityAssertion("Simulation from the model produced wrong class", stop = T) + + if(any(dim(simulatedResponse) != c(nObs, nSim) )) securityAssertion("Simulation from the model produced wrong dimension", stop = T) + + if(any(!is.finite(simulatedResponse))) message("Simulations from your fitted model produce infinite values. Consider if this is sensible") + + if(any(is.nan(simulatedResponse))) securityAssertion("Simulations from your fitted model produce NaN values. DHARMa cannot calculated residuals for this. This is nearly certainly an error of the regression package you are using", stop = T) + if(any(is.na(simulatedResponse))) securityAssertion("Simulations from your fitted model produce NA values. DHARMa cannot calculated residuals for this. This is nearly certainly an error of the regression package you are using", stop = T) + +} + + + + +#' Recalculate residuals with grouping +#' +#' The purpose of this function is to recalculate scaled residuals per group, based on the simulations done by \code{\link{simulateResiduals}} +#' +#' @param simulationOutput an object with simulated residuals created by \code{\link{simulateResiduals}} +#' @param group group of each data point +#' @param aggregateBy function for the aggregation. Default is sum. This should only be changed if you know what you are doing. Note in particular that the expected residual distribution might not be flat any more if you choose general functions, such as sd etc. +#' @param seed the random seed to be used within DHARMa. The default setting, recommended for most users, is keep the random seed on a fixed value 123. This means that you will always get the same randomization and thus teh same result when running the same code. NULL = no new seed is set, but previous random state will be restored after simulation. FALSE = no seed is set, and random state will not be restored. The latter two options are only recommended for simulation experiments. See vignette for details. +#' @param method the quantile randomization method used. The two options implemented at the moment are probability integral transform (PIT-) residuals (current default), and the "traditional" randomization procedure, that was used in DHARMa until version 0.3.0. For details, see \code{\link{getQuantile}} +#' @return an object of class DHARMa, similar to what is returned by \code{\link{simulateResiduals}}, but with additional outputs for the new grouped calculations. Note that the relevant outputs are 2x in the object, the first is the grouped calculations (which is returned by $name access), and later another time, under identical name, the original output. Moreover, there is a function 'aggregateByGroup', which can be used to aggregate predictor variables in the same way as the variables calculated here +#' +#' @example inst/examples/simulateResidualsHelp.R +#' @export +recalculateResiduals <- function(simulationOutput, group = NULL, aggregateBy = sum, seed = 123, method = c("PIT", "traditional")){ + + randomState <-getRandomState(seed) + on.exit({randomState$restoreCurrent()}) + match.arg(method) + + if(!is.null(simulationOutput$original)) simulationOutput = simulationOutput$original + + out = list() + out$original = simulationOutput + + if(is.null(group)) return(simulationOutput) + else group =as.factor(group) + out$nGroups = nlevels(group) + + aggregateByGroup <- function(x) aggregate(x, by=list(group), FUN=aggregateBy)[,2] + + out$observedResponse = aggregateByGroup(simulationOutput$observedResponse) + out$fittedPredictedResponse = aggregateByGroup(simulationOutput$fittedPredictedResponse) + + if (simulationOutput$refit == F){ + + out$simulatedResponse = apply(simulationOutput$simulatedResponse, 2, aggregateByGroup) + out$scaledResiduals = getQuantile(simulations = out$simulatedResponse , observed = out$observedResponse , integerResponse = simulationOutput$integerResponse, method = method) + + ######## refit = T ################## + } else { + + out$refittedPredictedResponse <- apply(simulationOutput$refittedPredictedResponse, 2, aggregateByGroup) + out$fittedResiduals = aggregateByGroup(simulationOutput$fittedResiduals) + out$refittedResiduals = apply(simulationOutput$refittedResiduals, 2, aggregateByGroup) + out$refittedPearsonResiduals = apply(simulationOutput$refittedPearsonResiduals, 2, aggregateByGroup) + + out$scaledResiduals = getQuantile(simulations = out$refittedResiduals , observed = out$fittedResiduals , integerResponse = simulationOutput$integerResponse, method = method) + + } + + # hack - the c here will result in both old and new outputs to be present resulting output, but a named access should refer to the new, grouped calculations + # question to myself - what's the use of that, why not erase the old outputs? they are anyway saved in the old object + + out$aggregateByGroup = aggregateByGroup + out = c(out, simulationOutput) + out$randomState = randomState + class(out) = "DHARMa" + return(out) +} + +################ simulateResiduals.R + +################ DHARMa.R + +#' @title DHARMa - Residual Diagnostics for HierArchical (Multi-level / Mixed) Regression Models +#' @name DHARMa +#' @docType package +#' @description The 'DHARMa' package uses a simulation-based approach to create readily interpretable scaled (quantile) residuals for fitted (generalized) linear mixed models. Currently supported are linear and generalized linear (mixed) models from 'lme4' (classes 'lmerMod', 'glmerMod'), 'glmmTMB' and 'spaMM', generalized additive models ('gam' from 'mgcv'), 'glm' (including 'negbin' from 'MASS', but excluding quasi-distributions) and 'lm' model classes. Moreover, externally created simulations, e.g. posterior predictive simulations from Bayesian software such as 'JAGS', 'STAN', or 'BUGS' can be processed as well. The resulting residuals are standardized to values between 0 and 1 and can be interpreted as intuitively as residuals from a linear regression. The package also provides a number of plot and test functions for typical model misspecification problems, such as over/underdispersion, zero-inflation, and residual spatial and temporal autocorrelation. +#' @details See index / vignette for details +#' @seealso \code{\link{simulateResiduals}} +#' @examples +#' vignette("DHARMa", package="DHARMa") +NULL + + +#' Print simulated residuals +#' +#' @param x an object with simulated residuals created by \code{\link{simulateResiduals}} +#' @param ... optional arguments for compatibility with the generic function, no function implemented +#' @export +print.DHARMa <- function(x, ...){ + cat(paste("Object of Class DHARMa with simulated residuals based on", x$nSim, "simulations with refit =", x$refit , ". See ?DHARMa::simulateResiduals for help."), "\n", "\n") + if (length(x$scaledResiduals) < 20) cat("Scaled residual values:", x$scaledResiduals) + else { + cat("Scaled residual values:", x$scaledResiduals[1:20], "...") + } +} + +#' Return residuals of a DHARMa simulation +#' +#' @param object an object with simulated residuals created by \code{\link{simulateResiduals}} +#' @param quantileFunction optional - a quantile function to transform the uniform 0/1 scaling of DHARMa to another distribution +#' @param outlierValues if a quantile function with infinite support (such as dnorm) is used, residuals that are 0/1 are mapped to -Inf / Inf. outlierValues allows to convert -Inf / Inf values to an optional min / max value. +#' @param ... optional arguments for compatibility with the generic function, no function implemented +#' @details the function accesses the slot $scaledResiduals in a fitted DHARMa object, and optionally transforms the standard DHARMa quantile residuals (which have a uniform distribution) to a particular pdf. +#' +#' @note some of the papers on simulated quantile residuals transforming the residuals (which are natively uniform) back to a normal distribution. I presume this is because of the larger familiarity of most users with normal residuals. Personally, I never considered this desirable, for the reasons explained in https://github.com/florianhartig/DHARMa/issues/39, but with this function, I wanted to give users the option to plot normal residuals if they so wish. +#' +#' @export +#' @example inst/examples/simulateResidualsHelp.R +#' +residuals.DHARMa <- function(object, quantileFunction = NULL, outlierValues = NULL, ...){ + + if(is.null(quantileFunction)){ + return(object$scaledResiduals) + } else { + res = quantileFunction(object$scaledResiduals) + if(!is.null(outlierValues)){ + res = ifelse(res == -Inf, outlierValues[1], res) + res = ifelse(res == Inf, outlierValues[2], res) + } + return(res) + } +} + + + +#' Return outliers +#' +#' Returns the outliers of a DHARMa object +#' +#' @param object an object with simulated residuals created by \code{\link{simulateResiduals}} +#' @param lowerQuantile lower threshold for outliers. Default is zero = outside simulation envelope +#' @param upperQuantile upper threshold for outliers. Default is 1 = outside simulation envelope +#' @param return wheter to return an indices of outliers or a logical vector +#' +#' @details First of all, note that the standard definition of outlier in the DHARMa plots and outlier tests is an observation that is outside the simulation envelope. How far outside that is depends a lot on how many simulations you do. If you have 100 data points and to 100 simulations, you would expect to have one "outlier" on average, even with a perfectly fitting model. This is in fact what the outlier test tests. +#' +#' Thus, keep in mind that for a small number of simulations, outliers are mostly a technical term: these are points that are outside our simulations, but we don't know how far away they are. +#' +#' If you are seriously interested in HOW FAR outside the expected distribution a data point is, you should increase the number of simulations in \code{\link{simulateResiduals}} to be sure to get the tail of the data distribution correctly. In this case, it may make sense to adjust lowerQuantile and upperQuantile, e.g. to 0.025, 0.975, which would define outliers as values outside the central 95% of the distribution. +#' +#' Also, note that outliers are particularly concerning if they have a strong influence on the model fit. One could test the influence, for example, by removing them from the data, or by some meausures of leverage, e.g. generalisations for Cook's distance as in Pinho, L. G. B., Nobre, J. S., & Singer, J. M. (2015). Cook’s distance for generalized linear mixed models. Computational Statistics & Data Analysis, 82, 126–136. doi:10.1016/j.csda.2014.08.008. At the moment, however, no such function is provided in DHARMa. +#' +#' @export +#' +outliers <- function(object, lowerQuantile = 0, upperQuantile = 1, return = c("index", "logical")){ + + return = match.arg(return) + + out = residuals(object) >= upperQuantile | residuals(object) <= lowerQuantile + + if(return == "logical") return(out) + else(return(which(out))) +} + + + +#' Create a DHARMa object from hand-coded simulations or Bayesian posterior predictive simulations +#' +#' @param simulatedResponse matrix of observations simulated from the fitted model - row index for observations and colum index for simulations +#' @param observedResponse true observations +#' @param fittedPredictedResponse optional fitted predicted response. For Bayesian posterior predictive simulations, using the median posterior prediction as fittedPredictedResponse is recommended. If not provided, the mean simulatedResponse will be used. +#' @param integerResponse if T, noise will be added at to the residuals to maintain a uniform expectations for integer responses (such as Poisson or Binomial). Unlike in \code{\link{simulateResiduals}}, the nature of the data is not automatically detected, so this MUST be set by the user appropriately +#' @param seed the random seed to be used within DHARMa. The default setting, recommended for most users, is keep the random seed on a fixed value 123. This means that you will always get the same randomization and thus teh same result when running the same code. NULL = no new seed is set, but previous random state will be restored after simulation. FALSE = no seed is set, and random state will not be restored. The latter two options are only recommended for simulation experiments. See vignette for details. +#' @param method the quantile randomization method used. The two options implemented at the moment are probability integral transform (PIT-) residuals (current default), and the "traditional" randomization procedure, that was used in DHARMa until version 0.3.0. For details, see \code{\link{getQuantile}} +#' @details The use of this function is to convert simulated residuals (e.g. from a point estimate, or Bayesian p-values) to a DHARMa object, to make use of the plotting / test functions in DHARMa +#' @note Either scaled residuals or (simulatedResponse AND observed response) have to be provided +#' @example inst/examples/createDharmaHelp.R +#' @export +createDHARMa <- function(simulatedResponse , observedResponse , fittedPredictedResponse = NULL, integerResponse = F, seed = 123, method = c("PIT", "traditional")){ + + randomState <-getRandomState(seed) + on.exit({randomState$restoreCurrent()}) + match.arg(method) + + out = list() + out$simulatedResponse = simulatedResponse + out$refit = F + out$integerResponse = integerResponse + out$observedResponse = observedResponse + + if(!is.matrix(simulatedResponse) & !is.null(observedResponse)) stop("either scaled residuals or simulations and observations have to be provided") + if(ncol(simulatedResponse) < 2) stop("simulatedResponse with less than 2 simulations provided - cannot calculate residuals on that.") + + if(ncol(simulatedResponse) < 10) warning("simulatedResponse with less than 10 simulations provided. This rarely makes sense") + + out$nObs = length(observedResponse) + + if (out$nObs < 3) stop("warning - number of observations < 3 ... this rarely makes sense") + + if(! (out$nObs == nrow(simulatedResponse))) stop("dimensions of observedResponse and simulatedResponse do not match") + + out$nSim = ncol(simulatedResponse) + + out$scaledResiduals = getQuantile(simulations = simulatedResponse , observed = observedResponse , integerResponse = integerResponse, method = method) + + + # makes sure that DHARM plots that rely on this vector won't crash + if(is.null(fittedPredictedResponse)){ + message("No fitted predicted response provided, using the mean of the simulations") + fittedPredictedResponse = apply(simulatedResponse, 1, mean) + } + out$fittedPredictedResponse = fittedPredictedResponse + out$randomState = randomState + class(out) = "DHARMa" + return(out) +} + + +#' Ensures that an object is of class DHARMa +#' +#' @param simulationOutput a DHARMa simulation output or an object that can be converted into a DHARMa simulation output +#' @param convert if TRUE, attempts to convert model + numeric to DHARMa, if "Model", converts only supported models to DHARMa +#' @details The +#' @return an object of class DHARMa +#' @keywords internal +ensureDHARMa <- function(simulationOutput, + convert = F){ + + if(inherits(simulationOutput, "DHARMa")){ + return(simulationOutput) + } else { + + if(convert == FALSE) stop("wrong argument to function, simulationOutput must be a DHARMa object!") + else { + + if (class(simulationOutput)[1] %in% getPossibleModels()){ + if (convert == "Model" | convert == T) return(simulateResiduals(simulationOutput)) + } else if(is.vector(simulationOutput, mode = "numeric") & convert == T) { + out = list() + out$scaledResiduals = simulationOutput + out$nObs = length(out$scaledResiduals) + class(out) = "DHARMa" + return(out) + } + } + } + stop("wrong argument to function, simulationOutput must be a DHARMa object or a numeric vector of quantile residuals!") +} + +####################### DHARMa.R + +####################### tests.R + +#' DHARMa general residual test +#' +#' Calls both uniformity and dispersion test +#' +#' This function is a wrapper for the various test functions implemented in DHARMa. Currently, this function calls the \code{\link{testUniformity}} and the \code{\link{testDispersion}} functions. All other tests (see list below) have to be called by hand. +#' +#' @param simulationOutput an object of class DHARMa with simulated quantile residuals, either created via \code{\link{simulateResiduals}} or by \code{\link{createDHARMa}} for simulations created outside DHARMa +#' @param plot if T, plots functions of the tests are called +#' @author Florian Hartig +#' @seealso \code{\link{testUniformity}}, \code{\link{testOutliers}}, \code{\link{testDispersion}}, \code{\link{testZeroInflation}}, \code{\link{testGeneric}}, \code{\link{testTemporalAutocorrelation}}, \code{\link{testSpatialAutocorrelation}}, \code{\link{testQuantiles}} +#' @example inst/examples/testsHelp.R +#' @export +testResiduals <- function(simulationOutput, plot = T){ + + opar = par(mfrow = c(1,3)) + on.exit(par(opar)) + out = list() + out$uniformity = testUniformity(simulationOutput, plot = plot) + out$dispersion = testDispersion(simulationOutput, plot = plot) + out$outliers = testOutliers(simulationOutput, plot = plot) + + print(out) + return(out) +} + +#' Residual tests +#' +#' @details Deprecated, switch your code to using the \code{\link{testResiduals}} function +#' +#' @param simulationOutput an object of class DHARMa with simulated quantile residuals, either created via \code{\link{simulateResiduals}} or by \code{\link{createDHARMa}} for simulations created outside DHARMa +#' @author Florian Hartig +#' @export +testSimulatedResiduals <- function(simulationOutput){ + message("testSimulatedResiduals is deprecated, switch your code to using the testResiduals function") + testResiduals(simulationOutput) +} + + +#' Test for overall uniformity +#' +#' This function tests the overall uniformity of the simulated residuals in a DHARMa object +#' +#' @param simulationOutput an object of class DHARMa with simulated quantile residuals, either created via \code{\link{simulateResiduals}} or by \code{\link{createDHARMa}} for simulations created outside DHARMa +#' @param alternative a character string specifying whether the test should test if observations are "greater", "less" or "two.sided" compared to the simulated null hypothesis. See \code{\link[stats]{ks.test}} for details +#' @param plot if T, plots calls \code{\link{plotQQunif}} as well +#' @details The function applies a \code{\link[stats]{ks.test}} for uniformity on the simulated residuals. +#' @author Florian Hartig +#' @seealso \code{\link{testResiduals}}, \code{\link{testOutliers}}, \code{\link{testDispersion}}, \code{\link{testZeroInflation}}, \code{\link{testGeneric}}, \code{\link{testTemporalAutocorrelation}}, \code{\link{testSpatialAutocorrelation}}, \code{\link{testQuantiles}} +#' @example inst/examples/testsHelp.R +#' @export +testUniformity<- function(simulationOutput, alternative = c("two.sided", "less", "greater"), plot = T){ + + simulationOutput = ensureDHARMa(simulationOutput, convert = T) + + out <- suppressWarnings(ks.test(simulationOutput$scaledResiduals, 'punif', alternative = alternative)) + if(plot == T) plotQQunif(simulationOutput = simulationOutput) + return(out) +} + + +# Experimental +testBivariateUniformity<- function(simulationOutput, alternative = c("two.sided", "less", "greater"), plot = T){ + + simulationOutput = ensureDHARMa(simulationOutput, convert = T) + + #out <- suppressWarnings(ks.test(simulationOutput$scaledResiduals, 'punif', alternative = alternative)) + #if(plot == T) plotQQunif(simulationOutput = simulationOutput) + out = NULL + return(out) +} + + + +#' Test for quantiles +#' +#' This function tests +#' +#' @param simulationOutput an object of class DHARMa with simulated quantile residuals, either created via \code{\link{simulateResiduals}} or by \code{\link{createDHARMa}} for simulations created outside DHARMa +#' @param predictor an optional predictor variable to be used, instead of the predicted response (default) +#' @param quantiles the quantiles to be tested +#' @param plot if T, the function will create an additional plot +#' @details The function fits quantile regressions (via package qgam) on the residuals, and compares their location to the expected location (because of the uniform distributionm, the expected location is 0.5 for the 0.5 quantile). +#' +#' A significant p-value for the splines means the fitted spline deviates from a flat line at the expected location (p-values of intercept and spline are combined via Benjamini & Hochberg adjustment to control the FDR) +#' +#' The p-values of the splines are combined into a total p-value via Benjamini & Hochberg adjustment to control the FDR. +#' +#' @author Florian Hartig +#' @example inst/examples/testQuantilesHelp.R +#' @seealso \code{\link{testResiduals}}, \code{\link{testUniformity}}, \code{\link{testDispersion}}, \code{\link{testZeroInflation}}, \code{\link{testGeneric}}, \code{\link{testTemporalAutocorrelation}}, \code{\link{testSpatialAutocorrelation}}, \code{\link{testOutliers}} +#' @export +testQuantiles <- function(simulationOutput, predictor = NULL, quantiles = c(0.25,0.5,0.75), plot = T){ + + if(plot == F){ + + out = list() + out$data.name = deparse(substitute(simulationOutput)) + + simulationOutput = ensureDHARMa(simulationOutput, convert = T) + res = simulationOutput$scaledResiduals + pred = ensurePredictor(simulationOutput, predictor) + + dat=data.frame(res = simulationOutput$scaledResiduals , pred = pred) + + quantileFits <- list() + pval = rep(NA, length(quantiles)) + predictions = data.frame(pred = sort(dat$pred)) + predictions = cbind(predictions, matrix(ncol = 2 * length(quantiles), nrow = nrow(dat))) + for(i in 1:length(quantiles)){ + datTemp = dat + datTemp$res = datTemp$res - quantiles[i] + + # settings for k = the dimension of the basis used to represent the smooth term. + # see https://github.com/mfasiolo/qgam/issues/37 + dimSmooth = min(length(unique(datTemp$pred)), 10) + quantResult = try(capture.output(quantileFits[[i]] <- qgam::qgam(res ~ s(pred, k = dimSmooth) , data =datTemp, qu = quantiles[i])), silent = T) + if(inherits(quantResult, "try-error")){ + message("Unable to calculate quantile regression for quantile ", quantiles[i], ". Possibly to few (unique) data points / predictions. Will be ommited in plots and significance calculations.") + } else { + x = summary(quantileFits[[i]]) + pval[i] = min(p.adjust(c(x$p.table[1,4], x$s.table[1,4]), method = "BH")) # correction for test on slope and intercept + quantPre = predict(quantileFits[[i]], newdata = predictions, se = T) + predictions[, 2*i] = quantPre$fit + quantiles[i] + predictions[, 2*i + 1] = quantPre$se.fit + } + } + + out$method = "Test for location of quantiles via qgam" + out$alternative = "both" + out$pvals = pval + out$p.value = min(p.adjust(pval, method = "BH")) # correction for multiple quantile tests + out$predictions = predictions + out$qgamFits = quantileFits + + class(out) = "htest" + + } else if(plot == T) { + out <- plotResiduals(simulationOutput = simulationOutput, predictor = predictor, quantiles = quantiles) + } + return(out) +} + + +#unif.2017YMi(X, type = c("Q1", "Q2", "Q3"), lower = rep(0, ncol(X)),upper = rep(1, ncol(X))) + +#' Test for outliers +#' +#' This function tests if the number of observations outside the simulatio envelope are larger or smaller than expected +#' +#' @param simulationOutput an object of class DHARMa with simulated quantile residuals, either created via \code{\link{simulateResiduals}} or by \code{\link{createDHARMa}} for simulations created outside DHARMa +#' @param alternative a character string specifying whether the test should test if observations are "greater", "less" or "two.sided" (default) compared to the simulated null hypothesis +#' @param margin whether to test for outliers only at the lower, only at the upper, or both sides (default) of the simulated data distribution +#' @param plot if T, the function will create an additional plot +#' @details DHARMa residuals are created by simulating from the fitted model, and comparing the simulated values to the observed data. It can occur that all simulated values are higher or smaller than the observed data, in which case they get the residual value of 0 and 1, respectively. I refer to these values as simulation outliers, or simply outliers. +#' +#' Because no data was simulated in the range of the observed value, we don't know "how strongly" these values deviate from the model expectation, so the term "outlier" should be used with a grain of salt - it's not a judgment about the magnitude of a deviation from an expectation, but simply that we are outside the simulated range, and thus cannot say anything more about the location of the residual. +#' +#' Note also that the number of outliers will decrease as we increase the number of simulations. Under the null hypothesis that the model is correct, we expect nData /(nSim +1) outliers at each margin of the distribution. For a reason, consider that if the data and the model distribution are identical, the probability that a given observation is higher than all simulations is 1/(nSim +1). +#' +#' Based on this null expectation, we can test for an excess or lack of outliers. Per default, testOutliers() looks for both, so if you get a significant p-value, you have to check if you have to many or too few outliers. An excess of outliers is to be interpreted as too many values outside the simulation envelope. This could be caused by overdispersion, or by what we classically call outliers. A lack of outliers would be caused, for example, by underdispersion. +#' +#' +#' @author Florian Hartig +#' @seealso \code{\link{testResiduals}}, \code{\link{testUniformity}}, \code{\link{testDispersion}}, \code{\link{testZeroInflation}}, \code{\link{testGeneric}}, \code{\link{testTemporalAutocorrelation}}, \code{\link{testSpatialAutocorrelation}}, \code{\link{testQuantiles}} +#' @example inst/examples/testOutliersHelp.R +#' @export +testOutliers <- function(simulationOutput, alternative = c("two.sided", "greater", "less"), margin = c("both", "upper", "lower"), plot = T){ + + # check inputs + alternative = match.arg(alternative) + margin = match.arg(margin) + data.name = deparse(substitute(simulationOutput)) # remember: needs to be called before ensureDHARMa + simulationOutput = ensureDHARMa(simulationOutput, convert = "Model") + + # calculation of outliers + if(margin == "both") outliers = sum(simulationOutput$scaledResiduals %in% c(0, 1)) + if(margin == "upper") outliers = sum(simulationOutput$scaledResiduals == 1) + if(margin == "lower") outliers = sum(simulationOutput$scaledResiduals == 0) + + # calculations of trials and H0 + outFreqH0 = 1/(simulationOutput$nSim +1) * ifelse(margin == "both", 2, 1) + trials = simulationOutput$nObs + + out = binom.test(outliers, trials, p = outFreqH0, alternative = alternative) + + # overwrite information in binom.test + + out$data.name = data.name + out$margin = margin + out$method = "DHARMa outlier test based on exact binomial test" + + names(out$statistic) = paste("outliers at", margin, "margin(s)") + names(out$parameter) = "simulations" + names(out$estimate) = paste("frequency of outliers (expected:", out$null.value,")") + + out$interval = "tst" + + out$interval = + + if(plot == T) { + + hist(simulationOutput, main = "") + + main = ifelse(out$p.value <= 0.05, + "Outlier test significant", + "Outlier test n.s.") + + title(main = main, cex.main = 1, + col.main = ifelse(out$p.value <= 0.05, "red", "black")) + + # legend("center", c(paste("p=", round(out$p.value, digits = 5)), paste("Deviation ", ifelse(out$p.value < 0.05, "significant", "n.s."))), text.col = ifelse(out$p.value < 0.05, "red", "black" )) + + } + return(out) +} + + +#' DHARMa dispersion tests +#' +#' This function performs a simulation-based test for over/underdispersion +#' +#' @param simulationOutput an object of class DHARMa with simulated quantile residuals, either created via \code{\link{simulateResiduals}} or by \code{\link{createDHARMa}} for simulations created outside DHARMa +#' @param plot whether to plot output +#' @param alternative a character string specifying whether the test should test if observations are "greater", "less" or "two.sided" compared to the simulated null hypothesis. Greater corresponds to overdispersion. +#' @param ... arguments to pass on to \code{\link{testGeneric}} +#' @details The function implements two tests, depending on whether it is applied on a simulation with refit = F, or refit = T. +#' +#' If refit = F, the function tests the sd of the data against the sd of the simulated data. +#' +#' If refit = T, the function compares the approximate deviance (via squared pearson residuals) with the same quantity from the models refitted with simulated data. Applying this is much slower than the previous alternative. Given the computational cost, I would suggest that most users will be satisfied with the standard dispersion test. +#' +#' @note The results of the dispersion test can can differ depending on whether it is evaluated on conditional (= conditional on fitted random effects) or unconditional (= REs are re-simulated) simulations. You can change between conditional or unconditional simulations in \code{\link{simulateResiduals}} if this is supported by the regression package that you use. The default in DHARMa is to use unconditional simulations, but I have often found that conditional simulations are more sensitive to dispersion problems. I recommend trying both, as neither test should be positive if the dispersion is correct. +#' +#' @author Florian Hartig +#' @seealso \code{\link{testResiduals}}, \code{\link{testUniformity}}, \code{\link{testOutliers}}, \code{\link{testZeroInflation}}, \code{\link{testGeneric}}, \code{\link{testTemporalAutocorrelation}}, \code{\link{testSpatialAutocorrelation}}, \code{\link{testQuantiles}} +#' @example inst/examples/testsHelp.R +#' @export +testDispersion <- function(simulationOutput, alternative = c("two.sided", "greater", "less"), plot = T, ...){ + + out = list() + out$data.name = deparse(substitute(simulationOutput)) + + alternative <- match.arg(alternative) + + simulationOutput = ensureDHARMa(simulationOutput, convert = "Model") + + if(simulationOutput$refit == F){ + + spread <- function(x) sd(x - simulationOutput$fittedPredictedResponse) + out = testGeneric(simulationOutput, summary = spread, alternative = alternative, methodName = "DHARMa nonparametric dispersion test via sd of residuals fitted vs. simulated", plot = plot, ...) + } else { + + observed = tryCatch(sum(residuals(simulationOutput$fittedModel, type = "pearson")^2), error = function(e) { + message(paste("DHARMa: the requested tests requires pearson residuals, but your model does not implement these calculations. Test will return NA. Error message:", e)) + return(NA) + }) + if(is.na(observed)) return(NA) + expected = apply(simulationOutput$refittedPearsonResiduals^2 , 2, sum) + out$statistic = c(dispersion = observed / mean(expected)) + out$method = "DHARMa nonparametric dispersion test via mean deviance residual fitted vs. simulated-refitted" + + p = getP(simulated = expected, observed = observed, alternative = alternative) + + out$alternative = alternative + out$p.value = p + class(out) = "htest" + + if(plot == T) { + #plotTitle = gsub('(.{1,50})(\\s|$)', '\\1\n', out$method) + xLabel = paste("Simulated values, red line = fitted model. p-value (",out$alternative, ") = ", out$p.value, sep ="") + + hist(expected, xlim = range(expected, observed, na.rm=T ), col = "lightgrey", main = "", xlab = xLabel, breaks = 20, cex.main = 1) + abline(v = observed, lwd= 2, col = "red") + + main = ifelse(out$p.value <= 0.05, + "Dispersion test significant", + "Dispersion test n.s.") + + title(main = main, cex.main = 1, + col.main = ifelse(out$p.value <= 0.05, "red", "black")) + } + } + + return(out) +} + +#' Simulated overdisperstion tests +#' +#' @details Deprecated, switch your code to using the \code{\link{testDispersion}} function +#' +#' @param simulationOutput an object of class DHARMa with simulated quantile residuals, either created via \code{\link{simulateResiduals}} or by \code{\link{createDHARMa}} for simulations created outside DHARMa +#' @param ... additional arguments to \code{\link{testDispersion}} +#' @export +testOverdispersion <- function(simulationOutput, ...){ + message("testOverdispersion is deprecated, switch your code to using the testDispersion function") + testDispersion(simulationOutput, ...) +} + +#' Parametric overdisperstion tests +#' +#' @details Deprecated, switch your code to using the \code{\link{testDispersion}} function. The function will do nothing, arguments will be ignored, the parametric tests is no longer recommend +#' +#' @param ... arguments will be ignored, the parametric tests is no longer recommend +#' @export +testOverdispersionParametric <- function(...){ + message("testOverdispersionParametric is deprecated and no longer recommended, see release notes in DHARMA 0.2.0 - switch your code to using the testDispersion function") + return(0) +} + + +#' Tests for zero-inflation +#' +#' This function compares the observed number of zeros with the zeros expected from simulations. +#' +#' @param simulationOutput an object of class DHARMa with simulated quantile residuals, either created via \code{\link{simulateResiduals}} or by \code{\link{createDHARMa}} for simulations created outside DHARMa +#' @param ... further arguments to \code{\link{testGeneric}} +#' @details The plot shows the expected distribution of zeros against the observed values, the ratioObsSim shows observed vs. simulated zeros. A value < 1 means that the observed data has less zeros than expected, a value > 1 means that it has more zeros than expected (aka zero-inflation). Per default, the function tests both sides. +#' +#' Some notes about common problems / questions: +#' +#' * Zero-inflation tests after fitting the model are crucial to see if you have zero-inflation. Just because there are a lot of zeros doesn't mean you have zero-inflation, see Warton, D. I. (2005). Many zeros does not mean zero inflation: comparing the goodness-of-fit of parametric models to multivariate abundance data. Environmetrics 16(3), 275-289. +#' +#' * That being said, zero-inflation tests are often not a reliable guide to decide wheter to add a zi term or not. In general, model structures should be decided on ideally a priori, if that is not possible via model selection techniques (AIC, BIC, WAIC, Bayes Factor). A zero-inflation test should only be run after that decision, and to validate the decision that was taken. +#' +#' @note This function is a wrapper for \code{\link{testGeneric}}, where the summary argument is set to function(x) sum(x == 0) +#' @author Florian Hartig +#' @example inst/examples/testsHelp.R +#' @seealso \code{\link{testResiduals}}, \code{\link{testUniformity}}, \code{\link{testOutliers}}, \code{\link{testDispersion}}, \code{\link{testGeneric}}, \code{\link{testTemporalAutocorrelation}}, \code{\link{testSpatialAutocorrelation}}, \code{\link{testQuantiles}} +#' @export +testZeroInflation <- function(simulationOutput, ...){ + countZeros <- function(x) sum( x == 0) + testGeneric(simulationOutput = simulationOutput, summary = countZeros, methodName = "DHARMa zero-inflation test via comparison to expected zeros with simulation under H0 = fitted model", ... ) +} + + +#' Generic simulation test of a summary statistic +#' +#' This function tests if a user-defined summary differs when applied to simulated / observed data. +#' +#' @param simulationOutput an object of class DHARMa with simulated quantile residuals, either created via \code{\link{simulateResiduals}} or by \code{\link{createDHARMa}} for simulations created outside DHARMa +#' @param summary a function that can be applied to simulated / observed data. See examples below +#' @param alternative a character string specifying whether the test should test if observations are "greater", "less" or "two.sided" compared to the simulated null hypothesis +#' @param plot whether to plot the simulated summary +#' @param methodName name of the test (will be used in plot) +#' +#' @details This function tests if a user-defined summary differs when applied to simulated / observed data. the function can easily be remodeled to apply summaries on the residuals, by simply defining f = function(x) summary (x - predictions), as done in \code{\link{testDispersion}} +#' +#' @note The function that you supply is applied on the data as it is represented in your fitted model, which may not always correspond to how you think. This is important in particular when you use k/n binomial data, and want to test for 1-inflation. As an example, if have k/20 observations, and you provide your data via cbind (y, y-20), you have to test for 20-inflation (because this is how the data is represented in the model). However, if you provide data via y/20, and weights = 20, you should test for 1-inflation. In doubt, check how the data is internally represented in model.frame(model), or via simulate(model) +#' +#' @export +#' @author Florian Hartig +#' @example inst/examples/testsHelp.R +#' @seealso \code{\link{testResiduals}}, \code{\link{testUniformity}}, \code{\link{testOutliers}}, \code{\link{testDispersion}}, \code{\link{testZeroInflation}}, \code{\link{testTemporalAutocorrelation}}, \code{\link{testSpatialAutocorrelation}}, \code{\link{testQuantiles}} +testGeneric <- function(simulationOutput, summary, alternative = c("two.sided", "greater", "less"), plot = T, methodName = "DHARMa generic simulation test"){ + + out = list() + out$data.name = deparse(substitute(simulationOutput)) + + simulationOutput = ensureDHARMa(simulationOutput, convert = "Model") + + alternative <- match.arg(alternative) + + observed = summary(simulationOutput$observedResponse) + + simulated = apply(simulationOutput$simulatedResponse, 2, summary) + + p = getP(simulated = simulated, observed = observed, alternative = alternative) + + out$statistic = c(ratioObsSim = observed / mean(simulated)) + out$method = methodName + out$alternative = alternative + out$p.value = p + + + class(out) = "htest" + + if(plot == T) { + plotTitle = gsub('(.{1,50})(\\s|$)', '\\1\n', methodName) + xLabel = paste("Simulated values, red line = fitted model. p-value (",out$alternative, ") = ", out$p.value, sep ="") + hist(simulated, xlim = range(simulated, observed, na.rm=T ), col = "lightgrey", main = plotTitle, xlab = xLabel, breaks = max(round(simulationOutput$nSim / 5), 20), cex.main = 0.8) + abline(v = observed, lwd= 2, col = "red") + } + return(out) +} + + +#' Test for temporal autocorrelation +#' +#' This function performs a standard test for temporal autocorrelation on the simulated residuals +#' +#' @param simulationOutput an object with simulated residuals created by \code{\link{simulateResiduals}} +#' @param time the time, in the same order as the data points. If not provided, random values will be created +#' @param alternative a character string specifying whether the test should test if observations are "greater", "less" or "two.sided" compared to the simulated null hypothesis +#' @param plot whether to plot output +#' @details The function performs a Durbin-Watson test on the uniformly scaled residuals, and plots the residuals against time. The DB test was originally be designed for normal residuals. In simulations, I didn't see a problem with this setting though. The alternative is to transform the uniform residuals to normal residuals and perform the DB test on those. +#' +#' If no time values are provided, random values will be created. The sense of being able to run the test with time = NULL (random values) is to test the rate of false positives under the current residual structure (random time corresponds to H0: no spatial autocorrelation), e.g. to check if the test has noninal error rates for particular residual structures (note that Durbin-Watson originally assumes normal residuals, error rates seem correct for uniform residuals, but may not be correct if there are still other residual problems). +#' +#' Testing for temporal autocorrelation requires unique time values - if you have several observations per time value, either use the recalculateResiduals function to aggregate residuals per time step, or extract the residuals from the fitted object, and plot / test each of them independently for temporally repeated subgroups (typical choices would be location / subject etc.). Note that the latter must be done by hand, outside testSpatialAutocorrelation. +#' +#' @note Important to note for all autocorrelation tests (spatial / temporal): the autocorrelation tests are valid to check for residual autocorrelation in models that don't assume such a correlation (in this case, you can use conditional or unconditional simulations), or if there is remaining residual autocorrelation after accounting for it in a spatial/temporal model (in that case, you have to use conditional simulations), but if checking unconditional simulations from a model with an autocorrelation structure on data that corresponds to this model, they will be significant, even if the model fully accounts for this structure. +#' +#' This behavior is not really a bug, but rather originates from the definition of the quantile residuals: quantile residuals are calculated independently per data point, i.e. without consideratin of any correlation structure between data points that may exist in the simulations. As a result, the simulated distributions from a unconditional simulaton will typically not reflect the correlation structure that is present in each single simulation, and the same is true for the subsequently calculated quantile residuals. +#' +#' The bottomline here is that spatial / temporal / other autoregressive models should either be tested based on conditional simulations, or (ideally) custom tests should be used that are not based on quantile residuals, but rather compare the correlation structure in the simulated data with the correlation structure in the observed data. +#' +#' @author Florian Hartig +#' @seealso \code{\link{testResiduals}}, \code{\link{testUniformity}}, \code{\link{testOutliers}}, \code{\link{testDispersion}}, \code{\link{testZeroInflation}}, \code{\link{testGeneric}}, \code{\link{testSpatialAutocorrelation}}, \code{\link{testQuantiles}} +#' @example inst/examples/testTemporalAutocorrelationHelp.R +#' @export +testTemporalAutocorrelation <- function(simulationOutput, time = NULL , alternative = c("two.sided", "greater", "less"), plot = T){ + + simulationOutput = ensureDHARMa(simulationOutput, convert = T) + + # actually not sure if this is neccessary for dwtest, but seems better to aggregate + if(any(duplicated(time))) stop("testing for temporal autocorrelation requires unique time values - if you have several observations per time value, either use the recalculateResiduals function to aggregate residuals per time step, or extract the residuals from the fitted object, and plot / test each of them independently for temporally repeated subgroups (typical choices would be location / subject etc.). Note that the latter must be done by hand, outside testSpatialAutocorrelation.") + + alternative <- match.arg(alternative) + + if(is.null(time)){ + time = sample.int(simulationOutput$nObs, simulationOutput$nObs) + message("DHARMa::testTemporalAutocorrelation - no time argument provided, using random times for each data point") + } + + out = lmtest::dwtest(simulationOutput$scaledResiduals ~ 1, order.by = time, alternative = alternative) + + if(plot == T) { + oldpar <- par(mfrow = c(1,2)) + on.exit(par(oldpar)) + + plot(simulationOutput$scaledResiduals[order(time)] ~ time[order(time)], + type = "l", ylab = "Scaled residuals", xlab = "Time", main = "Residuals vs. time") + acf(simulationOutput$scaledResiduals[order(time)], main = "Autocorrelation") + legend("topright", + c(paste(out$method, " p=", round(out$p.value, digits = 5)), + paste("Deviation ", ifelse(out$p.value < 0.05, "significant", "n.s."))), + text.col = ifelse(out$p.value < 0.05, "red", "black" ), bty="n") + + } + + return(out) +} + + +#' Test for spatial autocorrelation +#' +#' This function performs a standard test for spatial autocorrelation on the simulated residuals +#' +#' @param simulationOutput an object of class DHARMa with simulated quantile residuals, either created via \code{\link{simulateResiduals}} or by \code{\link{createDHARMa}} for simulations created outside DHARMa +#' @param x the x coordinate, in the same order as the data points. If not provided, random values will be created +#' @param y the y coordinate, in the same order as the data points. If not provided, random values will be created +#' @param distMat optional distance matrix. If not provided, a distance matrix will be calculated based on x and y. See details for explanation +#' @param alternative a character string specifying whether the test should test if observations are "greater", "less" or "two.sided" compared to the simulated null hypothesis +#' @param plot whether to plot output +#' @details The function performs Moran.I test from the package ape, based on the provided distance matrix of the data points. +#' +#' There are several ways to specify this distance. If a distance matrix (distMat) is provided, calculations will be based on this distance matrix, and x,y coordinates will only used for the plotting (if provided) +#' If distMat is not provided, the function will calculate the euclidian distances between x,y coordinates, and test Moran.I based on these distances. +#' +#' If no x/y values are provided, random values will be created. The sense of being able to run the test with x/y = NULL (random values) is to test the rate of false positives under the current residual structure (random x/y corresponds to H0: no spatial autocorrelation), e.g. to check if the test has nominal error rates for particular residual structures. +#' +#' Testing for spatial autocorrelation requires unique x,y values - if you have several observations per location, either use the recalculateResiduals function to aggregate residuals per location, or extract the residuals from the fitted object, and plot / test each of them independently for spatially repeated subgroups (a typical scenario would repeated spatial observation, in which case one could plot / test each time step separately for temporal autocorrelation). Note that the latter must be done by hand, outside testSpatialAutocorrelation. +#' +#' @note Important to note for all autocorrelation tests (spatial / temporal): the autocorrelation tests are valid to check for residual autocorrelation in models that don't assume such a correlation (in this case, you can use conditional or unconditional simulations), or if there is remaining residual autocorrelation after accounting for it in a spatial/temporal model (in that case, you have to use conditional simulations), but if checking unconditional simulations from a model with an autocorrelation structure on data that corresponds to this model, they will be significant, even if the model fully accounts for this structure. +#' +#' This behavior is not really a bug, but rather originates from the definition of the quantile residuals: quantile residuals are calculated independently per data point, i.e. without consideratin of any correlation structure between data points that may exist in the simulations. As a result, the simulated distributions from a unconditional simulaton will typically not reflect the correlation structure that is present in each single simulation, and the same is true for the subsequently calculated quantile residuals. +#' +#' The bottomline here is that spatial / temporal / other autoregressive models should either be tested based on conditional simulations, or (ideally) custom tests should be used that are not based on quantile residuals, but rather compare the correlation structure in the simulated data with the correlation structure in the observed data. +#' +#' @author Florian Hartig +#' @seealso \code{\link{testResiduals}}, \code{\link{testUniformity}}, \code{\link{testOutliers}}, \code{\link{testDispersion}}, \code{\link{testZeroInflation}}, \code{\link{testGeneric}}, \code{\link{testTemporalAutocorrelation}}, \code{\link{testQuantiles}} +#' @import grDevices +#' @example inst/examples/testSpatialAutocorrelationHelp.R +#' @export +testSpatialAutocorrelation <- function(simulationOutput, x = NULL, y = NULL, distMat = NULL, alternative = c("two.sided", "greater", "less"), plot = T){ + + alternative <- match.arg(alternative) + data.name = deparse(substitute(simulationOutput)) # needs to be before ensureDHARMa + simulationOutput = ensureDHARMa(simulationOutput, convert = T) + + if(any(duplicated(cbind(x,y)))) stop("testing for spatial autocorrelation requires unique x,y values - if you have several observations per location, either use the recalculateResiduals function to aggregate residuals per location, or extract the residuals from the fitted object, and plot / test each of them independently for spatially repeated subgroups (a typical scenario would repeated spatial observation, in which case one could plot / test each time step separately for temporal autocorrelation). Note that the latter must be done by hand, outside testSpatialAutocorrelation.") + + if( (!is.null(x) | !is.null(y)) & !is.null(distMat) ) message("both coordinates and distMat provided, calculations will be done based on the distance matrix, coordinates will only be used for plotting") + # if not provided, fill x and y with random numbers (Null model) + if(is.null(x)){ + x = runif(simulationOutput$nObs, -1,1) + message("DHARMa::testSpatialAutocorrelation - no x coordinates provided, using random values for each data point") + } + + if(is.null(y)){ + y = runif(simulationOutput$nObs, -1,1) + message("DHARMa::testSpatialAutocorrelation - no x coordinates provided, using random values for each data point") + } + + # if not provided, create distance matrix based on x and y + if(is.null(distMat)) distMat <- as.matrix(dist(cbind(x, y))) + + invDistMat <- 1/distMat + diag(invDistMat) <- 0 + + MI = ape::Moran.I(simulationOutput$scaledResiduals, weight = invDistMat, alternative = alternative) + + out = list() + out$statistic = c(observed = MI$observed, expected = MI$expected, sd = MI$sd) + out$method = "DHARMa Moran's I test for spatial autocorrelation" + out$alternative = "Spatial autocorrelation" + out$p.value = MI$p.value + out$data.name = data.name + + class(out) = "htest" + + + + if(plot == T) { + opar <- par(mfrow = c(1,1)) + on.exit(par(opar)) + + col = colorRamp(c("red", "white", "blue"))(simulationOutput$scaledResiduals) + plot(x,y, col = rgb(col, maxColorValue = 255), main = out$method, cex.main = 0.8 ) + + # TODO implement correlogram + } + + if(plot == T) { + + + } + return(out) +} + + +getP <- function(simulated, observed, alternative){ + + if(alternative == "greater") p = mean(simulated >= observed) + if(alternative == "less") p = mean(simulated <= observed) + if(alternative == "two.sided") p = min(min(mean(simulated <= observed), mean(simulated >= observed) ) * 2,1) + + return(p) +} + + + +####################### tests.R + +####################### compatibility.R + + +# New S3 methods + +#' Get model response +#' +#' Extract the response of a fitted model +#' +#' The purpose of this function is to savely extract the response (dependent variable) of the fitted model classes +#' +#' @param object a fitted model +#' @param ... additional parameters +#' +#' @example inst/examples/wrappersHelp.R +#' +#' @seealso \code{\link{getRefit}}, \code{\link{getSimulations}}, \code{\link{getFixedEffects}}, \code{\link{getFitted}} +#' @author Florian Hartig +#' @export +getObservedResponse <- function (object, ...) { + UseMethod("getObservedResponse", object) +} + +#' @rdname getObservedResponse +#' @export +getObservedResponse.default <- function (object, ...){ + out = model.frame(object)[,1] + + # check for weights in k/n case + if(family(object)$family %in% c("binomial", "betabinomial") & "(weights)" %in% colnames(model.frame(object))){ + x = model.frame(object) + out = out * x$`(weights)` + } + + # check for k/n binomial + if(is.matrix(out)){ + if(!(ncol(out) == 2)) securityAssertion("nKcase - wrong dimensions of response") + if(!(family(object)$family %in% c("binomial", "betabinomial"))) securityAssertion("nKcase - wrong family") + + out = out[,1] + } + + # observation is factor - unlike lme4 and older, glmmTMB simulates nevertheless as numeric + if(is.factor(out)) out = as.numeric(out) - 1 + + return(out) +} + +weightsWarning = "Model was fit with prior weights. These will be ignored in the simulation. See ?getSimulations for details" + +#' Get model simulations +#' +#' Wrapper to simulate from a fitted model +#' +#' The purpose of this wrapper for for the simulate function is to return the simulations from a model in a standardized way +#' +#' @param object a fitted model +#' @param nsim number of simulations +#' @param type if simulations should be prepared for getQuantile or for refit +#' @param ... additional parameters to be passed on, usually to the simulate function of the respective model class +#' +#' @return a matrix with simulations +#' @example inst/examples/wrappersHelp.R +#' +#' @seealso \code{\link{getObservedResponse}}, \code{\link{getRefit}}, \code{\link{getFixedEffects}}, \code{\link{getFitted}} +#' +#' @details The function is a wrapper for for the simulate function is to return the simulations from a model in a standardized way. +#' +#' Note: if the model was fit with weights, the function will throw a warning if used with a model class whose simulate function does not include the weightsi in the simulations. Note that the results may or may not be appropriate in this case, depending on how you use the weights. +#' +#' +#' @author Florian Hartig +#' @export +getSimulations <- function (object, nsim = 1 , type = c("normal", "refit"), ...) { + UseMethod("getSimulations", object) +} + +#' @rdname getSimulations +#' @export +getSimulations.default <- function (object, nsim = 1, type = c("normal", "refit"), ...){ + + type <- match.arg(type) + + out = simulate(object, nsim = nsim , ...) + + if (type == "normal"){ + if(family(object)$family %in% c("binomial", "betabinomial")){ + if("(weights)" %in% colnames(model.frame(object))){ + x = model.frame(object) + out = out * x$`(weights)` + } else if (is.matrix(out[[1]])){ + # this is for the k/n binomial case + out = as.matrix(out)[,seq(1, (2*nsim), by = 2)] + } else if(is.factor(out[[1]])){ + if(nlevels(out[[1]]) != 2){ + warning("The fitted model has a factorial response with number of levels not equal to 2 - there is currently no sensible application in DHARMa that would lead to this situation. Likely, you are trying something that doesn't work.") + } + else{ + out = data.matrix(out) - 1 + } + } + } + + if(!is.matrix(out)) out = data.matrix(out) + } else{ + if(family(object)$family %in% c("binomial", "betabinomial")){ + if (!is.matrix(out[[1]]) & !is.numeric(out)) data.frame(data.matrix(out)-1) + } + } + + return(out) +} + + +#' Extract fixed effects of a supported model +#' +#' A wrapper to extract fixed effects of a supported model +#' +#' @param fittedModel a fitted model +#' +#' @example inst/examples/wrappersHelp.R +#' +#' @importFrom lme4 fixef +#' +#' @seealso \code{\link{getObservedResponse}}, \code{\link{getSimulations}}, \code{\link{getRefit}}, \code{\link{getFitted}} +#' @export +getFixedEffects <- function(fittedModel){ + + if(class(fittedModel)[1] %in% c("glm", "lm", "gam", "bam", "negbin") ){ + out = coef(fittedModel) + } else if(class(fittedModel)[1] %in% c("glmerMod", "lmerMod", "HLfit")){ + out = fixef(fittedModel) + } else if(class(fittedModel)[1] %in% c("glmmTMB")){ + out = glmmTMB::fixef(fittedModel) + out = out$cond + } else { + out = coef(fittedModel) + if(is.null(out)) out = fixef(fittedModel) + } + return(out) +} + +#' Get model refit +#' +#' Wrapper to refit a fitted model +#' +#' @param object a fitted model +#' @param newresp the new response that should be used to refit the model +#' @param ... additional parameters to be passed on to the refit or update class that is used to refit the model +#' +#' @details The purpose of this wrapper is to standardize the refit of a model. The behavior of this function depends on the supplied model. When available, it uses the refit method, otherwise it will use update. For glmmTMB: since version 1.0, glmmTMB has a refit function, but this didn't work, so I switched back to this implementation, which is a hack based on the update function. +#' +#' @example inst/examples/wrappersHelp.R +#' +#' @seealso \code{\link{getObservedResponse}}, \code{\link{getSimulations}}, \code{\link{getFixedEffects}} +#' @author Florian Hartig +#' @export +getRefit <- function (object, newresp, ...) { + UseMethod("getRefit", object) +} + +#' @rdname getRefit +#' +#' @importFrom lme4 refit +#' +#' @export +getRefit.default <- function (object, newresp, ...){ + refit(object, newresp, ...) +} + +#' Get model fitted +#' +#' Wrapper to get the fitted value a fitted model +#' +#' The purpose of this wrapper is to standardize extract the fitted values +#' +#' @param object a fitted model +#' @param ... additional parameters to be passed on, usually to the simulate function of the respective model class +#' +#' @example inst/examples/wrappersHelp.R +#' +#' @seealso \code{\link{getObservedResponse}}, \code{\link{getSimulations}}, \code{\link{getRefit}}, \code{\link{getFixedEffects}} +#' +#' @author Florian Hartig +#' @export +getFitted <- function (object, ...) { + UseMethod("getFitted", object) +} + +#' @rdname getFitted +#' @export +getFitted.default <- function (object,...){ + fitted(object, ...) +} + +#' has NA +#' +#' checks if the fitted model excluded NA values +#' +#' @param object a fitted model +#' +#' @details Checks if the fitted model excluded NA values +#' +#' @export + + +# hasNA <- function(object){ +# x = rownames(model.frame(object)) +# if(length(x) < as.numeric(x[length(x) ])) return(TRUE) +# else return(FALSE) +# } + +######### LM ############# + +#' @rdname getRefit +#' @export +getRefit.lm <- function(object, newresp, ...){ + + newData <-model.frame(object) + + if(is.vector(newresp)){ + newData[,1] = newresp + } else if (is.factor(newresp)){ + # Hack to make the factor binomial case work + newData[,1] = as.numeric(newresp) - 1 + } else { + # Hack to make the binomial n/k case work + newData[[1]] = NULL + newData = cbind(newresp, newData) + } + + refittedModel = update(object, data = newData) + return(refittedModel) +} + + +hasWeigths.lm <- function(object, ...){ + if(length(unique(object$prior.weights)) != 1) return(TRUE) + else return(FALSE) +} + + +######### GLM ############# + +#' @rdname getSimulations +#' @export +getSimulations.negbin<- function (object, nsim = 1, type = c("normal", "refit"), ...){ + if("(weights)" %in% colnames(model.frame(object))) warning(weightsWarning) + getSimulations.default(object = object, nsim = nsim, type = type, ...) +} + + +######## MGCV ############ + +# This function overwrites the standard fitted function for GAM + +#' @rdname getFitted +#' @export +getFitted.gam <- function(object, ...){ + class(object) = "glm" + out = stats::fitted(object, ...) + names(out) = as.character(1:length(out)) + out +} + +# Check that this works +# plot(fitted(fittedModelGAM), predict(fittedModelGAM, type = "response")) + + +######## lme4 ############ + + +#' @rdname getSimulations +#' @export +getSimulations.lmerMod <- function (object, nsim = 1, type = c("normal", "refit"), ...){ + + if("(weights)" %in% colnames(model.frame(object))) warning(weightsWarning) + getSimulations.default(object = object, nsim = nsim, type = type, ...) +} + + +######## glmmTMB ###### + +#' @rdname getRefit +#' @export +getRefit.glmmTMB <- function(object, newresp, ...){ + newData <-model.frame(object) + + # hack to make update work - for some reason, glmmTMB wants the matrix embedded in the df for update to work ... should be solved ideally, see https://github.com/glmmTMB/glmmTMB/issues/549 + if(is.matrix(newresp)){ + tmp = colnames(newData[[1]]) + newData[[1]] = NULL + newData = cbind(newresp, newData) + colnames(newData)[1:2] = tmp + } else { + newData[[1]] = newresp + } + refittedModel = update(object, data = newData) + return(refittedModel) +} + + +# glmmTMB simulates normal counts (and not proportions in any case, so the check for the other models is not needed), see #158 +# note that if observation is factor - unlike lme4 and older, glmmTMB simulates nevertheless as numeric + +#' @rdname getSimulations +#' @export +getSimulations.glmmTMB <- function (object, nsim = 1, type = c("normal", "refit"), ...){ + + if("(weights)" %in% colnames(model.frame(object)) & ! family(object)$family %in% c("binomial", "betabinomial")) warning(weightsWarning) + + type <- match.arg(type) + + out = simulate(object, nsim = nsim, ...) + + if (type == "normal"){ + if (is.matrix(out[[1]])){ + # this is for the k/n binomial case + out = as.matrix(out)[,seq(1, (2*nsim), by = 2)] + } + if(!is.matrix(out)) out = data.matrix(out) + }else{ + + # check for weights in k/n case + if(family(object)$family %in% c("binomial", "betabinomial")){ + if("(weights)" %in% colnames(model.frame(object))){ + w = model.frame(object) + w = w$`(weights)` + tmp <- function(x)x/w + out = apply(out, 2, tmp) + out = as.data.frame(out) + } + else if(is.matrix(out[[1]]) & !is.matrix(model.frame(object)[[1]])){ + out = as.data.frame(as.matrix(out)[,seq(1, (2*nsim), by = 2)]) + } + } + + + + + + + # matrixResp = + # + # if(matrixResp & !is.null(ncol(newresp))){ + # # Hack to make the factor binomial case work + # tmp = colnames(newData[[1]]) + # newData[[1]] = NULL + # newData = cbind(newresp, newData) + # colnames(newData)[1:2] = tmp + # } else if(!is.null(ncol(newresp))){ + # newData[[1]] = newresp[,1] + # } else { + # newData[[1]] = newresp + # } + + + # if (out$modelClass == "glmmTMB" & ncol(simulations) == 2*n) simObserved = simulations[,(1+(2*(i-1))):(2+(2*(i-1)))] + } + + # else securityAssertion("Simulation results produced unsupported data structure", stop = TRUE) + + return(out) +} + +####### spaMM ######### + +#' @rdname getObservedResponse +#' @export +getObservedResponse.HLfit <- function(object, ...){ + out = spaMM::response(object, ...) + + nKcase = is.matrix(out) + if(nKcase){ + if(! (family(object) %in% c("binomial", "betabinomial"))) securityAssertion("nKcase - wrong family") + if(! (ncol(out)==2)) securityAssertion("nKcase - wrong dimensions of response") + out = out[,1] + } + + if(!is.numeric(out)) out = as.numeric(out) + + return(out) + +} + +#' @rdname getSimulations +#' @export +getSimulations.HLfit <- function(object, nsim = 1, type = c("normal", "refit"), ...){ + + type <- match.arg(type) + + capture.output({out = simulate(object, nsim = nsim, ...)}) + + if(type == "normal"){ + if(!is.matrix(out)) out = data.matrix(out) + }else{ + out = as.data.frame(out) + } + return(out) +} + +#' @rdname getRefit +#' @export +getRefit.HLfit <- function(object, newresp, ...) { + spaMM::update_resp(object, newresp, evaluate = TRUE) +} + +####################### compatibility.R + +####################### helper.R + +#' Modified ECDF function +#' +#' @details ensures symmetric ECDF (standard ECDF is <), and that 0 / 1 values are only produced if the data is strictly < > than the observed data +#' +#' @keywords internal +DHARMa.ecdf <- function (x) +{ + x <- sort(x) + n <- length(x) + if (n < 1) + stop(paste("DHARMa.ecdf - length vector < 1", x)) + vals <- unique(x) + rval <- approxfun(vals, cumsum(tabulate(match(x, vals)))/ (n +1), + method = "linear", yleft = 0, yright = 1, ties = "ordered") + class(rval) <- c("ecdf", "stepfun", class(rval)) + assign("nobs", n, envir = environment(rval)) + attr(rval, "call") <- sys.call() + rval +} + + + +#' calculate quantiles +#' +#' calculates residual quantiles from a given simulation +#' +#' @param simulations a matrix with simulations from a fitted model. Rows = observations, columns = replicate simulations +#' @param observed a vector with the observed data +#' @param integerResponse is the response integer-valued. Only has an effect for method = "traditional" +#' @param method the quantile randomization method used. See details +#' +#' @details The function calculates residual quantiles from the simulated data. For continous distributions, this will simply the the value of the ecdf. +#' +#' For discrete data, there are two options implemented. +#' +#' The current default (available since DHARMa 0.3.1) are probability integral transform (PIT-) residuals (Smith, 1985; Dunn & Smyth, 1996; see also see also Warton, et al., 2017). +#' +#' Before DHARMa 0.3.1, a different randomization procedure was used, in which the a U(-0.5, 0.5) distribution was added on observations and simualtions for discrete distributions. For a completely discrete distribution, the two procedures should deliver equivalent results, but the second method has the disadvantage that a) one has to know if the distribution is discrete (DHARMa tries to recognize this automatically), and b) that it leads to inefficiencies for some distributions such as the the Tweedie, which are partly continous, partly discrte (see e.g. https://github.com/florianhartig/DHARMa/issues/168). +#' +#' @references +#' +#' Smith, J. Q. "Diagnostic checks of non-standard time series models." Journal of Forecasting 4.3 (1985): 283-291. +#' +#' Dunn, P.K., & Smyth, G.K. (1996). Randomized quantile residuals. Journal of Computational and Graphical Statistics 5, 236-244. +#' +#' Warton, David I., Loïc Thibaut, and Yi Alice Wang. "The PIT-trap—A “model-free” bootstrap procedure for inference about regression models with discrete, multivariate responses." PloS one 12.7 (2017) +#' +#' @export +getQuantile <- function(simulations, observed, integerResponse, method = c("PIT", "traditional")){ + + method = match.arg(method) + + n = length(observed) + if (nrow(simulations) != n) stop("DHARMa::getquantile: wrong dimension of simulations") + nSim = ncol(simulations) + + + if(method == "traditional"){ + + if(integerResponse == F){ + + if(any(duplicated(observed))) message("Model family was recognized or set as continuous, but duplicate values were detected in the response. Consider if you are fitting an appropriate model.") + + values = as.vector(simulations)[duplicated(as.vector(simulations))] + if(length(values) > 0){ + if (all(values%%1==0)){ + integerResponse = T + message("Model family was recognized or set as continuous, but duplicate values were detected in the simulation - changing to integer residuals (see ?simulateResiduals for details)") + } else { + message("Duplicate non-integer values found in the simulation. If this is because you are fitting a non-inter valued discrete response model, note that DHARMa does not perform appropriate randomization for such cases.") + } + + } + } + + scaledResiduals = rep(NA, n) + for (i in 1:n){ + if(integerResponse == T){ + scaledResiduals[i] <- DHARMa.ecdf(simulations[i,] + runif(nSim, -0.5, 0.5))(observed[i] + runif(1, -0.5, 0.5)) + }else{ + scaledResiduals[i] <- DHARMa.ecdf(simulations[i,])(observed[i]) + } + } + + } else { + + + scaledResiduals = rep(NA, n) + for (i in 1:n){ + min <- sum(simulations[i,] < observed[i]) / length(simulations[i,]) + max <- sum(simulations[i,] <= observed[i]) / length(simulations[i,]) + if (min == max) scaledResiduals[i] = DHARMa.ecdf(simulations[i,])(observed[i]) + else{ + scaledResiduals[i] = runif(1, min, max) + } + } + } + + return(scaledResiduals) +} + +# +# +# testData = createData(sampleSize = 200, family = gaussian(), +# randomEffectVariance = 0, numGroups = 5) +# fittedModel <- glmmTMB(observedResponse ~ Environment1, +# data = testData) +# simulationOutput <- simulateResiduals(fittedModel = fittedModel) +# +# sims = simulationOutput$simulatedResponse +# sims[1, c(1,6,8)] = 0 +# any(apply(sims, 1, anyDuplicated)) +# getQuantile(simulations = sims, observed = testData$observedResponse, n = 200, integerResponse = F, nSim = 250) +# +# +# + + + +#' Check dot operator +#' +#' @param name variable name +#' @param default variable default +#' +#' @details modified from https://github.com/lcolladotor/dots +#' +#' @keywords internal +checkDots <- function(name, default, ...) { + args <- list(...) + if(!name %in% names(args)) { + ## Default value + return(default) + } else { + ## If the argument was defined in the ... part, return it + return(args[[name]]) + } +} + + +securityAssertion <- function(context = "Not provided", stop = F){ + generalMessage = "Message from DHARMa: During the execution of a DHARMa function, some unexpected conditions occurred. Even if you didn't get an error, your results may not be reliable. Please check with the help if you use the functions as intended. If you think that the error is not on your side, I would be grateful if you could report the problem at https://github.com/florianhartig/DHARMa/issues \n\n Context:" + if (stop == F) warning(paste(generalMessage, context)) + else stop(paste(generalMessage, context)) +} + +####################### helper.R + +####################### plot.R + +#' DHARMa standard residual plots +#' +#' This function creates standard plots for the simulated residuals +#' @param x an object with simulated residuals created by \code{\link{simulateResiduals}} +#' @param rank if T (default), the values of pred will be rank transformed. This will usually make patterns easier to spot visually, especially if the distribution of the predictor is skewed. +#' @param ... further options for \code{\link{plotResiduals}}. Consider in particular parameters quantreg, rank and asFactor. xlab, ylab and main cannot be changed when using plotSimulatedResiduals, but can be changed when using plotResiduals. +#' @details The function creates two plots. To the left, a qq-uniform plot to detect deviations from overall uniformity of the residuals (calling \code{\link{plotQQunif}}), and to the right, a plot of residuals against predicted values (calling \code{\link{plotResiduals}}). Outliers are highlighted in red (for more on outliers, see \code{\link{testOutliers}}). For a correctly specified model, we would expect +#' +#' a) a straight 1-1 line in the uniform qq-plot -> evidence for an overall uniform (flat) distribution of the residuals +#' +#' b) uniformity of residuals in the vertical direction in the res against predictor plot +#' +#' Deviations of this can be interpreted as for a linear regression. See the vignette for detailed examples. +#' +#' To provide a visual aid in detecting deviations from uniformity in y-direction, the plot of the residuals against the predicted values also performs an (optional) quantile regression, which provides 0.25, 0.5 and 0.75 quantile lines across the plots. These lines should be straight, horizontal, and at y-values of 0.25, 0.5 and 0.75. Note, however, that some deviations from this are to be expected by chance, even for a perfect model, especially if the sample size is small. See further comments on this plot, its interpretation and options, in \code{\link{plotResiduals}} +#' +#' The quantile regression can take some time to calculate, especially for larger datasets. For that reason, quantreg = F can be set to produce a smooth spline instead. This is default for n > 2000. +#' +#' @seealso \code{\link{plotResiduals}}, \code{\link{plotQQunif}} +#' @example inst/examples/plotsHelp.R +#' @import graphics +#' @import utils +#' @export +plot.DHARMa <- function(x, rank = TRUE, ...){ + + oldpar <- par(mfrow = c(1,2), oma = c(0,1,2,1)) + on.exit(par(oldpar)) + + plotQQunif(x) + plotResiduals(x, rank = rank, ...) + + mtext("DHARMa residual diagnostics", outer = T) +} + + +#' Histogram of DHARMa residuals +#' +#' The function produces a histogram from a DHARMa output +#' +#' @param x a DHARMa simulation output (class DHARMa) +#' @param breaks breaks for hist() function +#' @param col col for hist bars +#' @param main plot main +#' @param xlab plot xlab +#' @param cex.main plot cex.main +#' @param ... other arguments to be passed on to hist +#' @seealso \code{\link{plotSimulatedResiduals}}, \code{\link{plotResiduals}} +#' @example inst/examples/plotsHelp.R +#' @export +hist.DHARMa <- function(x, + breaks = seq(-0.02, 1.02, len = 53), + col = c("red",rep("lightgrey",50), "red"), + main = "Hist of DHARMa residuals", + xlab = "Residuals (outliers are marked red)", + cex.main = 1, + ...){ + + x = ensureDHARMa(x, convert = T) + + val = x$scaledResiduals + val[val == 0] = -0.01 + val[val == 1] = 1.01 + + hist(val, breaks = breaks, col = col, main = main, xlab = xlab, cex.main = cex.main, ...) +} + + +#' DHARMa standard residual plots +#' +#' DEPRECATED, use plot() instead +#' +#' @param simulationOutput an object with simulated residuals created by \code{\link{simulateResiduals}} +#' @param ... further options for \code{\link{plotResiduals}}. Consider in particular parameters quantreg, rank and asFactor. xlab, ylab and main cannot be changed when using plotSimulatedResiduals, but can be changed when using plotResiduals. +#' @note This function is deprecated. Use \code{\link{plot.DHARMa}} +#' +#' @seealso \code{\link{plotResiduals}}, \code{\link{plotQQunif}} +#' @export +plotSimulatedResiduals <- function(simulationOutput, ...){ + message("plotSimulatedResiduals is deprecated, please switch your code to simply using the plot() function") + plot(simulationOutput, ...) +} + + +#' Quantile-quantile plot for a uniform distribution +#' +#' The function produces a uniform quantile-quantile plot from a DHARMa output +#' +#' @param simulationOutput a DHARMa simulation output (class DHARMa) +#' @param testUniformity if T, the function \code{\link{testUniformity}} will be called and the result will be added to the plot +#' @param testOutliers if T, the function \code{\link{testOutliers}} will be called and the result will be added to the plot +#' @param testDispersion if T, the function \code{\link{testDispersion}} will be called and the result will be added to the plot +#' @param ... arguments to be passed on to \code{\link[gap]{qqunif}} +#' +#' @details the function calls qqunif from the R package gap to create a quantile-quantile plot for a uniform distribution. +#' @seealso \code{\link{plotSimulatedResiduals}}, \code{\link{plotResiduals}} +#' @example inst/examples/plotsHelp.R +#' @export +plotQQunif <- function(simulationOutput, testUniformity = T, testOutliers = T, testDispersion = T, ...){ + + simulationOutput = ensureDHARMa(simulationOutput, convert = "Model") + + gap::qqunif(simulationOutput$scaledResiduals,pch=2,bty="n", logscale = F, col = "black", cex = 0.6, main = "QQ plot residuals", cex.main = 1, ...) + + if(testUniformity == TRUE){ + temp = testUniformity(simulationOutput, plot = F) + legend("topleft", c(paste("KS test: p=", round(temp$p.value, digits = 5)), paste("Deviation ", ifelse(temp$p.value < 0.05, "significant", "n.s."))), text.col = ifelse(temp$p.value < 0.05, "red", "black" ), bty="n") + } + + if(testOutliers == TRUE){ + temp = testOutliers(simulationOutput, plot = F) + legend("bottomright", c(paste("Outlier test: p=", round(temp$p.value, digits = 5)), paste("Deviation ", ifelse(temp$p.value < 0.05, "significant", "n.s."))), text.col = ifelse(temp$p.value < 0.05, "red", "black" ), bty="n") + } + + if(testDispersion == TRUE){ + temp = testDispersion(simulationOutput, plot = F) + legend("center", c(paste("Dispersion test: p=", round(temp$p.value, digits = 5)), paste("Deviation ", ifelse(temp$p.value < 0.05, "significant", "n.s."))), text.col = ifelse(temp$p.value < 0.05, "red", "black" ), bty="n") + } + +} + + +#' Generic res ~ pred scatter plot with spline or quantile regression on top +#' +#' The function creates a generic residual plot with either spline or quantile regression to highlight patterns in the residuals. Outliers are highlighted in red. +#' +#' @param simulationOutput on object, usually a DHARMa object, from which residual values can be extracted. Alternatively, a vector with residuals or a fitted model can be provided, which will then be transformed into a DHARMa object. +#' @param form optional predictor against which the residuals should be plotted. Default is to used the predicted(simulationOutput) +#' @param quantreg whether to perform a quantile regression on 0.25, 0.5, 0.75 on the residuals. If F, a spline will be created instead. Default NULL chooses T for nObs < 2000, and F otherwise. +#' @param rank if T, the values provided in form will be rank transformed. This will usually make patterns easier to spot visually, especially if the distribution of the predictor is skewed. If form is a factor, this has no effect. +#' @param asFactor should a numeric predictor provided in form be treated as a factor. Default is to choose this for < 10 unique values, as long as enough predictions are available to draw a boxplot. +#' @param smoothScatter if T, a smooth scatter plot will plotted instead of a normal scatter plot. This makes sense when the number of residuals is very large. Default NULL chooses T for nObs < 10000, and F otherwise. +#' @param quantiles for a quantile regression, which quantiles should be plotted +#' @param ... additional arguments to plot / boxplot. +#' @details The function plots residuals against a predictor (by default against the fitted value, extracted from the DHARMa object, or any other predictor). +#' +#' Outliers are highlighted in red (for information on definition and interpretation of outliers, see \code{\link{testOutliers}}). +#' +#' To provide a visual aid in detecting deviations from uniformity in y-direction, the plot function calculates an (optional) quantile regression, which compares the empirical 0.25, 0.5 and 0.75 quantiles (default) in y direction (red solid lines) with the theoretical 0.25, 0.5 and 0.75 quantiles (dashed black line). +#' +#' Asymptotically (i.e. for lots of data / residuals), if the model is correct, theoretical and the empirical quantiles should be identical (i.e. dashed and solid lines should match). A p-value for the deviation is calculated for each quantile line. Significant deviations are highlighted by red color. +#' +#' If form is a factor, a boxplot will be plotted instead of a scatter plot. The distribution for each factor level should be uniformly distributed, so the box should go from 0.25 to 0.75, with the median line at 0.5. Again, chance deviations from this will increases when the sample size is smaller. You can run null simulations to test if the deviations you see exceed what you would expect from random variation. If you want to create box plots for categorical predictors (e.g. because you only have a small number of unique numeric predictor values), you can convert your predictor with as.factor(pred) +#' +#' @return if quantile tests are performed, the function returns them invisibly. +#' +#' @note The quantile regression can take some time to calculate, especially for larger datasets. For that reason, quantreg = F can be set to produce a smooth spline instead. +#' +#' @seealso \code{\link{plotQQunif}} +#' @example inst/examples/plotsHelp.R +#' @export +plotResiduals <- function(simulationOutput, form = NULL, quantreg = NULL, rank = F, asFactor = NULL, smoothScatter = NULL, quantiles = c(0.25, 0.5, 0.75), ...){ + + + ##### Checks ##### + + + a <- list(...) + a$ylab = checkDots("ylab", "Standardized residual", ...) + if(is.null(form)){ + a$xlab = checkDots("xlab", ifelse(rank, "Model predictions (rank transformed)", "Model predictions"), ...) + } + + simulationOutput = ensureDHARMa(simulationOutput, convert = T) + res = simulationOutput$scaledResiduals + if(inherits(form, "DHARMa"))stop("DHARMa::plotResiduals > argument form cannot be of class DHARMa. Note that the syntax of plotResiduals has changed since DHARMa 0.3.0. See ?plotResiduals.") + + pred = ensurePredictor(simulationOutput, form) + + ##### Rank transform and factor conversion##### + + if(!is.factor(pred)){ + + if (rank == T){ + pred = rank(pred, ties.method = "average") + pred = pred / max(pred) + } + + nuniq = length(unique(pred)) + ndata = length(pred) + if(is.null(asFactor)) asFactor = (nuniq == 1) | (nuniq < 10 & ndata / nuniq > 10) + if (asFactor) pred = factor(pred) + } + + ##### Residual scatter plots ##### + + if(is.null(quantreg)) if (length(res) > 2000) quantreg = FALSE else quantreg = TRUE + + switchScatter = 10000 + if(is.null(smoothScatter)) if (length(res) > switchScatter) smoothScatter = TRUE else smoothScatter = FALSE + + blackcol = rgb(0,0,0, alpha = max(0.1, 1 - 3 * length(res) / switchScatter)) + + + # categorical plot + if(is.factor(pred)){ + do.call(plot, append(list(res ~ pred, ylim = c(0,1), axes = FALSE), a)) + } + # smooth scatter + else if (smoothScatter == TRUE) { + defaultCol = ifelse(res == 0 | res == 1, 2,blackcol) + do.call(graphics::smoothScatter, append(list(x = pred, y = res , ylim = c(0,1), axes = FALSE, colramp = colorRampPalette(c("white", "darkgrey"))),a)) + points(pred[defaultCol == 2], res[defaultCol == 2], col = "red", cex = 0.5) + } + # normal plot + else{ + defaultCol = ifelse(res == 0 | res == 1, 2,blackcol) + defaultPch = ifelse(res == 0 | res == 1, 8,1) + a$col = checkDots("col", defaultCol, ...) + a$pch = checkDots("pch", defaultPch, ...) + do.call(plot, append(list(res ~ pred, ylim = c(0,1), axes = FALSE), a)) + } + + axis(1) + axis(2, at=c(0, 0.25, 0.5, 0.75, 1)) + + ##### Quantile regressions ##### + + main = checkDots("main", "Residual vs. predicted", ...) + out = NULL + + if(is.numeric(pred)){ + if(quantreg == F){ + title(main = main, cex.main = 1) + abline(h = c(0.25, 0.5, 0.75), col = "black", lwd = 0.5, lty = 2) + try({ + lines(smooth.spline(pred, res, df = 10), lty = 2, lwd = 2, col = "red") + abline(h = 0.5, col = "red", lwd = 2) + }, silent = T) + }else{ + + out = testQuantiles(simulationOutput, pred, quantiles = quantiles, plot = F) + + + if(any(out$pvals < 0.05, na.rm = TRUE)){ + main = paste(main, "Quantile deviations detected (red curves)", sep ="\n") + if(out$p.value <= 0.05){ + main = paste(main, "Combined adjusted quantile test significant", sep ="\n") + } else { + main = paste(main, "Combined adjusted quantile test n.s.", sep ="\n") + } + maincol = "red" + } else { + main = paste(main, "No significant problems detected", sep ="\n") + maincol = "black" + } + + + title(main = main, cex.main = 0.8, + col.main = maincol) + + for(i in 1:length(quantiles)){ + + lineCol = ifelse(out$pvals[i] <= 0.05 & !(is.na(out$pvals[i])), "red", "black") + filCol = ifelse(out$pvals[i] <= 0.05 & !(is.na(out$pvals[i])), "#FF000040", "#00000020") + + abline(h = quantiles[i], col = lineCol, lwd = 0.5, lty = 2) + polygon(c(out$predictions$pred, rev(out$predictions$pred)), + c(out$predictions[,2*i] - out$predictions[,2*i+1], rev(out$predictions[,2*i] + out$predictions[,2*i+1])), + col = "#00000020", border = F) + lines(out$predictions$pred, out$predictions[,2*i], col = lineCol, lwd = 2) + } + + # legend("bottomright", c(paste("Quantile test: p=", round(out$p.value, digits = 5)), paste("Deviation ", ifelse(out$p.value < 0.05, "significant", "n.s."))), text.col = ifelse(out$p.value < 0.05, "red", "black" ), bty="n") + + } + } + invisible(out) +} + +x = 0.01 +x <= 0.05 & !(is.na(x)) + + +#' Ensures the existence of a valid predictor to plot residuals against +#' +#' @param simulationOutput a DHARMa simulation output or an object that can be converted into a DHARMa simulation output +#' @param predictor an optional predictor. If no predictor is provided, will try to extract the fitted value +#' @keywords internal +ensurePredictor <- function(simulationOutput, + predictor = NULL){ + if(!is.null(predictor)){ + + if(length(predictor) != length(simulationOutput$scaledResiduals)) stop("DHARMa: residuals and predictor do not have the same length. The issue is possibly that you have NAs in your predictor that were removed during the model fit. Remove the NA values from your predictor.") + } else { + + predictor = simulationOutput$fittedPredictedResponse + if(is.null(predictor)) stop("DHARMa: can't extract predictor from simulationOutput, and no predictor provided") + } + return(predictor) +} + + + + +#plot(simulationOutput) + +#plot(simulationOutput$observedResponse, simulationOutput$scaledResiduals, xlab = "predicted", ylab = "Residual", main = "Residual vs. predicted") + +#plot(simulationOutput$observedResponse, simulationOutput$fittedPredictedResponse - simulationOutput$observedResponse) + +#plot(cumsum(sort(simulationOutput$scaledResiduals))) + + +#plotConventionalResiduals(fittedModel) + + +#' Conventional residual plot +#' +#' Convenience function to draw conventional residual plots +#' +#' @param fittedModel a fitted model object +#' @export +plotConventionalResiduals <- function(fittedModel){ + opar <- par(mfrow = c(1,3), oma = c(0,1,2,1)) + on.exit(par(opar)) + plot(predict(fittedModel), resid(fittedModel, type = "deviance"), main = "Deviance" , ylab = "Residual", xlab = "Predicted") + plot(predict(fittedModel), resid(fittedModel, type = "pearson") , main = "Pearson", ylab = "Residual", xlab = "Predicted") + plot(predict(fittedModel), resid(fittedModel, type = "response") , main = "Raw residuals" , ylab = "Residual", xlab = "Predicted") + mtext("Conventional residual plots", outer = T) +} + + + + +# +# +# if(quantreg == F){ +# +# lines(smooth.spline(simulationOutput$fittedPredictedResponse, simulationOutput$scaledResiduals, df = 10), lty = 2, lwd = 2, col = "red") +# +# abline(h = 0.5, col = "red", lwd = 2) +# +# }else{ +# +# #library(gamlss) +# +# # qrnn +# +# # http://r.789695.n4.nabble.com/Quantile-GAM-td894280.html +# +# #require(quantreg) +# #dat <- plyr::arrange(dat,pred) +# #fit<-quantreg::rqss(resid~qss(pred,constraint="N"),tau=0.5,data = dat) +# +# probs = c(0.25, 0.50, 0.75) +# +# w <- p <- list() +# for(i in seq_along(probs)){ +# capture.output(w[[i]] <- qrnn::qrnn.fit(x = as.matrix(simulationOutput$fittedPredictedResponse), y = as.matrix(simulationOutput$scaledResiduals), n.hidden = 4, tau = probs[i], iter.max = 1000, n.trials = 1, penalty = 1)) +# p[[i]] <- qrnn::qrnn.predict(as.matrix(sort(simulationOutput$fittedPredictedResponse)), w[[i]]) +# } +# +# +# +# #plot(simulationOutput$fittedPredictedResponse, simulationOutput$scaledResiduals, xlab = "Predicted", ylab = "Residual", main = "Residual vs. predicted\n lines should match", cex.main = 1) +# +# #lines(sort(simulationOutput$fittedPredictedResponse), as.vector(p[[1]]), col = "red") +# +# matlines(sort(simulationOutput$fittedPredictedResponse), matrix(unlist(p), nrow = length(simulationOutput$fittedPredictedResponse), ncol = length(p)), col = "red", lty = 1) +# +# # as.vector(p[[1]]) +# # +# # +# # lines(simulationOutput$fittedPredictedResponse,p[[1]], col = "red", lwd = 2) +# # abline(h = 0.5, col = "red", lwd = 2) +# # +# # fit<-quantreg::rqss(resid~qss(pred,constraint="N"),tau=0.25,data = dat) +# # lines(unique(dat$pred)[-1],fit$coef[1] + fit$coef[-1], col = "green", lwd = 2, lty =2) +# # abline(h = 0.25, col = "green", lwd = 2, lty =2) +# # +# # fit<-quantreg::rqss(resid~qss(pred,constraint="N"),tau=0.75,data = dat) +# # lines(unique(dat$pred)[-1],fit$coef[1] + fit$coef[-1], col = "blue", lwd = 2, lty = 2) +# # abline(h = 0.75, col = "blue", lwd = 2, lty =2) +# } + +####################### plot.R + +####################### random.R + +#' Record and restore a random state +#' +#' The aim of this function is to record, manipualate and restor a random state +#' +#' @details This function is intended for two (not mutually exclusive tasks) +#' +#' a) record the current random state +#' +#' b) change the current random state in a way that the previous state can be restored +#' +#' @return a list with various infos about the random state that after function execution, as well as a function to restore the previous state before the function execution +#' +#' @param seed seed argument to set.seed(). NULL = no seed, but random state will be restored. F = random state will not be restored +#' @export +#' @example inst/examples/getRandomStateHelp.R +#' @author Florian Hartig +#' +getRandomState <- function(seed = NULL){ + + # better to explicitly access the global RS? + # current = get(".Random.seed", .GlobalEnv, ifnotfound = NULL) + + current = mget(".Random.seed", envir = .GlobalEnv, ifnotfound = list(NULL))[[1]] + + if(is.logical(seed) & seed == F){ + restoreCurrent <- function(){} + }else{ + restoreCurrent <- function(){ + if(is.null(current)) rm(".Random.seed", envir = .GlobalEnv) else assign(".Random.seed", current , envir = .GlobalEnv) + } + } + + # setting seed + if(is.numeric(seed)) set.seed(seed) + + # ensuring that RNG has been initialized + if (is.null(current))runif(1) + + randomState = list(seed, state = get(".Random.seed", globalenv()), kind = RNGkind(), restoreCurrent = restoreCurrent) + return(randomState) +} + +####################### random.R + +######################################### Package DHARMa diff -r 000000000000 -r 0778efa9eb2e PAMPA_GLM_SP.xml --- /dev/null Thu Jan 01 00:00:00 1970 +0000 +++ b/PAMPA_GLM_SP.xml Tue Jul 21 06:00:51 2020 -0400 @@ -0,0 +1,144 @@ + + Compute a GLM of your choice on population data + + pampa_macros.xml + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + diff -r 000000000000 -r 0778efa9eb2e pampa_macros.xml --- /dev/null Thu Jan 01 00:00:00 1970 +0000 +++ b/pampa_macros.xml Tue Jul 21 06:00:51 2020 -0400 @@ -0,0 +1,82 @@ + + 0.0.1 + + + r-tidyr + + + + + r-gap + r-glmmtmb + r-multcomp + + + + + r-ggplot2 + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + @unpublished{pampayves, + title={ PAMPA "ressources et biodiversité" scripts }, + author={Yves Reecht}, + url={https://wwz.ifremer.fr/pampa/Meth.-Outils/Outils} + } + + + + diff -r 000000000000 -r 0778efa9eb2e test-data/GLM_table_population_analysis_on_Presence_absence_sansszcl_cropped.tabular --- /dev/null Thu Jan 01 00:00:00 1970 +0000 +++ b/test-data/GLM_table_population_analysis_on_Presence_absence_sansszcl_cropped.tabular Tue Jul 21 06:00:51 2020 -0400 @@ -0,0 +1,4 @@ +"species" "AIC" "BIC" "logLik" "deviance" "df.resid" "site Std.Dev" "site NbObservation" "site NbLevels" "(Intercept) Estimate" "(Intercept) Std.Err" "(Intercept) Zvalue" "(Intercept) Pvalue" "(Intercept) signif" "2007 Estimate" "2007 Std.Err" "2007 Zvalue" "2007 Pvalue" "2007 signif" "2008 Estimate" "2008 Std.Err" "2008 Zvalue" "2008 Pvalue" "2008 signif" "2009 Estimate" "2009 Std.Err" "2009 Zvalue" "2009 Pvalue" "2009 signif" "2010 Estimate" "2010 Std.Err" "2010 Zvalue" "2010 Pvalue" "2010 signif" "2012 Estimate" "2012 Std.Err" "2012 Zvalue" "2012 Pvalue" "2012 signif" "2013 Estimate" "2013 Std.Err" "2013 Zvalue" "2013 Pvalue" "2013 signif" "2014 Estimate" "2014 Std.Err" "2014 Zvalue" "2014 Pvalue" "2014 signif" "2015 Estimate" "2015 Std.Err" "2015 Zvalue" "2015 Pvalue" "2015 signif" "2017 Estimate" "2017 Std.Err" "2017 Zvalue" "2017 Pvalue" "2017 signif" "Algueraie Estimate" "Algueraie Std.Err" "Algueraie Zvalue" "Algueraie Pvalue" "Algueraie signif" "Corail vivant Estimate" "Corail vivant Std.Err" "Corail vivant Zvalue" "Corail vivant Pvalue" "Corail vivant signif" "Detritique Estimate" "Detritique Std.Err" "Detritique Zvalue" "Detritique Pvalue" "Detritique signif" "Fond lagonaire Estimate" "Fond lagonaire Std.Err" "Fond lagonaire Zvalue" "Fond lagonaire Pvalue" "Fond lagonaire signif" "Herbier Estimate" "Herbier Std.Err" "Herbier Zvalue" "Herbier Pvalue" "Herbier signif" +"Abalstel" 465.778668402852 530.012669606292 -217.889334201426 435.778668402852 520 2.02893200110294e-11 535 87 0.582003897784078 0.16995917980052 3.42437459669534 0.000616216168469682 "yes" NA NA NA NA NA -0.19415426356584 0.145972631275553 -1.33007305458058 0.183494202488272 "no" 0.00824541649995591 0.132249306065064 0.0623475218531531 0.950286085093627 "no" -0.0469231466299359 0.127874642775125 -0.366946453273407 0.713658960013819 "no" -0.026333156943764 0.127546916274464 -0.206458593535093 0.83643270551623 "no" 0.0449902599405432 0.123577649181079 0.364064701332996 0.715809694931448 "no" -0.00566671318079257 0.12968331601722 -0.0436965475191898 0.965146291270581 "no" -0.00315955678300799 0.134390106623576 -0.023510337646043 0.981243192515925 "no" -0.0211838550997583 0.134469226544777 -0.157536825666981 0.874821787532576 "no" NA NA NA NA NA -0.584431910188132 0.17913769577747 -3.26247308056328 0.00110444661730468 "yes" -0.555457917136758 0.181703900796363 -3.05693997048123 0.00223609052438647 "yes" -0.533422320342636 0.181778685227503 -2.9344602183421 0.00334128381555499 "yes" 2.60899691274078 0.221452905612334 11.7812719843377 4.87517680861174e-32 "yes" +"Hemifasc" 989.708308026567 1053.94230923001 -479.854154013284 959.708308026567 520 0.0731913677511507 535 87 0.80188975303788 0.301651463759325 2.65833204667515 0.00785284807116327 "yes" NA NA NA NA NA 0.481141192254312 0.272853104782075 1.76337078018076 0.0778379746547175 "no" 0.491975244697431 0.258717316966712 1.9015937953652 0.0572242797228078 "no" 0.52417509191558 0.257940994484472 2.03215116295574 0.0421383552019658 "yes" 0.704061126955671 0.258153165214832 2.72729999792859 0.00638549547621618 "yes" 0.922884191406201 0.242885260944276 3.79967144905484 0.000144888046528251 "yes" 1.07227573954628 0.268950382217829 3.98689055841469 6.69448864477017e-05 "yes" 1.20570832792662 0.291950452161748 4.12983887847734 3.63017553679052e-05 "yes" 0.952662560597608 0.276776209505792 3.44199583590898 0.000577439138478601 "yes" NA NA NA NA NA -1.4622104258899 0.300994684364961 -4.85792773707906 1.18620683066582e-06 "yes" -1.44397094980884 0.305397744683802 -4.72816507307175 2.26557963478985e-06 "yes" -1.45728966857269 0.302234347092491 -4.82172090165093 1.42324990478013e-06 "yes" -1.34910839377147 0.366744594037812 -3.67860471757186 0.000234513401805964 "yes" +"Zebrscop" 2937.50168275753 3001.73568396097 -1453.75084137876 2907.50168275753 520 6.86847494946857 535 87 -0.783376806033906 1.96843225335046 -0.397969909658067 0.690652366321943 "no" NA NA NA NA NA -2.46263154439423 1.71419485921636 -1.43661120621959 0.150828497639506 "no" -2.81277062425383 1.65194192826306 -1.70270551048445 0.0886231931264859 "no" -2.24200293533928 1.6471883066992 -1.36110906459264 0.173479225491309 "no" 1.92420443459089 1.66604387989188 1.15495423488832 0.248109168047627 "no" 5.03567066902903 1.4881081746922 3.38394127165561 0.00071453285120286 "yes" 2.56255810319688 1.81706438444276 1.41027369483263 0.158458882708268 "no" 0.73344942166209 1.94553641122863 0.37699084809156 0.706180406176162 "no" 0.419840113473674 1.90401994599711 0.220501951335289 0.825480252830466 "no" NA NA NA NA NA 1.33928270409068 1.87987517063075 0.712431721538894 0.47619747813314 "no" 0.437923054943406 1.89963982379853 0.230529519047318 0.817680328217623 "no" 0.52253919562426 1.87614268249488 0.278517833691301 0.780614877108231 "no" -1.7132623404351 2.24757733331173 -0.762270697004523 0.445898459177794 "no" diff -r 000000000000 -r 0778efa9eb2e test-data/Presence_absence_table_sansszcl_cropped.tabular --- /dev/null Thu Jan 01 00:00:00 1970 +0000 +++ b/test-data/Presence_absence_table_sansszcl_cropped.tabular Tue Jul 21 06:00:51 2020 -0400 @@ -0,0 +1,2134 @@ +"point" "year" "species.code" "number" "number.max" "number.sd" "pres.abs" "observation.unit" +"AB_0008" "08" "Abalstel" 0 0 0 0 "AB080008" +"AB_0015" "08" "Abalstel" 0 0 0 0 "AB080015" +"AB_0027" "08" "Abalstel" 0 0 0 0 "AB080027" +"AB_0031" "08" "Abalstel" 0 0 0 0 "AB080031" +"AB_0037" "08" "Abalstel" 0 0 NA 0 "AB080037" +"AB_0042" "08" "Abalstel" 0 0 NA 0 "AB080042" +"AB_0057" "08" "Abalstel" 0 0 0 0 "AB080057" +"AB_0076" "09" "Abalstel" 0 0 0 0 "AB090076" +"AB_0081" "09" "Abalstel" 0 0 0 0 "AB090081" +"AB_0095" "09" "Abalstel" 0 0 0 0 "AB090095" +"AB_0097" "09" "Abalstel" 0 0 0 0 "AB090097" +"AB_0098" "09" "Abalstel" 0 0 NA 0 "AB090098" +"AB_0104" "09" "Abalstel" 0 0 0 0 "AB090104" +"AB_0105" "09" "Abalstel" 0 0 0 0 "AB090105" +"AB_0106" "09" "Abalstel" 0 0 NA 0 "AB090106" +"AB_0120" "09" "Abalstel" 0 0 NA 0 "AB090120" +"AB_0121" "09" "Abalstel" 0 0 0 0 "AB090121" +"AB_0122" "09" "Abalstel" 0 0 0 0 "AB090122" +"AB_0123" "09" "Abalstel" 0 0 0 0 "AB090123" +"AB_0124" "09" "Abalstel" 0 0 NA 0 "AB090124" +"AB_0125" "09" "Abalstel" 0 0 0 0 "AB090125" +"AB_0126" "09" "Abalstel" 0 0 0 0 "AB090126" +"AB_0127" "09" "Abalstel" 0 0 0 0 "AB090127" +"AB_0132" "09" "Abalstel" 0 0 NA 0 "AB090132" +"AB_0133" "09" "Abalstel" 0 0 0 0 "AB090133" +"AB_0134" "09" "Abalstel" 0 0 0 0 "AB090134" +"AB_0135" "09" "Abalstel" 0 0 0 0 "AB090135" +"AB_0143" "09" "Abalstel" 0 0 NA 0 "AB090143" +"AB_0148" "09" "Abalstel" 0 0 NA 0 "AB090148" +"AB_0149" "09" "Abalstel" 0 0 0 0 "AB090149" +"AB_0151" "09" "Abalstel" 0 0 0 0 "AB090151" +"AB_0601" "09" "Abalstel" 0 0 0 0 "AB090601" +"AB_0602" "09" "Abalstel" 0 0 0 0 "AB090602" +"AB_0603" "09" "Abalstel" 0 0 NA 0 "AB090603" +"AB_0001" "10" "Abalstel" 0 0 NA 0 "AB100001" +"AB_0002" "10" "Abalstel" 0 0 0 0 "AB100002" +"AB_0006" "10" "Abalstel" 0 0 0 0 "AB100006" +"AB_0008" "10" "Abalstel" 0 0 0 0 "AB100008" +"AB_0009" "10" "Abalstel" 0 0 0 0 "AB100009" +"AB_0010" "10" "Abalstel" 0 0 0 0 "AB100010" +"AB_0011" "10" "Abalstel" 0 0 0 0 "AB100011" +"AB_0015" "10" "Abalstel" 0 0 0 0 "AB100015" +"AB_0017" "10" "Abalstel" 0 0 0 0 "AB100017" +"AB_0019" "10" "Abalstel" 0 0 0 0 "AB100019" +"AB_0020" "10" "Abalstel" 0 0 0 0 "AB100020" +"AB_0021" "10" "Abalstel" 0 0 0 0 "AB100021" +"AB_0023" "10" "Abalstel" 0 0 0 0 "AB100023" +"AB_0024" "10" "Abalstel" 0 0 0 0 "AB100024" +"AB_0025" "10" "Abalstel" 0 0 0 0 "AB100025" +"AB_0028" "10" "Abalstel" 0 0 0 0 "AB100028" +"AB_0029" "10" "Abalstel" 0 0 0 0 "AB100029" +"AB_0031" "10" "Abalstel" 0 0 0 0 "AB100031" +"AB_0035" "10" "Abalstel" 0 0 NA 0 "AB100035" +"AB_0036" "10" "Abalstel" 0 0 0 0 "AB100036" +"AB_0038" "10" "Abalstel" 0 0 0 0 "AB100038" +"AB_0042" "10" "Abalstel" 0 0 0 0 "AB100042" +"AB_0046" "10" "Abalstel" 0 0 0 0 "AB100046" +"AB_0047" "10" "Abalstel" 0 0 0 0 "AB100047" +"AB_0048" "10" "Abalstel" 0 0 0 0 "AB100048" +"AB_0049" "10" "Abalstel" 0 0 0 0 "AB100049" +"AB_0052" "10" "Abalstel" 0 0 0 0 "AB100052" +"AB_0055" "10" "Abalstel" 0 0 NA 0 "AB100055" +"AB_0060" "10" "Abalstel" 0 0 0 0 "AB100060" +"AB_0061" "10" "Abalstel" 0 0 0 0 "AB100061" +"AB_0062" "10" "Abalstel" 0 0 0 0 "AB100062" +"AB_0072" "10" "Abalstel" 0 0 NA 0 "AB100072" +"AB_0077" "10" "Abalstel" 0 0 NA 0 "AB100077" +"AB_0078" "10" "Abalstel" 0 0 NA 0 "AB100078" +"AB_0079" "10" "Abalstel" 0 0 0 0 "AB100079" +"AB_0081" "10" "Abalstel" 0 0 0 0 "AB100081" +"AB_0082" "10" "Abalstel" 0 0 NA 0 "AB100082" +"AB_0085" "10" "Abalstel" 0 0 0 0 "AB100085" +"AB_0086" "10" "Abalstel" 0 0 0 0 "AB100086" +"AB_0087" "10" "Abalstel" 0 0 0 0 "AB100087" +"AB_0088" "10" "Abalstel" 0 0 0 0 "AB100088" +"AB_0089" "10" "Abalstel" 0 0 NA 0 "AB100089" +"AB_0090" "10" "Abalstel" 0 0 0 0 "AB100090" +"AB_0091" "10" "Abalstel" 0 0 0 0 "AB100091" +"AB_0092" "10" "Abalstel" 0 0 0 0 "AB100092" +"AB_0093" "10" "Abalstel" 0 0 0 0 "AB100093" +"AB_0094" "10" "Abalstel" 0 0 0 0 "AB100094" +"AB_0095" "10" "Abalstel" 0 0 NA 0 "AB100095" +"AB_0096" "10" "Abalstel" 0 0 0 0 "AB100096" +"AB_0097" "10" "Abalstel" 0 0 0 0 "AB100097" +"AB_0098" "10" "Abalstel" 0 0 NA 0 "AB100098" +"AB_0099" "10" "Abalstel" 0 0 0 0 "AB100099" +"AB_0111" "10" "Abalstel" 0 0 0 0 "AB100111" +"AB_0112" "10" "Abalstel" 0 0 0 0 "AB100112" +"AB_0119" "10" "Abalstel" 0 0 NA 0 "AB100119" +"AB_0124" "10" "Abalstel" 0 0 0 0 "AB100124" +"AB_0131" "10" "Abalstel" 0 0 0 0 "AB100131" +"AB_0132" "10" "Abalstel" 0 0 0 0 "AB100132" +"AS_0048" "14" "Abalstel" 0 0 0 0 "AS140048" +"AS_0054" "14" "Abalstel" 0 0 0 0 "AS140054" +"AS_0059" "14" "Abalstel" 0 0 0 0 "AS140059" +"AS_0060" "14" "Abalstel" 0 0 0 0 "AS140060" +"AS_0061" "14" "Abalstel" 0 0 0 0 "AS140061" +"AS_0070" "14" "Abalstel" 0 0 NA 0 "AS140070" +"AS_0079" "14" "Abalstel" 0 0 0 0 "AS140079" +"AS_0081" "14" "Abalstel" 0 0 0 0 "AS140081" +"AS_0087" "14" "Abalstel" 0 0 0 0 "AS140087" +"AS_0088" "14" "Abalstel" 0 0 0 0 "AS140088" +"AS_0092" "14" "Abalstel" 0 0 0 0 "AS140092" +"AS_0094" "14" "Abalstel" 0 0 NA 0 "AS140094" +"AS_0097" "14" "Abalstel" 0 0 NA 0 "AS140097" +"AS_0155" "14" "Abalstel" 0 0 NA 0 "AS140155" +"AS_0156" "14" "Abalstel" 0 0 0 0 "AS140156" +"AS_0157" "14" "Abalstel" 0 0 0 0 "AS140157" +"AS_0159" "14" "Abalstel" 0 0 0 0 "AS140159" +"BE_S032" "13" "Abalstel" 0 0 0 0 "BE13S032" +"BE_S050" "13" "Abalstel" 0 0 0 0 "BE13S050" +"BE_S072" "13" "Abalstel" 0 0 NA 0 "BE13S072" +"BL_0001" "12" "Abalstel" 0 0 0 0 "BL120001" +"BL_0005" "12" "Abalstel" 0 0 NA 0 "BL120005" +"BL_0009" "12" "Abalstel" 0 0 NA 0 "BL120009" +"BL_0011" "12" "Abalstel" 0 0 0 0 "BL120011" +"BL_0014" "12" "Abalstel" 0 0 0 0 "BL120014" +"BL_0016" "12" "Abalstel" 0 0 NA 0 "BL120016" +"BL_0021" "12" "Abalstel" 0 0 0 0 "BL120021" +"BL_0022" "12" "Abalstel" 0 0 0 0 "BL120022" +"BL_0024" "12" "Abalstel" 0 0 NA 0 "BL120024" +"BL_0027" "12" "Abalstel" 0 0 0 0 "BL120027" +"BL_0028" "12" "Abalstel" 0 0 NA 0 "BL120028" +"BL_0033" "12" "Abalstel" 0 0 0 0 "BL120033" +"BL_0039" "12" "Abalstel" 0 0 NA 0 "BL120039" +"BL_0040" "12" "Abalstel" 0 0 0 0 "BL120040" +"BL_0041" "12" "Abalstel" 0 0 NA 0 "BL120041" +"BL_0051" "12" "Abalstel" 0 0 0 0 "BL120051" +"BL_0062" "12" "Abalstel" 0 0 0 0 "BL120062" +"BL_0068" "12" "Abalstel" 0 0 0 0 "BL120068" +"BL_0075" "12" "Abalstel" 0 0 0 0 "BL120075" +"BL_0076" "12" "Abalstel" 0 0 0 0 "BL120076" +"BL_0082" "12" "Abalstel" 0 0 0 0 "BL120082" +"BL_0085" "12" "Abalstel" 0 0 0 0 "BL120085" +"BL_0090" "12" "Abalstel" 0 0 0 0 "BL120090" +"BL_0091" "12" "Abalstel" 0 0 0 0 "BL120091" +"BL_0093" "12" "Abalstel" 0 0 NA 0 "BL120093" +"BL_0094" "12" "Abalstel" 0 0 0 0 "BL120094" +"BL_0097" "12" "Abalstel" 0 0 NA 0 "BL120097" +"BL_0106" "12" "Abalstel" 0 0 NA 0 "BL120106" +"BL_0128" "12" "Abalstel" 0 0 0 0 "BL120128" +"BL_0131" "12" "Abalstel" 0 0 0 0 "BL120131" +"BL_0133" "12" "Abalstel" 0 0 NA 0 "BL120133" +"BL_0136" "12" "Abalstel" 0 0 0 0 "BL120136" +"BL_0137" "12" "Abalstel" 0 0 0 0 "BL120137" +"BL_0140" "12" "Abalstel" 0 0 0 0 "BL120140" +"BL_0141" "12" "Abalstel" 0 0 0 0 "BL120141" +"BL_0154" "12" "Abalstel" 0 0 NA 0 "BL120154" +"BL_0155" "12" "Abalstel" 0 0 0 0 "BL120155" +"BL_0161" "12" "Abalstel" 0 0 NA 0 "BL120161" +"BL_0204" "12" "Abalstel" 0 0 0 0 "BL120204" +"BL_P003" "12" "Abalstel" 0 0 0 0 "BL12P003" +"BL_P017" "12" "Abalstel" 0 0 0 0 "BL12P017" +"BL_P077" "12" "Abalstel" 0 0 0 0 "BL12P077" +"BL_P078" "12" "Abalstel" 0 0 0 0 "BL12P078" +"BL_P087" "12" "Abalstel" 0 0 0 0 "BL12P087" +"BL_P124" "12" "Abalstel" 0 0 0 0 "BL12P124" +"BO_0007" "12" "Abalstel" 0 0 0 0 "BO120007" +"BO_0011" "12" "Abalstel" 0 0 0 0 "BO120011" +"BO_0014" "12" "Abalstel" 0 0 0 0 "BO120014" +"BO_0026" "12" "Abalstel" 0 0 NA 0 "BO120026" +"BO_0028" "12" "Abalstel" 0 0 0 0 "BO120028" +"BO_0029" "12" "Abalstel" 0 0 NA 0 "BO120029" +"BO_0032" "12" "Abalstel" 0 0 0 0 "BO120032" +"BO_0043" "12" "Abalstel" 0 0 NA 0 "BO120043" +"BO_0045" "12" "Abalstel" 0 0 NA 0 "BO120045" +"BO_0054" "12" "Abalstel" 0 0 0 0 "BO120054" +"BO_0055" "12" "Abalstel" 0 0 0 0 "BO120055" +"BO_0056" "12" "Abalstel" 0 0 0 0 "BO120056" +"BO_0095" "12" "Abalstel" 0 0 0 0 "BO120095" +"BO_0099" "12" "Abalstel" 0 0 0 0 "BO120099" +"BO_0206" "12" "Abalstel" 0 0 0 0 "BO120206" +"BO_0207" "12" "Abalstel" 0 0 NA 0 "BO120207" +"BO_0209" "12" "Abalstel" 0 0 0 0 "BO120209" +"BO_0212" "12" "Abalstel" 0 0 0 0 "BO120212" +"BO_0213" "12" "Abalstel" 0 0 0 0 "BO120213" +"BO_0214" "12" "Abalstel" 0 0 0 0 "BO120214" +"BO_0215" "12" "Abalstel" 0 0 0 0 "BO120215" +"BO_0216" "12" "Abalstel" 0 0 NA 0 "BO120216" +"BO_095B" "12" "Abalstel" 0 0 0 0 "BO12095B" +"CH_P032" "13" "Abalstel" 0 0 NA 0 "CH13P032" +"CH_P033" "13" "Abalstel" 0 0 0 0 "CH13P033" +"CH_P034" "13" "Abalstel" 0 0 NA 0 "CH13P034" +"CH_P037" "13" "Abalstel" 0 0 0 0 "CH13P037" +"CH_P040" "13" "Abalstel" 0 0 0 0 "CH13P040" +"CH_P041" "13" "Abalstel" 0 0 0 0 "CH13P041" +"CH_P055" "13" "Abalstel" 0 0 0 0 "CH13P055" +"CH_P056" "13" "Abalstel" 0 0 NA 0 "CH13P056" +"CH_P057" "13" "Abalstel" 0 0 NA 0 "CH13P057" +"CH_P059" "13" "Abalstel" 0 0 0 0 "CH13P059" +"CH_P061" "13" "Abalstel" 0 0 0 0 "CH13P061" +"CH_P063" "13" "Abalstel" 0 0 0 0 "CH13P063" +"CH_P066" "13" "Abalstel" 0 0 0 0 "CH13P066" +"CH_P068" "13" "Abalstel" 0 0 0 0 "CH13P068" +"CH_P071" "13" "Abalstel" 0 0 0 0 "CH13P071" +"CH_S095" "13" "Abalstel" 0 0 NA 0 "CH13S095" +"CH_S099" "13" "Abalstel" 0 0 NA 0 "CH13S099" +"CH_S131" "13" "Abalstel" 0 0 0 0 "CH13S131" +"CH_S148" "13" "Abalstel" 0 0 NA 0 "CH13S148" +"CH_S149" "13" "Abalstel" 0 0 NA 0 "CH13S149" +"CH_S151" "13" "Abalstel" 0 0 NA 0 "CH13S151" +"CH_S153" "13" "Abalstel" 0 0 NA 0 "CH13S153" +"CH_S156" "13" "Abalstel" 0 0 0 0 "CH13S156" +"CH_S160" "13" "Abalstel" 0 0 0 0 "CH13S160" +"CH_S192" "13" "Abalstel" 0 0 0 0 "CH13S192" +"CS_0007" "13" "Abalstel" 0 0 0 0 "CS130007" +"CS_0011" "13" "Abalstel" 0 0 0 0 "CS130011" +"CS_0015" "13" "Abalstel" 0 0 NA 0 "CS130015" +"CS_0018" "13" "Abalstel" 0 0 0 0 "CS130018" +"CS_0019" "13" "Abalstel" 0 0 NA 0 "CS130019" +"CS_0021" "13" "Abalstel" 0 0 0 0 "CS130021" +"CS_0023" "13" "Abalstel" 0 0 0 0 "CS130023" +"CS_0025" "13" "Abalstel" 0 0 0 0 "CS130025" +"CS_0027" "13" "Abalstel" 0 0 0 0 "CS130027" +"CS_0031" "13" "Abalstel" 0 0 0 0 "CS130031" +"CS_0033" "13" "Abalstel" 0 0 NA 0 "CS130033" +"CS_0035" "13" "Abalstel" 0 0 0 0 "CS130035" +"CS_0037" "13" "Abalstel" 0 0 0 0 "CS130037" +"CS_0039" "13" "Abalstel" 0 0 0 0 "CS130039" +"CS_0042" "13" "Abalstel" 0 0 NA 0 "CS130042" +"CS_0043" "13" "Abalstel" 0 0 0 0 "CS130043" +"CS_0044" "13" "Abalstel" 0 0 0 0 "CS130044" +"CS_0045" "13" "Abalstel" 0 0 0 0 "CS130045" +"CS_0047" "13" "Abalstel" 0 0 0 0 "CS130047" +"CS_0054" "13" "Abalstel" 0 0 NA 0 "CS130054" +"CS_0060" "13" "Abalstel" 0 0 0 0 "CS130060" +"CS_0064" "13" "Abalstel" 0 0 0 0 "CS130064" +"CS_0065" "13" "Abalstel" 0 0 0 0 "CS130065" +"CS_0069" "13" "Abalstel" 0 0 0 0 "CS130069" +"CS_0070" "13" "Abalstel" 0 0 0 0 "CS130070" +"CS_0071" "13" "Abalstel" 0 0 0 0 "CS130071" +"CS_0075" "13" "Abalstel" 0 0 0 0 "CS130075" +"CS_0077" "13" "Abalstel" 0 0 0 0 "CS130077" +"CS_0079" "13" "Abalstel" 0 0 0 0 "CS130079" +"CS_0081" "13" "Abalstel" 0 0 0 0 "CS130081" +"CS_0082" "13" "Abalstel" 0 0 0 0 "CS130082" +"CS_0083" "13" "Abalstel" 0 0 NA 0 "CS130083" +"CS_0085" "13" "Abalstel" 0 0 NA 0 "CS130085" +"CS_0092" "13" "Abalstel" 0 0 0 0 "CS130092" +"CS_0094" "13" "Abalstel" 0 0 0 0 "CS130094" +"CS_0095" "13" "Abalstel" 0 0 NA 0 "CS130095" +"CS_0098" "13" "Abalstel" 0 0 0 0 "CS130098" +"CS_0100" "13" "Abalstel" 0 0 0 0 "CS130100" +"CS_0101" "13" "Abalstel" 0 0 NA 0 "CS130101" +"CS_0104" "13" "Abalstel" 0 0 NA 0 "CS130104" +"CS_0108" "13" "Abalstel" 0 0 NA 0 "CS130108" +"CS_0109" "13" "Abalstel" 0 0 0 0 "CS130109" +"CS_0115" "13" "Abalstel" 0 0 0 0 "CS130115" +"CS_0116" "13" "Abalstel" 0 0 0 0 "CS130116" +"CS_0125" "13" "Abalstel" 0 0 0 0 "CS130125" +"CS_0126" "13" "Abalstel" 0 0 NA 0 "CS130126" +"CS_0129" "13" "Abalstel" 0 0 NA 0 "CS130129" +"CS_0130" "13" "Abalstel" 0 0 0 0 "CS130130" +"CS_0131" "13" "Abalstel" 0 0 0 0 "CS130131" +"CS_0133" "13" "Abalstel" 0 0 0 0 "CS130133" +"CS_0135" "13" "Abalstel" 0 0 NA 0 "CS130135" +"CS_0137" "13" "Abalstel" 0 0 0 0 "CS130137" +"CS_0140" "13" "Abalstel" 0 0 0 0 "CS130140" +"CS_0141" "13" "Abalstel" 0 0 0 0 "CS130141" +"CS_0142" "13" "Abalstel" 0 0 0 0 "CS130142" +"CS_0143" "13" "Abalstel" 0 0 0 0 "CS130143" +"CS_0144" "13" "Abalstel" 0 0 0 0 "CS130144" +"CS_0145" "13" "Abalstel" 0 0 NA 0 "CS130145" +"CS_0146" "13" "Abalstel" 0 0 0 0 "CS130146" +"CS_0304" "13" "Abalstel" 0 0 NA 0 "CS130304" +"CS_0305" "13" "Abalstel" 0 0 0 0 "CS130305" +"CS_0307" "13" "Abalstel" 0 0 0 0 "CS130307" +"CS_0308" "13" "Abalstel" 0 0 0 0 "CS130308" +"CS_0309" "13" "Abalstel" 0 0 NA 0 "CS130309" +"CS_0310" "13" "Abalstel" 0 0 NA 0 "CS130310" +"CS_0314" "13" "Abalstel" 0 0 0 0 "CS130314" +"CS_0315" "13" "Abalstel" 0 0 NA 0 "CS130315" +"CS_0316" "13" "Abalstel" 0 0 0 0 "CS130316" +"CS_0317" "13" "Abalstel" 0 0 0 0 "CS130317" +"CS_0318" "13" "Abalstel" 0 0 0 0 "CS130318" +"CS_0403" "13" "Abalstel" 0 0 0 0 "CS130403" +"CS_0404" "13" "Abalstel" 0 0 0 0 "CS130404" +"CS_0405" "13" "Abalstel" 0 0 NA 0 "CS130405" +"CS_0407" "13" "Abalstel" 0 0 0 0 "CS130407" +"CS_0900" "13" "Abalstel" 0 0 NA 0 "CS130900" +"CS_0904" "13" "Abalstel" 0 0 0 0 "CS130904" +"CS_0920" "13" "Abalstel" 0 0 NA 0 "CS130920" +"CS_0921" "13" "Abalstel" 0 0 0 0 "CS130921" +"CS_0922" "13" "Abalstel" 0 0 0 0 "CS130922" +"CS_0924" "13" "Abalstel" 0 0 NA 0 "CS130924" +"CS_0926" "13" "Abalstel" 0 0 NA 0 "CS130926" +"CS_0950" "13" "Abalstel" 0 0 0 0 "CS130950" +"CS_0951" "13" "Abalstel" 0 0 0 0 "CS130951" +"CS_0952" "13" "Abalstel" 0 0 NA 0 "CS130952" +"CS_0953" "13" "Abalstel" 0 0 0 0 "CS130953" +"CS_Z104" "13" "Abalstel" 0 0 0 0 "CS13Z104" +"CS_Z106" "13" "Abalstel" 0 0 0 0 "CS13Z106" +"EN_0001" "15" "Abalstel" 0 0 0 0 "EN150001" +"EN_0011" "15" "Abalstel" 0 0 NA 0 "EN150011" +"EN_0012" "15" "Abalstel" 0 0 0 0 "EN150012" +"EN_0023" "15" "Abalstel" 0 0 NA 0 "EN150023" +"EN_0027" "15" "Abalstel" 0 0 NA 0 "EN150027" +"EN_0028" "15" "Abalstel" 0 0 NA 0 "EN150028" +"EN_0030" "15" "Abalstel" 0 0 NA 0 "EN150030" +"EN_0032" "15" "Abalstel" 0 0 0 0 "EN150032" +"EN_0045" "15" "Abalstel" 0 0 0 0 "EN150045" +"EN_0060" "15" "Abalstel" 0 0 0 0 "EN150060" +"EN_0061" "15" "Abalstel" 0 0 0 0 "EN150061" +"EN_0066" "15" "Abalstel" 0 0 NA 0 "EN150066" +"EN_0087" "15" "Abalstel" 0 0 NA 0 "EN150087" +"EN_0090" "15" "Abalstel" 0 0 NA 0 "EN150090" +"EN_0094" "15" "Abalstel" 0 0 0 0 "EN150094" +"EN_0105" "15" "Abalstel" 0 0 0 0 "EN150105" +"EN_0108" "15" "Abalstel" 0 0 NA 0 "EN150108" +"EN_0115" "15" "Abalstel" 0 0 0 0 "EN150115" +"EN_0116" "15" "Abalstel" 0 0 0 0 "EN150116" +"EN_0119" "15" "Abalstel" 0 0 0 0 "EN150119" +"EN_0136" "15" "Abalstel" 0 0 0 0 "EN150136" +"EN_0137" "15" "Abalstel" 0 0 0 0 "EN150137" +"EN_0138" "15" "Abalstel" 0 0 0 0 "EN150138" +"EN_0139" "15" "Abalstel" 0 0 NA 0 "EN150139" +"EN_0140" "15" "Abalstel" 0 0 0 0 "EN150140" +"EN_0155" "15" "Abalstel" 0 0 0 0 "EN150155" +"EN_0202" "15" "Abalstel" 0 0 0 0 "EN150202" +"EN_0300" "15" "Abalstel" 0 0 0 0 "EN150300" +"EN_0301" "15" "Abalstel" 0 0 0 0 "EN150301" +"EN_0302" "15" "Abalstel" 0 0 0 0 "EN150302" +"EN_0305" "15" "Abalstel" 0 0 0 0 "EN150305" +"EN_0307" "15" "Abalstel" 0 0 0 0 "EN150307" +"EN_0309" "15" "Abalstel" 0 0 NA 0 "EN150309" +"EN_0311" "15" "Abalstel" 0 0 NA 0 "EN150311" +"EN_0313" "15" "Abalstel" 0 0 NA 0 "EN150313" +"EN_0350" "15" "Abalstel" 0 0 0 0 "EN150350" +"EN_0351" "15" "Abalstel" 0 0 0 0 "EN150351" +"EN_0352" "15" "Abalstel" 0 0 NA 0 "EN150352" +"EN_0400" "15" "Abalstel" 0 0 0 0 "EN150400" +"GN_0007" "13" "Abalstel" 0 0 NA 0 "GN130007" +"GN_0018" "13" "Abalstel" 0 0 0 0 "GN130018" +"GN_0030" "13" "Abalstel" 0 0 0 0 "GN130030" +"GN_0035" "13" "Abalstel" 0 0 NA 0 "GN130035" +"GN_0047" "13" "Abalstel" 0 0 0 0 "GN130047" +"GN_0058" "13" "Abalstel" 0 0 NA 0 "GN130058" +"GN_0060" "13" "Abalstel" 0 0 NA 0 "GN130060" +"GN_0066" "13" "Abalstel" 0 0 0 0 "GN130066" +"GN_0069" "13" "Abalstel" 0 0 0 0 "GN130069" +"GN_0091" "13" "Abalstel" 0 0 0 0 "GN130091" +"GN_0092" "13" "Abalstel" 0 0 NA 0 "GN130092" +"GN_0095" "13" "Abalstel" 8 8 NA 1 "GN130095" +"GN_0105" "13" "Abalstel" 8 8 NA 1 "GN130105" +"GN_0108" "13" "Abalstel" 0 0 NA 0 "GN130108" +"GN_0114" "13" "Abalstel" 0 0 NA 0 "GN130114" +"GN_0121" "13" "Abalstel" 0 0 NA 0 "GN130121" +"GN_0131" "13" "Abalstel" 0 0 NA 0 "GN130131" +"GN_0132" "13" "Abalstel" 0 0 0 0 "GN130132" +"GN_0135" "13" "Abalstel" 0 0 NA 0 "GN130135" +"GN_0139" "13" "Abalstel" 0 0 0 0 "GN130139" +"GN_0142" "13" "Abalstel" 0 0 NA 0 "GN130142" +"GN_0148" "13" "Abalstel" 0 0 0 0 "GN130148" +"GN_0152" "13" "Abalstel" 0 0 0 0 "GN130152" +"GN_0163" "13" "Abalstel" 0 0 0 0 "GN130163" +"GN_0164" "13" "Abalstel" 0 0 0 0 "GN130164" +"GN_0179" "13" "Abalstel" 0 0 NA 0 "GN130179" +"GN_0181" "13" "Abalstel" 0 0 0 0 "GN130181" +"GN_0185" "13" "Abalstel" 0 0 NA 0 "GN130185" +"GN_0190" "13" "Abalstel" 0 0 NA 0 "GN130190" +"GN_0192" "13" "Abalstel" 0 0 0 0 "GN130192" +"GN_0209" "13" "Abalstel" 0 0 0 0 "GN130209" +"GN_0223" "13" "Abalstel" 0 0 0 0 "GN130223" +"GN_0224" "13" "Abalstel" 0 0 NA 0 "GN130224" +"GN_0512" "13" "Abalstel" 0 0 0 0 "GN130512" +"GN_0513" "13" "Abalstel" 0 0 NA 0 "GN130513" +"HI_0001" "12" "Abalstel" 0 0 0 0 "HI120001" +"HI_0002" "12" "Abalstel" 0 0 NA 0 "HI120002" +"HI_0016" "12" "Abalstel" 0 0 0 0 "HI120016" +"HI_0018" "12" "Abalstel" 0 0 0 0 "HI120018" +"HI_0023" "12" "Abalstel" 0 0 0 0 "HI120023" +"HI_0024" "12" "Abalstel" 0 0 0 0 "HI120024" +"HI_0025" "12" "Abalstel" 0 0 0 0 "HI120025" +"HI_0026" "12" "Abalstel" 0 0 0 0 "HI120026" +"HI_0029" "12" "Abalstel" 0 0 NA 0 "HI120029" +"HI_0030" "12" "Abalstel" 0 0 0 0 "HI120030" +"HI_0042" "12" "Abalstel" 0 0 NA 0 "HI120042" +"HI_0046" "12" "Abalstel" 0 0 0 0 "HI120046" +"HI_0058" "12" "Abalstel" 0 0 NA 0 "HI120058" +"HI_0060" "12" "Abalstel" 0 0 NA 0 "HI120060" +"HI_0070" "12" "Abalstel" 0 0 NA 0 "HI120070" +"HI_0086" "12" "Abalstel" 0 0 NA 0 "HI120086" +"HI_0099" "12" "Abalstel" 0 0 0 0 "HI120099" +"HI_0149" "12" "Abalstel" 0 0 NA 0 "HI120149" +"HI_0156" "12" "Abalstel" 0 0 0 0 "HI120156" +"HI_0171" "12" "Abalstel" 0 0 0 0 "HI120171" +"HI_0172" "12" "Abalstel" 0 0 NA 0 "HI120172" +"HI_0173" "12" "Abalstel" 0 0 0 0 "HI120173" +"HI_0175" "12" "Abalstel" 0 0 0 0 "HI120175" +"HI_0201" "12" "Abalstel" 0 0 NA 0 "HI120201" +"HI_0204" "12" "Abalstel" 0 0 NA 0 "HI120204" +"HI_0205" "12" "Abalstel" 0 0 NA 0 "HI120205" +"HI_0210" "12" "Abalstel" 0 0 NA 0 "HI120210" +"HI_0211" "12" "Abalstel" 0 0 NA 0 "HI120211" +"HU_0031" "14" "Abalstel" 0 0 NA 0 "HU140031" +"HU_0035" "14" "Abalstel" 0 0 0 0 "HU140035" +"KO_0156" "07" "Abalstel" 0 0 0 0 "KO070156" +"KO_0022" "08" "Abalstel" 0 0 NA 0 "KO080022" +"KO_0024" "08" "Abalstel" 0 0 0 0 "KO080024" +"KO_0033" "08" "Abalstel" 0 0 0 0 "KO080033" +"KO_0183" "08" "Abalstel" 0 0 0 0 "KO080183" +"KO_0003" "13" "Abalstel" 0 0 NA 0 "KO130003" +"KO_0005" "13" "Abalstel" 0 0 NA 0 "KO130005" +"KO_0010" "13" "Abalstel" 0 0 NA 0 "KO130010" +"KO_0013" "13" "Abalstel" 0 0 0 0 "KO130013" +"KO_0031" "13" "Abalstel" 0 0 0 0 "KO130031" +"KO_0035" "13" "Abalstel" 0 0 0 0 "KO130035" +"KO_0041" "13" "Abalstel" 0 0 NA 0 "KO130041" +"KO_0053" "13" "Abalstel" 0 0 NA 0 "KO130053" +"KO_0059" "13" "Abalstel" 0 0 0 0 "KO130059" +"KO_0070" "13" "Abalstel" 0 0 NA 0 "KO130070" +"KO_0071" "13" "Abalstel" 0 0 NA 0 "KO130071" +"KO_0089" "13" "Abalstel" 0 0 NA 0 "KO130089" +"KO_0097" "13" "Abalstel" 0 0 0 0 "KO130097" +"KO_0098" "13" "Abalstel" 0 0 0 0 "KO130098" +"KO_0099" "13" "Abalstel" 0 0 0 0 "KO130099" +"KO_0101" "13" "Abalstel" 0 0 0 0 "KO130101" +"KO_0108" "13" "Abalstel" 0 0 0 0 "KO130108" +"KO_0110" "13" "Abalstel" 0 0 0 0 "KO130110" +"KO_0112" "13" "Abalstel" 0 0 0 0 "KO130112" +"KO_0113" "13" "Abalstel" 0 0 0 0 "KO130113" +"KO_0120" "13" "Abalstel" 0 0 NA 0 "KO130120" +"KO_0129" "13" "Abalstel" 0 0 NA 0 "KO130129" +"KO_0130" "13" "Abalstel" 0 0 0 0 "KO130130" +"KO_0131" "13" "Abalstel" 0 0 0 0 "KO130131" +"KO_0132" "13" "Abalstel" 0 0 NA 0 "KO130132" +"KO_0133" "13" "Abalstel" 0 0 0 0 "KO130133" +"KO_0138" "13" "Abalstel" 0 0 0 0 "KO130138" +"KO_0139" "13" "Abalstel" 0 0 0 0 "KO130139" +"KO_0147" "13" "Abalstel" 0 0 0 0 "KO130147" +"KO_0148" "13" "Abalstel" 0 0 0 0 "KO130148" +"KO_0154" "13" "Abalstel" 0 0 NA 0 "KO130154" +"KO_0160" "13" "Abalstel" 0 0 NA 0 "KO130160" +"KO_0165" "13" "Abalstel" 0 0 0 0 "KO130165" +"KO_0174" "13" "Abalstel" 0 0 NA 0 "KO130174" +"KO_0176" "13" "Abalstel" 0 0 0 0 "KO130176" +"KO_0177" "13" "Abalstel" 0 0 0 0 "KO130177" +"KO_0202" "13" "Abalstel" 0 0 0 0 "KO130202" +"KO_0203" "13" "Abalstel" 0 0 0 0 "KO130203" +"KO_0204" "13" "Abalstel" 0 0 NA 0 "KO130204" +"KO_0205" "13" "Abalstel" 0 0 0 0 "KO130205" +"KO_0208" "13" "Abalstel" 0 0 0 0 "KO130208" +"KO_0209" "13" "Abalstel" 0 0 NA 0 "KO130209" +"KO_0301" "13" "Abalstel" 0 0 0 0 "KO130301" +"KO_0302" "13" "Abalstel" 0 0 0 0 "KO130302" +"KO_0304" "13" "Abalstel" 0 0 NA 0 "KO130304" +"KO_0305" "13" "Abalstel" 0 0 0 0 "KO130305" +"KO_059b" "13" "Abalstel" 0 0 0 0 "KO13059b" +"LA_101B" "08" "Abalstel" 0 0 0 0 "LA08101B" +"LA_0012" "10" "Abalstel" 0 0 NA 0 "LA100012" +"LA_0028" "10" "Abalstel" 0 0 NA 0 "LA100028" +"LA_0039" "10" "Abalstel" 0 0 0 0 "LA100039" +"LI_0021" "14" "Abalstel" 0 0 0 0 "LI140021" +"LI_0022" "14" "Abalstel" 0 0 0 0 "LI140022" +"LI_0028" "14" "Abalstel" 0 0 0 0 "LI140028" +"LI_0033" "14" "Abalstel" 0 0 0 0 "LI140033" +"LI_0035" "14" "Abalstel" 0 0 NA 0 "LI140035" +"LI_0064" "14" "Abalstel" 0 0 NA 0 "LI140064" +"LI_0067" "14" "Abalstel" 0 0 NA 0 "LI140067" +"LI_0073" "14" "Abalstel" 0 0 0 0 "LI140073" +"LI_0077" "14" "Abalstel" 0 0 NA 0 "LI140077" +"LI_0081" "14" "Abalstel" 0 0 0 0 "LI140081" +"LI_0082" "14" "Abalstel" 0 0 NA 0 "LI140082" +"LI_0083" "14" "Abalstel" 0 0 0 0 "LI140083" +"LI_0086" "14" "Abalstel" 0 0 0 0 "LI140086" +"LI_0089" "14" "Abalstel" 0 0 0 0 "LI140089" +"LI_0093" "14" "Abalstel" 0 0 NA 0 "LI140093" +"LI_0094" "14" "Abalstel" 0 0 NA 0 "LI140094" +"LI_0096" "14" "Abalstel" 0 0 0 0 "LI140096" +"LI_0100" "14" "Abalstel" 0 0 0 0 "LI140100" +"LI_0102" "14" "Abalstel" 0 0 0 0 "LI140102" +"LI_0103" "14" "Abalstel" 0 0 0 0 "LI140103" +"LI_0104" "14" "Abalstel" 0 0 0 0 "LI140104" +"LI_0110" "14" "Abalstel" 0 0 NA 0 "LI140110" +"LI_0111" "14" "Abalstel" 0 0 0 0 "LI140111" +"LI_0113" "14" "Abalstel" 0 0 0 0 "LI140113" +"LI_0114" "14" "Abalstel" 0 0 0 0 "LI140114" +"LI_0121" "14" "Abalstel" 0 0 0 0 "LI140121" +"LI_0122" "14" "Abalstel" 0 0 NA 0 "LI140122" +"LI_0129" "14" "Abalstel" 0 0 0 0 "LI140129" +"LI_0149" "14" "Abalstel" 0 0 0 0 "LI140149" +"LI_0150" "14" "Abalstel" 0 0 0 0 "LI140150" +"LI_0151" "14" "Abalstel" 0 0 0 0 "LI140151" +"LI_0152" "14" "Abalstel" 0 0 0 0 "LI140152" +"LI_0305" "14" "Abalstel" 0 0 NA 0 "LI140305" +"LI_0307" "14" "Abalstel" 0 0 NA 0 "LI140307" +"LI_0401" "14" "Abalstel" 0 0 0 0 "LI140401" +"ME_0004" "13" "Abalstel" 0 0 0 0 "ME130004" +"ME_0018" "13" "Abalstel" 0 0 0 0 "ME130018" +"ME_0022" "13" "Abalstel" 0 0 0 0 "ME130022" +"ME_0034" "13" "Abalstel" 0 0 NA 0 "ME130034" +"ME_0036" "13" "Abalstel" 0 0 NA 0 "ME130036" +"ME_0046" "13" "Abalstel" 0 0 0 0 "ME130046" +"ME_0049" "13" "Abalstel" 0 0 0 0 "ME130049" +"ME_0050" "13" "Abalstel" 0 0 0 0 "ME130050" +"ME_0053" "13" "Abalstel" 0 0 0 0 "ME130053" +"ME_0054" "13" "Abalstel" 0 0 0 0 "ME130054" +"ME_0063" "13" "Abalstel" 0 0 0 0 "ME130063" +"ME_0066" "13" "Abalstel" 0 0 0 0 "ME130066" +"ME_0071" "13" "Abalstel" 0 0 0 0 "ME130071" +"ME_0073" "13" "Abalstel" 0 0 0 0 "ME130073" +"ME_0074" "13" "Abalstel" 0 0 0 0 "ME130074" +"ME_0075" "13" "Abalstel" 0 0 0 0 "ME130075" +"ME_0089" "13" "Abalstel" 0 0 0 0 "ME130089" +"ME_0090" "13" "Abalstel" 0 0 0 0 "ME130090" +"ME_0096" "13" "Abalstel" 0 0 NA 0 "ME130096" +"ME_0099" "13" "Abalstel" 0 0 0 0 "ME130099" +"ME_00F1" "13" "Abalstel" 0 0 0 0 "ME1300F1" +"ME_00F3" "13" "Abalstel" 0 0 0 0 "ME1300F3" +"ME_00F4" "13" "Abalstel" 0 0 NA 0 "ME1300F4" +"ME_00F5" "13" "Abalstel" 0 0 NA 0 "ME1300F5" +"ME_0101" "13" "Abalstel" 0 0 0 0 "ME130101" +"ME_0105" "13" "Abalstel" 0 0 0 0 "ME130105" +"ME_0106" "13" "Abalstel" 0 0 0 0 "ME130106" +"ME_0107" "13" "Abalstel" 0 0 0 0 "ME130107" +"ME_0108" "13" "Abalstel" 0 0 0 0 "ME130108" +"ME_0111" "13" "Abalstel" 0 0 0 0 "ME130111" +"ME_0115" "13" "Abalstel" 0 0 NA 0 "ME130115" +"ME_0116" "13" "Abalstel" 0 0 0 0 "ME130116" +"ME_0117" "13" "Abalstel" 0 0 0 0 "ME130117" +"ME_0120" "13" "Abalstel" 0 0 0 0 "ME130120" +"ME_0121" "13" "Abalstel" 0 0 0 0 "ME130121" +"ME_0124" "13" "Abalstel" 0 0 0 0 "ME130124" +"ME_0126" "13" "Abalstel" 0 0 0 0 "ME130126" +"ME_0128" "13" "Abalstel" 0 0 0 0 "ME130128" +"ME_0129" "13" "Abalstel" 0 0 NA 0 "ME130129" +"ME_0135" "13" "Abalstel" 0 0 NA 0 "ME130135" +"ME_0137" "13" "Abalstel" 0 0 0 0 "ME130137" +"ME_0154" "13" "Abalstel" 0 0 NA 0 "ME130154" +"ME_0160" "13" "Abalstel" 0 0 0 0 "ME130160" +"ME_0170" "13" "Abalstel" 0 0 NA 0 "ME130170" +"ME_0171" "13" "Abalstel" 0 0 NA 0 "ME130171" +"ME_0173" "13" "Abalstel" 0 0 NA 0 "ME130173" +"ME_0179" "13" "Abalstel" 0 0 NA 0 "ME130179" +"ME_0190" "13" "Abalstel" 0 0 0 0 "ME130190" +"ME_0207" "13" "Abalstel" 0 0 NA 0 "ME130207" +"ME_0208" "13" "Abalstel" 0 0 0 0 "ME130208" +"ME_0209" "13" "Abalstel" 0 0 0 0 "ME130209" +"ME_0210" "13" "Abalstel" 0 0 0 0 "ME130210" +"ME_0212" "13" "Abalstel" 0 0 NA 0 "ME130212" +"ME_0213" "13" "Abalstel" 0 0 NA 0 "ME130213" +"ME_0215" "13" "Abalstel" 0 0 0 0 "ME130215" +"ME_0241" "13" "Abalstel" 0 0 NA 0 "ME130241" +"ME_0246" "13" "Abalstel" 0 0 NA 0 "ME130246" +"ME_0248" "13" "Abalstel" 0 0 0 0 "ME130248" +"ME_0252" "13" "Abalstel" 0 0 0 0 "ME130252" +"ME_0260" "13" "Abalstel" 0 0 0 0 "ME130260" +"ME_0262" "13" "Abalstel" 0 0 0 0 "ME130262" +"ME_0265" "13" "Abalstel" 0 0 NA 0 "ME130265" +"ME_0266" "13" "Abalstel" 0 0 0 0 "ME130266" +"ME_0267" "13" "Abalstel" 0 0 NA 0 "ME130267" +"ME_0268" "13" "Abalstel" 0 0 0 0 "ME130268" +"ME_0273" "13" "Abalstel" 0 0 NA 0 "ME130273" +"ME_0400" "13" "Abalstel" 0 0 0 0 "ME130400" +"ME_0402" "13" "Abalstel" 0 0 NA 0 "ME130402" +"ME_0403" "13" "Abalstel" 0 0 0 0 "ME130403" +"ME_102PM" "13" "Abalstel" 0 0 0 0 "ME13102PM" +"ME_168PM" "13" "Abalstel" 0 0 NA 0 "ME13168PM" +"ME_47PM" "13" "Abalstel" 0 0 0 0 "ME1347PM" +"MK_0425" "08" "Abalstel" 0 0 0 0 "MK080425" +"MK_0426" "08" "Abalstel" 0 0 NA 0 "MK080426" +"MK_0427" "08" "Abalstel" 0 0 0 0 "MK080427" +"MK_0430" "08" "Abalstel" 0 0 NA 0 "MK080430" +"MK_0440" "08" "Abalstel" 0 0 0 0 "MK080440" +"MK_0453" "08" "Abalstel" 0 0 0 0 "MK080453" +"MK_0454" "08" "Abalstel" 0 0 0 0 "MK080454" +"MK_0458" "08" "Abalstel" 0 0 NA 0 "MK080458" +"MK_0462" "08" "Abalstel" 0 0 0 0 "MK080462" +"MK_0207" "09" "Abalstel" 0 0 0 0 "MK090207" +"MK_0208" "09" "Abalstel" 0 0 0 0 "MK090208" +"MK_0211" "09" "Abalstel" 0 0 0 0 "MK090211" +"MK_0225" "09" "Abalstel" 0 0 0 0 "MK090225" +"MK_0227" "09" "Abalstel" 0 0 0 0 "MK090227" +"MK_0228" "09" "Abalstel" 0 0 0 0 "MK090228" +"MK_0231" "09" "Abalstel" 0 0 NA 0 "MK090231" +"MK_0234" "09" "Abalstel" 0 0 NA 0 "MK090234" +"MK_0248" "09" "Abalstel" 0 0 0 0 "MK090248" +"MK_0249" "09" "Abalstel" 0 0 NA 0 "MK090249" +"MK_0250" "09" "Abalstel" 0 0 NA 0 "MK090250" +"MK_0200" "10" "Abalstel" 0 0 0 0 "MK100200" +"MK_0205" "10" "Abalstel" 0 0 NA 0 "MK100205" +"MK_0206" "10" "Abalstel" 0 0 NA 0 "MK100206" +"MK_0210" "10" "Abalstel" 0 0 0 0 "MK100210" +"MK_0213" "10" "Abalstel" 0 0 0 0 "MK100213" +"MK_0215" "10" "Abalstel" 0 0 0 0 "MK100215" +"MK_0219" "10" "Abalstel" 0 0 0 0 "MK100219" +"MK_0221" "10" "Abalstel" 0 0 NA 0 "MK100221" +"MK_0230" "10" "Abalstel" 0 0 0 0 "MK100230" +"MK_0231" "10" "Abalstel" 0 0 0 0 "MK100231" +"MK_0234" "10" "Abalstel" 0 0 0 0 "MK100234" +"MK_0240" "10" "Abalstel" 0 0 0 0 "MK100240" +"MK_0249" "10" "Abalstel" 0 0 0 0 "MK100249" +"OU_0002" "09" "Abalstel" 0 0 0 0 "OU090002" +"OU_0005" "09" "Abalstel" 1 1 NA 1 "OU090005" +"OU_0006" "09" "Abalstel" 1 1 NA 1 "OU090006" +"OU_0020" "09" "Abalstel" 1 1 NA 1 "OU090020" +"OU_0025" "09" "Abalstel" 0 0 0 0 "OU090025" +"OU_0061" "09" "Abalstel" 0 0 NA 0 "OU090061" +"OU_0108" "09" "Abalstel" 0 0 NA 0 "OU090108" +"OU_0116" "09" "Abalstel" 0 0 NA 0 "OU090116" +"OU_0123" "09" "Abalstel" 0 0 0 0 "OU090123" +"OU_0L13" "09" "Abalstel" 0 0 0 0 "OU090L13" +"OU_0L14" "09" "Abalstel" 0 0 0 0 "OU090L14" +"OU_0L22" "09" "Abalstel" 0 0 NA 0 "OU090L22" +"OU_0L51" "09" "Abalstel" 0 0 NA 0 "OU090L51" +"OU_0L52" "09" "Abalstel" 0 0 0 0 "OU090L52" +"OU_0L82" "09" "Abalstel" 0 0 NA 0 "OU090L82" +"OU_106C" "09" "Abalstel" 0 0 0 0 "OU09106C" +"OU_107C" "09" "Abalstel" 0 0 0 0 "OU09107C" +"OU_123B" "09" "Abalstel" 0 0 0 0 "OU09123B" +"OU_129B" "09" "Abalstel" 0 0 0 0 "OU09129B" +"OU_L12R" "09" "Abalstel" 0 0 0 0 "OU09L12R" +"OU_L14R" "09" "Abalstel" 0 0 0 0 "OU09L14R" +"OU_L22R" "09" "Abalstel" 0 0 0 0 "OU09L22R" +"OU_L36R" "09" "Abalstel" 0 0 0 0 "OU09L36R" +"OU_L51R" "09" "Abalstel" 0 0 0 0 "OU09L51R" +"OU_L52R" "09" "Abalstel" 0 0 0 0 "OU09L52R" +"PA_0004" "17" "Abalstel" 0 0 NA 0 "PA170004" +"PA_0005" "17" "Abalstel" 0 0 0 0 "PA170005" +"PA_0010" "17" "Abalstel" 0 0 NA 0 "PA170010" +"PA_0011" "17" "Abalstel" 0 0 0 0 "PA170011" +"PA_0012" "17" "Abalstel" 0 0 NA 0 "PA170012" +"PA_0013" "17" "Abalstel" 0 0 0 0 "PA170013" +"PA_0014" "17" "Abalstel" 0 0 0 0 "PA170014" +"PA_0015" "17" "Abalstel" 0 0 NA 0 "PA170015" +"PA_0016" "17" "Abalstel" 0 0 0 0 "PA170016" +"PA_0017" "17" "Abalstel" 0 0 0 0 "PA170017" +"PA_0018" "17" "Abalstel" 0 0 0 0 "PA170018" +"PA_0020" "17" "Abalstel" 0 0 NA 0 "PA170020" +"PA_0022" "17" "Abalstel" 0 0 0 0 "PA170022" +"PA_0025" "17" "Abalstel" 0 0 NA 0 "PA170025" +"PA_0027" "17" "Abalstel" 0 0 0 0 "PA170027" +"PA_0030" "17" "Abalstel" 0 0 NA 0 "PA170030" +"PA_0039" "17" "Abalstel" 0 0 0 0 "PA170039" +"PA_0041" "17" "Abalstel" 0 0 0 0 "PA170041" +"PA_0042" "17" "Abalstel" 0 0 0 0 "PA170042" +"PA_0043" "17" "Abalstel" 0 0 0 0 "PA170043" +"PA_0044" "17" "Abalstel" 0 0 NA 0 "PA170044" +"PA_0050" "17" "Abalstel" 0 0 0 0 "PA170050" +"PA_0051" "17" "Abalstel" 0 0 0 0 "PA170051" +"PA_0054" "17" "Abalstel" 0 0 NA 0 "PA170054" +"PA_0055" "17" "Abalstel" 0 0 NA 0 "PA170055" +"PA_0056" "17" "Abalstel" 0 0 0 0 "PA170056" +"PA_0057" "17" "Abalstel" 0 0 0 0 "PA170057" +"PA_0058" "17" "Abalstel" 0 0 0 0 "PA170058" +"PA_0059" "17" "Abalstel" 0 0 NA 0 "PA170059" +"PA_0060" "17" "Abalstel" 0 0 0 0 "PA170060" +"PA_0066" "17" "Abalstel" 0 0 NA 0 "PA170066" +"PA_0068" "17" "Abalstel" 0 0 0 0 "PA170068" +"PA_0074" "17" "Abalstel" 0 0 NA 0 "PA170074" +"PA_0079" "17" "Abalstel" 0 0 NA 0 "PA170079" +"PA_0080" "17" "Abalstel" 0 0 0 0 "PA170080" +"PA_0081" "17" "Abalstel" 0 0 0 0 "PA170081" +"PA_0083" "17" "Abalstel" 0 0 NA 0 "PA170083" +"PA_0084" "17" "Abalstel" 0 0 0 0 "PA170084" +"PA_0088" "17" "Abalstel" 0 0 0 0 "PA170088" +"PA_0091" "17" "Abalstel" 0 0 0 0 "PA170091" +"PA_0093" "17" "Abalstel" 0 0 0 0 "PA170093" +"PA_0094" "17" "Abalstel" 0 0 NA 0 "PA170094" +"PA_0100" "17" "Abalstel" 0 0 NA 0 "PA170100" +"PE_0007" "14" "Abalstel" 0 0 0 0 "PE140007" +"PE_0025" "14" "Abalstel" 0 0 NA 0 "PE140025" +"PE_0029" "14" "Abalstel" 0 0 NA 0 "PE140029" +"PE_0031" "14" "Abalstel" 0 0 0 0 "PE140031" +"PE_0033" "14" "Abalstel" 0 0 0 0 "PE140033" +"PE_0035" "14" "Abalstel" 0 0 0 0 "PE140035" +"PO_0001" "12" "Abalstel" 0 0 NA 0 "PO120001" +"PO_0004" "12" "Abalstel" 0 0 0 0 "PO120004" +"PO_0007" "12" "Abalstel" 0 0 0 0 "PO120007" +"PO_0018" "12" "Abalstel" 0 0 NA 0 "PO120018" +"PO_0028" "12" "Abalstel" 0 0 0 0 "PO120028" +"PO_0045" "12" "Abalstel" 0 0 0 0 "PO120045" +"PO_0048" "12" "Abalstel" 0 0 NA 0 "PO120048" +"PO_0053" "12" "Abalstel" 0 0 0 0 "PO120053" +"PO_0066" "12" "Abalstel" 0 0 0 0 "PO120066" +"PO_0092" "12" "Abalstel" 0 0 0 0 "PO120092" +"PO_0094" "12" "Abalstel" 0 0 0 0 "PO120094" +"PO_0096" "12" "Abalstel" 0 0 0 0 "PO120096" +"PO_0121" "12" "Abalstel" 0 0 0 0 "PO120121" +"PO_0134" "12" "Abalstel" 0 0 NA 0 "PO120134" +"PO_0136" "12" "Abalstel" 0 0 NA 0 "PO120136" +"PO_0200" "12" "Abalstel" 0 0 NA 0 "PO120200" +"PO_0203" "12" "Abalstel" 0 0 0 0 "PO120203" +"PO_0205" "12" "Abalstel" 0 0 NA 0 "PO120205" +"PO_0206" "12" "Abalstel" 0 0 0 0 "PO120206" +"PO_0233" "12" "Abalstel" 0 0 NA 0 "PO120233" +"RD_0219" "07" "Abalstel" 1 1 0 1 "RD070219" +"RD_0230" "07" "Abalstel" 1 1 NA 1 "RD070230" +"RD_0031" "08" "Abalstel" 2 2 NA 1 "RD080031" +"RD_0103" "09" "Abalstel" 1 1 NA 1 "RD090103" +"RD_0105" "09" "Abalstel" 1 1 NA 1 "RD090105" +"RD_0108" "09" "Abalstel" 1 1 NA 1 "RD090108" +"RD_0109" "09" "Abalstel" 1 1 NA 1 "RD090109" +"RD_0107" "10" "Abalstel" 1 1 NA 1 "RD100107" +"RL_0250" "07" "Abalstel" 0 0 NA 0 "RL070250" +"RL_0145" "08" "Abalstel" 0 0 0 0 "RL080145" +"RL_0078" "09" "Abalstel" 0 0 0 0 "RL090078" +"RL_0089" "09" "Abalstel" 0 0 0 0 "RL090089" +"RL_0093" "09" "Abalstel" 0 0 0 0 "RL090093" +"RL_0066" "10" "Abalstel" 0 0 NA 0 "RL100066" +"RL_0076" "10" "Abalstel" 0 0 0 0 "RL100076" +"RS_0169" "07" "Abalstel" 0 0 0 0 "RS070169" +"RS_0189" "07" "Abalstel" 0 0 0 0 "RS070189" +"SI_0078" "07" "Abalstel" 0 0 NA 0 "SI070078" +"SI_0079" "07" "Abalstel" 0 0 0 0 "SI070079" +"SI_0080" "07" "Abalstel" 0 0 0 0 "SI070080" +"SI_0082" "07" "Abalstel" 1 1 NA 1 "SI070082" +"SI_0197" "07" "Abalstel" 1 1 NA 1 "SI070197" +"SI_0222" "07" "Abalstel" 1 1 NA 1 "SI070222" +"SI_0194" "08" "Abalstel" 1 1 0 1 "SI080194" +"WA_0002" "14" "Abalstel" 0 0 0 0 "WA140002" +"AB_0008" "08" "Hemifasc" 0 0 0 0 "AB080008" +"AB_0015" "08" "Hemifasc" 0 0 0 0 "AB080015" +"AB_0027" "08" "Hemifasc" 0 0 0 0 "AB080027" +"AB_0031" "08" "Hemifasc" 0 0 0 0 "AB080031" +"AB_0037" "08" "Hemifasc" 0 0 NA 0 "AB080037" +"AB_0042" "08" "Hemifasc" 0 0 NA 0 "AB080042" +"AB_0057" "08" "Hemifasc" 0 0 0 0 "AB080057" +"AB_0076" "09" "Hemifasc" 0 0 0 0 "AB090076" +"AB_0081" "09" "Hemifasc" 0 0 0 0 "AB090081" +"AB_0095" "09" "Hemifasc" 0 0 0 0 "AB090095" +"AB_0097" "09" "Hemifasc" 0 0 0 0 "AB090097" +"AB_0098" "09" "Hemifasc" 0 0 NA 0 "AB090098" +"AB_0104" "09" "Hemifasc" 0 0 0 0 "AB090104" +"AB_0105" "09" "Hemifasc" 0 0 0 0 "AB090105" +"AB_0106" "09" "Hemifasc" 0 0 NA 0 "AB090106" +"AB_0120" "09" "Hemifasc" 0 0 NA 0 "AB090120" +"AB_0121" "09" "Hemifasc" 0 0 0 0 "AB090121" +"AB_0122" "09" "Hemifasc" 0 0 0 0 "AB090122" +"AB_0123" "09" "Hemifasc" 0 0 0 0 "AB090123" +"AB_0124" "09" "Hemifasc" 0 0 NA 0 "AB090124" +"AB_0125" "09" "Hemifasc" 0 0 0 0 "AB090125" +"AB_0126" "09" "Hemifasc" 0 0 0 0 "AB090126" +"AB_0127" "09" "Hemifasc" 0 0 0 0 "AB090127" +"AB_0132" "09" "Hemifasc" 0 0 NA 0 "AB090132" +"AB_0133" "09" "Hemifasc" 0 0 0 0 "AB090133" +"AB_0134" "09" "Hemifasc" 0 0 0 0 "AB090134" +"AB_0135" "09" "Hemifasc" 0 0 0 0 "AB090135" +"AB_0143" "09" "Hemifasc" 0 0 NA 0 "AB090143" +"AB_0148" "09" "Hemifasc" 0 0 NA 0 "AB090148" +"AB_0149" "09" "Hemifasc" 0 0 0 0 "AB090149" +"AB_0151" "09" "Hemifasc" 0 0 0 0 "AB090151" +"AB_0601" "09" "Hemifasc" 0 0 0 0 "AB090601" +"AB_0602" "09" "Hemifasc" 0.333333333333333 1 0.577350269189626 1 "AB090602" +"AB_0603" "09" "Hemifasc" 0 0 NA 0 "AB090603" +"AB_0001" "10" "Hemifasc" 0 0 NA 0 "AB100001" +"AB_0002" "10" "Hemifasc" 0 0 0 0 "AB100002" +"AB_0006" "10" "Hemifasc" 0 0 0 0 "AB100006" +"AB_0008" "10" "Hemifasc" 0 0 0 0 "AB100008" +"AB_0009" "10" "Hemifasc" 0 0 0 0 "AB100009" +"AB_0010" "10" "Hemifasc" 0 0 0 0 "AB100010" +"AB_0011" "10" "Hemifasc" 0 0 0 0 "AB100011" +"AB_0015" "10" "Hemifasc" 0 0 0 0 "AB100015" +"AB_0017" "10" "Hemifasc" 0 0 0 0 "AB100017" +"AB_0019" "10" "Hemifasc" 0 0 0 0 "AB100019" +"AB_0020" "10" "Hemifasc" 0 0 0 0 "AB100020" +"AB_0021" "10" "Hemifasc" 0 0 0 0 "AB100021" +"AB_0023" "10" "Hemifasc" 0 0 0 0 "AB100023" +"AB_0024" "10" "Hemifasc" 0 0 0 0 "AB100024" +"AB_0025" "10" "Hemifasc" 0 0 0 0 "AB100025" +"AB_0028" "10" "Hemifasc" 0 0 0 0 "AB100028" +"AB_0029" "10" "Hemifasc" 0.333333333333333 1 0.577350269189626 1 "AB100029" +"AB_0031" "10" "Hemifasc" 1 1 0 1 "AB100031" +"AB_0035" "10" "Hemifasc" 0 0 NA 0 "AB100035" +"AB_0036" "10" "Hemifasc" 0 0 0 0 "AB100036" +"AB_0038" "10" "Hemifasc" 0 0 0 0 "AB100038" +"AB_0042" "10" "Hemifasc" 0 0 0 0 "AB100042" +"AB_0046" "10" "Hemifasc" 0 0 0 0 "AB100046" +"AB_0047" "10" "Hemifasc" 0 0 0 0 "AB100047" +"AB_0048" "10" "Hemifasc" 0 0 0 0 "AB100048" +"AB_0049" "10" "Hemifasc" 0 0 0 0 "AB100049" +"AB_0052" "10" "Hemifasc" 0 0 0 0 "AB100052" +"AB_0055" "10" "Hemifasc" 0 0 NA 0 "AB100055" +"AB_0060" "10" "Hemifasc" 0 0 0 0 "AB100060" +"AB_0061" "10" "Hemifasc" 0 0 0 0 "AB100061" +"AB_0062" "10" "Hemifasc" 0.666666666666667 1 0.577350269189626 1 "AB100062" +"AB_0072" "10" "Hemifasc" 0 0 NA 0 "AB100072" +"AB_0077" "10" "Hemifasc" 0 0 NA 0 "AB100077" +"AB_0078" "10" "Hemifasc" 0 0 NA 0 "AB100078" +"AB_0079" "10" "Hemifasc" 0 0 0 0 "AB100079" +"AB_0081" "10" "Hemifasc" 0 0 0 0 "AB100081" +"AB_0082" "10" "Hemifasc" 0 0 NA 0 "AB100082" +"AB_0085" "10" "Hemifasc" 0 0 0 0 "AB100085" +"AB_0086" "10" "Hemifasc" 0 0 0 0 "AB100086" +"AB_0087" "10" "Hemifasc" 0 0 0 0 "AB100087" +"AB_0088" "10" "Hemifasc" 0 0 0 0 "AB100088" +"AB_0089" "10" "Hemifasc" 0 0 NA 0 "AB100089" +"AB_0090" "10" "Hemifasc" 0 0 0 0 "AB100090" +"AB_0091" "10" "Hemifasc" 0 0 0 0 "AB100091" +"AB_0092" "10" "Hemifasc" 0 0 0 0 "AB100092" +"AB_0093" "10" "Hemifasc" 0 0 0 0 "AB100093" +"AB_0094" "10" "Hemifasc" 0 0 0 0 "AB100094" +"AB_0095" "10" "Hemifasc" 1 1 NA 1 "AB100095" +"AB_0096" "10" "Hemifasc" 0 0 0 0 "AB100096" +"AB_0097" "10" "Hemifasc" 0 0 0 0 "AB100097" +"AB_0098" "10" "Hemifasc" 0 0 NA 0 "AB100098" +"AB_0099" "10" "Hemifasc" 0 0 0 0 "AB100099" +"AB_0111" "10" "Hemifasc" 0 0 0 0 "AB100111" +"AB_0112" "10" "Hemifasc" 0 0 0 0 "AB100112" +"AB_0119" "10" "Hemifasc" 0 0 NA 0 "AB100119" +"AB_0124" "10" "Hemifasc" 0 0 0 0 "AB100124" +"AB_0131" "10" "Hemifasc" 0 0 0 0 "AB100131" +"AB_0132" "10" "Hemifasc" 0.666666666666667 1 0.577350269189626 1 "AB100132" +"AS_0048" "14" "Hemifasc" 0 0 0 0 "AS140048" +"AS_0054" "14" "Hemifasc" 0 0 0 0 "AS140054" +"AS_0059" "14" "Hemifasc" 0 0 0 0 "AS140059" +"AS_0060" "14" "Hemifasc" 0 0 0 0 "AS140060" +"AS_0061" "14" "Hemifasc" 0 0 0 0 "AS140061" +"AS_0070" "14" "Hemifasc" 0 0 NA 0 "AS140070" +"AS_0079" "14" "Hemifasc" 1 2 1.4142135623731 1 "AS140079" +"AS_0081" "14" "Hemifasc" 1.33333333333333 2 1.15470053837925 1 "AS140081" +"AS_0087" "14" "Hemifasc" 0 0 0 0 "AS140087" +"AS_0088" "14" "Hemifasc" 0 0 0 0 "AS140088" +"AS_0092" "14" "Hemifasc" 0.666666666666667 2 1.15470053837925 1 "AS140092" +"AS_0094" "14" "Hemifasc" 2 2 NA 1 "AS140094" +"AS_0097" "14" "Hemifasc" 3 3 NA 1 "AS140097" +"AS_0155" "14" "Hemifasc" 2 2 NA 1 "AS140155" +"AS_0156" "14" "Hemifasc" 2 2 0 1 "AS140156" +"AS_0157" "14" "Hemifasc" 2 2 0 1 "AS140157" +"AS_0159" "14" "Hemifasc" 2 2 0 1 "AS140159" +"BE_S032" "13" "Hemifasc" 0 0 0 0 "BE13S032" +"BE_S050" "13" "Hemifasc" 0 0 0 0 "BE13S050" +"BE_S072" "13" "Hemifasc" 0 0 NA 0 "BE13S072" +"BL_0001" "12" "Hemifasc" 0 0 0 0 "BL120001" +"BL_0005" "12" "Hemifasc" 0 0 NA 0 "BL120005" +"BL_0009" "12" "Hemifasc" 0 0 NA 0 "BL120009" +"BL_0011" "12" "Hemifasc" 0 0 0 0 "BL120011" +"BL_0014" "12" "Hemifasc" 0 0 0 0 "BL120014" +"BL_0016" "12" "Hemifasc" 1 1 NA 1 "BL120016" +"BL_0021" "12" "Hemifasc" 0 0 0 0 "BL120021" +"BL_0022" "12" "Hemifasc" 0 0 0 0 "BL120022" +"BL_0024" "12" "Hemifasc" 0 0 NA 0 "BL120024" +"BL_0027" "12" "Hemifasc" 0 0 0 0 "BL120027" +"BL_0028" "12" "Hemifasc" 0 0 NA 0 "BL120028" +"BL_0033" "12" "Hemifasc" 0 0 0 0 "BL120033" +"BL_0039" "12" "Hemifasc" 0 0 NA 0 "BL120039" +"BL_0040" "12" "Hemifasc" 0 0 0 0 "BL120040" +"BL_0041" "12" "Hemifasc" 0 0 NA 0 "BL120041" +"BL_0051" "12" "Hemifasc" 0 0 0 0 "BL120051" +"BL_0062" "12" "Hemifasc" 0 0 0 0 "BL120062" +"BL_0068" "12" "Hemifasc" 0.5 1 0.707106781186548 1 "BL120068" +"BL_0075" "12" "Hemifasc" 0 0 0 0 "BL120075" +"BL_0076" "12" "Hemifasc" 0.333333333333333 1 0.577350269189626 1 "BL120076" +"BL_0082" "12" "Hemifasc" 0 0 0 0 "BL120082" +"BL_0085" "12" "Hemifasc" 0 0 0 0 "BL120085" +"BL_0090" "12" "Hemifasc" 0 0 0 0 "BL120090" +"BL_0091" "12" "Hemifasc" 0 0 0 0 "BL120091" +"BL_0093" "12" "Hemifasc" 0 0 NA 0 "BL120093" +"BL_0094" "12" "Hemifasc" 0 0 0 0 "BL120094" +"BL_0097" "12" "Hemifasc" 0 0 NA 0 "BL120097" +"BL_0106" "12" "Hemifasc" 0 0 NA 0 "BL120106" +"BL_0128" "12" "Hemifasc" 0 0 0 0 "BL120128" +"BL_0131" "12" "Hemifasc" 0 0 0 0 "BL120131" +"BL_0133" "12" "Hemifasc" 0 0 NA 0 "BL120133" +"BL_0136" "12" "Hemifasc" 0 0 0 0 "BL120136" +"BL_0137" "12" "Hemifasc" 0 0 0 0 "BL120137" +"BL_0140" "12" "Hemifasc" 0 0 0 0 "BL120140" +"BL_0141" "12" "Hemifasc" 0 0 0 0 "BL120141" +"BL_0154" "12" "Hemifasc" 0 0 NA 0 "BL120154" +"BL_0155" "12" "Hemifasc" 0 0 0 0 "BL120155" +"BL_0161" "12" "Hemifasc" 0 0 NA 0 "BL120161" +"BL_0204" "12" "Hemifasc" 0 0 0 0 "BL120204" +"BL_P003" "12" "Hemifasc" 0 0 0 0 "BL12P003" +"BL_P017" "12" "Hemifasc" 0 0 0 0 "BL12P017" +"BL_P077" "12" "Hemifasc" 0 0 0 0 "BL12P077" +"BL_P078" "12" "Hemifasc" 0 0 0 0 "BL12P078" +"BL_P087" "12" "Hemifasc" 0 0 0 0 "BL12P087" +"BL_P124" "12" "Hemifasc" 0 0 0 0 "BL12P124" +"BO_0007" "12" "Hemifasc" 0 0 0 0 "BO120007" +"BO_0011" "12" "Hemifasc" 0 0 0 0 "BO120011" +"BO_0014" "12" "Hemifasc" 0 0 0 0 "BO120014" +"BO_0026" "12" "Hemifasc" 0 0 NA 0 "BO120026" +"BO_0028" "12" "Hemifasc" 0 0 0 0 "BO120028" +"BO_0029" "12" "Hemifasc" 0 0 NA 0 "BO120029" +"BO_0032" "12" "Hemifasc" 0 0 0 0 "BO120032" +"BO_0043" "12" "Hemifasc" 0 0 NA 0 "BO120043" +"BO_0045" "12" "Hemifasc" 0 0 NA 0 "BO120045" +"BO_0054" "12" "Hemifasc" 0 0 0 0 "BO120054" +"BO_0055" "12" "Hemifasc" 0 0 0 0 "BO120055" +"BO_0056" "12" "Hemifasc" 0 0 0 0 "BO120056" +"BO_0095" "12" "Hemifasc" 0 0 0 0 "BO120095" +"BO_0099" "12" "Hemifasc" 0 0 0 0 "BO120099" +"BO_0206" "12" "Hemifasc" 0 0 0 0 "BO120206" +"BO_0207" "12" "Hemifasc" 0 0 NA 0 "BO120207" +"BO_0209" "12" "Hemifasc" 0 0 0 0 "BO120209" +"BO_0212" "12" "Hemifasc" 0 0 0 0 "BO120212" +"BO_0213" "12" "Hemifasc" 0 0 0 0 "BO120213" +"BO_0214" "12" "Hemifasc" 0 0 0 0 "BO120214" +"BO_0215" "12" "Hemifasc" 0 0 0 0 "BO120215" +"BO_0216" "12" "Hemifasc" 0 0 NA 0 "BO120216" +"BO_095B" "12" "Hemifasc" 0 0 0 0 "BO12095B" +"CH_P032" "13" "Hemifasc" 0 0 NA 0 "CH13P032" +"CH_P033" "13" "Hemifasc" 0 0 0 0 "CH13P033" +"CH_P034" "13" "Hemifasc" 0 0 NA 0 "CH13P034" +"CH_P037" "13" "Hemifasc" 0.333333333333333 1 0.577350269189626 1 "CH13P037" +"CH_P040" "13" "Hemifasc" 0 0 0 0 "CH13P040" +"CH_P041" "13" "Hemifasc" 0 0 0 0 "CH13P041" +"CH_P055" "13" "Hemifasc" 0 0 0 0 "CH13P055" +"CH_P056" "13" "Hemifasc" 0 0 NA 0 "CH13P056" +"CH_P057" "13" "Hemifasc" 0 0 NA 0 "CH13P057" +"CH_P059" "13" "Hemifasc" 0.666666666666667 2 1.15470053837925 1 "CH13P059" +"CH_P061" "13" "Hemifasc" 0 0 0 0 "CH13P061" +"CH_P063" "13" "Hemifasc" 1.5 2 0.707106781186548 1 "CH13P063" +"CH_P066" "13" "Hemifasc" 1.66666666666667 2 0.577350269189626 1 "CH13P066" +"CH_P068" "13" "Hemifasc" 0 0 0 0 "CH13P068" +"CH_P071" "13" "Hemifasc" 0 0 0 0 "CH13P071" +"CH_S095" "13" "Hemifasc" 0 0 NA 0 "CH13S095" +"CH_S099" "13" "Hemifasc" 0 0 NA 0 "CH13S099" +"CH_S131" "13" "Hemifasc" 0 0 0 0 "CH13S131" +"CH_S148" "13" "Hemifasc" 0 0 NA 0 "CH13S148" +"CH_S149" "13" "Hemifasc" 0 0 NA 0 "CH13S149" +"CH_S151" "13" "Hemifasc" 0 0 NA 0 "CH13S151" +"CH_S153" "13" "Hemifasc" 1 1 NA 1 "CH13S153" +"CH_S156" "13" "Hemifasc" 0 0 0 0 "CH13S156" +"CH_S160" "13" "Hemifasc" 1.66666666666667 3 1.15470053837925 1 "CH13S160" +"CH_S192" "13" "Hemifasc" 0 0 0 0 "CH13S192" +"CS_0007" "13" "Hemifasc" 0 0 0 0 "CS130007" +"CS_0011" "13" "Hemifasc" 0.666666666666667 1 0.577350269189626 1 "CS130011" +"CS_0015" "13" "Hemifasc" 0 0 NA 0 "CS130015" +"CS_0018" "13" "Hemifasc" 0 0 0 0 "CS130018" +"CS_0019" "13" "Hemifasc" 0 0 NA 0 "CS130019" +"CS_0021" "13" "Hemifasc" 0 0 0 0 "CS130021" +"CS_0023" "13" "Hemifasc" 0 0 0 0 "CS130023" +"CS_0025" "13" "Hemifasc" 0 0 0 0 "CS130025" +"CS_0027" "13" "Hemifasc" 0 0 0 0 "CS130027" +"CS_0031" "13" "Hemifasc" 0 0 0 0 "CS130031" +"CS_0033" "13" "Hemifasc" 0 0 NA 0 "CS130033" +"CS_0035" "13" "Hemifasc" 0 0 0 0 "CS130035" +"CS_0037" "13" "Hemifasc" 0.666666666666667 1 0.577350269189626 1 "CS130037" +"CS_0039" "13" "Hemifasc" 0 0 0 0 "CS130039" +"CS_0042" "13" "Hemifasc" 0 0 NA 0 "CS130042" +"CS_0043" "13" "Hemifasc" 0 0 0 0 "CS130043" +"CS_0044" "13" "Hemifasc" 0.333333333333333 1 0.577350269189626 1 "CS130044" +"CS_0045" "13" "Hemifasc" 0 0 0 0 "CS130045" +"CS_0047" "13" "Hemifasc" 0 0 0 0 "CS130047" +"CS_0054" "13" "Hemifasc" 0 0 NA 0 "CS130054" +"CS_0060" "13" "Hemifasc" 0 0 0 0 "CS130060" +"CS_0064" "13" "Hemifasc" 0 0 0 0 "CS130064" +"CS_0065" "13" "Hemifasc" 1 1 0 1 "CS130065" +"CS_0069" "13" "Hemifasc" 0 0 0 0 "CS130069" +"CS_0070" "13" "Hemifasc" 0 0 0 0 "CS130070" +"CS_0071" "13" "Hemifasc" 0 0 0 0 "CS130071" +"CS_0075" "13" "Hemifasc" 0.333333333333333 1 0.577350269189626 1 "CS130075" +"CS_0077" "13" "Hemifasc" 0 0 0 0 "CS130077" +"CS_0079" "13" "Hemifasc" 0 0 0 0 "CS130079" +"CS_0081" "13" "Hemifasc" 0 0 0 0 "CS130081" +"CS_0082" "13" "Hemifasc" 0 0 0 0 "CS130082" +"CS_0083" "13" "Hemifasc" 0 0 NA 0 "CS130083" +"CS_0085" "13" "Hemifasc" 0 0 NA 0 "CS130085" +"CS_0092" "13" "Hemifasc" 0.333333333333333 1 0.577350269189626 1 "CS130092" +"CS_0094" "13" "Hemifasc" 0 0 0 0 "CS130094" +"CS_0095" "13" "Hemifasc" 0 0 NA 0 "CS130095" +"CS_0098" "13" "Hemifasc" 0 0 0 0 "CS130098" +"CS_0100" "13" "Hemifasc" 0.333333333333333 1 0.577350269189626 1 "CS130100" +"CS_0101" "13" "Hemifasc" 0 0 NA 0 "CS130101" +"CS_0104" "13" "Hemifasc" 0 0 NA 0 "CS130104" +"CS_0108" "13" "Hemifasc" 1 1 NA 1 "CS130108" +"CS_0109" "13" "Hemifasc" 0 0 0 0 "CS130109" +"CS_0115" "13" "Hemifasc" 0 0 0 0 "CS130115" +"CS_0116" "13" "Hemifasc" 0 0 0 0 "CS130116" +"CS_0125" "13" "Hemifasc" 1 1 0 1 "CS130125" +"CS_0126" "13" "Hemifasc" 1 1 NA 1 "CS130126" +"CS_0129" "13" "Hemifasc" 0 0 NA 0 "CS130129" +"CS_0130" "13" "Hemifasc" 0.333333333333333 1 0.577350269189626 1 "CS130130" +"CS_0131" "13" "Hemifasc" 0 0 0 0 "CS130131" +"CS_0133" "13" "Hemifasc" 0 0 0 0 "CS130133" +"CS_0135" "13" "Hemifasc" 0 0 NA 0 "CS130135" +"CS_0137" "13" "Hemifasc" 0 0 0 0 "CS130137" +"CS_0140" "13" "Hemifasc" 0 0 0 0 "CS130140" +"CS_0141" "13" "Hemifasc" 0 0 0 0 "CS130141" +"CS_0142" "13" "Hemifasc" 0 0 0 0 "CS130142" +"CS_0143" "13" "Hemifasc" 0 0 0 0 "CS130143" +"CS_0144" "13" "Hemifasc" 0 0 0 0 "CS130144" +"CS_0145" "13" "Hemifasc" 0 0 NA 0 "CS130145" +"CS_0146" "13" "Hemifasc" 0 0 0 0 "CS130146" +"CS_0304" "13" "Hemifasc" 0 0 NA 0 "CS130304" +"CS_0305" "13" "Hemifasc" 0 0 0 0 "CS130305" +"CS_0307" "13" "Hemifasc" 0 0 0 0 "CS130307" +"CS_0308" "13" "Hemifasc" 0 0 0 0 "CS130308" +"CS_0309" "13" "Hemifasc" 0 0 NA 0 "CS130309" +"CS_0310" "13" "Hemifasc" 1 1 NA 1 "CS130310" +"CS_0314" "13" "Hemifasc" 0 0 0 0 "CS130314" +"CS_0315" "13" "Hemifasc" 0 0 NA 0 "CS130315" +"CS_0316" "13" "Hemifasc" 0 0 0 0 "CS130316" +"CS_0317" "13" "Hemifasc" 0 0 0 0 "CS130317" +"CS_0318" "13" "Hemifasc" 0 0 0 0 "CS130318" +"CS_0403" "13" "Hemifasc" 0 0 0 0 "CS130403" +"CS_0404" "13" "Hemifasc" 0 0 0 0 "CS130404" +"CS_0405" "13" "Hemifasc" 0 0 NA 0 "CS130405" +"CS_0407" "13" "Hemifasc" 0 0 0 0 "CS130407" +"CS_0900" "13" "Hemifasc" 1 1 NA 1 "CS130900" +"CS_0904" "13" "Hemifasc" 0 0 0 0 "CS130904" +"CS_0920" "13" "Hemifasc" 0 0 NA 0 "CS130920" +"CS_0921" "13" "Hemifasc" 0 0 0 0 "CS130921" +"CS_0922" "13" "Hemifasc" 0 0 0 0 "CS130922" +"CS_0924" "13" "Hemifasc" 0 0 NA 0 "CS130924" +"CS_0926" "13" "Hemifasc" 0 0 NA 0 "CS130926" +"CS_0950" "13" "Hemifasc" 0 0 0 0 "CS130950" +"CS_0951" "13" "Hemifasc" 0 0 0 0 "CS130951" +"CS_0952" "13" "Hemifasc" 0 0 NA 0 "CS130952" +"CS_0953" "13" "Hemifasc" 0 0 0 0 "CS130953" +"CS_Z104" "13" "Hemifasc" 0 0 0 0 "CS13Z104" +"CS_Z106" "13" "Hemifasc" 0 0 0 0 "CS13Z106" +"EN_0001" "15" "Hemifasc" 0.5 1 0.707106781186548 1 "EN150001" +"EN_0011" "15" "Hemifasc" 1 1 NA 1 "EN150011" +"EN_0012" "15" "Hemifasc" 1.33333333333333 2 0.577350269189626 1 "EN150012" +"EN_0023" "15" "Hemifasc" 1 1 NA 1 "EN150023" +"EN_0027" "15" "Hemifasc" 1 1 NA 1 "EN150027" +"EN_0028" "15" "Hemifasc" 1 1 NA 1 "EN150028" +"EN_0030" "15" "Hemifasc" 0 0 NA 0 "EN150030" +"EN_0032" "15" "Hemifasc" 1 2 1.4142135623731 1 "EN150032" +"EN_0045" "15" "Hemifasc" 0 0 0 0 "EN150045" +"EN_0060" "15" "Hemifasc" 0.666666666666667 1 0.577350269189626 1 "EN150060" +"EN_0061" "15" "Hemifasc" 0 0 0 0 "EN150061" +"EN_0066" "15" "Hemifasc" 1 1 NA 1 "EN150066" +"EN_0087" "15" "Hemifasc" 1 1 NA 1 "EN150087" +"EN_0090" "15" "Hemifasc" 0 0 NA 0 "EN150090" +"EN_0094" "15" "Hemifasc" 0 0 0 0 "EN150094" +"EN_0105" "15" "Hemifasc" 0 0 0 0 "EN150105" +"EN_0108" "15" "Hemifasc" 0 0 NA 0 "EN150108" +"EN_0115" "15" "Hemifasc" 0 0 0 0 "EN150115" +"EN_0116" "15" "Hemifasc" 1 1 0 1 "EN150116" +"EN_0119" "15" "Hemifasc" 0.333333333333333 1 0.577350269189626 1 "EN150119" +"EN_0136" "15" "Hemifasc" 0.333333333333333 1 0.577350269189626 1 "EN150136" +"EN_0137" "15" "Hemifasc" 0 0 0 0 "EN150137" +"EN_0138" "15" "Hemifasc" 0 0 0 0 "EN150138" +"EN_0139" "15" "Hemifasc" 0 0 NA 0 "EN150139" +"EN_0140" "15" "Hemifasc" 0 0 0 0 "EN150140" +"EN_0155" "15" "Hemifasc" 1 1 0 1 "EN150155" +"EN_0202" "15" "Hemifasc" 1 1 0 1 "EN150202" +"EN_0300" "15" "Hemifasc" 1 1 0 1 "EN150300" +"EN_0301" "15" "Hemifasc" 0 0 0 0 "EN150301" +"EN_0302" "15" "Hemifasc" 1 1 0 1 "EN150302" +"EN_0305" "15" "Hemifasc" 0 0 0 0 "EN150305" +"EN_0307" "15" "Hemifasc" 0 0 0 0 "EN150307" +"EN_0309" "15" "Hemifasc" 0 0 NA 0 "EN150309" +"EN_0311" "15" "Hemifasc" 0 0 NA 0 "EN150311" +"EN_0313" "15" "Hemifasc" 0 0 NA 0 "EN150313" +"EN_0350" "15" "Hemifasc" 0 0 0 0 "EN150350" +"EN_0351" "15" "Hemifasc" 0 0 0 0 "EN150351" +"EN_0352" "15" "Hemifasc" 1 1 NA 1 "EN150352" +"EN_0400" "15" "Hemifasc" 1 1 0 1 "EN150400" +"GN_0007" "13" "Hemifasc" 0 0 NA 0 "GN130007" +"GN_0018" "13" "Hemifasc" 0 0 0 0 "GN130018" +"GN_0030" "13" "Hemifasc" 0 0 0 0 "GN130030" +"GN_0035" "13" "Hemifasc" 0 0 NA 0 "GN130035" +"GN_0047" "13" "Hemifasc" 0 0 0 0 "GN130047" +"GN_0058" "13" "Hemifasc" 0 0 NA 0 "GN130058" +"GN_0060" "13" "Hemifasc" 0 0 NA 0 "GN130060" +"GN_0066" "13" "Hemifasc" 0 0 0 0 "GN130066" +"GN_0069" "13" "Hemifasc" 0 0 0 0 "GN130069" +"GN_0091" "13" "Hemifasc" 0 0 0 0 "GN130091" +"GN_0092" "13" "Hemifasc" 0 0 NA 0 "GN130092" +"GN_0095" "13" "Hemifasc" 0 0 NA 0 "GN130095" +"GN_0105" "13" "Hemifasc" 0 0 NA 0 "GN130105" +"GN_0108" "13" "Hemifasc" 8 8 NA 1 "GN130108" +"GN_0114" "13" "Hemifasc" 0 0 NA 0 "GN130114" +"GN_0121" "13" "Hemifasc" 0 0 NA 0 "GN130121" +"GN_0131" "13" "Hemifasc" 0 0 NA 0 "GN130131" +"GN_0132" "13" "Hemifasc" 5.66666666666667 17 9.81495457622364 1 "GN130132" +"GN_0135" "13" "Hemifasc" 0 0 NA 0 "GN130135" +"GN_0139" "13" "Hemifasc" 0 0 0 0 "GN130139" +"GN_0142" "13" "Hemifasc" 0 0 NA 0 "GN130142" +"GN_0148" "13" "Hemifasc" 0 0 0 0 "GN130148" +"GN_0152" "13" "Hemifasc" 0 0 0 0 "GN130152" +"GN_0163" "13" "Hemifasc" 0 0 0 0 "GN130163" +"GN_0164" "13" "Hemifasc" 0 0 0 0 "GN130164" +"GN_0179" "13" "Hemifasc" 0 0 NA 0 "GN130179" +"GN_0181" "13" "Hemifasc" 2.33333333333333 7 4.04145188432738 1 "GN130181" +"GN_0185" "13" "Hemifasc" 0 0 NA 0 "GN130185" +"GN_0190" "13" "Hemifasc" 0 0 NA 0 "GN130190" +"GN_0192" "13" "Hemifasc" 0 0 0 0 "GN130192" +"GN_0209" "13" "Hemifasc" 0 0 0 0 "GN130209" +"GN_0223" "13" "Hemifasc" 6 10 5.29150262212918 1 "GN130223" +"GN_0224" "13" "Hemifasc" 0 0 NA 0 "GN130224" +"GN_0512" "13" "Hemifasc" 0 0 0 0 "GN130512" +"GN_0513" "13" "Hemifasc" 0 0 NA 0 "GN130513" +"HI_0001" "12" "Hemifasc" 0 0 0 0 "HI120001" +"HI_0002" "12" "Hemifasc" 1 1 NA 1 "HI120002" +"HI_0016" "12" "Hemifasc" 0 0 0 0 "HI120016" +"HI_0018" "12" "Hemifasc" 0 0 0 0 "HI120018" +"HI_0023" "12" "Hemifasc" 0 0 0 0 "HI120023" +"HI_0024" "12" "Hemifasc" 0 0 0 0 "HI120024" +"HI_0025" "12" "Hemifasc" 1 1 0 1 "HI120025" +"HI_0026" "12" "Hemifasc" 0 0 0 0 "HI120026" +"HI_0029" "12" "Hemifasc" 0 0 NA 0 "HI120029" +"HI_0030" "12" "Hemifasc" 0 0 0 0 "HI120030" +"HI_0042" "12" "Hemifasc" 0 0 NA 0 "HI120042" +"HI_0046" "12" "Hemifasc" 0 0 0 0 "HI120046" +"HI_0058" "12" "Hemifasc" 0 0 NA 0 "HI120058" +"HI_0060" "12" "Hemifasc" 0 0 NA 0 "HI120060" +"HI_0070" "12" "Hemifasc" 0 0 NA 0 "HI120070" +"HI_0086" "12" "Hemifasc" 0 0 NA 0 "HI120086" +"HI_0099" "12" "Hemifasc" 0 0 0 0 "HI120099" +"HI_0149" "12" "Hemifasc" 0 0 NA 0 "HI120149" +"HI_0156" "12" "Hemifasc" 0 0 0 0 "HI120156" +"HI_0171" "12" "Hemifasc" 0 0 0 0 "HI120171" +"HI_0172" "12" "Hemifasc" 0 0 NA 0 "HI120172" +"HI_0173" "12" "Hemifasc" 0 0 0 0 "HI120173" +"HI_0175" "12" "Hemifasc" 0 0 0 0 "HI120175" +"HI_0201" "12" "Hemifasc" 0 0 NA 0 "HI120201" +"HI_0204" "12" "Hemifasc" 0 0 NA 0 "HI120204" +"HI_0205" "12" "Hemifasc" 0 0 NA 0 "HI120205" +"HI_0210" "12" "Hemifasc" 1 1 NA 1 "HI120210" +"HI_0211" "12" "Hemifasc" 0 0 NA 0 "HI120211" +"HU_0031" "14" "Hemifasc" 0 0 NA 0 "HU140031" +"HU_0035" "14" "Hemifasc" 0 0 0 0 "HU140035" +"KO_0156" "07" "Hemifasc" 0 0 0 0 "KO070156" +"KO_0022" "08" "Hemifasc" 0 0 NA 0 "KO080022" +"KO_0024" "08" "Hemifasc" 0 0 0 0 "KO080024" +"KO_0033" "08" "Hemifasc" 0 0 0 0 "KO080033" +"KO_0183" "08" "Hemifasc" 0 0 0 0 "KO080183" +"KO_0003" "13" "Hemifasc" 0 0 NA 0 "KO130003" +"KO_0005" "13" "Hemifasc" 0 0 NA 0 "KO130005" +"KO_0010" "13" "Hemifasc" 0 0 NA 0 "KO130010" +"KO_0013" "13" "Hemifasc" 0 0 0 0 "KO130013" +"KO_0031" "13" "Hemifasc" 0 0 0 0 "KO130031" +"KO_0035" "13" "Hemifasc" 0 0 0 0 "KO130035" +"KO_0041" "13" "Hemifasc" 0 0 NA 0 "KO130041" +"KO_0053" "13" "Hemifasc" 0 0 NA 0 "KO130053" +"KO_0059" "13" "Hemifasc" 0 0 0 0 "KO130059" +"KO_0070" "13" "Hemifasc" 1 1 NA 1 "KO130070" +"KO_0071" "13" "Hemifasc" 1 1 NA 1 "KO130071" +"KO_0089" "13" "Hemifasc" 0 0 NA 0 "KO130089" +"KO_0097" "13" "Hemifasc" 0 0 0 0 "KO130097" +"KO_0098" "13" "Hemifasc" 0 0 0 0 "KO130098" +"KO_0099" "13" "Hemifasc" 0 0 0 0 "KO130099" +"KO_0101" "13" "Hemifasc" 0.5 1 0.707106781186548 1 "KO130101" +"KO_0108" "13" "Hemifasc" 0 0 0 0 "KO130108" +"KO_0110" "13" "Hemifasc" 0.333333333333333 1 0.577350269189626 1 "KO130110" +"KO_0112" "13" "Hemifasc" 0 0 0 0 "KO130112" +"KO_0113" "13" "Hemifasc" 0 0 0 0 "KO130113" +"KO_0120" "13" "Hemifasc" 0 0 NA 0 "KO130120" +"KO_0129" "13" "Hemifasc" 0 0 NA 0 "KO130129" +"KO_0130" "13" "Hemifasc" 0 0 0 0 "KO130130" +"KO_0131" "13" "Hemifasc" 0 0 0 0 "KO130131" +"KO_0132" "13" "Hemifasc" 0 0 NA 0 "KO130132" +"KO_0133" "13" "Hemifasc" 0.5 1 0.707106781186548 1 "KO130133" +"KO_0138" "13" "Hemifasc" 0 0 0 0 "KO130138" +"KO_0139" "13" "Hemifasc" 0 0 0 0 "KO130139" +"KO_0147" "13" "Hemifasc" 0 0 0 0 "KO130147" +"KO_0148" "13" "Hemifasc" 0 0 0 0 "KO130148" +"KO_0154" "13" "Hemifasc" 0 0 NA 0 "KO130154" +"KO_0160" "13" "Hemifasc" 0 0 NA 0 "KO130160" +"KO_0165" "13" "Hemifasc" 0 0 0 0 "KO130165" +"KO_0174" "13" "Hemifasc" 0 0 NA 0 "KO130174" +"KO_0176" "13" "Hemifasc" 0 0 0 0 "KO130176" +"KO_0177" "13" "Hemifasc" 0 0 0 0 "KO130177" +"KO_0202" "13" "Hemifasc" 0 0 0 0 "KO130202" +"KO_0203" "13" "Hemifasc" 0 0 0 0 "KO130203" +"KO_0204" "13" "Hemifasc" 0 0 NA 0 "KO130204" +"KO_0205" "13" "Hemifasc" 0 0 0 0 "KO130205" +"KO_0208" "13" "Hemifasc" 0 0 0 0 "KO130208" +"KO_0209" "13" "Hemifasc" 0 0 NA 0 "KO130209" +"KO_0301" "13" "Hemifasc" 0.333333333333333 1 0.577350269189626 1 "KO130301" +"KO_0302" "13" "Hemifasc" 1 1 0 1 "KO130302" +"KO_0304" "13" "Hemifasc" 0 0 NA 0 "KO130304" +"KO_0305" "13" "Hemifasc" 0 0 0 0 "KO130305" +"KO_059b" "13" "Hemifasc" 0 0 0 0 "KO13059b" +"LA_101B" "08" "Hemifasc" 0.333333333333333 1 0.577350269189626 1 "LA08101B" +"LA_0012" "10" "Hemifasc" 0 0 NA 0 "LA100012" +"LA_0028" "10" "Hemifasc" 0 0 NA 0 "LA100028" +"LA_0039" "10" "Hemifasc" 0 0 0 0 "LA100039" +"LI_0021" "14" "Hemifasc" 0 0 0 0 "LI140021" +"LI_0022" "14" "Hemifasc" 0 0 0 0 "LI140022" +"LI_0028" "14" "Hemifasc" 0 0 0 0 "LI140028" +"LI_0033" "14" "Hemifasc" 0 0 0 0 "LI140033" +"LI_0035" "14" "Hemifasc" 0 0 NA 0 "LI140035" +"LI_0064" "14" "Hemifasc" 0 0 NA 0 "LI140064" +"LI_0067" "14" "Hemifasc" 1.2 1.2 NA 1 "LI140067" +"LI_0073" "14" "Hemifasc" 0 0 0 0 "LI140073" +"LI_0077" "14" "Hemifasc" 1 1 NA 1 "LI140077" +"LI_0081" "14" "Hemifasc" 0.333333333333333 1 0.577350269189626 1 "LI140081" +"LI_0082" "14" "Hemifasc" 0 0 NA 0 "LI140082" +"LI_0083" "14" "Hemifasc" 0 0 0 0 "LI140083" +"LI_0086" "14" "Hemifasc" 0 0 0 0 "LI140086" +"LI_0089" "14" "Hemifasc" 0 0 0 0 "LI140089" +"LI_0093" "14" "Hemifasc" 0 0 NA 0 "LI140093" +"LI_0094" "14" "Hemifasc" 0 0 NA 0 "LI140094" +"LI_0096" "14" "Hemifasc" 0.666666666666667 1 0.577350269189626 1 "LI140096" +"LI_0100" "14" "Hemifasc" 0 0 0 0 "LI140100" +"LI_0102" "14" "Hemifasc" 0 0 0 0 "LI140102" +"LI_0103" "14" "Hemifasc" 0.666666666666667 1 0.577350269189626 1 "LI140103" +"LI_0104" "14" "Hemifasc" 0 0 0 0 "LI140104" +"LI_0110" "14" "Hemifasc" 0 0 NA 0 "LI140110" +"LI_0111" "14" "Hemifasc" 1 1 0 1 "LI140111" +"LI_0113" "14" "Hemifasc" 0 0 0 0 "LI140113" +"LI_0114" "14" "Hemifasc" 0 0 0 0 "LI140114" +"LI_0121" "14" "Hemifasc" 0 0 0 0 "LI140121" +"LI_0122" "14" "Hemifasc" 0 0 NA 0 "LI140122" +"LI_0129" "14" "Hemifasc" 0.666666666666667 1 0.577350269189626 1 "LI140129" +"LI_0149" "14" "Hemifasc" 1 1 0 1 "LI140149" +"LI_0150" "14" "Hemifasc" 0 0 0 0 "LI140150" +"LI_0151" "14" "Hemifasc" 0.5 1 0.707106781186548 1 "LI140151" +"LI_0152" "14" "Hemifasc" 0.4 1.2 0.692820323027551 1 "LI140152" +"LI_0305" "14" "Hemifasc" 0 0 NA 0 "LI140305" +"LI_0307" "14" "Hemifasc" 0 0 NA 0 "LI140307" +"LI_0401" "14" "Hemifasc" 0 0 0 0 "LI140401" +"ME_0004" "13" "Hemifasc" 0 0 0 0 "ME130004" +"ME_0018" "13" "Hemifasc" 0 0 0 0 "ME130018" +"ME_0022" "13" "Hemifasc" 0 0 0 0 "ME130022" +"ME_0034" "13" "Hemifasc" 0 0 NA 0 "ME130034" +"ME_0036" "13" "Hemifasc" 0 0 NA 0 "ME130036" +"ME_0046" "13" "Hemifasc" 0.333333333333333 1 0.577350269189626 1 "ME130046" +"ME_0049" "13" "Hemifasc" 1 1 0 1 "ME130049" +"ME_0050" "13" "Hemifasc" 0 0 0 0 "ME130050" +"ME_0053" "13" "Hemifasc" 0 0 0 0 "ME130053" +"ME_0054" "13" "Hemifasc" 0 0 0 0 "ME130054" +"ME_0063" "13" "Hemifasc" 0 0 0 0 "ME130063" +"ME_0066" "13" "Hemifasc" 0 0 0 0 "ME130066" +"ME_0071" "13" "Hemifasc" 0 0 0 0 "ME130071" +"ME_0073" "13" "Hemifasc" 0 0 0 0 "ME130073" +"ME_0074" "13" "Hemifasc" 0 0 0 0 "ME130074" +"ME_0075" "13" "Hemifasc" 0 0 0 0 "ME130075" +"ME_0089" "13" "Hemifasc" 0 0 0 0 "ME130089" +"ME_0090" "13" "Hemifasc" 0 0 0 0 "ME130090" +"ME_0096" "13" "Hemifasc" 1 1 NA 1 "ME130096" +"ME_0099" "13" "Hemifasc" 0 0 0 0 "ME130099" +"ME_00F1" "13" "Hemifasc" 1 1 0 1 "ME1300F1" +"ME_00F3" "13" "Hemifasc" 0.333333333333333 1 0.577350269189626 1 "ME1300F3" +"ME_00F4" "13" "Hemifasc" 1 1 NA 1 "ME1300F4" +"ME_00F5" "13" "Hemifasc" 0 0 NA 0 "ME1300F5" +"ME_0101" "13" "Hemifasc" 1 2 1.4142135623731 1 "ME130101" +"ME_0105" "13" "Hemifasc" 0 0 0 0 "ME130105" +"ME_0106" "13" "Hemifasc" 0 0 0 0 "ME130106" +"ME_0107" "13" "Hemifasc" 0 0 0 0 "ME130107" +"ME_0108" "13" "Hemifasc" 0 0 0 0 "ME130108" +"ME_0111" "13" "Hemifasc" 0 0 0 0 "ME130111" +"ME_0115" "13" "Hemifasc" 1 1 NA 1 "ME130115" +"ME_0116" "13" "Hemifasc" 0 0 0 0 "ME130116" +"ME_0117" "13" "Hemifasc" 0 0 0 0 "ME130117" +"ME_0120" "13" "Hemifasc" 0 0 0 0 "ME130120" +"ME_0121" "13" "Hemifasc" 0 0 0 0 "ME130121" +"ME_0124" "13" "Hemifasc" 0 0 0 0 "ME130124" +"ME_0126" "13" "Hemifasc" 0 0 0 0 "ME130126" +"ME_0128" "13" "Hemifasc" 0 0 0 0 "ME130128" +"ME_0129" "13" "Hemifasc" 0 0 NA 0 "ME130129" +"ME_0135" "13" "Hemifasc" 0 0 NA 0 "ME130135" +"ME_0137" "13" "Hemifasc" 0.666666666666667 1 0.577350269189626 1 "ME130137" +"ME_0154" "13" "Hemifasc" 0 0 NA 0 "ME130154" +"ME_0160" "13" "Hemifasc" 0 0 0 0 "ME130160" +"ME_0170" "13" "Hemifasc" 0 0 NA 0 "ME130170" +"ME_0171" "13" "Hemifasc" 0 0 NA 0 "ME130171" +"ME_0173" "13" "Hemifasc" 0 0 NA 0 "ME130173" +"ME_0179" "13" "Hemifasc" 2 2 NA 1 "ME130179" +"ME_0190" "13" "Hemifasc" 0 0 0 0 "ME130190" +"ME_0207" "13" "Hemifasc" 0 0 NA 0 "ME130207" +"ME_0208" "13" "Hemifasc" 0 0 0 0 "ME130208" +"ME_0209" "13" "Hemifasc" 0.333333333333333 1 0.577350269189626 1 "ME130209" +"ME_0210" "13" "Hemifasc" 0 0 0 0 "ME130210" +"ME_0212" "13" "Hemifasc" 0 0 NA 0 "ME130212" +"ME_0213" "13" "Hemifasc" 0 0 NA 0 "ME130213" +"ME_0215" "13" "Hemifasc" 0 0 0 0 "ME130215" +"ME_0241" "13" "Hemifasc" 0 0 NA 0 "ME130241" +"ME_0246" "13" "Hemifasc" 0 0 NA 0 "ME130246" +"ME_0248" "13" "Hemifasc" 0 0 0 0 "ME130248" +"ME_0252" "13" "Hemifasc" 0 0 0 0 "ME130252" +"ME_0260" "13" "Hemifasc" 0 0 0 0 "ME130260" +"ME_0262" "13" "Hemifasc" 0 0 0 0 "ME130262" +"ME_0265" "13" "Hemifasc" 0 0 NA 0 "ME130265" +"ME_0266" "13" "Hemifasc" 0 0 0 0 "ME130266" +"ME_0267" "13" "Hemifasc" 1.5 1.5 NA 1 "ME130267" +"ME_0268" "13" "Hemifasc" 0 0 0 0 "ME130268" +"ME_0273" "13" "Hemifasc" 0 0 NA 0 "ME130273" +"ME_0400" "13" "Hemifasc" 0 0 0 0 "ME130400" +"ME_0402" "13" "Hemifasc" 0 0 NA 0 "ME130402" +"ME_0403" "13" "Hemifasc" 0.333333333333333 1 0.577350269189626 1 "ME130403" +"ME_102PM" "13" "Hemifasc" 2 2.4 0.692820323027551 1 "ME13102PM" +"ME_168PM" "13" "Hemifasc" 1 1 NA 1 "ME13168PM" +"ME_47PM" "13" "Hemifasc" 0 0 0 0 "ME1347PM" +"MK_0425" "08" "Hemifasc" 0 0 0 0 "MK080425" +"MK_0426" "08" "Hemifasc" 0 0 NA 0 "MK080426" +"MK_0427" "08" "Hemifasc" 0 0 0 0 "MK080427" +"MK_0430" "08" "Hemifasc" 0 0 NA 0 "MK080430" +"MK_0440" "08" "Hemifasc" 0 0 0 0 "MK080440" +"MK_0453" "08" "Hemifasc" 0 0 0 0 "MK080453" +"MK_0454" "08" "Hemifasc" 0 0 0 0 "MK080454" +"MK_0458" "08" "Hemifasc" 0 0 NA 0 "MK080458" +"MK_0462" "08" "Hemifasc" 0 0 0 0 "MK080462" +"MK_0207" "09" "Hemifasc" 0 0 0 0 "MK090207" +"MK_0208" "09" "Hemifasc" 0 0 0 0 "MK090208" +"MK_0211" "09" "Hemifasc" 0 0 0 0 "MK090211" +"MK_0225" "09" "Hemifasc" 0 0 0 0 "MK090225" +"MK_0227" "09" "Hemifasc" 0 0 0 0 "MK090227" +"MK_0228" "09" "Hemifasc" 0 0 0 0 "MK090228" +"MK_0231" "09" "Hemifasc" 0 0 NA 0 "MK090231" +"MK_0234" "09" "Hemifasc" 0 0 NA 0 "MK090234" +"MK_0248" "09" "Hemifasc" 0 0 0 0 "MK090248" +"MK_0249" "09" "Hemifasc" 0 0 NA 0 "MK090249" +"MK_0250" "09" "Hemifasc" 0 0 NA 0 "MK090250" +"MK_0200" "10" "Hemifasc" 0 0 0 0 "MK100200" +"MK_0205" "10" "Hemifasc" 0 0 NA 0 "MK100205" +"MK_0206" "10" "Hemifasc" 0 0 NA 0 "MK100206" +"MK_0210" "10" "Hemifasc" 0 0 0 0 "MK100210" +"MK_0213" "10" "Hemifasc" 0 0 0 0 "MK100213" +"MK_0215" "10" "Hemifasc" 0 0 0 0 "MK100215" +"MK_0219" "10" "Hemifasc" 0 0 0 0 "MK100219" +"MK_0221" "10" "Hemifasc" 0 0 NA 0 "MK100221" +"MK_0230" "10" "Hemifasc" 0 0 0 0 "MK100230" +"MK_0231" "10" "Hemifasc" 0 0 0 0 "MK100231" +"MK_0234" "10" "Hemifasc" 0 0 0 0 "MK100234" +"MK_0240" "10" "Hemifasc" 0 0 0 0 "MK100240" +"MK_0249" "10" "Hemifasc" 0 0 0 0 "MK100249" +"OU_0002" "09" "Hemifasc" 0 0 0 0 "OU090002" +"OU_0005" "09" "Hemifasc" 0 0 NA 0 "OU090005" +"OU_0006" "09" "Hemifasc" 0 0 NA 0 "OU090006" +"OU_0020" "09" "Hemifasc" 0 0 NA 0 "OU090020" +"OU_0025" "09" "Hemifasc" 0 0 0 0 "OU090025" +"OU_0061" "09" "Hemifasc" 0 0 NA 0 "OU090061" +"OU_0108" "09" "Hemifasc" 0 0 NA 0 "OU090108" +"OU_0116" "09" "Hemifasc" 0 0 NA 0 "OU090116" +"OU_0123" "09" "Hemifasc" 0 0 0 0 "OU090123" +"OU_0L13" "09" "Hemifasc" 0 0 0 0 "OU090L13" +"OU_0L14" "09" "Hemifasc" 0 0 0 0 "OU090L14" +"OU_0L22" "09" "Hemifasc" 0 0 NA 0 "OU090L22" +"OU_0L51" "09" "Hemifasc" 0 0 NA 0 "OU090L51" +"OU_0L52" "09" "Hemifasc" 0 0 0 0 "OU090L52" +"OU_0L82" "09" "Hemifasc" 0 0 NA 0 "OU090L82" +"OU_106C" "09" "Hemifasc" 0 0 0 0 "OU09106C" +"OU_107C" "09" "Hemifasc" 0 0 0 0 "OU09107C" +"OU_123B" "09" "Hemifasc" 0 0 0 0 "OU09123B" +"OU_129B" "09" "Hemifasc" 0.333333333333333 1 0.577350269189626 1 "OU09129B" +"OU_L12R" "09" "Hemifasc" 0 0 0 0 "OU09L12R" +"OU_L14R" "09" "Hemifasc" 0 0 0 0 "OU09L14R" +"OU_L22R" "09" "Hemifasc" 0 0 0 0 "OU09L22R" +"OU_L36R" "09" "Hemifasc" 0 0 0 0 "OU09L36R" +"OU_L51R" "09" "Hemifasc" 0 0 0 0 "OU09L51R" +"OU_L52R" "09" "Hemifasc" 0 0 0 0 "OU09L52R" +"PA_0004" "17" "Hemifasc" 1 1 NA 1 "PA170004" +"PA_0005" "17" "Hemifasc" 1 1 0 1 "PA170005" +"PA_0010" "17" "Hemifasc" 1 1 NA 1 "PA170010" +"PA_0011" "17" "Hemifasc" 0 0 0 0 "PA170011" +"PA_0012" "17" "Hemifasc" 0 0 NA 0 "PA170012" +"PA_0013" "17" "Hemifasc" 1 1 0 1 "PA170013" +"PA_0014" "17" "Hemifasc" 0.333333333333333 1 0.577350269189626 1 "PA170014" +"PA_0015" "17" "Hemifasc" 1 1 NA 1 "PA170015" +"PA_0016" "17" "Hemifasc" 0.666666666666667 1 0.577350269189626 1 "PA170016" +"PA_0017" "17" "Hemifasc" 1 1 0 1 "PA170017" +"PA_0018" "17" "Hemifasc" 1 1 0 1 "PA170018" +"PA_0020" "17" "Hemifasc" 2 2 NA 1 "PA170020" +"PA_0022" "17" "Hemifasc" 0 0 0 0 "PA170022" +"PA_0025" "17" "Hemifasc" 0 0 NA 0 "PA170025" +"PA_0027" "17" "Hemifasc" 0 0 0 0 "PA170027" +"PA_0030" "17" "Hemifasc" 0 0 NA 0 "PA170030" +"PA_0039" "17" "Hemifasc" 1 1 0 1 "PA170039" +"PA_0041" "17" "Hemifasc" 0 0 0 0 "PA170041" +"PA_0042" "17" "Hemifasc" 1.66666666666667 2 0.577350269189626 1 "PA170042" +"PA_0043" "17" "Hemifasc" 0 0 0 0 "PA170043" +"PA_0044" "17" "Hemifasc" 0 0 NA 0 "PA170044" +"PA_0050" "17" "Hemifasc" 1.66666666666667 2 0.577350269189626 1 "PA170050" +"PA_0051" "17" "Hemifasc" 0.5 1 0.707106781186548 1 "PA170051" +"PA_0054" "17" "Hemifasc" 1 1 NA 1 "PA170054" +"PA_0055" "17" "Hemifasc" 1 1 NA 1 "PA170055" +"PA_0056" "17" "Hemifasc" 0.666666666666667 1 0.577350269189626 1 "PA170056" +"PA_0057" "17" "Hemifasc" 0.333333333333333 1 0.577350269189626 1 "PA170057" +"PA_0058" "17" "Hemifasc" 0 0 0 0 "PA170058" +"PA_0059" "17" "Hemifasc" 1 1 NA 1 "PA170059" +"PA_0060" "17" "Hemifasc" 0.666666666666667 1 0.577350269189626 1 "PA170060" +"PA_0066" "17" "Hemifasc" 0 0 NA 0 "PA170066" +"PA_0068" "17" "Hemifasc" 0 0 0 0 "PA170068" +"PA_0074" "17" "Hemifasc" 1 1 NA 1 "PA170074" +"PA_0079" "17" "Hemifasc" 0 0 NA 0 "PA170079" +"PA_0080" "17" "Hemifasc" 1 1 0 1 "PA170080" +"PA_0081" "17" "Hemifasc" 0.5 1 0.707106781186548 1 "PA170081" +"PA_0083" "17" "Hemifasc" 0 0 NA 0 "PA170083" +"PA_0084" "17" "Hemifasc" 0 0 0 0 "PA170084" +"PA_0088" "17" "Hemifasc" 0 0 0 0 "PA170088" +"PA_0091" "17" "Hemifasc" 0.333333333333333 1 0.577350269189626 1 "PA170091" +"PA_0093" "17" "Hemifasc" 0.5 1 0.707106781186548 1 "PA170093" +"PA_0094" "17" "Hemifasc" 0 0 NA 0 "PA170094" +"PA_0100" "17" "Hemifasc" 1 1 NA 1 "PA170100" +"PE_0007" "14" "Hemifasc" 0 0 0 0 "PE140007" +"PE_0025" "14" "Hemifasc" 1 1 NA 1 "PE140025" +"PE_0029" "14" "Hemifasc" 1 1 NA 1 "PE140029" +"PE_0031" "14" "Hemifasc" 0 0 0 0 "PE140031" +"PE_0033" "14" "Hemifasc" 1 1 0 1 "PE140033" +"PE_0035" "14" "Hemifasc" 0.333333333333333 1 0.577350269189626 1 "PE140035" +"PO_0001" "12" "Hemifasc" 0 0 NA 0 "PO120001" +"PO_0004" "12" "Hemifasc" 0 0 0 0 "PO120004" +"PO_0007" "12" "Hemifasc" 0 0 0 0 "PO120007" +"PO_0018" "12" "Hemifasc" 0 0 NA 0 "PO120018" +"PO_0028" "12" "Hemifasc" 0 0 0 0 "PO120028" +"PO_0045" "12" "Hemifasc" 0 0 0 0 "PO120045" +"PO_0048" "12" "Hemifasc" 0 0 NA 0 "PO120048" +"PO_0053" "12" "Hemifasc" 0 0 0 0 "PO120053" +"PO_0066" "12" "Hemifasc" 0 0 0 0 "PO120066" +"PO_0092" "12" "Hemifasc" 0 0 0 0 "PO120092" +"PO_0094" "12" "Hemifasc" 0 0 0 0 "PO120094" +"PO_0096" "12" "Hemifasc" 0 0 0 0 "PO120096" +"PO_0121" "12" "Hemifasc" 0 0 0 0 "PO120121" +"PO_0134" "12" "Hemifasc" 1 1 NA 1 "PO120134" +"PO_0136" "12" "Hemifasc" 0 0 NA 0 "PO120136" +"PO_0200" "12" "Hemifasc" 0 0 NA 0 "PO120200" +"PO_0203" "12" "Hemifasc" 0 0 0 0 "PO120203" +"PO_0205" "12" "Hemifasc" 0 0 NA 0 "PO120205" +"PO_0206" "12" "Hemifasc" 0 0 0 0 "PO120206" +"PO_0233" "12" "Hemifasc" 0 0 NA 0 "PO120233" +"RD_0219" "07" "Hemifasc" 0 0 0 0 "RD070219" +"RD_0230" "07" "Hemifasc" 0 0 NA 0 "RD070230" +"RD_0031" "08" "Hemifasc" 0 0 NA 0 "RD080031" +"RD_0103" "09" "Hemifasc" 0 0 NA 0 "RD090103" +"RD_0105" "09" "Hemifasc" 0 0 NA 0 "RD090105" +"RD_0108" "09" "Hemifasc" 0 0 NA 0 "RD090108" +"RD_0109" "09" "Hemifasc" 0 0 NA 0 "RD090109" +"RD_0107" "10" "Hemifasc" 0 0 NA 0 "RD100107" +"RL_0250" "07" "Hemifasc" 0 0 NA 0 "RL070250" +"RL_0145" "08" "Hemifasc" 0 0 0 0 "RL080145" +"RL_0078" "09" "Hemifasc" 0 0 0 0 "RL090078" +"RL_0089" "09" "Hemifasc" 0 0 0 0 "RL090089" +"RL_0093" "09" "Hemifasc" 0 0 0 0 "RL090093" +"RL_0066" "10" "Hemifasc" 0 0 NA 0 "RL100066" +"RL_0076" "10" "Hemifasc" 0 0 0 0 "RL100076" +"RS_0169" "07" "Hemifasc" 0 0 0 0 "RS070169" +"RS_0189" "07" "Hemifasc" 0 0 0 0 "RS070189" +"SI_0078" "07" "Hemifasc" 0 0 NA 0 "SI070078" +"SI_0079" "07" "Hemifasc" 0 0 0 0 "SI070079" +"SI_0080" "07" "Hemifasc" 0 0 0 0 "SI070080" +"SI_0082" "07" "Hemifasc" 0 0 NA 0 "SI070082" +"SI_0197" "07" "Hemifasc" 0 0 NA 0 "SI070197" +"SI_0222" "07" "Hemifasc" 0 0 NA 0 "SI070222" +"SI_0194" "08" "Hemifasc" 0 0 0 0 "SI080194" +"WA_0002" "14" "Hemifasc" 0 0 0 0 "WA140002" +"AB_0008" "08" "Zebrscop" 2.66666666666667 3 0.577350269189626 1 "AB080008" +"AB_0015" "08" "Zebrscop" 3 5 2 1 "AB080015" +"AB_0027" "08" "Zebrscop" 1.33333333333333 2 0.577350269189626 1 "AB080027" +"AB_0031" "08" "Zebrscop" 1.33333333333333 2 0.577350269189626 1 "AB080031" +"AB_0037" "08" "Zebrscop" 1 1 NA 1 "AB080037" +"AB_0042" "08" "Zebrscop" 1 1 NA 1 "AB080042" +"AB_0057" "08" "Zebrscop" 1 1 0 1 "AB080057" +"AB_0076" "09" "Zebrscop" 1 1 0 1 "AB090076" +"AB_0081" "09" "Zebrscop" 1 1 0 1 "AB090081" +"AB_0095" "09" "Zebrscop" 2.33333333333333 3 0.577350269189626 1 "AB090095" +"AB_0097" "09" "Zebrscop" 1 1 0 1 "AB090097" +"AB_0098" "09" "Zebrscop" 1 1 NA 1 "AB090098" +"AB_0104" "09" "Zebrscop" 1.2 1.2 0 1 "AB090104" +"AB_0105" "09" "Zebrscop" 1.33333333333333 2 0.577350269189626 1 "AB090105" +"AB_0106" "09" "Zebrscop" 2 2 NA 1 "AB090106" +"AB_0120" "09" "Zebrscop" 1 1 NA 1 "AB090120" +"AB_0121" "09" "Zebrscop" 2.33333333333333 3 1.15470053837925 1 "AB090121" +"AB_0122" "09" "Zebrscop" 1 1 0 1 "AB090122" +"AB_0123" "09" "Zebrscop" 1.5 2 0.707106781186548 1 "AB090123" +"AB_0124" "09" "Zebrscop" 1 1 NA 1 "AB090124" +"AB_0125" "09" "Zebrscop" 3.33333333333333 4 0.577350269189626 1 "AB090125" +"AB_0126" "09" "Zebrscop" 4.33333333333333 5 0.577350269189626 1 "AB090126" +"AB_0127" "09" "Zebrscop" 1.66666666666667 2 0.577350269189626 1 "AB090127" +"AB_0132" "09" "Zebrscop" 1.5 1.5 NA 1 "AB090132" +"AB_0133" "09" "Zebrscop" 2 3 1 1 "AB090133" +"AB_0134" "09" "Zebrscop" 2 2 0 1 "AB090134" +"AB_0135" "09" "Zebrscop" 1 1 0 1 "AB090135" +"AB_0143" "09" "Zebrscop" 1 1 NA 1 "AB090143" +"AB_0148" "09" "Zebrscop" 1 1 NA 1 "AB090148" +"AB_0149" "09" "Zebrscop" 3 4 1 1 "AB090149" +"AB_0151" "09" "Zebrscop" 1.33333333333333 2 0.577350269189626 1 "AB090151" +"AB_0601" "09" "Zebrscop" 1.66666666666667 2 0.577350269189626 1 "AB090601" +"AB_0602" "09" "Zebrscop" 4.33333333333333 5 0.577350269189626 1 "AB090602" +"AB_0603" "09" "Zebrscop" 1 1 NA 1 "AB090603" +"AB_0001" "10" "Zebrscop" 2 2 NA 1 "AB100001" +"AB_0002" "10" "Zebrscop" 4.33333333333333 6 1.52752523165195 1 "AB100002" +"AB_0006" "10" "Zebrscop" 2.33333333333333 3 0.577350269189626 1 "AB100006" +"AB_0008" "10" "Zebrscop" 3.33333333333333 5 1.52752523165195 1 "AB100008" +"AB_0009" "10" "Zebrscop" 1.5 2 0.707106781186548 1 "AB100009" +"AB_0010" "10" "Zebrscop" 1.33333333333333 2 0.577350269189626 1 "AB100010" +"AB_0011" "10" "Zebrscop" 1.66666666666667 2 0.577350269189626 1 "AB100011" +"AB_0015" "10" "Zebrscop" 1 1 0 1 "AB100015" +"AB_0017" "10" "Zebrscop" 3.33333333333333 5 1.52752523165195 1 "AB100017" +"AB_0019" "10" "Zebrscop" 1.5 2 0.707106781186548 1 "AB100019" +"AB_0020" "10" "Zebrscop" 2 2 0 1 "AB100020" +"AB_0021" "10" "Zebrscop" 3 4 1 1 "AB100021" +"AB_0023" "10" "Zebrscop" 5.33333333333333 7 1.52752523165195 1 "AB100023" +"AB_0024" "10" "Zebrscop" 1.33333333333333 2 0.577350269189626 1 "AB100024" +"AB_0025" "10" "Zebrscop" 1 1 0 1 "AB100025" +"AB_0028" "10" "Zebrscop" 3.33333333333333 5 1.52752523165195 1 "AB100028" +"AB_0029" "10" "Zebrscop" 6.66666666666667 10 3.05505046330389 1 "AB100029" +"AB_0031" "10" "Zebrscop" 0 0 0 0 "AB100031" +"AB_0035" "10" "Zebrscop" 1 1 NA 1 "AB100035" +"AB_0036" "10" "Zebrscop" 2.66666666666667 4 1.15470053837925 1 "AB100036" +"AB_0038" "10" "Zebrscop" 3 4 1 1 "AB100038" +"AB_0042" "10" "Zebrscop" 1 1 0 1 "AB100042" +"AB_0046" "10" "Zebrscop" 4 5 1 1 "AB100046" +"AB_0047" "10" "Zebrscop" 2 4 1.73205080756888 1 "AB100047" +"AB_0048" "10" "Zebrscop" 2.66666666666667 4 1.15470053837925 1 "AB100048" +"AB_0049" "10" "Zebrscop" 1.66666666666667 3 1.15470053837925 1 "AB100049" +"AB_0052" "10" "Zebrscop" 1 1 0 1 "AB100052" +"AB_0055" "10" "Zebrscop" 1 1 NA 1 "AB100055" +"AB_0060" "10" "Zebrscop" 4.33333333333333 6 2.08166599946613 1 "AB100060" +"AB_0061" "10" "Zebrscop" 2.66666666666667 3 0.577350269189626 1 "AB100061" +"AB_0062" "10" "Zebrscop" 3 3 0 1 "AB100062" +"AB_0072" "10" "Zebrscop" 1 1 NA 1 "AB100072" +"AB_0077" "10" "Zebrscop" 1 1 NA 1 "AB100077" +"AB_0078" "10" "Zebrscop" 1 1 NA 1 "AB100078" +"AB_0079" "10" "Zebrscop" 1 1 0 1 "AB100079" +"AB_0081" "10" "Zebrscop" 1 1 0 1 "AB100081" +"AB_0082" "10" "Zebrscop" 2 2 NA 1 "AB100082" +"AB_0085" "10" "Zebrscop" 2 3 1.4142135623731 1 "AB100085" +"AB_0086" "10" "Zebrscop" 3.33333333333333 4 1.15470053837925 1 "AB100086" +"AB_0087" "10" "Zebrscop" 1.66666666666667 2 0.577350269189626 1 "AB100087" +"AB_0088" "10" "Zebrscop" 2.33333333333333 3 0.577350269189626 1 "AB100088" +"AB_0089" "10" "Zebrscop" 3 3 NA 1 "AB100089" +"AB_0090" "10" "Zebrscop" 1 1 0 1 "AB100090" +"AB_0091" "10" "Zebrscop" 1 1 0 1 "AB100091" +"AB_0092" "10" "Zebrscop" 2.66666666666667 4 1.15470053837925 1 "AB100092" +"AB_0093" "10" "Zebrscop" 1.66666666666667 2 0.577350269189626 1 "AB100093" +"AB_0094" "10" "Zebrscop" 3 5 1.73205080756888 1 "AB100094" +"AB_0095" "10" "Zebrscop" 1 1 NA 1 "AB100095" +"AB_0096" "10" "Zebrscop" 2.66666666666667 3 0.577350269189626 1 "AB100096" +"AB_0097" "10" "Zebrscop" 1 1 0 1 "AB100097" +"AB_0098" "10" "Zebrscop" 1 1 NA 1 "AB100098" +"AB_0099" "10" "Zebrscop" 1 1 0 1 "AB100099" +"AB_0111" "10" "Zebrscop" 1.66666666666667 3 1.15470053837925 1 "AB100111" +"AB_0112" "10" "Zebrscop" 3 4 1 1 "AB100112" +"AB_0119" "10" "Zebrscop" 1 1 NA 1 "AB100119" +"AB_0124" "10" "Zebrscop" 4.33333333333333 5 0.577350269189626 1 "AB100124" +"AB_0131" "10" "Zebrscop" 3.5 4 0.707106781186548 1 "AB100131" +"AB_0132" "10" "Zebrscop" 4.33333333333333 6 1.52752523165195 1 "AB100132" +"AS_0048" "14" "Zebrscop" 5.66666666666667 13 6.35085296108588 1 "AS140048" +"AS_0054" "14" "Zebrscop" 2.5 3 0.707106781186548 1 "AS140054" +"AS_0059" "14" "Zebrscop" 7 14 6.08276253029822 1 "AS140059" +"AS_0060" "14" "Zebrscop" 2 2 0 1 "AS140060" +"AS_0061" "14" "Zebrscop" 27.3333333333333 28 0.577350269189626 1 "AS140061" +"AS_0070" "14" "Zebrscop" 2 2 NA 1 "AS140070" +"AS_0079" "14" "Zebrscop" 8 13 7.07106781186548 1 "AS140079" +"AS_0081" "14" "Zebrscop" 0.666666666666667 2 1.15470053837925 1 "AS140081" +"AS_0087" "14" "Zebrscop" 17 23 5.29150262212918 1 "AS140087" +"AS_0088" "14" "Zebrscop" 9 23 12.1243556529821 1 "AS140088" +"AS_0092" "14" "Zebrscop" 21.3333333333333 27 7.37111479583199 1 "AS140092" +"AS_0094" "14" "Zebrscop" 0 0 NA 0 "AS140094" +"AS_0097" "14" "Zebrscop" 0 0 NA 0 "AS140097" +"AS_0155" "14" "Zebrscop" 0 0 NA 0 "AS140155" +"AS_0156" "14" "Zebrscop" 0 0 0 0 "AS140156" +"AS_0157" "14" "Zebrscop" 0 0 0 0 "AS140157" +"AS_0159" "14" "Zebrscop" 0 0 0 0 "AS140159" +"BE_S032" "13" "Zebrscop" 1 1 0 1 "BE13S032" +"BE_S050" "13" "Zebrscop" 5.33333333333333 8 2.3094010767585 1 "BE13S050" +"BE_S072" "13" "Zebrscop" 1 1 NA 1 "BE13S072" +"BL_0001" "12" "Zebrscop" 1 1 0 1 "BL120001" +"BL_0005" "12" "Zebrscop" 1 1 NA 1 "BL120005" +"BL_0009" "12" "Zebrscop" 1 1 NA 1 "BL120009" +"BL_0011" "12" "Zebrscop" 3 6 2.64575131106459 1 "BL120011" +"BL_0014" "12" "Zebrscop" 1.5 2 0.707106781186548 1 "BL120014" +"BL_0016" "12" "Zebrscop" 0 0 NA 0 "BL120016" +"BL_0021" "12" "Zebrscop" 1 1 0 1 "BL120021" +"BL_0022" "12" "Zebrscop" 1 1 0 1 "BL120022" +"BL_0024" "12" "Zebrscop" 1 1 NA 1 "BL120024" +"BL_0027" "12" "Zebrscop" 4.33333333333333 6 1.52752523165195 1 "BL120027" +"BL_0028" "12" "Zebrscop" 1 1 NA 1 "BL120028" +"BL_0033" "12" "Zebrscop" 3 5 2 1 "BL120033" +"BL_0039" "12" "Zebrscop" 1 1 NA 1 "BL120039" +"BL_0040" "12" "Zebrscop" 1.66666666666667 2 0.577350269189626 1 "BL120040" +"BL_0041" "12" "Zebrscop" 1 1 NA 1 "BL120041" +"BL_0051" "12" "Zebrscop" 1.33333333333333 2 0.577350269189626 1 "BL120051" +"BL_0062" "12" "Zebrscop" 2.5 3 0.707106781186548 1 "BL120062" +"BL_0068" "12" "Zebrscop" 1.5 2 0.707106781186548 1 "BL120068" +"BL_0075" "12" "Zebrscop" 3 4 1 1 "BL120075" +"BL_0076" "12" "Zebrscop" 3.66666666666667 8 3.78593889720018 1 "BL120076" +"BL_0082" "12" "Zebrscop" 5.33333333333333 9 4.04145188432738 1 "BL120082" +"BL_0085" "12" "Zebrscop" 3.66666666666667 5 1.52752523165195 1 "BL120085" +"BL_0090" "12" "Zebrscop" 1.33333333333333 2 0.577350269189626 1 "BL120090" +"BL_0091" "12" "Zebrscop" 1 1 0 1 "BL120091" +"BL_0093" "12" "Zebrscop" 1 1 NA 1 "BL120093" +"BL_0094" "12" "Zebrscop" 2.66666666666667 4 1.15470053837925 1 "BL120094" +"BL_0097" "12" "Zebrscop" 1 1 NA 1 "BL120097" +"BL_0106" "12" "Zebrscop" 2 2 NA 1 "BL120106" +"BL_0128" "12" "Zebrscop" 1 1 0 1 "BL120128" +"BL_0131" "12" "Zebrscop" 1.33333333333333 2 0.577350269189626 1 "BL120131" +"BL_0133" "12" "Zebrscop" 1 1 NA 1 "BL120133" +"BL_0136" "12" "Zebrscop" 2 2 0 1 "BL120136" +"BL_0137" "12" "Zebrscop" 1 1 0 1 "BL120137" +"BL_0140" "12" "Zebrscop" 2 3 1.4142135623731 1 "BL120140" +"BL_0141" "12" "Zebrscop" 3 3 0 1 "BL120141" +"BL_0154" "12" "Zebrscop" 1 1 NA 1 "BL120154" +"BL_0155" "12" "Zebrscop" 1 1 0 1 "BL120155" +"BL_0161" "12" "Zebrscop" 1 1 NA 1 "BL120161" +"BL_0204" "12" "Zebrscop" 1.5 2 0.707106781186548 1 "BL120204" +"BL_P003" "12" "Zebrscop" 1.66666666666667 2 0.577350269189626 1 "BL12P003" +"BL_P017" "12" "Zebrscop" 3.33333333333333 4 0.577350269189626 1 "BL12P017" +"BL_P077" "12" "Zebrscop" 1.5 2 0.707106781186548 1 "BL12P077" +"BL_P078" "12" "Zebrscop" 4.5 5 0.707106781186548 1 "BL12P078" +"BL_P087" "12" "Zebrscop" 2 3 1.4142135623731 1 "BL12P087" +"BL_P124" "12" "Zebrscop" 2 2 0 1 "BL12P124" +"BO_0007" "12" "Zebrscop" 1 1 0 1 "BO120007" +"BO_0011" "12" "Zebrscop" 2.66666666666667 4 1.52752523165195 1 "BO120011" +"BO_0014" "12" "Zebrscop" 2 3 1 1 "BO120014" +"BO_0026" "12" "Zebrscop" 1 1 NA 1 "BO120026" +"BO_0028" "12" "Zebrscop" 4.33333333333333 5 1.15470053837925 1 "BO120028" +"BO_0029" "12" "Zebrscop" 1 1 NA 1 "BO120029" +"BO_0032" "12" "Zebrscop" 2.5 3 0.707106781186548 1 "BO120032" +"BO_0043" "12" "Zebrscop" 1 1 NA 1 "BO120043" +"BO_0045" "12" "Zebrscop" 2 2 NA 1 "BO120045" +"BO_0054" "12" "Zebrscop" 1.66666666666667 2 0.577350269189626 1 "BO120054" +"BO_0055" "12" "Zebrscop" 1 1 0 1 "BO120055" +"BO_0056" "12" "Zebrscop" 1.66666666666667 3 1.15470053837925 1 "BO120056" +"BO_0095" "12" "Zebrscop" 2 3 1 1 "BO120095" +"BO_0099" "12" "Zebrscop" 1.33333333333333 2 0.577350269189626 1 "BO120099" +"BO_0206" "12" "Zebrscop" 1 1 0 1 "BO120206" +"BO_0207" "12" "Zebrscop" 1 1 NA 1 "BO120207" +"BO_0209" "12" "Zebrscop" 1.66666666666667 2 0.577350269189626 1 "BO120209" +"BO_0212" "12" "Zebrscop" 1.66666666666667 2 0.577350269189626 1 "BO120212" +"BO_0213" "12" "Zebrscop" 2 2 0 1 "BO120213" +"BO_0214" "12" "Zebrscop" 1 1 0 1 "BO120214" +"BO_0215" "12" "Zebrscop" 4.66666666666667 10 4.61880215351701 1 "BO120215" +"BO_0216" "12" "Zebrscop" 1 1 NA 1 "BO120216" +"BO_095B" "12" "Zebrscop" 4.66666666666667 6 1.15470053837925 1 "BO12095B" +"CH_P032" "13" "Zebrscop" 1 1 NA 1 "CH13P032" +"CH_P033" "13" "Zebrscop" 1.5 2 0.707106781186548 1 "CH13P033" +"CH_P034" "13" "Zebrscop" 1 1 NA 1 "CH13P034" +"CH_P037" "13" "Zebrscop" 1.33333333333333 2 0.577350269189626 1 "CH13P037" +"CH_P040" "13" "Zebrscop" 2 3 1 1 "CH13P040" +"CH_P041" "13" "Zebrscop" 3 4 1.73205080756888 1 "CH13P041" +"CH_P055" "13" "Zebrscop" 4.33333333333333 6 1.52752523165195 1 "CH13P055" +"CH_P056" "13" "Zebrscop" 1 1 NA 1 "CH13P056" +"CH_P057" "13" "Zebrscop" 1 1 NA 1 "CH13P057" +"CH_P059" "13" "Zebrscop" 2 2 0 1 "CH13P059" +"CH_P061" "13" "Zebrscop" 5.66666666666667 13 6.42910050732864 1 "CH13P061" +"CH_P063" "13" "Zebrscop" 0 0 0 0 "CH13P063" +"CH_P066" "13" "Zebrscop" 22 22 0 1 "CH13P066" +"CH_P068" "13" "Zebrscop" 8.66666666666667 12 5.77350269189626 1 "CH13P068" +"CH_P071" "13" "Zebrscop" 1.66666666666667 2 0.577350269189626 1 "CH13P071" +"CH_S095" "13" "Zebrscop" 1 1 NA 1 "CH13S095" +"CH_S099" "13" "Zebrscop" 1 1 NA 1 "CH13S099" +"CH_S131" "13" "Zebrscop" 1 1 0 1 "CH13S131" +"CH_S148" "13" "Zebrscop" 1 1 NA 1 "CH13S148" +"CH_S149" "13" "Zebrscop" 1 1 NA 1 "CH13S149" +"CH_S151" "13" "Zebrscop" 1 1 NA 1 "CH13S151" +"CH_S153" "13" "Zebrscop" 0 0 NA 0 "CH13S153" +"CH_S156" "13" "Zebrscop" 2.5 3 0.707106781186548 1 "CH13S156" +"CH_S160" "13" "Zebrscop" 0 0 0 0 "CH13S160" +"CH_S192" "13" "Zebrscop" 6.66666666666667 9 2.51661147842358 1 "CH13S192" +"CS_0007" "13" "Zebrscop" 1.5 2 0.707106781186548 1 "CS130007" +"CS_0011" "13" "Zebrscop" 10.3333333333333 11 0.577350269189626 1 "CS130011" +"CS_0015" "13" "Zebrscop" 1 1 NA 1 "CS130015" +"CS_0018" "13" "Zebrscop" 2 4 1.73205080756888 1 "CS130018" +"CS_0019" "13" "Zebrscop" 1 1 NA 1 "CS130019" +"CS_0021" "13" "Zebrscop" 2 2 0 1 "CS130021" +"CS_0023" "13" "Zebrscop" 2 2 0 1 "CS130023" +"CS_0025" "13" "Zebrscop" 1.5 2 0.707106781186548 1 "CS130025" +"CS_0027" "13" "Zebrscop" 9.33333333333333 11 2.08166599946613 1 "CS130027" +"CS_0031" "13" "Zebrscop" 1 1 0 1 "CS130031" +"CS_0033" "13" "Zebrscop" 1 1 NA 1 "CS130033" +"CS_0035" "13" "Zebrscop" 1.66666666666667 3 1.15470053837925 1 "CS130035" +"CS_0037" "13" "Zebrscop" 0.666666666666667 1 0.577350269189626 1 "CS130037" +"CS_0039" "13" "Zebrscop" 1 1 0 1 "CS130039" +"CS_0042" "13" "Zebrscop" 1 1 NA 1 "CS130042" +"CS_0043" "13" "Zebrscop" 2.5 4 2.12132034355964 1 "CS130043" +"CS_0044" "13" "Zebrscop" 2.66666666666667 3 0.577350269189626 1 "CS130044" +"CS_0045" "13" "Zebrscop" 1.5 2 0.707106781186548 1 "CS130045" +"CS_0047" "13" "Zebrscop" 3 4 1.4142135623731 1 "CS130047" +"CS_0054" "13" "Zebrscop" 1 1 NA 1 "CS130054" +"CS_0060" "13" "Zebrscop" 1 1 0 1 "CS130060" +"CS_0064" "13" "Zebrscop" 2 3 1.4142135623731 1 "CS130064" +"CS_0065" "13" "Zebrscop" 0 0 0 0 "CS130065" +"CS_0069" "13" "Zebrscop" 2 2 0 1 "CS130069" +"CS_0070" "13" "Zebrscop" 3 5 2 1 "CS130070" +"CS_0071" "13" "Zebrscop" 1.33333333333333 2 0.577350269189626 1 "CS130071" +"CS_0075" "13" "Zebrscop" 8 12 6.08276253029822 1 "CS130075" +"CS_0077" "13" "Zebrscop" 1 1 0 1 "CS130077" +"CS_0079" "13" "Zebrscop" 2.66666666666667 3 0.577350269189626 1 "CS130079" +"CS_0081" "13" "Zebrscop" 2.66666666666667 3 0.577350269189626 1 "CS130081" +"CS_0082" "13" "Zebrscop" 2 2 0 1 "CS130082" +"CS_0083" "13" "Zebrscop" 1 1 NA 1 "CS130083" +"CS_0085" "13" "Zebrscop" 1 1 NA 1 "CS130085" +"CS_0092" "13" "Zebrscop" 1 1 0 1 "CS130092" +"CS_0094" "13" "Zebrscop" 1 1 0 1 "CS130094" +"CS_0095" "13" "Zebrscop" 1 1 NA 1 "CS130095" +"CS_0098" "13" "Zebrscop" 5 9 3.60555127546399 1 "CS130098" +"CS_0100" "13" "Zebrscop" 1.66666666666667 2 0.577350269189626 1 "CS130100" +"CS_0101" "13" "Zebrscop" 1 1 NA 1 "CS130101" +"CS_0104" "13" "Zebrscop" 1 1 NA 1 "CS130104" +"CS_0108" "13" "Zebrscop" 4 4 NA 1 "CS130108" +"CS_0109" "13" "Zebrscop" 2.4 2.4 0 1 "CS130109" +"CS_0115" "13" "Zebrscop" 1.33333333333333 2 0.577350269189626 1 "CS130115" +"CS_0116" "13" "Zebrscop" 2.33333333333333 3 0.577350269189626 1 "CS130116" +"CS_0125" "13" "Zebrscop" 2 4 2 1 "CS130125" +"CS_0126" "13" "Zebrscop" 3 3 NA 1 "CS130126" +"CS_0129" "13" "Zebrscop" 2 2 NA 1 "CS130129" +"CS_0130" "13" "Zebrscop" 5.33333333333333 7 1.52752523165195 1 "CS130130" +"CS_0131" "13" "Zebrscop" 2.66666666666667 4 1.15470053837925 1 "CS130131" +"CS_0133" "13" "Zebrscop" 1.66666666666667 3 1.15470053837925 1 "CS130133" +"CS_0135" "13" "Zebrscop" 1 1 NA 1 "CS130135" +"CS_0137" "13" "Zebrscop" 2.66666666666667 4 1.52752523165195 1 "CS130137" +"CS_0140" "13" "Zebrscop" 3.66666666666667 5 1.52752523165195 1 "CS130140" +"CS_0141" "13" "Zebrscop" 8 9.6 1.83303027798234 1 "CS130141" +"CS_0142" "13" "Zebrscop" 2 4 1.73205080756888 1 "CS130142" +"CS_0143" "13" "Zebrscop" 5.33333333333333 7 2.08166599946613 1 "CS130143" +"CS_0144" "13" "Zebrscop" 1 1 0 1 "CS130144" +"CS_0145" "13" "Zebrscop" 1 1 NA 1 "CS130145" +"CS_0146" "13" "Zebrscop" 1 1 0 1 "CS130146" +"CS_0304" "13" "Zebrscop" 1 1 NA 1 "CS130304" +"CS_0305" "13" "Zebrscop" 1 1 0 1 "CS130305" +"CS_0307" "13" "Zebrscop" 1 1 0 1 "CS130307" +"CS_0308" "13" "Zebrscop" 2 3 1.4142135623731 1 "CS130308" +"CS_0309" "13" "Zebrscop" 1 1 NA 1 "CS130309" +"CS_0310" "13" "Zebrscop" 0 0 NA 0 "CS130310" +"CS_0314" "13" "Zebrscop" 2.66666666666667 3 0.577350269189626 1 "CS130314" +"CS_0315" "13" "Zebrscop" 1 1 NA 1 "CS130315" +"CS_0316" "13" "Zebrscop" 2.5 3 0.707106781186548 1 "CS130316" +"CS_0317" "13" "Zebrscop" 3.5 4 0.707106781186548 1 "CS130317" +"CS_0318" "13" "Zebrscop" 5.33333333333333 6 0.577350269189626 1 "CS130318" +"CS_0403" "13" "Zebrscop" 4.33333333333333 6 1.52752523165195 1 "CS130403" +"CS_0404" "13" "Zebrscop" 3 4 1 1 "CS130404" +"CS_0405" "13" "Zebrscop" 1 1 NA 1 "CS130405" +"CS_0407" "13" "Zebrscop" 1.33333333333333 2 0.577350269189626 1 "CS130407" +"CS_0900" "13" "Zebrscop" 0 0 NA 0 "CS130900" +"CS_0904" "13" "Zebrscop" 2 2 0 1 "CS130904" +"CS_0920" "13" "Zebrscop" 1 1 NA 1 "CS130920" +"CS_0921" "13" "Zebrscop" 1 1 0 1 "CS130921" +"CS_0922" "13" "Zebrscop" 1.66666666666667 2 0.577350269189626 1 "CS130922" +"CS_0924" "13" "Zebrscop" 1 1 NA 1 "CS130924" +"CS_0926" "13" "Zebrscop" 4 4 NA 1 "CS130926" +"CS_0950" "13" "Zebrscop" 14.6666666666667 20 6.80685928555405 1 "CS130950" +"CS_0951" "13" "Zebrscop" 1.66666666666667 2 0.577350269189626 1 "CS130951" +"CS_0952" "13" "Zebrscop" 1 1 NA 1 "CS130952" +"CS_0953" "13" "Zebrscop" 1.33333333333333 2 0.577350269189626 1 "CS130953" +"CS_Z104" "13" "Zebrscop" 13 28.5 13.9373598647664 1 "CS13Z104" +"CS_Z106" "13" "Zebrscop" 2 3 1 1 "CS13Z106" +"EN_0001" "15" "Zebrscop" 1 1 0 1 "EN150001" +"EN_0011" "15" "Zebrscop" 2 2 NA 1 "EN150011" +"EN_0012" "15" "Zebrscop" 1.66666666666667 3 1.52752523165195 1 "EN150012" +"EN_0023" "15" "Zebrscop" 0 0 NA 0 "EN150023" +"EN_0027" "15" "Zebrscop" 0 0 NA 0 "EN150027" +"EN_0028" "15" "Zebrscop" 0 0 NA 0 "EN150028" +"EN_0030" "15" "Zebrscop" 1 1 NA 1 "EN150030" +"EN_0032" "15" "Zebrscop" 1.5 2 0.707106781186548 1 "EN150032" +"EN_0045" "15" "Zebrscop" 3.33333333333333 6 2.3094010767585 1 "EN150045" +"EN_0060" "15" "Zebrscop" 2.66666666666667 3 0.577350269189626 1 "EN150060" +"EN_0061" "15" "Zebrscop" 1.5 2 0.707106781186548 1 "EN150061" +"EN_0066" "15" "Zebrscop" 0 0 NA 0 "EN150066" +"EN_0087" "15" "Zebrscop" 0 0 NA 0 "EN150087" +"EN_0090" "15" "Zebrscop" 1 1 NA 1 "EN150090" +"EN_0094" "15" "Zebrscop" 1.5 2 0.707106781186548 1 "EN150094" +"EN_0105" "15" "Zebrscop" 2.33333333333333 4 1.52752523165195 1 "EN150105" +"EN_0108" "15" "Zebrscop" 2 2 NA 1 "EN150108" +"EN_0115" "15" "Zebrscop" 1 1 0 1 "EN150115" +"EN_0116" "15" "Zebrscop" 0 0 0 0 "EN150116" +"EN_0119" "15" "Zebrscop" 0.666666666666667 1 0.577350269189626 1 "EN150119" +"EN_0136" "15" "Zebrscop" 3 5 1.73205080756888 1 "EN150136" +"EN_0137" "15" "Zebrscop" 9.66666666666667 12 2.08166599946613 1 "EN150137" +"EN_0138" "15" "Zebrscop" 3 5 2 1 "EN150138" +"EN_0139" "15" "Zebrscop" 2 2 NA 1 "EN150139" +"EN_0140" "15" "Zebrscop" 2.5 3 0.707106781186548 1 "EN150140" +"EN_0155" "15" "Zebrscop" 0 0 0 0 "EN150155" +"EN_0202" "15" "Zebrscop" 0 0 0 0 "EN150202" +"EN_0300" "15" "Zebrscop" 0.5 1 0.707106781186548 1 "EN150300" +"EN_0301" "15" "Zebrscop" 4.33333333333333 7 2.3094010767585 1 "EN150301" +"EN_0302" "15" "Zebrscop" 0 0 0 0 "EN150302" +"EN_0305" "15" "Zebrscop" 1 1 0 1 "EN150305" +"EN_0307" "15" "Zebrscop" 3.33333333333333 6 2.3094010767585 1 "EN150307" +"EN_0309" "15" "Zebrscop" 1 1 NA 1 "EN150309" +"EN_0311" "15" "Zebrscop" 1 1 NA 1 "EN150311" +"EN_0313" "15" "Zebrscop" 1 1 NA 1 "EN150313" +"EN_0350" "15" "Zebrscop" 2.66666666666667 5 2.08166599946613 1 "EN150350" +"EN_0351" "15" "Zebrscop" 1.33333333333333 2 0.577350269189626 1 "EN150351" +"EN_0352" "15" "Zebrscop" 2 2 NA 1 "EN150352" +"EN_0400" "15" "Zebrscop" 0 0 0 0 "EN150400" +"GN_0007" "13" "Zebrscop" 8 8 NA 1 "GN130007" +"GN_0018" "13" "Zebrscop" 8 8 0 1 "GN130018" +"GN_0030" "13" "Zebrscop" 18.6666666666667 23 7.50555349946513 1 "GN130030" +"GN_0035" "13" "Zebrscop" 8 8 NA 1 "GN130035" +"GN_0047" "13" "Zebrscop" 8 8 0 1 "GN130047" +"GN_0058" "13" "Zebrscop" 8 8 NA 1 "GN130058" +"GN_0060" "13" "Zebrscop" 8 8 NA 1 "GN130060" +"GN_0066" "13" "Zebrscop" 7 7 0 1 "GN130066" +"GN_0069" "13" "Zebrscop" 8 8 0 1 "GN130069" +"GN_0091" "13" "Zebrscop" 10.3333333333333 15 4.04145188432738 1 "GN130091" +"GN_0092" "13" "Zebrscop" 8 8 NA 1 "GN130092" +"GN_0095" "13" "Zebrscop" 0 0 NA 0 "GN130095" +"GN_0105" "13" "Zebrscop" 0 0 NA 0 "GN130105" +"GN_0108" "13" "Zebrscop" 0 0 NA 0 "GN130108" +"GN_0114" "13" "Zebrscop" 7 7 NA 1 "GN130114" +"GN_0121" "13" "Zebrscop" 8 8 NA 1 "GN130121" +"GN_0131" "13" "Zebrscop" 8 8 NA 1 "GN130131" +"GN_0132" "13" "Zebrscop" 6 10 5.29150262212918 1 "GN130132" +"GN_0135" "13" "Zebrscop" 8 8 NA 1 "GN130135" +"GN_0139" "13" "Zebrscop" 8 8 0 1 "GN130139" +"GN_0142" "13" "Zebrscop" 7 7 NA 1 "GN130142" +"GN_0148" "13" "Zebrscop" 25.6666666666667 36 13.0511813003013 1 "GN130148" +"GN_0152" "13" "Zebrscop" 46.6666666666667 56 10.0664459136943 1 "GN130152" +"GN_0163" "13" "Zebrscop" 35.3333333333333 57 19.0875177362939 1 "GN130163" +"GN_0164" "13" "Zebrscop" 8 8 0 1 "GN130164" +"GN_0179" "13" "Zebrscop" 10 10 NA 1 "GN130179" +"GN_0181" "13" "Zebrscop" 25.6666666666667 36 9.29157324317757 1 "GN130181" +"GN_0185" "13" "Zebrscop" 8 8 NA 1 "GN130185" +"GN_0190" "13" "Zebrscop" 7 7 NA 1 "GN130190" +"GN_0192" "13" "Zebrscop" 9 11 2.82842712474619 1 "GN130192" +"GN_0209" "13" "Zebrscop" 8 8 0 1 "GN130209" +"GN_0223" "13" "Zebrscop" 10.6666666666667 12 1.52752523165195 1 "GN130223" +"GN_0224" "13" "Zebrscop" 8 8 NA 1 "GN130224" +"GN_0512" "13" "Zebrscop" 8 8 0 1 "GN130512" +"GN_0513" "13" "Zebrscop" 7 7 NA 1 "GN130513" +"HI_0001" "12" "Zebrscop" 1 1 0 1 "HI120001" +"HI_0002" "12" "Zebrscop" 0 0 NA 0 "HI120002" +"HI_0016" "12" "Zebrscop" 3 5 1.73205080756888 1 "HI120016" +"HI_0018" "12" "Zebrscop" 1 1 0 1 "HI120018" +"HI_0023" "12" "Zebrscop" 1.5 2 0.707106781186548 1 "HI120023" +"HI_0024" "12" "Zebrscop" 3 3 0 1 "HI120024" +"HI_0025" "12" "Zebrscop" 0 0 0 0 "HI120025" +"HI_0026" "12" "Zebrscop" 1.5 2 0.707106781186548 1 "HI120026" +"HI_0029" "12" "Zebrscop" 1 1 NA 1 "HI120029" +"HI_0030" "12" "Zebrscop" 1.33333333333333 2 0.577350269189626 1 "HI120030" +"HI_0042" "12" "Zebrscop" 2 2 NA 1 "HI120042" +"HI_0046" "12" "Zebrscop" 1.66666666666667 3 1.15470053837925 1 "HI120046" +"HI_0058" "12" "Zebrscop" 3 3 NA 1 "HI120058" +"HI_0060" "12" "Zebrscop" 1 1 NA 1 "HI120060" +"HI_0070" "12" "Zebrscop" 1 1 NA 1 "HI120070" +"HI_0086" "12" "Zebrscop" 1 1 NA 1 "HI120086" +"HI_0099" "12" "Zebrscop" 1.33333333333333 2 0.577350269189626 1 "HI120099" +"HI_0149" "12" "Zebrscop" 1 1 NA 1 "HI120149" +"HI_0156" "12" "Zebrscop" 2.33333333333333 4 1.52752523165195 1 "HI120156" +"HI_0171" "12" "Zebrscop" 2 2 0 1 "HI120171" +"HI_0172" "12" "Zebrscop" 1 1 NA 1 "HI120172" +"HI_0173" "12" "Zebrscop" 2.66666666666667 3 0.577350269189626 1 "HI120173" +"HI_0175" "12" "Zebrscop" 3 5 2 1 "HI120175" +"HI_0201" "12" "Zebrscop" 1 1 NA 1 "HI120201" +"HI_0204" "12" "Zebrscop" 1 1 NA 1 "HI120204" +"HI_0205" "12" "Zebrscop" 2 2 NA 1 "HI120205" +"HI_0210" "12" "Zebrscop" 0 0 NA 0 "HI120210" +"HI_0211" "12" "Zebrscop" 1 1 NA 1 "HI120211" +"HU_0031" "14" "Zebrscop" 2 2 NA 1 "HU140031" +"HU_0035" "14" "Zebrscop" 4 4 0 1 "HU140035" +"KO_0156" "07" "Zebrscop" 1.5 2 0.707106781186548 1 "KO070156" +"KO_0022" "08" "Zebrscop" 1 1 NA 1 "KO080022" +"KO_0024" "08" "Zebrscop" 2 2 0 1 "KO080024" +"KO_0033" "08" "Zebrscop" 2 2 0 1 "KO080033" +"KO_0183" "08" "Zebrscop" 2 3 1 1 "KO080183" +"KO_0003" "13" "Zebrscop" 1 1 NA 1 "KO130003" +"KO_0005" "13" "Zebrscop" 1 1 NA 1 "KO130005" +"KO_0010" "13" "Zebrscop" 1 1 NA 1 "KO130010" +"KO_0013" "13" "Zebrscop" 1.66666666666667 2 0.577350269189626 1 "KO130013" +"KO_0031" "13" "Zebrscop" 6.33333333333333 13 5.85946527708232 1 "KO130031" +"KO_0035" "13" "Zebrscop" 1.66666666666667 3 1.15470053837925 1 "KO130035" +"KO_0041" "13" "Zebrscop" 2 2 NA 1 "KO130041" +"KO_0053" "13" "Zebrscop" 1 1 NA 1 "KO130053" +"KO_0059" "13" "Zebrscop" 2 3 1.4142135623731 1 "KO130059" +"KO_0070" "13" "Zebrscop" 1 1 NA 1 "KO130070" +"KO_0071" "13" "Zebrscop" 0 0 NA 0 "KO130071" +"KO_0089" "13" "Zebrscop" 1 1 NA 1 "KO130089" +"KO_0097" "13" "Zebrscop" 1.5 2 0.707106781186548 1 "KO130097" +"KO_0098" "13" "Zebrscop" 1.5 2 0.707106781186548 1 "KO130098" +"KO_0099" "13" "Zebrscop" 1 1 0 1 "KO130099" +"KO_0101" "13" "Zebrscop" 1 1 0 1 "KO130101" +"KO_0108" "13" "Zebrscop" 3.66666666666667 5 1.52752523165195 1 "KO130108" +"KO_0110" "13" "Zebrscop" 2 3 1 1 "KO130110" +"KO_0112" "13" "Zebrscop" 1.66666666666667 3 1.15470053837925 1 "KO130112" +"KO_0113" "13" "Zebrscop" 2 2 0 1 "KO130113" +"KO_0120" "13" "Zebrscop" 1 1 NA 1 "KO130120" +"KO_0129" "13" "Zebrscop" 1 1 NA 1 "KO130129" +"KO_0130" "13" "Zebrscop" 2 2 0 1 "KO130130" +"KO_0131" "13" "Zebrscop" 1.5 2 0.707106781186548 1 "KO130131" +"KO_0132" "13" "Zebrscop" 1 1 NA 1 "KO130132" +"KO_0133" "13" "Zebrscop" 0.5 1 0.707106781186548 1 "KO130133" +"KO_0138" "13" "Zebrscop" 5.66666666666667 9 3.51188458428425 1 "KO130138" +"KO_0139" "13" "Zebrscop" 1.33333333333333 2 0.577350269189626 1 "KO130139" +"KO_0147" "13" "Zebrscop" 2 2 0 1 "KO130147" +"KO_0148" "13" "Zebrscop" 1 1 0 1 "KO130148" +"KO_0154" "13" "Zebrscop" 1 1 NA 1 "KO130154" +"KO_0160" "13" "Zebrscop" 1 1 NA 1 "KO130160" +"KO_0165" "13" "Zebrscop" 1.33333333333333 2 0.577350269189626 1 "KO130165" +"KO_0174" "13" "Zebrscop" 1 1 NA 1 "KO130174" +"KO_0176" "13" "Zebrscop" 2.66666666666667 4 1.52752523165195 1 "KO130176" +"KO_0177" "13" "Zebrscop" 1 1 0 1 "KO130177" +"KO_0202" "13" "Zebrscop" 1 1 0 1 "KO130202" +"KO_0203" "13" "Zebrscop" 1.33333333333333 2 0.577350269189626 1 "KO130203" +"KO_0204" "13" "Zebrscop" 1 1 NA 1 "KO130204" +"KO_0205" "13" "Zebrscop" 5 6 1 1 "KO130205" +"KO_0208" "13" "Zebrscop" 2 2 0 1 "KO130208" +"KO_0209" "13" "Zebrscop" 1 1 NA 1 "KO130209" +"KO_0301" "13" "Zebrscop" 0.666666666666667 1 0.577350269189626 1 "KO130301" +"KO_0302" "13" "Zebrscop" 0.5 1 0.707106781186548 1 "KO130302" +"KO_0304" "13" "Zebrscop" 1 1 NA 1 "KO130304" +"KO_0305" "13" "Zebrscop" 1.33333333333333 2 0.577350269189626 1 "KO130305" +"KO_059b" "13" "Zebrscop" 1 1 0 1 "KO13059b" +"LA_101B" "08" "Zebrscop" 2 3 1 1 "LA08101B" +"LA_0012" "10" "Zebrscop" 2 2 NA 1 "LA100012" +"LA_0028" "10" "Zebrscop" 1 1 NA 1 "LA100028" +"LA_0039" "10" "Zebrscop" 1 1 0 1 "LA100039" +"LI_0021" "14" "Zebrscop" 1.5 2 0.707106781186548 1 "LI140021" +"LI_0022" "14" "Zebrscop" 2.66666666666667 4 1.15470053837925 1 "LI140022" +"LI_0028" "14" "Zebrscop" 1 1 0 1 "LI140028" +"LI_0033" "14" "Zebrscop" 2 3 1 1 "LI140033" +"LI_0035" "14" "Zebrscop" 1 1 NA 1 "LI140035" +"LI_0064" "14" "Zebrscop" 1 1 NA 1 "LI140064" +"LI_0067" "14" "Zebrscop" 1.2 1.2 NA 1 "LI140067" +"LI_0073" "14" "Zebrscop" 1 1 0 1 "LI140073" +"LI_0077" "14" "Zebrscop" 1 1 NA 1 "LI140077" +"LI_0081" "14" "Zebrscop" 2.33333333333333 3 1.15470053837925 1 "LI140081" +"LI_0082" "14" "Zebrscop" 1 1 NA 1 "LI140082" +"LI_0083" "14" "Zebrscop" 2.66666666666667 4 1.52752523165195 1 "LI140083" +"LI_0086" "14" "Zebrscop" 1.33333333333333 2 0.577350269189626 1 "LI140086" +"LI_0089" "14" "Zebrscop" 3.33333333333333 4 1.15470053837925 1 "LI140089" +"LI_0093" "14" "Zebrscop" 1 1 NA 1 "LI140093" +"LI_0094" "14" "Zebrscop" 3 3 NA 1 "LI140094" +"LI_0096" "14" "Zebrscop" 2.66666666666667 4 1.52752523165195 1 "LI140096" +"LI_0100" "14" "Zebrscop" 2.5 3 0.707106781186548 1 "LI140100" +"LI_0102" "14" "Zebrscop" 4.33333333333333 5 0.577350269189626 1 "LI140102" +"LI_0103" "14" "Zebrscop" 3.33333333333333 5 1.52752523165195 1 "LI140103" +"LI_0104" "14" "Zebrscop" 1.33333333333333 2 0.577350269189626 1 "LI140104" +"LI_0110" "14" "Zebrscop" 1 1 NA 1 "LI140110" +"LI_0111" "14" "Zebrscop" 0.666666666666667 2 1.15470053837925 1 "LI140111" +"LI_0113" "14" "Zebrscop" 1.66666666666667 2 0.577350269189626 1 "LI140113" +"LI_0114" "14" "Zebrscop" 1 1 0 1 "LI140114" +"LI_0121" "14" "Zebrscop" 1.25 1.25 0 1 "LI140121" +"LI_0122" "14" "Zebrscop" 1 1 NA 1 "LI140122" +"LI_0129" "14" "Zebrscop" 0.666666666666667 1 0.577350269189626 1 "LI140129" +"LI_0149" "14" "Zebrscop" 0 0 0 0 "LI140149" +"LI_0150" "14" "Zebrscop" 2 3 1.4142135623731 1 "LI140150" +"LI_0151" "14" "Zebrscop" 0.5 1 0.707106781186548 1 "LI140151" +"LI_0152" "14" "Zebrscop" 2.4 3.6 1.2 1 "LI140152" +"LI_0305" "14" "Zebrscop" 2 2 NA 1 "LI140305" +"LI_0307" "14" "Zebrscop" 1 1 NA 1 "LI140307" +"LI_0401" "14" "Zebrscop" 4.33333333333333 5 0.577350269189626 1 "LI140401" +"ME_0004" "13" "Zebrscop" 2 3 1 1 "ME130004" +"ME_0018" "13" "Zebrscop" 3 5 2 1 "ME130018" +"ME_0022" "13" "Zebrscop" 2 2 0 1 "ME130022" +"ME_0034" "13" "Zebrscop" 4 4 NA 1 "ME130034" +"ME_0036" "13" "Zebrscop" 2 2 NA 1 "ME130036" +"ME_0046" "13" "Zebrscop" 3 5 2 1 "ME130046" +"ME_0049" "13" "Zebrscop" 2.5 3 0.707106781186548 1 "ME130049" +"ME_0050" "13" "Zebrscop" 1.5 2 0.707106781186548 1 "ME130050" +"ME_0053" "13" "Zebrscop" 2.66666666666667 4 1.52752523165195 1 "ME130053" +"ME_0054" "13" "Zebrscop" 1 1 0 1 "ME130054" +"ME_0063" "13" "Zebrscop" 1.66666666666667 2 0.577350269189626 1 "ME130063" +"ME_0066" "13" "Zebrscop" 2.66666666666667 4 1.15470053837925 1 "ME130066" +"ME_0071" "13" "Zebrscop" 2.33333333333333 3 1.15470053837925 1 "ME130071" +"ME_0073" "13" "Zebrscop" 1.5 2 0.707106781186548 1 "ME130073" +"ME_0074" "13" "Zebrscop" 1.66666666666667 2 0.577350269189626 1 "ME130074" +"ME_0075" "13" "Zebrscop" 4.66666666666667 6 1.52752523165195 1 "ME130075" +"ME_0089" "13" "Zebrscop" 3 3 0 1 "ME130089" +"ME_0090" "13" "Zebrscop" 1.66666666666667 2 0.577350269189626 1 "ME130090" +"ME_0096" "13" "Zebrscop" 0 0 NA 0 "ME130096" +"ME_0099" "13" "Zebrscop" 3.33333333333333 4 1.15470053837925 1 "ME130099" +"ME_00F1" "13" "Zebrscop" 0 0 0 0 "ME1300F1" +"ME_00F3" "13" "Zebrscop" 0.666666666666667 1 0.577350269189626 1 "ME1300F3" +"ME_00F4" "13" "Zebrscop" 0 0 NA 0 "ME1300F4" +"ME_00F5" "13" "Zebrscop" 1.2 1.2 NA 1 "ME1300F5" +"ME_0101" "13" "Zebrscop" 1 1 0 1 "ME130101" +"ME_0105" "13" "Zebrscop" 3.66666666666667 4 0.577350269189626 1 "ME130105" +"ME_0106" "13" "Zebrscop" 1 1 0 1 "ME130106" +"ME_0107" "13" "Zebrscop" 1.5 2 0.707106781186548 1 "ME130107" +"ME_0108" "13" "Zebrscop" 2.33333333333333 3 1.15470053837925 1 "ME130108" +"ME_0111" "13" "Zebrscop" 2 2 0 1 "ME130111" +"ME_0115" "13" "Zebrscop" 0 0 NA 0 "ME130115" +"ME_0116" "13" "Zebrscop" 9 10 1.73205080756888 1 "ME130116" +"ME_0117" "13" "Zebrscop" 9.33333333333333 13 5.5075705472861 1 "ME130117" +"ME_0120" "13" "Zebrscop" 3 3 0 1 "ME130120" +"ME_0121" "13" "Zebrscop" 1 1 0 1 "ME130121" +"ME_0124" "13" "Zebrscop" 1.5 2 0.707106781186548 1 "ME130124" +"ME_0126" "13" "Zebrscop" 1.66666666666667 2 0.577350269189626 1 "ME130126" +"ME_0128" "13" "Zebrscop" 1.5 2 0.707106781186548 1 "ME130128" +"ME_0129" "13" "Zebrscop" 2 2 NA 1 "ME130129" +"ME_0135" "13" "Zebrscop" 1 1 NA 1 "ME130135" +"ME_0137" "13" "Zebrscop" 1.66666666666667 2 0.577350269189626 1 "ME130137" +"ME_0154" "13" "Zebrscop" 1 1 NA 1 "ME130154" +"ME_0160" "13" "Zebrscop" 2.66666666666667 4 1.15470053837925 1 "ME130160" +"ME_0170" "13" "Zebrscop" 1.2 1.2 NA 1 "ME130170" +"ME_0171" "13" "Zebrscop" 1 1 NA 1 "ME130171" +"ME_0173" "13" "Zebrscop" 1 1 NA 1 "ME130173" +"ME_0179" "13" "Zebrscop" 0 0 NA 0 "ME130179" +"ME_0190" "13" "Zebrscop" 1.33333333333333 2 0.577350269189626 1 "ME130190" +"ME_0207" "13" "Zebrscop" 1 1 NA 1 "ME130207" +"ME_0208" "13" "Zebrscop" 2 3 1.4142135623731 1 "ME130208" +"ME_0209" "13" "Zebrscop" 1.33333333333333 2 0.577350269189626 1 "ME130209" +"ME_0210" "13" "Zebrscop" 3 5 2.82842712474619 1 "ME130210" +"ME_0212" "13" "Zebrscop" 1 1 NA 1 "ME130212" +"ME_0213" "13" "Zebrscop" 1 1 NA 1 "ME130213" +"ME_0215" "13" "Zebrscop" 1 1 0 1 "ME130215" +"ME_0241" "13" "Zebrscop" 3 3 NA 1 "ME130241" +"ME_0246" "13" "Zebrscop" 1 1 NA 1 "ME130246" +"ME_0248" "13" "Zebrscop" 1.2 1.2 0 1 "ME130248" +"ME_0252" "13" "Zebrscop" 2.33333333333333 3 1.15470053837925 1 "ME130252" +"ME_0260" "13" "Zebrscop" 3 3 0 1 "ME130260" +"ME_0262" "13" "Zebrscop" 1.66666666666667 2 0.577350269189626 1 "ME130262" +"ME_0265" "13" "Zebrscop" 1 1 NA 1 "ME130265" +"ME_0266" "13" "Zebrscop" 5.66666666666667 6 0.577350269189626 1 "ME130266" +"ME_0267" "13" "Zebrscop" 0 0 NA 0 "ME130267" +"ME_0268" "13" "Zebrscop" 2.33333333333333 3 0.577350269189626 1 "ME130268" +"ME_0273" "13" "Zebrscop" 2 2 NA 1 "ME130273" +"ME_0400" "13" "Zebrscop" 3 5 2.82842712474619 1 "ME130400" +"ME_0402" "13" "Zebrscop" 1 1 NA 1 "ME130402" +"ME_0403" "13" "Zebrscop" 7 9 1.73205080756888 1 "ME130403" +"ME_102PM" "13" "Zebrscop" 6 9.6 4.32666153055679 1 "ME13102PM" +"ME_168PM" "13" "Zebrscop" 1 1 NA 1 "ME13168PM" +"ME_47PM" "13" "Zebrscop" 3.66666666666667 4 0.577350269189626 1 "ME1347PM" +"MK_0425" "08" "Zebrscop" 2.66666666666667 4 1.52752523165195 1 "MK080425" +"MK_0426" "08" "Zebrscop" 1 1 NA 1 "MK080426" +"MK_0427" "08" "Zebrscop" 3 4 1.4142135623731 1 "MK080427" +"MK_0430" "08" "Zebrscop" 2 2 NA 1 "MK080430" +"MK_0440" "08" "Zebrscop" 1.66666666666667 2 0.577350269189626 1 "MK080440" +"MK_0453" "08" "Zebrscop" 1 1 0 1 "MK080453" +"MK_0454" "08" "Zebrscop" 1.5 2 0.707106781186548 1 "MK080454" +"MK_0458" "08" "Zebrscop" 1 1 NA 1 "MK080458" +"MK_0462" "08" "Zebrscop" 1 1 0 1 "MK080462" +"MK_0207" "09" "Zebrscop" 1.33333333333333 2 0.577350269189626 1 "MK090207" +"MK_0208" "09" "Zebrscop" 1.33333333333333 2 0.577350269189626 1 "MK090208" +"MK_0211" "09" "Zebrscop" 1.66666666666667 2 0.577350269189626 1 "MK090211" +"MK_0225" "09" "Zebrscop" 2 2 0 1 "MK090225" +"MK_0227" "09" "Zebrscop" 1.66666666666667 3 1.15470053837925 1 "MK090227" +"MK_0228" "09" "Zebrscop" 3.5 5 2.12132034355964 1 "MK090228" +"MK_0231" "09" "Zebrscop" 1 1 NA 1 "MK090231" +"MK_0234" "09" "Zebrscop" 1 1 NA 1 "MK090234" +"MK_0248" "09" "Zebrscop" 2 2 0 1 "MK090248" +"MK_0249" "09" "Zebrscop" 1 1 NA 1 "MK090249" +"MK_0250" "09" "Zebrscop" 1 1 NA 1 "MK090250" +"MK_0200" "10" "Zebrscop" 3 4 1.4142135623731 1 "MK100200" +"MK_0205" "10" "Zebrscop" 1 1 NA 1 "MK100205" +"MK_0206" "10" "Zebrscop" 2 2 NA 1 "MK100206" +"MK_0210" "10" "Zebrscop" 1.66666666666667 2 0.577350269189626 1 "MK100210" +"MK_0213" "10" "Zebrscop" 2.5 3 0.707106781186548 1 "MK100213" +"MK_0215" "10" "Zebrscop" 1 1 0 1 "MK100215" +"MK_0219" "10" "Zebrscop" 3.66666666666667 5 2.3094010767585 1 "MK100219" +"MK_0221" "10" "Zebrscop" 1 1 NA 1 "MK100221" +"MK_0230" "10" "Zebrscop" 1 1 0 1 "MK100230" +"MK_0231" "10" "Zebrscop" 1.5 2 0.707106781186548 1 "MK100231" +"MK_0234" "10" "Zebrscop" 1.5 2 0.707106781186548 1 "MK100234" +"MK_0240" "10" "Zebrscop" 1.5 2 0.707106781186548 1 "MK100240" +"MK_0249" "10" "Zebrscop" 1 1 0 1 "MK100249" +"OU_0002" "09" "Zebrscop" 1 1 0 1 "OU090002" +"OU_0005" "09" "Zebrscop" 0 0 NA 0 "OU090005" +"OU_0006" "09" "Zebrscop" 0 0 NA 0 "OU090006" +"OU_0020" "09" "Zebrscop" 0 0 NA 0 "OU090020" +"OU_0025" "09" "Zebrscop" 1 1 0 1 "OU090025" +"OU_0061" "09" "Zebrscop" 1 1 NA 1 "OU090061" +"OU_0108" "09" "Zebrscop" 1 1 NA 1 "OU090108" +"OU_0116" "09" "Zebrscop" 2 2 NA 1 "OU090116" +"OU_0123" "09" "Zebrscop" 1.5 2 0.707106781186548 1 "OU090123" +"OU_0L13" "09" "Zebrscop" 1.33333333333333 2 0.577350269189626 1 "OU090L13" +"OU_0L14" "09" "Zebrscop" 2 3 1 1 "OU090L14" +"OU_0L22" "09" "Zebrscop" 1 1 NA 1 "OU090L22" +"OU_0L51" "09" "Zebrscop" 1 1 NA 1 "OU090L51" +"OU_0L52" "09" "Zebrscop" 2 3 1 1 "OU090L52" +"OU_0L82" "09" "Zebrscop" 1 1 NA 1 "OU090L82" +"OU_106C" "09" "Zebrscop" 2.33333333333333 3 1.15470053837925 1 "OU09106C" +"OU_107C" "09" "Zebrscop" 3.66666666666667 4 0.577350269189626 1 "OU09107C" +"OU_123B" "09" "Zebrscop" 1 1 0 1 "OU09123B" +"OU_129B" "09" "Zebrscop" 1.33333333333333 2 0.577350269189626 1 "OU09129B" +"OU_L12R" "09" "Zebrscop" 2 3 1 1 "OU09L12R" +"OU_L14R" "09" "Zebrscop" 1 1 0 1 "OU09L14R" +"OU_L22R" "09" "Zebrscop" 2.33333333333333 3 0.577350269189626 1 "OU09L22R" +"OU_L36R" "09" "Zebrscop" 3 3 0 1 "OU09L36R" +"OU_L51R" "09" "Zebrscop" 1.66666666666667 2 0.577350269189626 1 "OU09L51R" +"OU_L52R" "09" "Zebrscop" 1.5 2 0.707106781186548 1 "OU09L52R" +"PA_0004" "17" "Zebrscop" 0 0 NA 0 "PA170004" +"PA_0005" "17" "Zebrscop" 0 0 0 0 "PA170005" +"PA_0010" "17" "Zebrscop" 0 0 NA 0 "PA170010" +"PA_0011" "17" "Zebrscop" 1.33333333333333 2 0.577350269189626 1 "PA170011" +"PA_0012" "17" "Zebrscop" 2 2 NA 1 "PA170012" +"PA_0013" "17" "Zebrscop" 0 0 0 0 "PA170013" +"PA_0014" "17" "Zebrscop" 1.33333333333333 2 0.577350269189626 1 "PA170014" +"PA_0015" "17" "Zebrscop" 0 0 NA 0 "PA170015" +"PA_0016" "17" "Zebrscop" 1.33333333333333 2 0.577350269189626 1 "PA170016" +"PA_0017" "17" "Zebrscop" 0 0 0 0 "PA170017" +"PA_0018" "17" "Zebrscop" 0.5 1 0.707106781186548 1 "PA170018" +"PA_0020" "17" "Zebrscop" 1 1 NA 1 "PA170020" +"PA_0022" "17" "Zebrscop" 1 1 0 1 "PA170022" +"PA_0025" "17" "Zebrscop" 1 1 NA 1 "PA170025" +"PA_0027" "17" "Zebrscop" 1 1 0 1 "PA170027" +"PA_0030" "17" "Zebrscop" 2 2 NA 1 "PA170030" +"PA_0039" "17" "Zebrscop" 0 0 0 0 "PA170039" +"PA_0041" "17" "Zebrscop" 3 4 1 1 "PA170041" +"PA_0042" "17" "Zebrscop" 0 0 0 0 "PA170042" +"PA_0043" "17" "Zebrscop" 1.33333333333333 2 0.577350269189626 1 "PA170043" +"PA_0044" "17" "Zebrscop" 1 1 NA 1 "PA170044" +"PA_0050" "17" "Zebrscop" 1 2 1 1 "PA170050" +"PA_0051" "17" "Zebrscop" 0.5 1 0.707106781186548 1 "PA170051" +"PA_0054" "17" "Zebrscop" 0 0 NA 0 "PA170054" +"PA_0055" "17" "Zebrscop" 1 1 NA 1 "PA170055" +"PA_0056" "17" "Zebrscop" 4 5 1.73205080756888 1 "PA170056" +"PA_0057" "17" "Zebrscop" 9.66666666666667 17 6.35085296108588 1 "PA170057" +"PA_0058" "17" "Zebrscop" 18 25 6.08276253029822 1 "PA170058" +"PA_0059" "17" "Zebrscop" 0 0 NA 0 "PA170059" +"PA_0060" "17" "Zebrscop" 5.33333333333333 8 2.51661147842358 1 "PA170060" +"PA_0066" "17" "Zebrscop" 2 2 NA 1 "PA170066" +"PA_0068" "17" "Zebrscop" 1 1 0 1 "PA170068" +"PA_0074" "17" "Zebrscop" 0 0 NA 0 "PA170074" +"PA_0079" "17" "Zebrscop" 1 1 NA 1 "PA170079" +"PA_0080" "17" "Zebrscop" 5.66666666666667 7 1.52752523165195 1 "PA170080" +"PA_0081" "17" "Zebrscop" 2.5 4 2.12132034355964 1 "PA170081" +"PA_0083" "17" "Zebrscop" 1 1 NA 1 "PA170083" +"PA_0084" "17" "Zebrscop" 2.33333333333333 3 1.15470053837925 1 "PA170084" +"PA_0088" "17" "Zebrscop" 1.5 2 0.707106781186548 1 "PA170088" +"PA_0091" "17" "Zebrscop" 1.33333333333333 2 0.577350269189626 1 "PA170091" +"PA_0093" "17" "Zebrscop" 1 1 0 1 "PA170093" +"PA_0094" "17" "Zebrscop" 3 3 NA 1 "PA170094" +"PA_0100" "17" "Zebrscop" 0 0 NA 0 "PA170100" +"PE_0007" "14" "Zebrscop" 1 1 0 1 "PE140007" +"PE_0025" "14" "Zebrscop" 0 0 NA 0 "PE140025" +"PE_0029" "14" "Zebrscop" 0 0 NA 0 "PE140029" +"PE_0031" "14" "Zebrscop" 1 1 0 1 "PE140031" +"PE_0033" "14" "Zebrscop" 0 0 0 0 "PE140033" +"PE_0035" "14" "Zebrscop" 2.33333333333333 3 1.15470053837925 1 "PE140035" +"PO_0001" "12" "Zebrscop" 1 1 NA 1 "PO120001" +"PO_0004" "12" "Zebrscop" 1.5 2 0.707106781186548 1 "PO120004" +"PO_0007" "12" "Zebrscop" 2 3 1 1 "PO120007" +"PO_0018" "12" "Zebrscop" 1 1 NA 1 "PO120018" +"PO_0028" "12" "Zebrscop" 2 3 1.4142135623731 1 "PO120028" +"PO_0045" "12" "Zebrscop" 2.33333333333333 3 0.577350269189626 1 "PO120045" +"PO_0048" "12" "Zebrscop" 1 1 NA 1 "PO120048" +"PO_0053" "12" "Zebrscop" 1 1 0 1 "PO120053" +"PO_0066" "12" "Zebrscop" 1 1 0 1 "PO120066" +"PO_0092" "12" "Zebrscop" 6.16666666666667 8.5 2.25462487641145 1 "PO120092" +"PO_0094" "12" "Zebrscop" 1 1 0 1 "PO120094" +"PO_0096" "12" "Zebrscop" 2 3 1 1 "PO120096" +"PO_0121" "12" "Zebrscop" 5 6 1.4142135623731 1 "PO120121" +"PO_0134" "12" "Zebrscop" 0 0 NA 0 "PO120134" +"PO_0136" "12" "Zebrscop" 1 1 NA 1 "PO120136" +"PO_0200" "12" "Zebrscop" 2 2 NA 1 "PO120200" +"PO_0203" "12" "Zebrscop" 3.6 4 0.565685424949238 1 "PO120203" +"PO_0205" "12" "Zebrscop" 1 1 NA 1 "PO120205" +"PO_0206" "12" "Zebrscop" 1.33333333333333 2 0.577350269189626 1 "PO120206" +"PO_0233" "12" "Zebrscop" 2 2 NA 1 "PO120233" +"RD_0219" "07" "Zebrscop" 0 0 0 0 "RD070219" +"RD_0230" "07" "Zebrscop" 0 0 NA 0 "RD070230" +"RD_0031" "08" "Zebrscop" 0 0 NA 0 "RD080031" +"RD_0103" "09" "Zebrscop" 0 0 NA 0 "RD090103" +"RD_0105" "09" "Zebrscop" 0 0 NA 0 "RD090105" +"RD_0108" "09" "Zebrscop" 0 0 NA 0 "RD090108" +"RD_0109" "09" "Zebrscop" 0 0 NA 0 "RD090109" +"RD_0107" "10" "Zebrscop" 0 0 NA 0 "RD100107" +"RL_0250" "07" "Zebrscop" 1 1 NA 1 "RL070250" +"RL_0145" "08" "Zebrscop" 1 1 0 1 "RL080145" +"RL_0078" "09" "Zebrscop" 1.33333333333333 2 0.577350269189626 1 "RL090078" +"RL_0089" "09" "Zebrscop" 2 2 0 1 "RL090089" +"RL_0093" "09" "Zebrscop" 1 1 0 1 "RL090093" +"RL_0066" "10" "Zebrscop" 1 1 NA 1 "RL100066" +"RL_0076" "10" "Zebrscop" 1.33333333333333 2 0.577350269189626 1 "RL100076" +"RS_0169" "07" "Zebrscop" 2.33333333333333 3 0.577350269189626 1 "RS070169" +"RS_0189" "07" "Zebrscop" 1 1 0 1 "RS070189" +"SI_0078" "07" "Zebrscop" 1 1 NA 1 "SI070078" +"SI_0079" "07" "Zebrscop" 8.33333333333333 12 4.04145188432738 1 "SI070079" +"SI_0080" "07" "Zebrscop" 2 3 1.4142135623731 1 "SI070080" +"SI_0082" "07" "Zebrscop" 0 0 NA 0 "SI070082" +"SI_0197" "07" "Zebrscop" 0 0 NA 0 "SI070197" +"SI_0222" "07" "Zebrscop" 0 0 NA 0 "SI070222" +"SI_0194" "08" "Zebrscop" 0 0 0 0 "SI080194" +"WA_0002" "14" "Zebrscop" 1 1 0 1 "WA140002" diff -r 000000000000 -r 0778efa9eb2e test-data/Simple_statistics_on_Presence_absence_sansszcl_cropped.txt --- /dev/null Thu Jan 01 00:00:00 1970 +0000 +++ b/test-data/Simple_statistics_on_Presence_absence_sansszcl_cropped.txt Tue Jul 21 06:00:51 2020 -0400 @@ -0,0 +1,614 @@ + +################################################## +Metrics and factors (and possible units/selections): + + Metrics: number + aggregated per observation units. + +Analyses factor(s): + * year + * habitat + * site + * + +######################## +Base statistics: + + Min. 1st Qu. Median Mean 3rd Qu. Max. + 0.0000000 0.0000000 0.0000000 0.8886154 1.0000000 46.6666667 + sd N + 2.3900000 2133.0000000 + +######################################### +Statistics per combination of factor levels: + + Min. 1st Qu. Median +2007.Algueraie.Ilot Signal 0 0.00000000 0.0000000 +2007.Algueraie.Radiales Signal laregnere 0 0.00000000 0.0000000 +2007.Corail vivant.Ilot Signal 0 0.00000000 0.0000000 +2007.Corail vivant.NA 0 0.00000000 0.0000000 +2007.Corail vivant.Recif Senez 0 0.00000000 0.0000000 +2007.Detritique.Recif Laregnere 0 0.00000000 0.0000000 +2007.Fond lagonaire.Ilot Signal 0 0.00000000 0.0000000 +2007.Herbier.Ilot Signal 0 0.00000000 0.0000000 +2008.Corail vivant.Abore 0 0.00000000 0.0000000 +2008.Corail vivant.Laregnere 0 0.16666667 0.3333333 +2008.Corail vivant.NA 0 0.00000000 0.0000000 +2008.Detritique.Mbe Kouen 0 0.00000000 0.0000000 +2008.Detritique.NA 0 0.00000000 0.0000000 +2008.Detritique.Recif Laregnere 0 0.00000000 0.0000000 +2008.Fond lagonaire.Abore 0 0.00000000 0.0000000 +2008.Fond lagonaire.NA 0 0.00000000 0.0000000 +2008.Herbier.Ilot Signal 0 0.00000000 0.0000000 +2008.Herbier.Radiales Signal laregnere 0 0.00000000 0.0000000 +2009.Algueraie.NA 0 0.00000000 0.0000000 +2009.Corail vivant.Abore 0 0.00000000 0.0000000 +2009.Corail vivant.Mbe Kouen 0 0.00000000 0.0000000 +2009.Corail vivant.NA 0 0.00000000 0.0000000 +2009.Corail vivant.Recif Laregnere 0 0.00000000 0.0000000 +2009.Detritique.Mbe Kouen 0 0.00000000 0.0000000 +2009.Detritique.NA 0 0.00000000 0.0000000 +2009.Detritique.Recif Laregnere 0 0.00000000 0.0000000 +2009.Fond lagonaire.Mbe Kouen 0 0.00000000 0.0000000 +2009.Fond lagonaire.NA 0 0.00000000 0.0000000 +2009.Fond lagonaire.Radiales Signal laregnere 0 0.00000000 0.0000000 +2009.Herbier.Radiales Signal laregnere 0 0.00000000 0.0000000 +2010.Corail vivant.Abore 0 0.00000000 0.0000000 +2010.Detritique.Abore 0 0.00000000 0.0000000 +2010.Detritique.Laregnere 0 0.00000000 0.0000000 +2010.Detritique.Mbe Kouen 0 0.00000000 0.0000000 +2010.Detritique.Recif Laregnere 0 0.00000000 0.0000000 +2010.Fond lagonaire.Abore 0 0.00000000 0.0000000 +2010.Fond lagonaire.Laregnere 0 0.00000000 0.0000000 +2010.Fond lagonaire.Mbe Kouen 0 0.00000000 0.0000000 +2010.Herbier.Radiales Signal laregnere 0 0.00000000 0.0000000 +2012.Corail vivant.Baie Port Bouquet 0 0.00000000 0.0000000 +2012.Corail vivant.Cap Goulvain 0 0.00000000 0.0000000 +2012.Corail vivant.Deva 0 0.00000000 0.0000000 +2012.Corail vivant.Grand recif Ngoe 0 0.00000000 0.0000000 +2012.Corail vivant.Ilot de sable 0 0.00000000 0.0000000 +2012.Corail vivant.Ilots 0 0.00000000 0.0000000 +2012.Corail vivant.NA 0 0.00000000 0.0000000 +2012.Corail vivant.Poe 0 0.00000000 0.0000000 +2012.Corail vivant.Recif Doiman 0 0.00000000 0.0000000 +2012.Detritique.Cap Goulvain 0 0.00000000 0.0000000 +2012.Detritique.Deva 0 0.00000000 0.0000000 +2012.Detritique.Dongan Hienga 0 0.00000000 0.0000000 +2012.Detritique.Dongan Hiengu 0 0.00000000 0.0000000 +2012.Detritique.Faille aux requins 0 0.00000000 0.0000000 +2012.Detritique.Gouaro 0 0.00000000 0.0000000 +2012.Detritique.Grand recif Ngoe 0 0.00000000 0.0000000 +2012.Detritique.Ile Verte 0 0.00000000 0.0000000 +2012.Detritique.Ilot de sable 0 0.00000000 0.0000000 +2012.Detritique.Ilot Hiengabat 0 0.00000000 0.0000000 +2012.Detritique.Ilot Hienghene 0 0.00000000 0.0000000 +2012.Detritique.Ilot Tiguit 0 0.00000000 0.0000000 +2012.Detritique.Les Charpentiers 0 0.00000000 0.0000000 +2012.Detritique.Poe 0 0.00000000 0.0000000 +2012.Detritique.Recif Doiman 0 0.00000000 0.0000000 +2012.Detritique.Recif Douok 0 0.00000000 0.0000000 +2012.Detritique.Recif Mengalia 0 0.00000000 0.0000000 +2012.Detritique.Recif Pidanain 0 0.00000000 0.0000000 +2012.Fond lagonaire.Baie Port Bouquet 0 0.00000000 0.0000000 +2012.Fond lagonaire.Deva 0 0.00000000 0.0000000 +2012.Fond lagonaire.Faille aux requins 0 0.00000000 0.0000000 +2012.Fond lagonaire.Grand recif Ngoe 0 0.00000000 0.0000000 +2012.Fond lagonaire.Ile Verte 0 0.00000000 0.0000000 +2012.Fond lagonaire.Ilots 0 0.00000000 0.0000000 +2012.Fond lagonaire.NA 0 0.00000000 0.0000000 +2012.Fond lagonaire.Poe 0 0.00000000 0.0000000 +2012.Fond lagonaire.Recif Doiman 0 0.00000000 0.0000000 +2013.Algueraie.Lagon Mba Mbo 0 0.00000000 0.0000000 +2013.Algueraie.Seche Croissant 0 3.00000000 6.0000000 +2013.Corail vivant.Bampton nord 0 0.00000000 0.0000000 +2013.Corail vivant.Barriere nord-ouest 0 0.00000000 0.0000000 +2013.Corail vivant.Barriere ouest 0 0.00000000 0.0000000 +2013.Corail vivant.Canard 0 0.00000000 0.0000000 +2013.Corail vivant.Corne sud 0 0.00000000 0.0000000 +2013.Corail vivant.Ilot Gi 0 0.00000000 0.0000000 +2013.Corail vivant.Ilot Kouare 0 0.00000000 0.0000000 +2013.Corail vivant.Ilot Maitre 0 0.00000000 0.0000000 +2013.Corail vivant.Ilot Mbore 0 0.00000000 0.0000000 +2013.Corail vivant.Ilot Ndo 0 0.00000000 0.0000000 +2013.Corail vivant.Ilot Nge 0 0.00000000 0.0000000 +2013.Corail vivant.Ilot Signal 0 0.00000000 0.0000000 +2013.Corail vivant.Ilot Ua 0 0.00000000 0.0000000 +2013.Corail vivant.Ilot Uatio 0 0.00000000 0.3333333 +2013.Corail vivant.La Palette 0 0.00000000 0.0000000 +2013.Corail vivant.Laregnere 0 0.00000000 0.0000000 +2013.Corail vivant.Mba 0 0.00000000 0.0000000 +2013.Corail vivant.Mbo 0 1.16666667 2.3333333 +2013.Corail vivant.NA 0 0.00000000 0.0000000 +2013.Corail vivant.Recif Bellona milieu 0 0.00000000 0.0000000 +2013.Corail vivant.Recif Bellona Nord-ouest 0 0.00000000 0.0000000 +2013.Corail vivant.Recif Cimenia 0 0.00000000 0.0000000 +2013.Corail vivant.Recif de Prony 0 0.00000000 0.0000000 +2013.Corail vivant.Recif Garanhua 0 0.00000000 0.0000000 +2013.Corail vivant.Recif Mbe Kouen 0 0.00000000 0.0000000 +2013.Corail vivant.Recif Neokouie 0 0.00000000 0.0000000 +2013.Corail vivant.Recif Neokumbi 0 0.00000000 0.0000000 +2013.Corail vivant.Recif Nogumatiugi 0 0.00000000 0.0000000 +2013.Corail vivant.Recif Purembi 0 0.00000000 0.0000000 +2013.Corail vivant.Recif Senez 0 0.00000000 0.0000000 +2013.Corail vivant.Recif Tiendi 0 0.00000000 0.0000000 +2013.Corail vivant.Recif Tironhua 0 0.00000000 0.0000000 +2013.Corail vivant.Recif Tiukuru 0 0.00000000 0.0000000 +2013.Corail vivant.Recif Ua 0 0.00000000 0.0000000 +2013.Corail vivant.Recif Umadu 0 0.00000000 0.0000000 +2013.Corail vivant.Recif Umbei 0 0.00000000 0.0000000 +2013.Detritique.Barriere nord-ouest 0 0.00000000 0.0000000 +2013.Detritique.Goeland 0 0.00000000 0.0000000 +2013.Detritique.Ilot Gi 0 0.00000000 0.0000000 +2013.Detritique.Ilot Kouare 0 0.00000000 0.0000000 +2013.Detritique.Ilot Tere 0 0.00000000 0.0000000 +2013.Detritique.La Palette 0 0.00000000 0.0000000 +2013.Detritique.Mbe Kouen 0 2.83333333 5.6666667 +2013.Detritique.Mbo 0 0.00000000 0.0000000 +2013.Detritique.NA 0 0.00000000 0.0000000 +2013.Detritique.Recif Cimenia 0 0.16666667 0.3333333 +2013.Detritique.Recif Garanhua 0 0.00000000 0.3333333 +2013.Detritique.Recif Ie 0 0.00000000 0.0000000 +2013.Detritique.Recif Kanre 0 0.00000000 0.0000000 +2013.Detritique.Recif Mbe Kouen 0 0.00000000 0.0000000 +2013.Detritique.Recif Ndunekunie 0 0.00000000 0.0000000 +2013.Detritique.Recif Nogumatiugi 0 0.00000000 0.0000000 +2013.Detritique.Recif Tironhua 0 0.00000000 0.0000000 +2013.Detritique.Seche Croissant 0 0.00000000 0.0000000 +2013.Fond lagonaire.Bampton nord 0 0.00000000 0.0000000 +2013.Fond lagonaire.Barriere nord-ouest 0 0.00000000 0.0000000 +2013.Fond lagonaire.Corne sud 0 0.00000000 0.0000000 +2013.Fond lagonaire.Crouy 0 0.00000000 0.0000000 +2013.Fond lagonaire.Ilot Koko 0 0.00000000 0.0000000 +2013.Fond lagonaire.Lagon Mba Mbo 0 0.00000000 0.0000000 +2013.Fond lagonaire.Mba 0 0.00000000 0.0000000 +2013.Fond lagonaire.Mbe Kouen 0 0.00000000 0.0000000 +2013.Fond lagonaire.Mbo 0 0.00000000 0.0000000 +2013.Fond lagonaire.NA 0 0.00000000 0.0000000 +2013.Fond lagonaire.Recif Bellona Sud 0 0.00000000 0.0000000 +2013.Fond lagonaire.Recif Cimenia 0 0.00000000 0.0000000 +2013.Fond lagonaire.Recif Ia 0 0.00000000 0.0000000 +2013.Fond lagonaire.Recif Ie 0 0.00000000 0.0000000 +2013.Fond lagonaire.Recif Mbe Kouen 0 0.00000000 0.0000000 +2013.Fond lagonaire.Recif Ndunekunie 0 0.00000000 0.0000000 +2013.Fond lagonaire.Recif Neokouie 0 0.00000000 0.0000000 +2013.Fond lagonaire.Recif Neokumbi 0 0.00000000 0.0000000 +2013.Fond lagonaire.Recif Nogumatiugi 0 0.00000000 0.0000000 +2013.Fond lagonaire.Recif Puakue 0 0.00000000 0.0000000 +2013.Fond lagonaire.Recif Purembi 0 0.00000000 0.0000000 +2013.Fond lagonaire.Recif Senez 0 0.00000000 0.0000000 +2013.Fond lagonaire.Recif Umbei 0 0.00000000 0.0000000 +2013.Fond lagonaire.Seche Croissant 0 0.00000000 0.0000000 +2013.Herbier.Ilot Signal 0 0.00000000 0.0000000 +2013.Herbier.Laregnere 0 0.00000000 0.0000000 +2014.Corail vivant.Baie Xepenehe 0 0.00000000 0.0000000 +2014.Corail vivant.Grand Astrolabe 0 0.00000000 0.0000000 +2014.Corail vivant.Jinek 0 0.00000000 0.0000000 +2014.Corail vivant.Petit Astrolabe 0 0.00000000 0.0000000 +2014.Corail vivant.Petrie 0 0.00000000 0.0000000 +2014.Corail vivant.Pointe Easo 0 0.00000000 0.1666667 +2014.Corail vivant.Recif Jinek 0 0.00000000 0.0000000 +2014.Corail vivant.Walpole 0 0.00000000 0.0000000 +2014.Detritique.Baie Xepenehe 0 0.00000000 0.0000000 +2014.Detritique.Grand Astrolabe 0 0.00000000 0.0000000 +2014.Detritique.Hunter 0 0.00000000 0.0000000 +2014.Detritique.Jinek 0 0.00000000 0.0000000 +2014.Detritique.Petrie 0 0.00000000 0.0000000 +2014.Fond lagonaire.Baie Xepenehe 0 0.00000000 0.0000000 +2014.Fond lagonaire.Grand Astrolabe 0 0.00000000 0.0000000 +2014.Fond lagonaire.Jinek 0 0.00000000 0.3333333 +2015.Corail vivant.Grand Guilbert 0 0.25000000 0.5000000 +2015.Corail vivant.Huon 0 0.00000000 0.0000000 +2015.Corail vivant.Merite 0 0.00000000 0.0000000 +2015.Corail vivant.Pelotas 0 0.00000000 1.0000000 +2015.Corail vivant.Petit Guilbert 0 0.00000000 0.0000000 +2015.Corail vivant.Portail 0 0.00000000 0.0000000 +2015.Corail vivant.Surprise 0 0.00000000 0.0000000 +2015.Detritique.Huon 0 0.08333333 0.4166667 +2015.Detritique.Portail 0 0.00000000 0.0000000 +2015.Fond lagonaire.Huon 0 0.00000000 0.0000000 +2015.Fond lagonaire.Portail 0 0.00000000 0.0000000 +2017.Corail vivant.Grand Astrolabe 0 0.00000000 0.3333333 +2017.Corail vivant.Petit Astrolabe 0 0.00000000 0.0000000 +2017.Corail vivant.Petrie 0 0.00000000 0.3333333 +2017.Detritique.Grand Astrolabe 0 0.00000000 0.0000000 +2017.Detritique.Petit Astrolabe 0 0.00000000 0.0000000 +2017.Detritique.Petrie 0 0.00000000 0.0000000 +2017.Fond lagonaire.Grand Astrolabe 0 0.00000000 0.0000000 +2017.Fond lagonaire.Petit Astrolabe 0 0.00000000 0.0000000 +2017.Fond lagonaire.Petrie 0 0.00000000 0.0000000 + Mean 3rd Qu. Max. +2007.Algueraie.Ilot Signal 0.3333333 0.5000000 1.000000 +2007.Algueraie.Radiales Signal laregnere 0.3333333 0.7500000 1.000000 +2007.Corail vivant.Ilot Signal 1.2592593 1.0000000 8.333333 +2007.Corail vivant.NA 0.5000000 0.7500000 1.500000 +2007.Corail vivant.Recif Senez 0.5555556 0.7500000 2.333333 +2007.Detritique.Recif Laregnere 0.3333333 0.5000000 1.000000 +2007.Fond lagonaire.Ilot Signal 0.3333333 0.5000000 1.000000 +2007.Herbier.Ilot Signal 0.3333333 0.5000000 1.000000 +2008.Corail vivant.Abore 0.9444444 2.0000000 3.000000 +2008.Corail vivant.Laregnere 0.7777778 1.1666667 2.000000 +2008.Corail vivant.NA 0.3333333 0.5000000 1.000000 +2008.Detritique.Mbe Kouen 0.5493827 1.0000000 3.000000 +2008.Detritique.NA 0.6666667 1.0000000 2.000000 +2008.Detritique.Recif Laregnere 0.3333333 0.5000000 1.000000 +2008.Fond lagonaire.Abore 0.3777778 1.0000000 1.333333 +2008.Fond lagonaire.NA 0.6666667 1.5000000 2.000000 +2008.Herbier.Ilot Signal 0.3333333 0.5000000 1.000000 +2008.Herbier.Radiales Signal laregnere 0.6666667 1.0000000 2.000000 +2009.Algueraie.NA 0.6296296 1.0000000 3.666667 +2009.Corail vivant.Abore 0.5827160 1.0000000 4.333333 +2009.Corail vivant.Mbe Kouen 0.6666667 1.0000000 2.000000 +2009.Corail vivant.NA 0.5972222 1.0000000 3.000000 +2009.Corail vivant.Recif Laregnere 0.4444444 0.6666667 1.333333 +2009.Detritique.Mbe Kouen 0.4583333 1.0000000 2.000000 +2009.Detritique.NA 0.5000000 1.0833333 2.000000 +2009.Detritique.Recif Laregnere 0.5000000 0.7500000 2.000000 +2009.Fond lagonaire.Mbe Kouen 0.7500000 0.7500000 3.500000 +2009.Fond lagonaire.NA 0.3888889 1.0000000 2.000000 +2009.Fond lagonaire.Radiales Signal laregnere 0.3333333 1.0000000 1.000000 +2009.Herbier.Radiales Signal laregnere 0.3333333 0.5000000 1.000000 +2010.Corail vivant.Abore 0.8000000 1.0000000 6.666667 +2010.Detritique.Abore 0.6587302 1.0000000 4.000000 +2010.Detritique.Laregnere 0.5000000 0.7500000 2.000000 +2010.Detritique.Mbe Kouen 0.5555556 1.0000000 3.666667 +2010.Detritique.Recif Laregnere 0.3888889 0.7500000 1.333333 +2010.Fond lagonaire.Abore 0.7083333 1.0000000 5.333333 +2010.Fond lagonaire.Laregnere 0.3333333 0.5000000 1.000000 +2010.Fond lagonaire.Mbe Kouen 0.6666667 1.1250000 2.500000 +2010.Herbier.Radiales Signal laregnere 0.3333333 0.5000000 1.000000 +2012.Corail vivant.Baie Port Bouquet 0.5634921 1.0000000 2.666667 +2012.Corail vivant.Cap Goulvain 0.6666667 1.0000000 2.000000 +2012.Corail vivant.Deva 0.8888889 1.3333333 2.666667 +2012.Corail vivant.Grand recif Ngoe 0.4444444 0.6666667 1.333333 +2012.Corail vivant.Ilot de sable 1.0000000 1.5000000 3.000000 +2012.Corail vivant.Ilots 0.7500000 1.1666667 4.666667 +2012.Corail vivant.NA 0.7318519 1.0000000 6.166667 +2012.Corail vivant.Poe 0.5555556 0.8333333 1.666667 +2012.Corail vivant.Recif Doiman 0.5000000 0.7500000 2.000000 +2012.Detritique.Cap Goulvain 0.6666667 0.7500000 3.000000 +2012.Detritique.Deva 0.3888889 1.0000000 1.500000 +2012.Detritique.Dongan Hienga 0.4444444 1.0000000 2.000000 +2012.Detritique.Dongan Hiengu 0.3333333 1.0000000 1.000000 +2012.Detritique.Faille aux requins 0.6527778 1.0000000 4.333333 +2012.Detritique.Gouaro 0.8888889 1.5000000 3.333333 +2012.Detritique.Grand recif Ngoe 0.7407407 1.0000000 4.666667 +2012.Detritique.Ile Verte 1.0111111 1.5000000 4.500000 +2012.Detritique.Ilot de sable 0.3333333 0.5000000 1.000000 +2012.Detritique.Ilot Hiengabat 0.3888889 0.7500000 1.333333 +2012.Detritique.Ilot Hienghene 0.4583333 1.0000000 2.000000 +2012.Detritique.Ilot Tiguit 0.8888889 1.3333333 2.666667 +2012.Detritique.Les Charpentiers 0.7777778 1.1666667 2.333333 +2012.Detritique.Poe 0.4814815 1.0000000 2.000000 +2012.Detritique.Recif Doiman 0.5555556 1.0000000 3.000000 +2012.Detritique.Recif Douok 0.7500000 1.1250000 3.000000 +2012.Detritique.Recif Mengalia 0.4444444 0.7500000 1.666667 +2012.Detritique.Recif Pidanain 0.7222222 1.0000000 3.000000 +2012.Fond lagonaire.Baie Port Bouquet 0.3333333 0.5000000 1.000000 +2012.Fond lagonaire.Deva 0.5000000 1.0000000 3.000000 +2012.Fond lagonaire.Faille aux requins 0.3703704 1.0000000 1.333333 +2012.Fond lagonaire.Grand recif Ngoe 0.6666667 1.5000000 2.000000 +2012.Fond lagonaire.Ile Verte 0.9861111 1.6250000 5.333333 +2012.Fond lagonaire.Ilots 0.3333333 0.5000000 1.000000 +2012.Fond lagonaire.NA 0.4000000 1.0000000 2.000000 +2012.Fond lagonaire.Poe 0.4444444 1.0000000 1.500000 +2012.Fond lagonaire.Recif Doiman 0.3333333 0.5000000 1.000000 +2013.Algueraie.Lagon Mba Mbo 2.3333333 3.5000000 7.000000 +2013.Algueraie.Seche Croissant 5.5555556 8.3333333 10.666667 +2013.Corail vivant.Bampton nord 3.4259259 1.6666667 22.000000 +2013.Corail vivant.Barriere nord-ouest 0.6851852 1.0000000 2.500000 +2013.Corail vivant.Barriere ouest 0.5555556 1.0000000 4.333333 +2013.Corail vivant.Canard 2.6666667 4.0000000 8.000000 +2013.Corail vivant.Corne sud 0.5317460 1.0000000 3.000000 +2013.Corail vivant.Ilot Gi 0.3333333 0.5000000 1.000000 +2013.Corail vivant.Ilot Kouare 0.5648148 1.0000000 2.666667 +2013.Corail vivant.Ilot Maitre 2.6666667 4.0000000 8.000000 +2013.Corail vivant.Ilot Mbore 0.3333333 0.5000000 1.000000 +2013.Corail vivant.Ilot Ndo 4.3333333 6.5000000 13.000000 +2013.Corail vivant.Ilot Nge 0.3333333 0.5000000 1.000000 +2013.Corail vivant.Ilot Signal 2.5000000 5.2500000 8.000000 +2013.Corail vivant.Ilot Ua 3.1111111 3.0000000 14.666667 +2013.Corail vivant.Ilot Uatio 2.0000000 0.9166667 10.333333 +2013.Corail vivant.La Palette 0.5555556 0.8333333 1.666667 +2013.Corail vivant.Laregnere 4.0317460 8.0000000 35.333333 +2013.Corail vivant.Mba 2.6666667 5.2500000 9.000000 +2013.Corail vivant.Mbo 9.3333333 14.0000000 25.666667 +2013.Corail vivant.NA 0.7398413 1.0000000 8.666667 +2013.Corail vivant.Recif Bellona milieu 1.7777778 2.6666667 5.333333 +2013.Corail vivant.Recif Bellona Nord-ouest 0.3333333 0.5000000 1.000000 +2013.Corail vivant.Recif Cimenia 0.3333333 1.0000000 1.000000 +2013.Corail vivant.Recif de Prony 2.6666667 4.0000000 8.000000 +2013.Corail vivant.Recif Garanhua 0.3333333 0.5000000 1.000000 +2013.Corail vivant.Recif Mbe Kouen 2.6666667 4.0000000 8.000000 +2013.Corail vivant.Recif Neokouie 0.8333333 1.2500000 2.500000 +2013.Corail vivant.Recif Neokumbi 1.2222222 1.5000000 5.333333 +2013.Corail vivant.Recif Nogumatiugi 0.8253968 1.0000000 8.000000 +2013.Corail vivant.Recif Purembi 0.6666667 1.5000000 2.000000 +2013.Corail vivant.Recif Senez 2.6666667 4.0000000 8.000000 +2013.Corail vivant.Recif Tiendi 1.2222222 1.8333333 3.666667 +2013.Corail vivant.Recif Tironhua 1.0740741 1.5000000 5.333333 +2013.Corail vivant.Recif Tiukuru 0.9333333 1.0000000 4.000000 +2013.Corail vivant.Recif Ua 1.6666667 1.5000000 8.000000 +2013.Corail vivant.Recif Umadu 0.3333333 0.5000000 1.000000 +2013.Corail vivant.Recif Umbei 3.1111111 4.6666667 9.333333 +2013.Detritique.Barriere nord-ouest 0.3333333 0.5000000 1.000000 +2013.Detritique.Goeland 6.2222222 9.3333333 18.666667 +2013.Detritique.Ilot Gi 0.5555556 0.8333333 1.666667 +2013.Detritique.Ilot Kouare 0.5000000 0.7500000 1.500000 +2013.Detritique.Ilot Tere 0.3333333 0.5000000 1.000000 +2013.Detritique.La Palette 2.2222222 3.3333333 6.666667 +2013.Detritique.Mbe Kouen 3.8888889 5.8333333 6.000000 +2013.Detritique.Mbo 8.5555556 12.8333333 25.666667 +2013.Detritique.NA 0.6285714 1.0000000 3.666667 +2013.Detritique.Recif Cimenia 0.6666667 1.0000000 1.666667 +2013.Detritique.Recif Garanhua 0.5000000 0.6666667 1.666667 +2013.Detritique.Recif Ie 0.8888889 1.3333333 2.666667 +2013.Detritique.Recif Kanre 0.3333333 0.5000000 1.000000 +2013.Detritique.Recif Mbe Kouen 2.6666667 4.0000000 8.000000 +2013.Detritique.Recif Ndunekunie 0.4444444 0.6666667 1.333333 +2013.Detritique.Recif Nogumatiugi 0.3333333 0.5000000 1.000000 +2013.Detritique.Recif Tironhua 0.3333333 0.5000000 1.000000 +2013.Detritique.Seche Croissant 2.6666667 4.0000000 8.000000 +2013.Fond lagonaire.Bampton nord 0.5555556 0.8333333 1.666667 +2013.Fond lagonaire.Barriere nord-ouest 0.3333333 0.5000000 1.000000 +2013.Fond lagonaire.Corne sud 0.3333333 0.5000000 1.000000 +2013.Fond lagonaire.Crouy 2.6666667 4.0000000 8.000000 +2013.Fond lagonaire.Ilot Koko 0.5000000 0.7500000 2.000000 +2013.Fond lagonaire.Lagon Mba Mbo 2.6666667 4.0000000 8.000000 +2013.Fond lagonaire.Mba 2.6666667 4.0000000 8.000000 +2013.Fond lagonaire.Mbe Kouen 9.1111111 6.0000000 46.666667 +2013.Fond lagonaire.Mbo 2.3333333 3.5000000 7.000000 +2013.Fond lagonaire.NA 0.6873016 1.0000000 9.333333 +2013.Fond lagonaire.Recif Bellona Sud 0.3333333 0.5000000 1.000000 +2013.Fond lagonaire.Recif Cimenia 0.6666667 1.0000000 5.000000 +2013.Fond lagonaire.Recif Ia 0.5000000 0.7500000 1.500000 +2013.Fond lagonaire.Recif Ie 0.3333333 0.5000000 1.000000 +2013.Fond lagonaire.Recif Mbe Kouen 3.3333333 5.0000000 10.000000 +2013.Fond lagonaire.Recif Ndunekunie 0.7777778 1.1666667 2.333333 +2013.Fond lagonaire.Recif Neokouie 0.7500000 0.7500000 3.500000 +2013.Fond lagonaire.Recif Neokumbi 0.5833333 1.1250000 2.000000 +2013.Fond lagonaire.Recif Nogumatiugi 0.6666667 1.5000000 3.000000 +2013.Fond lagonaire.Recif Puakue 0.4444444 0.6666667 1.333333 +2013.Fond lagonaire.Recif Purembi 0.4444444 0.6666667 1.333333 +2013.Fond lagonaire.Recif Senez 2.6666667 4.0000000 8.000000 +2013.Fond lagonaire.Recif Umbei 0.3333333 0.5000000 1.000000 +2013.Fond lagonaire.Seche Croissant 2.6666667 4.0000000 8.000000 +2013.Herbier.Ilot Signal 2.6666667 4.0000000 8.000000 +2013.Herbier.Laregnere 2.6666667 4.0000000 8.000000 +2014.Corail vivant.Baie Xepenehe 0.7341270 1.0000000 3.333333 +2014.Corail vivant.Grand Astrolabe 3.5000000 2.9166667 27.333333 +2014.Corail vivant.Jinek 0.6370370 1.0000000 4.333333 +2014.Corail vivant.Petit Astrolabe 2.1818182 2.0000000 21.333333 +2014.Corail vivant.Petrie 0.4722222 1.0000000 2.333333 +2014.Corail vivant.Pointe Easo 0.6111111 0.8333333 2.333333 +2014.Corail vivant.Recif Jinek 0.3750000 0.7500000 1.250000 +2014.Corail vivant.Walpole 0.3333333 0.5000000 1.000000 +2014.Detritique.Baie Xepenehe 0.9722222 1.1250000 4.333333 +2014.Detritique.Grand Astrolabe 0.8333333 1.2500000 2.500000 +2014.Detritique.Hunter 1.0000000 1.5000000 4.000000 +2014.Detritique.Jinek 0.4814815 0.6666667 2.000000 +2014.Detritique.Petrie 0.3333333 0.7500000 1.000000 +2014.Fond lagonaire.Baie Xepenehe 0.4444444 0.6666667 1.333333 +2014.Fond lagonaire.Grand Astrolabe 0.6666667 1.0000000 2.000000 +2014.Fond lagonaire.Jinek 0.4444444 0.9166667 1.000000 +2015.Corail vivant.Grand Guilbert 0.5000000 0.7500000 1.000000 +2015.Corail vivant.Huon 0.8576389 1.0000000 9.666667 +2015.Corail vivant.Merite 0.3333333 0.5000000 1.000000 +2015.Corail vivant.Pelotas 0.9861111 1.5416667 3.333333 +2015.Corail vivant.Petit Guilbert 0.3333333 0.5000000 1.000000 +2015.Corail vivant.Portail 0.5925926 1.0000000 2.666667 +2015.Corail vivant.Surprise 0.3571429 1.0000000 1.500000 +2015.Detritique.Huon 0.8055556 0.8750000 3.000000 +2015.Detritique.Portail 0.4166667 0.7500000 1.500000 +2015.Fond lagonaire.Huon 0.3333333 0.5000000 1.000000 +2015.Fond lagonaire.Portail 0.3333333 0.5000000 1.000000 +2017.Corail vivant.Grand Astrolabe 1.1388889 1.4166667 5.333333 +2017.Corail vivant.Petit Astrolabe 0.5000000 0.7500000 2.000000 +2017.Corail vivant.Petrie 0.9777778 1.1666667 5.666667 +2017.Detritique.Grand Astrolabe 1.3888889 1.0000000 18.000000 +2017.Detritique.Petit Astrolabe 0.4583333 1.0000000 2.000000 +2017.Detritique.Petrie 0.4722222 1.0000000 3.000000 +2017.Fond lagonaire.Grand Astrolabe 0.3333333 0.5000000 1.000000 +2017.Fond lagonaire.Petit Astrolabe 0.5000000 0.7500000 2.000000 +2017.Fond lagonaire.Petrie 0.5000000 0.7500000 1.500000 + sd N +2007.Algueraie.Ilot Signal 0.5774 3 +2007.Algueraie.Radiales Signal laregnere 0.5164 6 +2007.Corail vivant.Ilot Signal 2.7430 9 +2007.Corail vivant.NA 0.8660 3 +2007.Corail vivant.Recif Senez 0.9584 6 +2007.Detritique.Recif Laregnere 0.5774 3 +2007.Fond lagonaire.Ilot Signal 0.5774 3 +2007.Herbier.Ilot Signal 0.5774 3 +2008.Corail vivant.Abore 1.4670 6 +2008.Corail vivant.Laregnere 1.0720 3 +2008.Corail vivant.NA 0.5774 3 +2008.Detritique.Mbe Kouen 0.8985 27 +2008.Detritique.NA 1.1550 3 +2008.Detritique.Recif Laregnere 0.5774 3 +2008.Fond lagonaire.Abore 0.5616 15 +2008.Fond lagonaire.NA 1.0330 6 +2008.Herbier.Ilot Signal 0.5774 3 +2008.Herbier.Radiales Signal laregnere 1.1550 3 +2009.Algueraie.NA 1.2180 9 +2009.Corail vivant.Abore 0.9951 81 +2009.Corail vivant.Mbe Kouen 1.1550 3 +2009.Corail vivant.NA 0.9376 24 +2009.Corail vivant.Recif Laregnere 0.7698 3 +2009.Detritique.Mbe Kouen 0.6937 24 +2009.Detritique.NA 0.7534 24 +2009.Detritique.Recif Laregnere 0.8367 6 +2009.Fond lagonaire.Mbe Kouen 1.4050 6 +2009.Fond lagonaire.NA 0.6077 18 +2009.Fond lagonaire.Radiales Signal laregnere 0.5000 9 +2009.Herbier.Radiales Signal laregnere 0.5774 3 +2010.Corail vivant.Abore 1.3170 105 +2010.Detritique.Abore 1.1770 21 +2010.Detritique.Laregnere 0.8367 6 +2010.Detritique.Mbe Kouen 0.9443 33 +2010.Detritique.Recif Laregnere 0.6116 6 +2010.Fond lagonaire.Abore 1.2690 48 +2010.Fond lagonaire.Laregnere 0.5774 3 +2010.Fond lagonaire.Mbe Kouen 1.0800 6 +2010.Herbier.Radiales Signal laregnere 0.5774 3 +2012.Corail vivant.Baie Port Bouquet 0.9075 21 +2012.Corail vivant.Cap Goulvain 1.1550 3 +2012.Corail vivant.Deva 1.5400 3 +2012.Corail vivant.Grand recif Ngoe 0.7698 3 +2012.Corail vivant.Ilot de sable 1.7320 3 +2012.Corail vivant.Ilots 1.3410 24 +2012.Corail vivant.NA 1.3680 45 +2012.Corail vivant.Poe 0.9623 3 +2012.Corail vivant.Recif Doiman 0.8367 6 +2012.Detritique.Cap Goulvain 1.2110 6 +2012.Detritique.Deva 0.6009 9 +2012.Detritique.Dongan Hienga 0.7265 9 +2012.Detritique.Dongan Hiengu 0.5000 9 +2012.Detritique.Faille aux requins 1.2760 12 +2012.Detritique.Gouaro 1.4400 6 +2012.Detritique.Grand recif Ngoe 1.5350 9 +2012.Detritique.Ile Verte 1.6240 15 +2012.Detritique.Ilot de sable 0.5774 3 +2012.Detritique.Ilot Hiengabat 0.6116 6 +2012.Detritique.Ilot Hienghene 0.7217 12 +2012.Detritique.Ilot Tiguit 1.5400 3 +2012.Detritique.Les Charpentiers 1.3470 3 +2012.Detritique.Poe 0.7658 9 +2012.Detritique.Recif Doiman 1.0140 9 +2012.Detritique.Recif Douok 1.2550 6 +2012.Detritique.Recif Mengalia 0.7201 6 +2012.Detritique.Recif Pidanain 1.2370 6 +2012.Fond lagonaire.Baie Port Bouquet 0.5774 3 +2012.Fond lagonaire.Deva 0.8438 39 +2012.Fond lagonaire.Faille aux requins 0.5638 9 +2012.Fond lagonaire.Grand recif Ngoe 1.0330 6 +2012.Fond lagonaire.Ile Verte 1.7060 12 +2012.Fond lagonaire.Ilots 0.5774 3 +2012.Fond lagonaire.NA 0.6325 15 +2012.Fond lagonaire.Poe 0.5833 9 +2012.Fond lagonaire.Recif Doiman 0.5774 3 +2013.Algueraie.Lagon Mba Mbo 4.0410 3 +2013.Algueraie.Seche Croissant 5.3470 3 +2013.Corail vivant.Bampton nord 7.2070 9 +2013.Corail vivant.Barriere nord-ouest 0.9663 9 +2013.Corail vivant.Barriere ouest 1.1390 15 +2013.Corail vivant.Canard 4.6190 3 +2013.Corail vivant.Corne sud 0.8426 21 +2013.Corail vivant.Ilot Gi 0.5774 3 +2013.Corail vivant.Ilot Kouare 0.8914 18 +2013.Corail vivant.Ilot Maitre 4.6190 3 +2013.Corail vivant.Ilot Mbore 0.5774 3 +2013.Corail vivant.Ilot Ndo 7.5060 3 +2013.Corail vivant.Ilot Nge 0.5774 3 +2013.Corail vivant.Ilot Signal 3.8860 6 +2013.Corail vivant.Ilot Ua 5.8830 6 +2013.Corail vivant.Ilot Uatio 4.1040 6 +2013.Corail vivant.La Palette 0.9623 3 +2013.Corail vivant.Laregnere 8.1210 21 +2013.Corail vivant.Mba 4.1790 6 +2013.Corail vivant.Mbo 14.1900 3 +2013.Corail vivant.NA 1.3450 210 +2013.Corail vivant.Recif Bellona milieu 3.0790 3 +2013.Corail vivant.Recif Bellona Nord-ouest 0.5774 3 +2013.Corail vivant.Recif Cimenia 0.5000 9 +2013.Corail vivant.Recif de Prony 4.6190 3 +2013.Corail vivant.Recif Garanhua 0.5774 3 +2013.Corail vivant.Recif Mbe Kouen 4.6190 3 +2013.Corail vivant.Recif Neokouie 1.4430 3 +2013.Corail vivant.Recif Neokumbi 2.1670 6 +2013.Corail vivant.Recif Nogumatiugi 1.8120 21 +2013.Corail vivant.Recif Purembi 1.0330 6 +2013.Corail vivant.Recif Senez 4.6190 3 +2013.Corail vivant.Recif Tiendi 2.1170 3 +2013.Corail vivant.Recif Tironhua 1.6730 27 +2013.Corail vivant.Recif Tiukuru 1.4110 9 +2013.Corail vivant.Recif Ua 3.2040 6 +2013.Corail vivant.Recif Umadu 0.5774 3 +2013.Corail vivant.Recif Umbei 5.3890 3 +2013.Detritique.Barriere nord-ouest 0.5774 3 +2013.Detritique.Goeland 10.7800 3 +2013.Detritique.Ilot Gi 0.9623 3 +2013.Detritique.Ilot Kouare 0.8660 3 +2013.Detritique.Ilot Tere 0.5774 3 +2013.Detritique.La Palette 3.8490 3 +2013.Detritique.Mbe Kouen 3.3720 3 +2013.Detritique.Mbo 14.8200 3 +2013.Detritique.NA 0.9952 21 +2013.Detritique.Recif Cimenia 0.8819 3 +2013.Detritique.Recif Garanhua 0.6583 6 +2013.Detritique.Recif Ie 1.5400 3 +2013.Detritique.Recif Kanre 0.5774 3 +2013.Detritique.Recif Mbe Kouen 4.6190 3 +2013.Detritique.Recif Ndunekunie 0.7698 3 +2013.Detritique.Recif Nogumatiugi 0.5774 3 +2013.Detritique.Recif Tironhua 0.5774 3 +2013.Detritique.Seche Croissant 4.6190 3 +2013.Fond lagonaire.Bampton nord 0.9623 3 +2013.Fond lagonaire.Barriere nord-ouest 0.5774 3 +2013.Fond lagonaire.Corne sud 0.5774 3 +2013.Fond lagonaire.Crouy 4.6190 3 +2013.Fond lagonaire.Ilot Koko 0.8367 6 +2013.Fond lagonaire.Lagon Mba Mbo 4.6190 3 +2013.Fond lagonaire.Mba 4.6190 3 +2013.Fond lagonaire.Mbe Kouen 18.6700 6 +2013.Fond lagonaire.Mbo 4.0410 3 +2013.Fond lagonaire.NA 1.4070 147 +2013.Fond lagonaire.Recif Bellona Sud 0.5774 3 +2013.Fond lagonaire.Recif Cimenia 1.2880 18 +2013.Fond lagonaire.Recif Ia 0.8660 3 +2013.Fond lagonaire.Recif Ie 0.5774 3 +2013.Fond lagonaire.Recif Mbe Kouen 5.7740 3 +2013.Fond lagonaire.Recif Ndunekunie 1.3470 3 +2013.Fond lagonaire.Recif Neokouie 1.4050 6 +2013.Fond lagonaire.Recif Neokumbi 0.9174 6 +2013.Fond lagonaire.Recif Nogumatiugi 1.0470 15 +2013.Fond lagonaire.Recif Puakue 0.7698 3 +2013.Fond lagonaire.Recif Purembi 0.7698 3 +2013.Fond lagonaire.Recif Senez 4.6190 3 +2013.Fond lagonaire.Recif Umbei 0.5774 3 +2013.Fond lagonaire.Seche Croissant 4.6190 3 +2013.Herbier.Ilot Signal 4.6190 3 +2013.Herbier.Laregnere 4.6190 3 +2014.Corail vivant.Baie Xepenehe 1.1140 42 +2014.Corail vivant.Grand Astrolabe 7.8930 12 +2014.Corail vivant.Jinek 0.9786 27 +2014.Corail vivant.Petit Astrolabe 4.8880 33 +2014.Corail vivant.Petrie 0.7311 12 +2014.Corail vivant.Pointe Easo 0.9290 6 +2014.Corail vivant.Recif Jinek 0.5863 6 +2014.Corail vivant.Walpole 0.5774 3 +2014.Detritique.Baie Xepenehe 1.7530 6 +2014.Detritique.Grand Astrolabe 1.4430 3 +2014.Detritique.Hunter 1.6730 6 +2014.Detritique.Jinek 0.6894 9 +2014.Detritique.Petrie 0.5164 6 +2014.Fond lagonaire.Baie Xepenehe 0.7698 3 +2014.Fond lagonaire.Grand Astrolabe 1.1550 3 +2014.Fond lagonaire.Jinek 0.5018 6 +2015.Corail vivant.Grand Guilbert 0.5000 3 +2015.Corail vivant.Huon 1.6960 48 +2015.Corail vivant.Merite 0.5774 3 +2015.Corail vivant.Pelotas 1.0550 12 +2015.Corail vivant.Petit Guilbert 0.5774 3 +2015.Corail vivant.Portail 0.8941 9 +2015.Corail vivant.Surprise 0.5278 21 +2015.Detritique.Huon 1.1370 6 +2015.Detritique.Portail 0.6646 6 +2015.Fond lagonaire.Huon 0.5774 3 +2015.Fond lagonaire.Portail 0.5774 3 +2017.Corail vivant.Grand Astrolabe 1.7660 12 +2017.Corail vivant.Petit Astrolabe 0.8367 6 +2017.Corail vivant.Petrie 1.5490 15 +2017.Detritique.Grand Astrolabe 3.6290 30 +2017.Detritique.Petit Astrolabe 0.5751 36 +2017.Detritique.Petrie 0.7760 18 +2017.Fond lagonaire.Grand Astrolabe 0.5774 3 +2017.Fond lagonaire.Petit Astrolabe 0.8367 6 +2017.Fond lagonaire.Petrie 0.8660 3 + +######################################### +Fitted model: + number ~ year + habitat + (1 | site) + + +Family : gaussian +Response : number \ No newline at end of file diff -r 000000000000 -r 0778efa9eb2e test-data/Unitobs.tabular --- /dev/null Thu Jan 01 00:00:00 1970 +0000 +++ b/test-data/Unitobs.tabular Tue Jul 21 06:00:51 2020 -0400 @@ -0,0 +1,2862 @@ +"AMP" "observation.unit" "type" "site" "station" "carac1" "carac2" "fraction" "jour" "mois" "year" "heure" "nebulosite" "dirVent" "forceVent" "etatMer" "courant" "maree" "lune" "latitude" "longitude" "statut_protection" "avant_apres" "biotop1" "biotop2" "habitat" "habitat2" "habitat3" "visibilite" "prof_min" "prof_max" "DimObs1" "DimObs2" "nb_observateur" "observateur" +"AMP" "AB080001" "SVR" "Abore" NA NA NA 1 10 7 2008 NA NA NA 3 -999 NA "MM" "PQ" -22.43877 166.34874 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA1" 6 4.2 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB080002" "SVR" "Abore" NA NA NA 1 10 7 2008 NA NA NA 3 -999 NA "MM" "PQ" -22.43975 166.35523 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA1" 6 2.2 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB080003" "SVR" "Abore" NA NA NA 1 10 7 2008 NA NA NA 2 -999 NA "MM" "PQ" -22.4474 166.36406 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA1" 8 2.2 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB080004" "SVR" "Abore" NA NA NA 1 10 7 2008 NA NA NA 2 -999 NA "MM" "PQ" -22.44773 166.36715 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Herbier" "Recif barriere interne" "SG1" 8 2.7 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB080005" "SVR" "Abore" NA NA NA 1 10 7 2008 NA NA NA 3 -999 NA "MM" "PQ" -22.45701 166.37434 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" NA 7 4.1 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB080006" "SVR" "Abore" NA NA NA 1 10 7 2008 NA NA NA 3 -999 NA "MM" "PQ" -22.45893 166.3782 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA1" 10 1.8 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB080007" "SVR" "Abore" NA NA NA 1 10 7 2008 NA NA "0" 0 -999 NA "MM" "PQ" -22.46091 166.37847 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA1" 7 1.6 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB080008" "SVR" "Abore" NA NA NA 1 10 7 2008 NA NA "0" 0 -999 NA "MM" "PQ" -22.46931 166.38774 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Corail vivant" "Recif barriere interne" "LC3" 8 2.3 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB080009" "SVR" "Abore" NA NA NA 1 10 7 2008 NA NA "0" 0 -999 NA "MM" "PQ" -22.47137 166.39462 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA1" 10 3 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB080010" "SVR" "Abore" NA NA NA 1 10 7 2008 NA NA "0" 0 -999 NA "MM" "PQ" -22.47395 166.39954 "RE" "AP" "Complexe de recif barriere externe" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA3" 7 3.7 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB080011" "SVR" "Abore" NA NA NA 1 10 7 2008 NA NA "0" 0 -999 NA "MM" "PQ" -22.47507 166.39572 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA3" 10 2 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB080012" "SVR" "Abore" NA NA NA 1 10 7 2008 NA NA "0" 0 -999 NA "MM" "PQ" -22.48081 166.41733 "RE" "AP" "Complexe de recif barriere externe" "platier recifal" "Detritique" "Recif barriere interne" "SA5" 9 2 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB080013" "SVR" "Abore" NA NA NA 1 10 7 2008 NA NA "0" 0 -999 NA "MM" "PQ" -22.48161 166.41947 "RE" "AP" "Complexe de recif barriere externe" "platier recifal" "Detritique" "Recif barriere interne" "D7" 8 2.2 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB080014" "SVR" "Abore" NA NA NA 1 10 7 2008 NA NA "0" 0 -999 NA "PM" "PQ" -22.48274 166.42438 "RE" "AP" "Complexe de recif barriere externe" "platier recifal" "Detritique" "Recif barriere interne" "D1" 5 2.5 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB080015" "SVR" "Abore" NA NA NA 1 10 7 2008 NA NA "0" 0 -999 NA "MD" "PQ" -22.48328 166.42625 "RE" "AP" "Complexe de recif barriere externe" "platier recifal" "Corail vivant" "Recif barriere interne" "LC5" 8 2.7 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB080016" "SVR" "Abore" NA NA NA 1 11 7 2008 NA NA NA 4 -999 NA "MM" "LM" -22.42827 166.3303 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" NA 8 2.8 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB080017" "SVR" "Abore" NA NA NA 1 11 7 2008 NA NA NA 4 -999 NA "MM" "LM" -22.4299 166.33216 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA1" 10 3 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB080018" "SVR" "Abore" NA NA NA 1 11 7 2008 NA NA NA 4 -999 NA "MM" "LM" -22.43222 166.33415 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA1" 10 3.5 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB080019" "SVR" "Abore" NA NA NA 1 11 7 2008 NA NA NA 4 -999 NA "MM" "LM" -22.43327 166.33458 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA3" 10 2.5 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB080020" "SVR" "Abore" NA NA NA 1 11 7 2008 NA NA NA 4 -999 NA "MM" "LM" -22.43428 166.33776 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA3" 8 4.7 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB080021" "SVR" "Abore" NA NA NA 1 11 7 2008 NA NA NA 4 -999 NA "MM" "LM" -22.43669 166.3387 "RE" "AP" "Complexe de recif barriere externe" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA3" 10 2.7 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB080022" "SVR" "Abore" NA NA NA 1 11 7 2008 NA NA NA 4 -999 NA "MM" "LM" -22.43683 166.34298 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA1" 10 3.8 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB080023" "SVR" "Abore" NA NA NA 1 11 7 2008 NA NA NA 4 -999 NA "MM" "LM" -22.43827 166.34232 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA1" 10 2.6 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB080024" "SVR" "Abore" NA NA NA 1 11 7 2008 NA NA NA 4 -999 NA "MM" "LM" -22.44837 166.37318 "RE" "AP" "Complexe de recif barriere externe" "terrasse profonde a champ de constructions coralliennes" "Fond lagonaire" "Recif intermediaire" "SA1" 7 3.3 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB080025" "SVR" "Abore" NA NA NA 1 11 7 2008 NA NA NA 4 -999 NA "MM" "LM" -22.44942 166.37383 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA1" 7 3.8 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB080026" "SVR" "Abore" NA NA NA 1 11 7 2008 NA NA NA 3 -999 NA "MM" "LM" -22.45204 166.37237 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Herbier" "Recif barriere interne" "SG2" 10 3.1 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB080027" "SVR" "Abore" NA NA NA 1 11 7 2008 NA NA NA 3 -999 NA "MM" "LM" -22.45455 166.37203 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA3" 8 2.1 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB080028" "SVR" "Abore" NA NA NA 1 11 7 2008 NA NA NA 3 -999 NA "MM" "LM" -22.47272 166.39261 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA1" 8 3.7 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB080030" "SVR" "Abore" NA NA NA 1 11 7 2008 NA NA NA 3 -999 NA "MM" "LM" -22.47637 166.3996 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA3" 8 2.9 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB080031" "SVR" "Abore" NA NA NA 1 11 7 2008 NA NA NA 3 -999 NA "MM" "LM" -22.47748 166.40108 "RE" "AP" "Complexe de recif barriere externe" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA5" 6 2.6 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB080032" "SVR" "Abore" NA NA NA 1 11 7 2008 NA NA NA 3 -999 NA "MM" "LM" -22.47709 166.41654 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA1" 7 5.1 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB080033" "SVR" "Abore" NA NA NA 1 11 7 2008 NA NA NA 3 -999 NA "MM" "LM" -22.47933 166.41634 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Recif barriere interne" NA 7 3.7 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB080034" "SVR" "Abore" NA NA NA 1 11 7 2008 NA NA NA 3 -999 NA "PM" "LM" -22.48299 166.42958 "RE" "AP" "Complexe de recif barriere externe" "platier recifal" "Fond lagonaire" "Recif barriere interne" NA 7 3.1 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB080035" "SVR" "Abore" NA NA NA 1 11 7 2008 NA NA NA 3 -999 NA "MD" "LM" -22.48464 166.43309 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Recif barriere interne" NA 7 3 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB080036" "SVR" "Abore" NA NA NA 1 13 8 2008 NA NA NA 2 -999 NA "MM" "LM" -22.41519 166.32349 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA3" 8 4 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB080037" "SVR" "Abore" NA NA NA 1 13 8 2008 NA NA NA 2 -999 NA "MM" "LM" -22.41114 166.32144 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA1" 10 3.8 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB080038" "SVR" "Abore" NA NA NA 1 13 8 2008 NA NA NA 2 -999 NA "MM" "LM" -22.41017 166.31919 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Recif barriere interne" "MA4" 10 3.8 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB080039" "SVR" "Abore" NA NA NA 1 13 8 2008 NA NA NA 2 -999 NA "MM" "LM" -22.40933 166.31844 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA1" 10 4 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB080040" "SVR" "Abore" NA NA NA 1 13 8 2008 NA NA NA 2 -999 NA "MM" "LM" -22.40768 166.31567 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Algueraie" "Recif barriere interne" "MA3" 10 3.5 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB080041" "SVR" "Abore" NA NA NA 1 13 8 2008 NA NA NA 2 -999 NA "BM" "LM" -22.40697 166.3143 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Algueraie" "Recif barriere interne" "MA4" 7 3.3 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB080042" "SVR" "Abore" NA NA NA 1 13 8 2008 NA NA NA 2 -999 NA "MD" "LM" -22.40599 166.31025 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA3" 10 3 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB080044" "SVR" "Abore" NA NA NA 1 13 8 2008 NA NA NA 2 -999 NA "MD" "LM" -22.38923 166.29376 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA1" 10 3.9 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB080045" "SVR" "Abore" NA NA NA 1 13 8 2008 NA NA NA 2 -999 NA "MD" "LM" -22.3871 166.29162 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" NA 10 3 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB080046" "SVR" "Abore" NA NA NA 1 13 8 2008 NA NA NA 2 -999 NA "MD" "LM" -22.38303 166.29008 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA1" 8 4.7 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB080054" "SVR" "Abore" NA NA NA 1 22 8 2008 NA NA NA 4 -999 NA "MM" "LD" -22.49973 166.44574 "RE" "AP" "Complexe de recif barriere externe" "passe" "Fond lagonaire" "Passe" "LC5" 8 7.5 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB080055" "SVR" "Abore" NA NA NA 1 13 8 2008 NA NA NA 2 -999 NA "MD" "LM" -22.39561 166.29802 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA1" 10 3 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB080056" "SVR" "Abore" NA NA NA 1 13 8 2008 NA NA NA 2 -999 NA "MM" "LM" -22.41928 166.32612 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA3" 7 3.2 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB080057" "SVR" "Abore" NA NA NA 1 13 8 2008 NA NA NA 2 -999 NA "MM" "LM" -22.42318 166.32856 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "LC5" 8 2.6 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB090060" "SVR" "Abore" NA NA NA 1 26 2 2009 NA NA "0" 0 -999 NA "MD" "PC" -22.36268 166.26856 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA1" -999 19.4 -999 -999 -999 -999 NA +"AMP" "AB090061" "SVR" "Abore" NA NA NA 1 26 2 2009 NA NA "0" 0 -999 NA "MD" "PC" -22.36485 166.27353 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA2" 5 16.2 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB090062" "SVR" "Abore" NA NA NA 1 26 2 2009 NA NA "0" 0 -999 NA "MD" "PC" -22.3657 166.27868 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA1" -999 18.6 -999 -999 -999 -999 NA +"AMP" "AB090063" "SVR" "Abore" NA NA NA 1 26 2 2009 NA NA "0" 0 -999 NA "MD" "PC" -22.36847 166.2832 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA1" 5 18.5 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB090064" "SVR" "Abore" NA NA NA 1 26 2 2009 NA NA "SE" 2 -999 NA "MD" "PC" -22.37154 166.28714 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA1" -999 15 -999 -999 -999 -999 NA +"AMP" "AB090066" "SVR" "Abore" NA NA NA 1 26 2 2009 NA NA "SE" 2 -999 NA "MD" "PC" -22.37953 166.29329 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Recif barriere interne" "SA1" 5 14.4 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB090067" "SVR" "Abore" NA NA NA 1 26 2 2009 NA NA "SE" 2 -999 NA "MD" "PC" -22.38306 166.2961 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA1" -999 13.4 -999 -999 -999 -999 NA +"AMP" "AB090068" "SVR" "Abore" NA NA NA 1 26 2 2009 NA NA "SE" 2 -999 NA "MD" "PC" -22.38765 166.29837 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Recif barriere interne" "SA1" -999 13.7 -999 -999 -999 -999 NA +"AMP" "AB090069" "SVR" "Abore" NA NA NA 1 26 2 2009 NA NA "SE" 2 -999 NA "MD" "PC" -22.39233 166.30061 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Recif barriere interne" "SA3" -999 15 -999 -999 -999 -999 NA +"AMP" "AB090070" "SVR" "Abore" NA NA NA 1 26 2 2009 NA NA "SE" 2 -999 NA "PM" "PC" -22.39541 166.30505 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Recif barriere interne" "SA1" 5 13 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB090072" "SVR" "Abore" NA NA NA 1 26 2 2009 NA NA "SE" 2 -999 NA "MM" "PC" -22.40229 166.31727 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA1" 5 12.7 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB090073" "SVR" "Abore" NA NA NA 1 26 2 2009 NA NA "SE" 2 -999 NA "MM" "PC" -22.40307 166.31856 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Recif barriere interne" "SA3" -999 11.8 -999 -999 -999 -999 NA +"AMP" "AB090074" "SVR" "Abore" NA NA NA 1 26 2 2009 NA NA "SE" 2 -999 NA "MM" "PC" -22.40685 166.32235 "RE" "AP" "Ile lagonaire" "lagon profond" "Corail vivant" "Recif barriere interne" "LC3" -999 11.7 -999 -999 -999 -999 NA +"AMP" "AB090075" "SVR" "Abore" NA NA NA 1 26 2 2009 NA NA "SE" 2 -999 NA "MM" "PC" -22.41155 166.32526 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA3" 5 11 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB090076" "SVR" "Abore" NA NA NA 1 24 2 2009 NA NA "SE" 3 -999 NA "MM" "NL" -22.41935 166.33985 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Corail vivant" "Recif barriere interne" "LC4" -999 11.8 -999 -999 -999 -999 NA +"AMP" "AB090079" "SVR" "Abore" NA NA NA 1 24 2 2009 NA NA "SE" 3 -999 NA "MM" "NL" -22.42381 166.35111 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Corail vivant" "Recif barriere interne" "LC4" -999 9.5 -999 -999 -999 -999 NA +"AMP" "AB090081" "SVR" "Abore" NA NA NA 1 24 2 2009 NA NA "SE" 3 -999 NA "MM" "NL" -22.4292 166.36295 "RE" "AP" "Ile lagonaire" "lagon profond" "Corail vivant" "Recif barriere interne" "LC6" 5 8.5 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB090083" "SVR" "Abore" NA NA NA 1 24 2 2009 NA NA "SE" 3 -999 NA "MD" "NL" -22.43471 166.37431 "RE" "AP" "Ile lagonaire" "lagon profond" "Corail vivant" "Recif barriere interne" "LC4" 5 7.2 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB090086" "SVR" "Abore" NA NA NA 1 24 2 2009 NA NA "SE" 3 -999 NA "MD" "NL" -22.44756 166.38747 "RE" "AP" "Complexe de recif barriere externe" "terrasse profonde a champ de constructions coralliennes" "Detritique" "Recif intermediaire" NA -999 3.9 -999 -999 -999 -999 NA +"AMP" "AB090087" "SVR" "Abore" NA NA NA 1 24 2 2009 NA NA "SE" 3 -999 NA "MD" "NL" -22.45223 166.39065 "RE" "AP" "Complexe de recif barriere externe" "terrasse profonde a champ de constructions coralliennes" "Detritique" "Recif intermediaire" NA -999 6.5 -999 -999 -999 -999 NA +"AMP" "AB090089" "SVR" "Abore" NA NA NA 1 24 2 2009 NA NA "SE" 3 -999 NA "MD" "NL" -22.45904 166.40023 "RE" "AP" "Complexe de recif barriere externe" "terrasse profonde a champ de constructions coralliennes" "Detritique" "Recif intermediaire" NA -999 6.5 -999 -999 -999 -999 NA +"AMP" "AB090090" "SVR" "Abore" NA NA NA 1 24 2 2009 NA NA "SE" 3 -999 NA "MD" "NL" -22.46111 166.40213 "RE" "AP" "Complexe de recif barriere externe" "terrasse profonde a champ de constructions coralliennes" "Detritique" "Recif intermediaire" NA -999 8.7 -999 -999 -999 -999 NA +"AMP" "AB090091" "SVR" "Abore" NA NA NA 1 24 2 2009 NA NA "SE" 3 -999 NA "MD" "NL" -22.46204 166.40497 "RE" "AP" "Complexe de recif barriere externe" "terrasse profonde a champ de constructions coralliennes" "Detritique" "Recif intermediaire" NA -999 8 -999 -999 -999 -999 NA +"AMP" "AB090092" "SVR" "Abore" NA NA NA 1 24 2 2009 NA NA "SE" 3 -999 NA "MD" "NL" -22.46353 166.40749 "RE" "AP" "Complexe de recif barriere externe" "terrasse profonde a champ de constructions coralliennes" "Detritique" "Recif intermediaire" NA -999 5.5 -999 -999 -999 -999 NA +"AMP" "AB090095" "SVR" "Abore" NA NA NA 1 20 2 2009 NA NA NA 4 -999 NA "MD" "DC" -22.47372 166.4239 "RE" "AP" "Ile lagonaire" "lagon profond" "Corail vivant" "Recif barriere interne" "LC4" 5 9.5 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB090096" "SVR" "Abore" NA NA NA 1 20 2 2009 NA NA NA 4 -999 NA "MD" "DC" -22.47826 166.42492 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA1" -999 9.5 -999 -999 -999 -999 NA +"AMP" "AB090097" "SVR" "Abore" NA NA NA 1 20 2 2009 NA NA NA 4 -999 NA "MD" "DC" -22.47823 166.42749 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Corail vivant" "Recif barriere interne" "LC4" 6 11 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB090098" "SVR" "Abore" NA NA NA 1 20 2 2009 NA NA NA 4 -999 NA "MD" "DC" -22.47877 166.42878 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Corail vivant" "Recif barriere interne" "LC5" 7 10 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB090099" "SVR" "Abore" NA NA NA 1 20 2 2009 NA NA NA 4 -999 NA "MD" "DC" -22.4794 166.43073 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA1" -999 9.6 -999 -999 -999 -999 NA +"AMP" "AB090100" "SVR" "Abore" NA NA NA 1 20 2 2009 NA NA NA 4 -999 NA "MM" "DC" -22.49341 166.44238 "RE" "AP" "Complexe de recif barriere externe" "passe" "Detritique" "Passe" "D1" 8 21.8 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB090101" "SVR" "Abore" NA NA NA 1 20 2 2009 NA NA NA 4 -999 NA "MM" "DC" -22.49567 166.44267 "RE" "AP" "Complexe de recif barriere externe" "passe" "Corail vivant" "Passe" "LC4" 6 11.5 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB090103" "SVR" "Abore" NA NA NA 1 20 2 2009 NA NA NA 4 -999 NA "MM" "DC" -22.50882 166.45568 "RE" "AP" "Ile lagonaire" "lagon profond" "Corail vivant" "Recif barriere interne" "LC2" 8 7.8 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB090104" "SVR" "Abore" NA NA NA 1 20 2 2009 NA NA NA 4 -999 NA "MM" "DC" -22.49987 166.44373 "RE" "AP" "Complexe de recif barriere externe" "passe" "Corail vivant" "Passe" "LC2" 7 9 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB090105" "SVR" "Abore" NA NA NA 1 20 2 2009 NA NA NA 4 -999 NA "MM" "DC" -22.49928 166.44523 "RE" "AP" "Complexe de recif barriere externe" "passe" "Corail vivant" "Passe" "LC1" 8 8.5 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB090106" "SVR" "Abore" NA NA NA 1 20 2 2009 NA NA NA 4 -999 NA "MM" "DC" -22.50741 166.45589 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Corail vivant" "Recif barriere interne" "LC4" 8 7.4 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB090109" "SVR" "Abore" NA NA NA 1 20 2 2009 NA NA NA 4 -999 NA "MM" "DC" -22.52745 166.44969 "RE" "AP" "Complexe de recif barriere externe" "platier recifal ennoye" "Corail vivant" "Recif barriere interne" "LC4" 8 7.6 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB090110" "SVR" "Abore" NA NA NA 1 20 2 2009 NA NA NA 4 -999 NA "MM" "DC" -22.52648 166.4477 "RE" "AP" "Complexe de recif barriere externe" "platier recifal ennoye" "Detritique" "Recif barriere interne" NA 7 5 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB090120" "SVR" "Abore" NA NA NA 1 25 2 2009 NA NA "SE" 3 -999 NA "MD" "NL" -22.46969 166.39903 "RE" "AP" "Complexe de recif barriere externe" "terrasse profonde a champ de constructions coralliennes" "Corail vivant" "Recif intermediaire" "LC1" -999 6.3 -999 -999 -999 -999 NA +"AMP" "AB090121" "SVR" "Abore" NA NA NA 1 25 2 2009 NA NA "SE" 3 -999 NA "MD" "NL" -22.46642 166.39698 "RE" "AP" "Complexe de recif barriere externe" "terrasse profonde a champ de constructions coralliennes" "Corail vivant" "Recif intermediaire" "LC1" 7 4.8 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB090122" "SVR" "Abore" NA NA NA 1 25 2 2009 NA NA "SE" 3 -999 NA "MD" "NL" -22.46458 166.39331 "RE" "AP" "Complexe de recif barriere externe" "terrasse profonde a champ de constructions coralliennes" "Corail vivant" "Recif intermediaire" "LC1" -999 4.3 -999 -999 -999 -999 NA +"AMP" "AB090123" "SVR" "Abore" NA NA NA 1 25 2 2009 NA NA "SE" 3 -999 NA "MD" "NL" -22.46357 166.38956 "RE" "AP" "Complexe de recif barriere externe" "terrasse profonde a champ de constructions coralliennes" "Corail vivant" "Recif intermediaire" "LC1" -999 2.1 -999 -999 -999 -999 NA +"AMP" "AB090124" "SVR" "Abore" NA NA NA 1 25 2 2009 NA NA "SE" 3 -999 NA "MD" "NL" -22.4615 166.38687 "RE" "AP" "Complexe de recif barriere externe" "terrasse profonde a champ de constructions coralliennes" "Corail vivant" "Recif intermediaire" "LC1" -999 5.3 -999 -999 -999 -999 NA +"AMP" "AB090125" "SVR" "Abore" NA NA NA 1 25 2 2009 NA NA "SE" 3 -999 NA "MD" "NL" -22.45864 166.38477 "RE" "AP" "Complexe de recif barriere externe" "terrasse profonde a champ de constructions coralliennes" "Corail vivant" "Recif intermediaire" "LC1" -999 6.4 -999 -999 -999 -999 NA +"AMP" "AB090126" "SVR" "Abore" NA NA NA 1 25 2 2009 NA NA "SE" 3 -999 NA "MD" "NL" -22.45627 166.38156 "RE" "AP" "Complexe de recif barriere externe" "terrasse profonde a champ de constructions coralliennes" "Corail vivant" "Recif intermediaire" "LC1" -999 5 -999 -999 -999 -999 NA +"AMP" "AB090127" "SVR" "Abore" NA NA NA 1 25 2 2009 NA NA "SE" 3 -999 NA "MD" "NL" -22.45375 166.37935 "RE" "AP" "Complexe de recif barriere externe" "terrasse profonde a champ de constructions coralliennes" "Corail vivant" "Recif intermediaire" "LC1" 5 3.5 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB090128" "SVR" "Abore" NA NA NA 1 25 2 2009 NA NA "SE" 3 -999 NA "MD" "NL" -22.45047 166.37857 "RE" "AP" "Complexe de recif barriere externe" "terrasse profonde a champ de constructions coralliennes" "Corail vivant" "Recif intermediaire" "LC5" -999 5.5 -999 -999 -999 -999 NA +"AMP" "AB090129" "SVR" "Abore" NA NA NA 1 25 2 2009 NA NA "SE" 3 -999 NA "MD" "NL" -22.44739 166.37694 "RE" "AP" "Complexe de recif barriere externe" "terrasse profonde a champ de constructions coralliennes" "Corail vivant" "Recif intermediaire" "LC1" -999 6.9 -999 -999 -999 -999 NA +"AMP" "AB090130" "SVR" "Abore" NA NA NA 1 25 2 2009 NA NA "SE" 4 -999 NA "MD" "NL" -22.44648 166.37198 "RE" "AP" "Complexe de recif barriere externe" "terrasse profonde a champ de constructions coralliennes" "Corail vivant" "Recif intermediaire" "LC5" -999 6.5 -999 -999 -999 -999 NA +"AMP" "AB090131" "SVR" "Abore" NA NA NA 1 25 2 2009 NA NA "SE" 4 -999 NA "MD" "NL" -22.4428 166.36713 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Corail vivant" "Recif barriere interne" "LC2" 5 8.2 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB090132" "SVR" "Abore" NA NA NA 1 25 2 2009 NA NA "SE" 4 -999 NA "MD" "NL" -22.43941 166.36402 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Corail vivant" "Recif barriere interne" "LC1" -999 5.3 -999 -999 -999 -999 NA +"AMP" "AB090133" "SVR" "Abore" NA NA NA 1 25 2 2009 NA NA "SE" 4 -999 NA "MD" "NL" -22.43774 166.35884 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Corail vivant" "Recif barriere interne" "LC1" 6 8.4 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB090134" "SVR" "Abore" NA NA NA 1 25 2 2009 NA NA "SE" 4 -999 NA "MD" "NL" -22.43403 166.35399 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Corail vivant" "Recif barriere interne" "LC1" -999 9 -999 -999 -999 -999 NA +"AMP" "AB090135" "SVR" "Abore" NA NA NA 1 25 2 2009 NA NA "SE" 4 -999 NA "MD" "NL" -22.42892 166.35068 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Corail vivant" "Recif barriere interne" "LC3" 6 9.7 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB090138" "SVR" "Abore" NA NA NA 1 18 3 2009 NA NA NA 5 -999 NA "MM" "DQ" -22.52554 166.44651 "RE" "AP" "Complexe de recif barriere externe" "platier recifal ennoye" "Detritique" "Recif barriere interne" NA 8 5.6 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB090139" "SVR" "Abore" NA NA NA 1 18 3 2009 NA NA NA 6 -999 NA "MM" "DQ" -22.52364 166.44497 "RE" "AP" "Complexe de recif barriere externe" "platier recifal ennoye" "Detritique" "Recif barriere interne" "LC3" 10 6 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB090140" "SVR" "Abore" NA NA NA 1 18 3 2009 NA NA NA 6 -999 NA "MM" "DQ" -22.48017 166.4347 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "LC6" -999 11.6 -999 -999 -999 -999 NA +"AMP" "AB090141" "SVR" "Abore" NA NA NA 1 18 3 2009 NA NA NA 6 -999 NA "MM" "DQ" -22.4803 166.4332 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA1" 7 11.1 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB090142" "SVR" "Abore" NA NA NA 1 18 3 2009 NA NA NA 6 -999 NA "MM" "DQ" -22.46486 166.40942 "RE" "AP" "Complexe de recif barriere externe" "terrasse profonde a champ de constructions coralliennes" "Detritique" "Recif intermediaire" NA 5 7.2 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB090143" "SVR" "Abore" NA NA NA 1 18 3 2009 NA NA NA 6 -999 NA "MM" "DQ" -22.4658 166.41041 "RE" "AP" "Complexe de recif barriere externe" "terrasse profonde a champ de constructions coralliennes" "Corail vivant" "Recif intermediaire" "LC4" -999 7.5 -999 -999 -999 -999 NA +"AMP" "AB090144" "SVR" "Abore" NA NA NA 1 18 3 2009 NA NA NA 6 -999 NA "MM" "DQ" -22.45399 166.3927 "RE" "AP" "Complexe de recif barriere externe" "terrasse profonde a champ de constructions coralliennes" "Detritique" "Recif intermediaire" NA -999 7.6 -999 -999 -999 -999 NA +"AMP" "AB090145" "SVR" "Abore" NA NA NA 1 18 3 2009 NA NA NA 7 -999 NA "MM" "DQ" -22.45485 166.39254 "RE" "AP" "Complexe de recif barriere externe" "terrasse profonde a champ de constructions coralliennes" "Detritique" "Recif intermediaire" "SA5" 5 5.7 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB090146" "SVR" "Abore" NA NA NA 1 18 3 2009 NA NA NA 7 -999 NA "MM" "DQ" -22.44498 166.38477 "RE" "AP" "Complexe de recif barriere externe" "terrasse profonde a champ de constructions coralliennes" "Detritique" "Recif intermediaire" NA -999 5.6 -999 -999 -999 -999 NA +"AMP" "AB090147" "SVR" "Abore" NA NA NA 1 18 3 2009 NA NA NA 7 -999 NA "MM" "DQ" -22.43881 166.38172 "RE" "AP" "Complexe de recif barriere externe" "terrasse profonde a champ de constructions coralliennes" "Fond lagonaire" "Recif intermediaire" "SA3" 5 4.9 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB090148" "SVR" "Abore" NA NA NA 1 18 3 2009 NA NA NA 7 -999 NA "MM" "DQ" -22.43166 166.369 "RE" "AP" "Ile lagonaire" "lagon profond" "Corail vivant" "Recif barriere interne" "LC2" -999 9.8 -999 -999 -999 -999 NA +"AMP" "AB090149" "SVR" "Abore" NA NA NA 1 18 3 2009 NA NA NA 7 -999 NA "MM" "DQ" -22.43295 166.36778 "RE" "AP" "Ile lagonaire" "lagon profond" "Corail vivant" "Recif barriere interne" "LC1" 5 7.8 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB090151" "SVR" "Abore" NA NA NA 1 18 3 2009 NA NA NA 8 -999 NA "PM" "DQ" -22.42169 166.34295 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Corail vivant" "Recif barriere interne" "LC2" 8 9.9 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB090152" "SVR" "Abore" NA NA NA 1 18 3 2009 NA NA NA 8 -999 NA "PM" "DQ" -22.39563 166.31067 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Recif barriere interne" "SA3" -999 12.4 -999 -999 -999 -999 NA +"AMP" "AB090153" "SVR" "Abore" NA NA NA 1 18 3 2009 NA NA NA 8 -999 NA "MD" "DQ" -22.39574 166.3092 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Recif barriere interne" "SA1" -999 11.3 -999 -999 -999 -999 NA +"AMP" "AB090156" "SVR" "Abore" NA NA NA 1 18 3 2009 NA NA NA 8 -999 NA "MD" "DQ" -22.36259 166.25933 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Corail vivant" "Recif barriere interne" "LC2" -999 4 -999 -999 -999 -999 NA +"AMP" "AB090601" "SVR" "Abore" NA NA NA 1 26 2 2009 NA NA "0" 0 -999 NA "MD" "PC" -22.36535 166.26534 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Corail vivant" "Recif barriere interne" "LC6" 6 3.9 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB090602" "SVR" "Abore" NA NA NA 1 26 2 2009 NA NA "0" 0 -999 NA "MD" "PC" -22.3639 166.26193 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Corail vivant" "Recif barriere interne" "LC5" 7 3.8 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB090603" "SVR" "Abore" NA NA NA 1 26 2 2009 NA NA "0" 0 -999 NA "MD" "PC" -22.36298 166.26095 "RE" "AP" "Complexe de recif barriere externe" "platier recifal" "Corail vivant" "Recif barriere interne" "LC1" -999 3 -999 -999 -999 -999 NA +"AMP" "AB090606" "SVR" "Abore" NA NA NA 1 26 2 2009 NA NA "0" 0 -999 NA "MD" "PC" -22.36202 166.2585 "RE" "AP" "Complexe de recif barriere externe" "passe" "Detritique" "Recif barriere interne" NA 7 6.5 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB090761" "SVR" "Abore" NA NA NA 1 24 2 2009 NA NA "SE" 3 -999 NA "MM" "NL" -22.41758 166.3364 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Corail vivant" "Recif barriere interne" "LC2" 5 10 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB090891" "SVR" "Abore" NA NA NA 1 24 2 2009 NA NA "SE" 3 -999 NA "MD" "NL" -22.45813 166.39763 "RE" "AP" "Complexe de recif barriere externe" "terrasse profonde a champ de constructions coralliennes" "Detritique" "Recif intermediaire" NA -999 3.4 -999 -999 -999 -999 NA +"AMP" "AB090991" "SVR" "Abore" NA NA NA 1 20 2 2009 NA NA NA 4 -999 NA "MD" "DC" -22.48034 166.43283 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA1" -999 7.6 -999 -999 -999 -999 NA +"AMP" "AB090993" "SVR" "Abore" NA NA NA 1 20 2 2009 NA NA NA 4 -999 NA "MD" "DC" -22.48313 166.43617 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA1" 5 16.5 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB090994" "SVR" "Abore" NA NA NA 1 20 2 2009 NA NA NA 4 -999 NA "BM" "DC" -22.48514 166.43796 "RE" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Recif barriere interne" "SA1" -999 19 -999 -999 -999 -999 NA +"AMP" "AB090995" "SVR" "Abore" NA NA NA 1 20 2 2009 NA NA NA 4 -999 NA "MM" "DC" -22.48725 166.43969 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Recif barriere interne" "SA1" 5 21.2 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB090996" "SVR" "Abore" NA NA NA 1 20 2 2009 NA NA NA 4 -999 NA "MM" "DC" -22.49085 166.44168 "RE" "AP" "Ile lagonaire" "lagon profond" "Detritique" "Passe" NA -999 17.5 -999 -999 -999 -999 NA +"AMP" "AB100001" "SVR" "Abore" NA "Lagon" NA 1 13 4 2010 NA NA "0" 0 -999 NA "MM" "DC" -22.4391957 166.3491088 "RE" "AP" "Complexe de recif barriere externe" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA3" 8 3.2 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100002" "SVR" "Abore" NA "Lagon" NA 1 13 4 2010 NA NA "0" 0 -999 NA "MM" "DC" -22.4396189 166.355594 "RE" "AP" "Complexe de recif barriere externe" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA3" 8 2 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100003" "SVR" "Abore" NA "Coraux" NA 1 13 4 2010 NA NA "0" 0 -999 NA "MD" "DC" -22.4477638 166.3635959 "RE" "AP" "Complexe de recif barriere externe" "platier recifal" "Detritique" "Recif barriere interne" "D2" 10 2.1 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100004" "SVR" "Abore" NA "Herbier" NA 1 13 4 2010 NA NA "0" 0 -999 NA "MD" "DC" -22.4476222 166.3673714 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Herbier" "Recif barriere interne" "SG1" 7 2.5 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100005" "SVR" "Abore" NA "Lagon" NA 1 15 4 2010 NA NA "NO" 3 -999 NA "MD" "PC" -22.4568733 166.3744796 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA3" 10 4.2 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100006" "SVR" "Abore" NA "Coraux" NA 1 13 4 2010 NA NA "0" 0 -999 NA "MD" "DC" -22.4589603 166.3780887 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Corail vivant" "Recif barriere interne" "LC3" 10 1.8 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100007" "SVR" "Abore" NA "Lagon" NA 1 13 4 2010 NA NA "0" 0 -999 NA "MD" "DC" -22.4610211 166.3785735 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA3" 10 1.6 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100008" "SVR" "Abore" NA "Coraux" NA 1 13 4 2010 NA NA "0" 0 -999 NA "MD" "DC" -22.4695532 166.3878682 "RE" "AP" "Complexe de recif barriere externe" "platier recifal" "Corail vivant" "Recif barriere interne" "D6" 10 2.2 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100009" "SVR" "Abore" NA "Lagon" NA 1 13 4 2010 NA NA "0" 0 -999 NA "MD" "DC" -22.471346 166.3946943 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA3" 8 3.5 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100010" "SVR" "Abore" NA "Coraux" NA 1 13 4 2010 NA NA "0" 0 -999 NA "MD" "DC" -22.4739242 166.399694 "RE" "AP" "Complexe de recif barriere externe" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA5" 7 4.2 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100011" "SVR" "Abore" NA "Coraux" NA 1 13 4 2010 NA NA "0" 0 -999 NA "MD" "DC" -22.4751208 166.3958625 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Recif barriere interne" NA 10 2.2 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100012" "SVR" "Abore" NA "Debris" NA 1 4 3 2010 NA NA NA 3 -999 NA "MM" "LD" -22.4807312 166.4173086 "RE" "AP" "Complexe de recif barriere externe" "platier recifal" "Detritique" "Recif barriere interne" "D1" 7 2.3 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100013" "SVR" "Abore" NA "Debris" NA 1 4 3 2010 NA NA NA 3 -999 NA "MM" "LD" -22.4815316 166.4194578 "RE" "AP" "Complexe de recif barriere externe" "platier recifal" "Detritique" "Recif barriere interne" "D1" 10 2.9 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100014" "SVR" "Abore" NA "Debris" NA 1 4 3 2010 NA NA NA 3 -999 NA "MM" "LD" -22.4826868 166.4243802 "RE" "AP" "Complexe de recif barriere externe" "platier recifal" "Detritique" "Recif barriere interne" "D1" 10 2.9 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100015" "SVR" "Abore" NA "Coraux" NA 1 4 3 2010 NA NA NA 3 -999 NA "MM" "LD" -22.4833296 166.4263966 "RE" "AP" "Complexe de recif barriere externe" "platier recifal" "Corail vivant" "Recif barriere interne" "D6" 8 2.8 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100016" "SVR" "Abore" NA "Debris" NA 1 15 4 2010 NA NA NA -999 -999 NA "PM" "PC" -22.4283514 166.3302985 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Recif barriere interne" "D1" 8 3.6 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100017" "SVR" "Abore" NA "Coraux" NA 1 15 4 2010 NA NA NA -999 -999 NA "PM" "PC" -22.430075 166.332085 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA3" 8 4.7 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100018" "SVR" "Abore" NA "Lagon" NA 1 15 4 2010 NA NA NA -999 -999 NA "MD" "PC" -22.4321884 166.3341386 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Recif barriere interne" "D2" 7 4.2 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100019" "SVR" "Abore" NA "Lagon" NA 1 15 4 2010 NA NA NA -999 -999 NA "MD" "PC" -22.4330902 166.3349636 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA5" 7 4.4 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100020" "SVR" "Abore" NA "Coraux" NA 1 15 4 2010 NA NA NA -999 -999 NA "MD" "PC" -22.434294 166.3378851 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Corail vivant" "Recif barriere interne" NA 8 4.9 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100021" "SVR" "Abore" NA "Lagon" NA 1 15 4 2010 NA NA NA -999 -999 NA "MD" "PC" -22.4367188 166.3388586 "RE" "AP" "Complexe de recif barriere externe" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA5" 8 3.1 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100022" "SVR" "Abore" NA "Lagon" NA 1 15 4 2010 NA NA NA -999 -999 NA "MD" "PC" -22.4368315 166.3431997 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA2" 10 4.7 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100023" "SVR" "Abore" NA "Coraux" NA 1 15 4 2010 NA NA NA -999 -999 NA "MD" "PC" -22.4384325 166.3424297 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA5" 7 3.4 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100024" "SVR" "Abore" NA "Coraux" NA 1 5 3 2010 NA NA NA 3 -999 NA "MM" "LD" -22.4480982 166.3729539 "RE" "AP" "Complexe de recif barriere externe" "terrasse profonde a champ de constructions coralliennes" "Corail vivant" "Recif intermediaire" "LC1" 8 3.1 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100025" "SVR" "Abore" NA "Coraux" NA 1 5 3 2010 NA NA NA 3 -999 NA "MM" "LD" -22.4498261 166.3739434 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Corail vivant" "Recif barriere interne" "LC1" 7 3.6 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100026" "SVR" "Abore" NA "Sable" NA 1 5 3 2010 NA NA NA 3 -999 NA "MM" "LD" -22.4520491 166.3724885 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Herbier" "Recif barriere interne" "SG3" 7 3.8 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100027" "SVR" "Abore" NA "Lagon" NA 1 13 4 2010 NA NA "0" 0 -999 NA "MD" "DC" -22.4545822 166.3720449 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA5" 5 1.6 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100028" "SVR" "Abore" NA "Coraux" NA 1 13 4 2010 NA NA "0" 0 -999 NA "MD" "DC" -22.4725877 166.3927274 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Corail vivant" "Recif barriere interne" "LC2" 8 4 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100029" "SVR" "Abore" NA "Coraux" NA 1 5 3 2010 NA NA NA 3 -999 NA "MD" "LD" -22.4774791 166.4011401 "RE" "AP" "Complexe de recif barriere externe" "platier recifal" "Corail vivant" "Recif barriere interne" "LC4" 10 2 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100030" "SVR" "Abore" NA "Lagon" NA 1 5 3 2010 NA NA NA 3 -999 NA "MD" "LD" -22.4761445 166.3996264 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Recif barriere interne" "D3" 6 3 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100031" "SVR" "Abore" NA "Coraux" NA 1 4 3 2010 NA NA NA 3 -999 NA "MM" "LD" -22.4769521 166.4166082 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA3" 10 3.5 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100032" "SVR" "Abore" NA NA NA 1 4 3 2010 NA NA NA -999 -999 NA "MM" "LD" -22.4794444 166.4161111 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Recif barriere interne" "D1" -999 3.8 -999 -999 -999 -999 NA +"AMP" "AB100033" "SVR" "Abore" NA "Debris" NA 1 4 3 2010 NA NA NA 3 -999 NA "MM" "LD" -22.482936 166.4297682 "RE" "AP" "Complexe de recif barriere externe" "platier recifal" "Detritique" "Recif barriere interne" "D1" 10 4 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100034" "SVR" "Abore" NA "Debris" NA 1 4 3 2010 NA NA NA 3 -999 NA "MM" "LD" -22.4846488 166.4331822 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Recif barriere interne" "D1" 10 3.3 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100035" "SVR" "Abore" NA "Lagon" NA 1 14 4 2010 NA NA "S" 2 -999 NA "MD" "NL" -22.4152085 166.3234363 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Recif barriere interne" "SA5" 7 4.2 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100036" "SVR" "Abore" NA "Lagon" NA 1 14 4 2010 NA NA "S" 2 -999 NA "MD" "NL" -22.4112272 166.321449 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA3" 7 4.1 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100037" "SVR" "Abore" NA "Lagon" NA 1 14 4 2010 NA NA "S" 2 -999 NA "MD" "NL" -22.4102625 166.3192365 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Recif barriere interne" "D5" 7 4.2 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100038" "SVR" "Abore" NA "Lagon" NA 1 14 4 2010 NA NA "S" 2 -999 NA "MD" "NL" -22.4094264 166.3185703 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA3" 7 4.4 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100039" "SVR" "Abore" NA "Debris" NA 1 14 4 2010 NA NA "S" 2 -999 NA "MD" "NL" -22.4077251 166.3158335 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Recif barriere interne" "D2" 6 3.9 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100040" "SVR" "Abore" NA "Debris" NA 1 14 4 2010 NA NA "S" 2 -999 NA "MD" "NL" -22.4072604 166.3144897 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Recif barriere interne" "D1" 7 2.9 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100041" "SVR" "Abore" NA "Debris" NA 1 14 4 2010 NA NA "S" 2 -999 NA "MD" "NL" -22.4060101 166.310431 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Recif barriere interne" "D1" 10 3.5 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100042" "SVR" "Abore" NA "Coraux" NA 1 14 4 2010 NA NA "0" 0 -999 NA "MD" "NL" -22.3894217 166.2938299 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA5" 10 4.5 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100043" "SVR" "Abore" NA "Lagon" NA 1 14 4 2010 NA NA "0" 0 -999 NA "MD" "NL" -22.3871215 166.2917027 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Recif barriere interne" "D3" 10 3.8 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100044" "SVR" "Abore" NA "Coraux" NA 1 14 4 2010 NA NA "0" 0 -999 NA "MD" "NL" -22.3831802 166.2901891 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA4" 10 5.3 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100045" "SVR" "Abore" NA "Lagon" NA 1 14 4 2010 NA NA "0" 0 -999 NA "MD" "NL" -22.3956057 166.2980673 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Recif barriere interne" "D4" 8 3.7 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100046" "SVR" "Abore" NA "Lagon" NA 1 14 4 2010 NA NA "S" 2 -999 NA "MD" "NL" -22.4193033 166.3260266 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Recif barriere interne" NA 8 3.2 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100047" "SVR" "Abore" NA "Coraux" NA 1 15 4 2010 NA NA NA -999 -999 NA "MM" "PC" -22.4231851 166.3286174 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Corail vivant" "Recif barriere interne" NA 6 3.5 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100048" "SVR" "Abore" NA "Coraux" NA 1 4 3 2010 NA NA NA 3 -999 NA "MD" "LD" -22.4997848 166.4460976 "RE" "AP" "Complexe de recif barriere externe" "passe" "Corail vivant" "Passe" "LC3" 8 8.3 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100049" "SVR" "Abore" NA "Coraux" NA 1 4 3 2010 NA NA NA 3 -999 NA "MM" "LD" -22.4735852 166.4239412 "RE" "AP" "Ile lagonaire" "lagon profond" "Corail vivant" "Recif barriere interne" "LC2" 5 11.2 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100050" "SVR" "Abore" NA "Lagon" NA 1 4 3 2010 NA NA NA 3 -999 NA "MM" "LD" -22.4783609 166.4249337 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA1" 7 6.2 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100051" "SVR" "Abore" NA "Coraux" NA 1 4 3 2010 NA NA NA 3 -999 NA "MM" "LD" -22.4783372 166.4272803 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Corail vivant" "Recif barriere interne" "LC5" 6 11 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100052" "SVR" "Abore" NA "Coraux" NA 1 4 3 2010 NA NA NA 3 -999 NA "MM" "LD" -22.4788198 166.4288444 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Corail vivant" "Recif barriere interne" NA 7 10.4 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100053" "SVR" "Abore" NA "Coraux" NA 1 4 3 2010 NA NA NA 3 -999 NA "MM" "LD" -22.4793467 166.4309034 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA3" 8 9.5 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100054" "SVR" "Abore" NA "Lagon" NA 1 4 3 2010 NA NA NA 3 -999 NA "MM" "LD" -22.4802716 166.4328641 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA1" 8 10.5 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100055" "SVR" "Abore" NA "Lagon" NA 1 4 3 2010 NA NA NA 3 -999 NA "PM" "LD" -22.4840089 166.4351528 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA3" 8 6.2 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100056" "SVR" "Abore" NA "Lagon" NA 1 4 3 2010 NA NA NA 3 -999 NA "MD" "LD" -22.4855745 166.4369425 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA3" 8 7.2 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100058" "SVR" "Abore" NA "Lagon" NA 1 4 3 2010 NA NA NA 3 -999 NA "MD" "LD" -22.4893347 166.4398803 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA3" 5 10.5 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100059" "SVR" "Abore" NA "Debris" NA 1 4 3 2010 NA NA NA 3 -999 NA "MD" "LD" -22.4933065 166.442389 "RE" "AP" "Complexe de recif barriere externe" "passe" "Detritique" "Passe" "D7" 10 23.2 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100060" "SVR" "Abore" NA "Coraux" NA 1 4 3 2010 NA NA NA 3 -999 NA "MD" "LD" -22.5004116 166.4442261 "RE" "AP" "Complexe de recif barriere externe" "passe" "Corail vivant" "Passe" "LC4" 8 7.9 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100061" "SVR" "Abore" NA "Coraux" NA 1 4 3 2010 NA NA NA 3 -999 NA "MD" "LD" -22.4999277 166.4443347 "RE" "AP" "Complexe de recif barriere externe" "passe" "Corail vivant" "Passe" "D6" 10 11.6 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100062" "SVR" "Abore" NA "Coraux" NA 1 4 3 2010 NA NA NA 3 -999 NA "MD" "LD" -22.4994497 166.4457022 "RE" "AP" "Complexe de recif barriere externe" "passe" "Corail vivant" "Passe" "LC2" 8 9 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100063" "SVR" "Abore" NA "Debris" NA 1 4 3 2010 NA NA NA 3 -999 NA "MD" "LD" -22.5274304 166.4496598 "RE" "AP" "Complexe de recif barriere externe" "platier recifal ennoye" "Detritique" "Recif barriere interne" "D7" 8 8 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100064" "SVR" "Abore" NA "Debris" NA 1 13 4 2010 NA NA "0" 0 -999 NA "MD" "DC" -22.5265019 166.4479341 "RE" "AP" "Complexe de recif barriere externe" "platier recifal ennoye" "Detritique" "Recif barriere interne" "D2" 8 5.6 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100065" "SVR" "Abore" NA "Debris" NA 1 4 3 2010 NA NA NA 3 -999 NA "MD" "LD" -22.508878 166.4556366 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Recif barriere interne" "D7" 7 7.6 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100066" "SVR" "Abore" NA "Debris" NA 1 4 3 2010 NA NA NA 3 -999 NA "MD" "LD" -22.5072001 166.455691 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Recif barriere interne" "D5" 8 7.4 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100067" "SVR" "Abore" NA "Foret" NA 1 4 6 2010 NA NA "SE" 4 -999 NA "MM" "DQ" -22.4636054 166.4073123 "RE" "AP" "Complexe de recif barriere externe" "terrasse profonde a champ de constructions coralliennes" "Detritique" "Recif intermediaire" NA 6 7.9 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100068" "SVR" "Abore" NA "Foret" NA 1 5 3 2010 NA NA NA 3 -999 NA "MM" "LD" -22.462025 166.4050677 "RE" "AP" "Complexe de recif barriere externe" "terrasse profonde a champ de constructions coralliennes" "Detritique" "Recif intermediaire" NA 6 8.9 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100069" "SVR" "Abore" NA "Foret" NA 1 4 6 2010 NA NA "SE" 4 -999 NA "MM" "DQ" -22.4611208 166.4019916 "RE" "AP" "Complexe de recif barriere externe" "terrasse profonde a champ de constructions coralliennes" "Detritique" "Recif intermediaire" NA 6 6.8 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100071" "SVR" "Abore" NA "Foret" NA 1 4 6 2010 NA NA "SE" 4 -999 NA "MM" "DQ" -22.4581912 166.397527 "RE" "AP" "Complexe de recif barriere externe" "terrasse profonde a champ de constructions coralliennes" "Detritique" "Recif intermediaire" NA 5 3.5 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100072" "SVR" "Abore" NA "Foret" NA 1 4 6 2010 NA NA "SE" 4 -999 NA "MM" "DQ" -22.452064 166.3905753 "RE" "AP" "Complexe de recif barriere externe" "terrasse profonde a champ de constructions coralliennes" "Detritique" "Recif intermediaire" NA 6 7 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100073" "SVR" "Abore" NA "Foret" NA 1 4 6 2010 NA NA "SE" 4 -999 NA "MM" "DQ" -22.4474593 166.3872049 "RE" "AP" "Complexe de recif barriere externe" "terrasse profonde a champ de constructions coralliennes" "Corail vivant" "Recif intermediaire" "LC6" 5 6.9 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100077" "SVR" "Abore" NA "Coraux" NA 1 15 4 2010 NA NA NA -999 -999 NA "MD" "PC" -22.4237539 166.3513929 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Corail vivant" "Recif barriere interne" "LC2" 5 10.3 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100078" "SVR" "Abore" NA "Coraux" NA 1 15 4 2010 NA NA NA -999 -999 NA "MD" "PC" -22.4203834 166.3485375 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Recif barriere interne" "SA5" 8 13.1 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100079" "SVR" "Abore" NA "Coraux" NA 1 15 4 2010 NA NA NA -999 -999 NA "MD" "PC" -22.4193075 166.3399845 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Corail vivant" "Recif barriere interne" "LC2" 7 12.3 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100080" "SVR" "Abore" NA "Coraux" NA 1 15 4 2010 NA NA NA -999 -999 NA "MD" "PC" -22.4176501 166.3365448 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Corail vivant" "Recif barriere interne" "LC4" 6 10.9 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100081" "SVR" "Abore" NA "Coraux" NA 1 13 4 2010 NA NA "0" 0 -999 NA "MD" "DC" -22.4696303 166.3990289 "RE" "AP" "Complexe de recif barriere externe" "terrasse profonde a champ de constructions coralliennes" "Corail vivant" "Recif intermediaire" "LC1" 6 5.6 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100082" "SVR" "Abore" NA "Coraux" NA 1 13 4 2010 NA NA "0" 0 -999 NA "MD" "DC" -22.4664898 166.3970471 "RE" "AP" "Complexe de recif barriere externe" "terrasse profonde a champ de constructions coralliennes" "Corail vivant" "Recif intermediaire" "LC1" 8 6.6 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100083" "SVR" "Abore" NA "Coraux" NA 1 13 4 2010 NA NA "0" 0 -999 NA "MD" "DC" -22.4649222 166.3928223 "RE" "AP" "Complexe de recif barriere externe" "terrasse profonde a champ de constructions coralliennes" "Corail vivant" "Recif intermediaire" "LC1" 7 5.8 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100084" "SVR" "Abore" NA "Lagon" NA 1 13 4 2010 NA NA "0" 0 -999 NA "MD" "DC" -22.4652029 166.3883707 "RE" "AP" "Complexe de recif barriere externe" "terrasse profonde a champ de constructions coralliennes" "Fond lagonaire" "Recif intermediaire" "SA3" 6 4.2 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100085" "SVR" "Abore" NA "Coraux" NA 1 13 4 2010 NA NA "0" 0 -999 NA "MD" "DC" -22.4615831 166.3868687 "RE" "AP" "Complexe de recif barriere externe" "terrasse profonde a champ de constructions coralliennes" "Corail vivant" "Recif intermediaire" "LC1" 6 3 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100086" "SVR" "Abore" NA "Coraux" NA 1 13 4 2010 NA NA "0" 0 -999 NA "MD" "DC" -22.4586409 166.3849267 "RE" "AP" "Complexe de recif barriere externe" "terrasse profonde a champ de constructions coralliennes" "Corail vivant" "Recif intermediaire" "LC3" 7 5.5 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100087" "SVR" "Abore" NA "Coraux" NA 1 13 4 2010 NA NA "0" 0 -999 NA "MD" "DC" -22.4563301 166.3817501 "RE" "AP" "Complexe de recif barriere externe" "terrasse profonde a champ de constructions coralliennes" "Corail vivant" "Recif intermediaire" "LC1" 6 3.8 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100088" "SVR" "Abore" NA "Coraux" NA 1 13 4 2010 NA NA "0" 0 -999 NA "MD" "DC" -22.4535702 166.3796819 "RE" "AP" "Complexe de recif barriere externe" "terrasse profonde a champ de constructions coralliennes" "Corail vivant" "Recif intermediaire" "LC1" 6 3 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100089" "SVR" "Abore" NA "Coraux" NA 1 15 4 2010 NA NA "NO" 3 -999 NA "MD" "PC" -22.4503721 166.3785687 "RE" "AP" "Complexe de recif barriere externe" "terrasse profonde a champ de constructions coralliennes" "Corail vivant" "Recif intermediaire" "LC5" 7 6.7 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100090" "SVR" "Abore" NA "Coraux" NA 1 15 4 2010 NA NA "NO" 3 -999 NA "MD" "PC" -22.4474225 166.3769852 "RE" "AP" "Complexe de recif barriere externe" "terrasse profonde a champ de constructions coralliennes" "Corail vivant" "Recif intermediaire" "LC1" 7 7 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100091" "SVR" "Abore" NA "Coraux" NA 1 5 3 2010 NA NA NA 3 -999 NA "MM" "LD" -22.4465064 166.3721289 "RE" "AP" "Complexe de recif barriere externe" "terrasse profonde a champ de constructions coralliennes" "Corail vivant" "Recif intermediaire" "LC5" 6 6.9 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100092" "SVR" "Abore" NA "Coraux" NA 1 13 4 2010 NA NA "0" 0 -999 NA "MD" "DC" -22.442863 166.3671553 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Corail vivant" "Recif barriere interne" "LC1" 6 7.3 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100093" "SVR" "Abore" NA "Coraux" NA 1 13 4 2010 NA NA "0" 0 -999 NA "BM" "DC" -22.4394695 166.3641062 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Corail vivant" "Recif barriere interne" "LC1" 5 6 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100094" "SVR" "Abore" NA "Coraux" NA 1 13 4 2010 NA NA "0" 0 -999 NA "MM" "DC" -22.4378117 166.3587872 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Corail vivant" "Recif barriere interne" "LC2" 7 9 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100095" "SVR" "Abore" NA "Coraux" NA 1 13 4 2010 NA NA "0" 0 -999 NA "MM" "DC" -22.4340051 166.3540565 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Corail vivant" "Recif barriere interne" "LC4" 6 9 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100096" "SVR" "Abore" NA "Coraux" NA 1 13 4 2010 NA NA "0" 0 -999 NA "MM" "DC" -22.4289046 166.3506997 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Corail vivant" "Recif barriere interne" "LC2" 5 9.5 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100097" "SVR" "Abore" NA "Coraux" NA 1 15 4 2010 NA NA NA -999 -999 NA "MM" "PC" -22.4115791 166.3253852 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA3" 6 11.7 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100098" "SVR" "Abore" NA "Coraux" NA 1 14 4 2010 NA NA "S" 2 -999 NA "MD" "NL" -22.4068195 166.3224572 "RE" "AP" "Ile lagonaire" "lagon profond" "Corail vivant" "Recif barriere interne" "LC3" 5 10.7 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100099" "SVR" "Abore" NA "Lagon" NA 1 14 4 2010 NA NA "S" 2 -999 NA "MD" "NL" -22.4029528 166.3189296 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Recif barriere interne" "SA2" 7 11.3 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100100" "SVR" "Abore" NA "Lagon" NA 1 14 4 2010 NA NA "0" 0 -999 NA "MD" "NL" -22.4022308 166.3174356 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA2" 7 11.2 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100101" "SVR" "Abore" NA "Lagon" NA 1 14 4 2010 NA NA "0" 0 -999 NA "MD" "NL" -22.395322 166.3051229 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Recif barriere interne" "SA3" 6 12.7 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100102" "SVR" "Abore" NA "Coraux isoles" NA 1 14 4 2010 NA NA "0" 0 -999 NA "MD" "NL" -22.3923255 166.3008521 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Recif barriere interne" "SA3" 5 14.8 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100103" "SVR" "Abore" NA "Sable" NA 1 14 4 2010 NA NA "0" 0 -999 NA "MD" "NL" -22.3876323 166.2985293 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Recif barriere interne" "SA2" 7 13.5 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100104" "SVR" "Abore" NA "Lagon" NA 1 14 4 2010 NA NA "0" 0 -999 NA "MD" "NL" -22.3830903 166.2961884 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Recif barriere interne" "SA2" 7 14 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100105" "SVR" "Abore" NA "Lagon" NA 1 14 4 2010 NA NA "0" 0 -999 NA "MD" "NL" -22.3796049 166.2933257 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Recif barriere interne" "SA2" 7 14.2 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100106" "SVR" "Abore" NA "Lagon" NA 1 14 4 2010 NA NA "0" 0 -999 NA "MD" "NL" -22.3717011 166.2872805 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA1" 5 15.2 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100108" "SVR" "Abore" NA "Lagon" NA 1 14 4 2010 NA NA "0" 0 -999 NA "MD" "NL" -22.3657345 166.2787498 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA2" 10 18.7 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100109" "SVR" "Abore" NA "Lagon" NA 1 14 4 2010 NA NA "0" 0 -999 NA "MD" "NL" -22.3649911 166.2736088 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA2" 8 15.9 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100110" "SVR" "Abore" NA "Lagon" NA 1 14 4 2010 NA NA "0" 0 -999 NA "MD" "NL" -22.3627312 166.2685444 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA1" 6 19.6 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100111" "SVR" "Abore" NA "Coraux" NA 1 14 4 2010 NA NA "0" 0 -999 NA "MD" "NL" -22.3654547 166.2655177 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Recif barriere interne" "D5" 8 4.9 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100112" "SVR" "Abore" NA "Coraux" NA 1 14 4 2010 NA NA "0" 0 -999 NA "MD" "NL" -22.363939 166.2621264 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Corail vivant" "Recif barriere interne" "LC5" 8 4.4 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100114" "SVR" "Abore" NA "Debris" NA 1 14 4 2010 NA NA "0" 0 -999 NA "MD" "NL" -22.3620975 166.2585858 "RE" "AP" "Complexe de recif barriere externe" "passe" "Detritique" "Recif barriere interne" "D7" 8 5.9 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100115" "SVR" "Abore" NA "Debris" NA 1 13 4 2010 NA NA "0" 0 -999 NA "MD" "DC" -22.525559 166.4465032 "RE" "AP" "Complexe de recif barriere externe" "platier recifal ennoye" "Detritique" "Recif barriere interne" "D2" 8 5.5 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100119" "SVR" "Abore" NA "Foret" NA 1 4 6 2010 NA NA "SE" 4 -999 NA "MM" "DQ" -22.4649624 166.4091243 "RE" "AP" "Complexe de recif barriere externe" "terrasse profonde a champ de constructions coralliennes" "Detritique" "Recif intermediaire" NA 5 5.9 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100120" "SVR" "Abore" NA "Foret" NA 1 4 6 2010 NA NA "SE" 4 -999 NA "MM" "DQ" -22.4650812 166.4106723 "RE" "AP" "Complexe de recif barriere externe" "terrasse profonde a champ de constructions coralliennes" "Detritique" "Recif intermediaire" NA 5 8.9 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100122" "SVR" "Abore" NA "Foret" NA 1 4 6 2010 NA NA "SE" 4 -999 NA "MM" "DQ" -22.4547727 166.3925386 "RE" "AP" "Complexe de recif barriere externe" "terrasse profonde a champ de constructions coralliennes" "Corail vivant" "Recif intermediaire" "LC4" 5 5.5 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100123" "SVR" "Abore" NA "Foret" NA 1 4 6 2010 NA NA "SE" 4 -999 NA "MM" "DQ" -22.4450832 166.3848729 "RE" "AP" "Complexe de recif barriere externe" "terrasse profonde a champ de constructions coralliennes" "Detritique" "Recif intermediaire" NA 5 5.7 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100124" "SVR" "Abore" NA "Coraux" NA 1 5 3 2010 NA NA NA 3 -999 NA "MM" "LD" -22.438602 166.3816726 "RE" "AP" "Complexe de recif barriere externe" "terrasse profonde a champ de constructions coralliennes" "Corail vivant" "Recif intermediaire" "LC2" 5 2.8 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100128" "SVR" "Abore" NA "Lagon" NA 1 14 4 2010 NA NA "0" 0 -999 NA "MD" "NL" -22.3956212 166.3109056 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Recif barriere interne" "SA3" 6 12.5 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100129" "SVR" "Abore" NA "Lagon" NA 1 14 4 2010 NA NA "0" 0 -999 NA "MD" "NL" -22.3956893 166.3094079 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Recif barriere interne" "SA1" 7 11.5 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100130" "SVR" "Abore" NA "Coraux" NA 1 14 4 2010 NA NA "0" 0 -999 NA "MD" "NL" -22.362579 166.2595047 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Corail vivant" "Recif barriere interne" NA 10 5.2 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100131" "SVR" "Abore" NA "Debris" NA 1 4 3 2010 NA NA NA 3 -999 NA "MD" "LD" -22.4990592 166.446391 "RE" "AP" "Ile lagonaire" "lagon profond" "Detritique" "Passe" NA 8 8.4 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100132" "SVR" "Abore" NA "Coraux" NA 1 4 3 2010 NA NA NA 3 -999 NA "MD" "LD" -22.4995548 166.4465217 "RE" "AP" "Ile lagonaire" "lagon profond" "Corail vivant" "Passe" "LC4" 8 5.3 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AB100142" "SVR" "Abore" NA "Foret" NA 1 5 3 2010 NA NA NA 3 -999 NA "MM" "LD" -22.4548717 166.3926474 "RE" "AP" "Complexe de recif barriere externe" "terrasse profonde a champ de constructions coralliennes" "Detritique" "Recif intermediaire" NA 5 3.3 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "AS140041" "SVR" "Grand Astrolabe" NA "Barriere" NA 1 7 7 2014 NA NA "SE" 4 4 NA NA "LM" -19.71928 165.5932 "HR" "AP" "Banc lagonaire" "terrasse lagonaire peu profonde" "Detritique" "Recif barriere interne" "D4" 10 9 -999 -999 -999 -999 "William Roman" +"AMP" "AS140042" "SVR" "Grand Astrolabe" NA "Barriere" NA 1 7 7 2014 NA NA "SE" 4 4 NA NA "LM" -19.71475 165.5925 "HR" "AP" "Banc de recif barriere" "platier recifal" "Detritique" "Recif barriere interne" "D1" 10 8 -999 -999 -999 -999 "William Roman" +"AMP" "AS140043" "SVR" "Grand Astrolabe" NA "Barriere" NA 1 7 7 2014 NA NA "SE" 4 4 NA NA "LM" -19.71155 165.59108 "HR" "AP" "Banc lagonaire" "terrasse lagonaire peu profonde" "Fond lagonaire" "Recif barriere interne" "SA1" 10 11 -999 -999 -999 -999 "William Roman" +"AMP" "AS140044" "SVR" "Grand Astrolabe" NA "Barriere" NA 1 7 7 2014 NA NA "SE" 4 4 NA NA "LM" -19.70871 165.59151 "HR" "AP" "Banc de recif barriere" "platier recifal" "Detritique" "Recif barriere interne" "D1" 10 8 -999 -999 -999 -999 "William Roman" +"AMP" "AS140045" "SVR" "Grand Astrolabe" NA "Barriere" NA 1 7 7 2014 NA NA "SE" 4 4 NA NA "LM" -19.7122 165.58693 "HR" "AP" "Banc lagonaire" "terrasse lagonaire peu profonde" "Detritique" "Recif barriere interne" "D7" 10 18 -999 -999 -999 -999 "William Roman" +"AMP" "AS140046" "SVR" "Grand Astrolabe" NA "Barriere" NA 1 7 7 2014 NA NA "SE" 4 4 NA NA "LM" -19.71172 165.58307 "HR" "AP" "Banc de recif barriere" "platier recifal" "Detritique" "Recif barriere interne" "D7" 10 9 -999 -999 -999 -999 "William Roman" +"AMP" "AS140047" "SVR" "Grand Astrolabe" NA "Barriere" NA 1 7 7 2014 NA NA "SE" 4 4 NA NA "LM" -19.71747 165.58877 "HR" "AP" "Banc lagonaire" "terrasse profonde" "Detritique" "Fond lagonaire" "D7" 10 22 -999 -999 -999 -999 "William Roman" +"AMP" "AS140048" "SVR" "Grand Astrolabe" NA "Barriere" NA 1 7 7 2014 NA NA "SE" 4 4 NA NA "LM" -19.71825 165.59047 "HR" "AP" "Banc lagonaire" "terrasse profonde" "Corail vivant" "Fond lagonaire" NA 10 18 -999 -999 -999 -999 "William Roman" +"AMP" "AS140049" "SVR" "Grand Astrolabe" NA "Barriere" NA 1 7 7 2014 NA NA "SE" 4 4 NA NA "LM" -19.72221 165.59302 "HR" "AP" "Banc lagonaire" "terrasse lagonaire peu profonde" "Fond lagonaire" "Recif barriere interne" "SA1" 10 14 -999 -999 -999 -999 "William Roman" +"AMP" "AS140050" "SVR" "Grand Astrolabe" NA "Barriere" NA 1 7 7 2014 NA NA "SE" 4 4 NA NA "LM" -19.72305 165.59474 "HR" "AP" "Banc de recif barriere" "platier recifal" "Detritique" "Recif barriere interne" "D5" 10 9 -999 -999 -999 -999 "William Roman" +"AMP" "AS140051" "SVR" "Grand Astrolabe" NA "Barriere" NA 1 7 7 2014 NA NA "SE" 4 4 NA NA "LM" -19.75588 165.59471 "HR" "AP" "Banc lagonaire" "terrasse profonde" "Detritique" "Fond lagonaire" "D5" 10 9 -999 -999 -999 -999 "William Roman" +"AMP" "AS140052" "SVR" "Grand Astrolabe" NA "Barriere" NA 1 7 7 2014 NA NA "SE" 4 4 NA NA "LM" -19.72636 165.59447 "HR" "AP" "Banc de recif barriere" "platier recifal" "Detritique" "Recif barriere interne" "D1" 10 8 -999 -999 -999 -999 "William Roman" +"AMP" "AS140053" "SVR" "Grand Astrolabe" NA "Barriere" NA 1 8 7 2014 NA NA "SE" 2 2 NA NA "LM" -19.72089 165.58288 "HR" "AP" "Banc lagonaire" "terrasse profonde" "Detritique" "Fond lagonaire" "D5" 10 14 -999 -999 -999 -999 "William Roman" +"AMP" "AS140054" "SVR" "Grand Astrolabe" NA "Barriere" NA 1 8 7 2014 NA NA "SE" 2 2 NA NA "LM" -19.72035 165.58383 "HR" "AP" "Banc lagonaire" "terrasse profonde" "Detritique" "Fond lagonaire" "D7" 10 25.5 -999 -999 -999 -999 "William Roman" +"AMP" "AS140055" "SVR" "Grand Astrolabe" NA "Barriere" NA 1 8 7 2014 NA NA "SE" 2 2 NA NA "LM" -19.78518 165.60475 "HR" "AP" "Banc lagonaire" "terrasse profonde" "Detritique" "Recif barriere interne" "D7" 10 17 -999 -999 -999 -999 "William Roman" +"AMP" "AS140056" "SVR" "Grand Astrolabe" NA "Barriere" NA 1 8 7 2014 NA NA "SE" 2 2 NA NA "LM" -19.78669 165.60516 "HR" "AP" "Banc lagonaire" "terrasse lagonaire peu profonde" "Detritique" "Recif barriere interne" NA 10 13 -999 -999 -999 -999 "William Roman" +"AMP" "AS140058" "SVR" "Grand Astrolabe" NA "Barriere" NA 1 8 7 2014 NA NA "SE" 2 2 NA NA "LM" -19.7925 165.60384 "HR" "AP" "Banc lagonaire" "terrasse lagonaire peu profonde" "Detritique" "Recif barriere interne" "D7" 10 14 -999 -999 -999 -999 "William Roman" +"AMP" "AS140059" "SVR" "Grand Astrolabe" NA "Barriere" NA 1 8 7 2014 NA NA "SE" 2 2 NA NA "LM" -19.79636 165.58615 "HR" "AP" "Banc lagonaire" "terrasse profonde" "Corail vivant" "Recif isole" "D7" 10 22 -999 -999 -999 -999 "William Roman" +"AMP" "AS140060" "SVR" "Grand Astrolabe" NA "Barriere" NA 1 8 7 2014 NA NA "SE" 2 2 NA NA "LM" -19.79949 165.58868 "HR" "AP" "Banc lagonaire" "terrasse profonde" "Fond lagonaire" "Fond lagonaire" "SA5" 10 16 -999 -999 -999 -999 "William Roman" +"AMP" "AS140061" "SVR" "Grand Astrolabe" NA "Barriere" NA 1 8 7 2014 NA NA "SE" 2 2 NA NA "LM" -19.80371 165.56871 "HR" "AP" "Banc lagonaire" "terrasse profonde" "Corail vivant" "Recif isole" "LC1" 10 3 -999 -999 -999 -999 "William Roman" +"AMP" "AS140062" "SVR" "Grand Astrolabe" NA "Barriere" NA 1 8 7 2014 NA NA "SE" 2 2 NA NA "LM" -19.80489 165.56779 "HR" "AP" "Banc lagonaire" "terrasse profonde" "Detritique" "Recif isole" "D5" 10 15 -999 -999 -999 -999 "William Roman" +"AMP" "AS140063" "SVR" "Grand Astrolabe" NA "Barriere" NA 1 8 7 2014 NA NA "SE" 2 2 NA NA "LM" -19.87194 165.56752 "HR" "AP" "Banc de recif barriere" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA3" 10 4 -999 -999 -999 -999 "William Roman" +"AMP" "AS140066" "SVR" "Grand Astrolabe" NA "Barriere" NA 1 8 7 2014 NA NA "SE" 2 2 NA NA "LM" -19.87341 165.55426 "HR" "AP" "Banc de recif barriere" "platier recifal" "Corail vivant" "Recif barriere interne" "LC5" 10 10 -999 -999 -999 -999 "William Roman" +"AMP" "AS140067" "SVR" "Grand Astrolabe" NA "Barriere" NA 1 8 7 2014 NA NA "SE" 2 2 NA NA "LM" -19.87705 165.52962 "HR" "AP" "Banc de recif barriere" "platier recifal" "Detritique" "Recif barriere interne" "D7" 10 9 -999 -999 -999 -999 "William Roman" +"AMP" "AS140070" "SVR" "Grand Astrolabe" NA "Barriere" NA 1 8 7 2014 NA NA "SE" 2 2 NA NA "LM" -19.88011 165.51617 "HR" "AP" "Banc de recif barriere" "platier recifal" "Corail vivant" "Recif barriere interne" "LC1" 10 4 -999 -999 -999 -999 "William Roman" +"AMP" "AS140072" "SVR" "Grand Astrolabe" NA "Barriere" NA 1 8 7 2014 NA NA "SE" 2 2 NA NA "LM" -19.88363 165.52594 "HR" "AP" "" "" "Detritique" "Recif barriere externe" NA 10 5 -999 -999 -999 -999 "William Roman" +"AMP" "AS140076" "SVR" "Petit Astrolabe" NA "Barriere" NA 1 9 7 2014 NA NA "SE" 2 2 NA NA "LM" -19.84451 165.84303 "HR" "AP" "Banc lagonaire" "terrasse profonde" "Corail vivant" "Recif barriere interne" "LC5" 10 14 -999 -999 -999 -999 "William Roman" +"AMP" "AS140077" "SVR" "Petit Astrolabe" NA "Barriere" NA 1 9 7 2014 NA NA "SE" 2 2 NA NA "LM" -19.84321 165.84384 "HR" "AP" "Banc lagonaire" "terrasse profonde" "Detritique" "Recif barriere interne" "D5" 10 8 -999 -999 -999 -999 "William Roman" +"AMP" "AS140078" "SVR" "Petit Astrolabe" NA "Barriere" NA 1 9 7 2014 NA NA "SE" 2 2 NA NA "LM" -19.8449 165.84534 "HR" "AP" "Banc lagonaire" "terrasse profonde" "Detritique" "Recif barriere interne" "D5" 10 6 -999 -999 -999 -999 "William Roman" +"AMP" "AS140079" "SVR" "Petit Astrolabe" NA "Barriere" NA 1 9 7 2014 NA NA "SE" 2 2 NA NA "LM" -19.85374 165.84222 "HR" "AP" "Banc lagonaire" "terrasse profonde" "Corail vivant" "Recif barriere interne" "LC3" 10 16 -999 -999 -999 -999 "William Roman" +"AMP" "AS140080" "SVR" "Petit Astrolabe" NA "Barriere" NA 1 9 7 2014 NA NA "SE" 2 2 NA NA "LM" -19.85446 165.84297 "HR" "AP" "Banc de recif barriere" "platier recifal" "Corail vivant" "Recif barriere interne" "LC5" 10 9 -999 -999 -999 -999 "William Roman" +"AMP" "AS140081" "SVR" "Petit Astrolabe" NA "Barriere" NA 1 9 7 2014 NA NA "SE" 2 2 NA NA "LM" -19.86095 165.84058 "HR" "AP" "Banc de recif barriere" "platier recifal" "Corail vivant" "Recif barriere interne" "LC3" 10 9 -999 -999 -999 -999 "William Roman" +"AMP" "AS140082" "SVR" "Petit Astrolabe" NA "Barriere" NA 1 9 7 2014 NA NA "SE" 2 2 NA NA "LM" -19.86077 165.83949 "HR" "AP" "Banc lagonaire" "terrasse profonde" "Fond lagonaire" "Recif barriere interne" "SA3" 10 24 -999 -999 -999 -999 "William Roman" +"AMP" "AS140084" "SVR" "Petit Astrolabe" NA "Barriere" NA 1 9 7 2014 NA NA "SE" 2 2 NA NA "LM" -19.8673 165.8383 "HR" "AP" "Banc de recif barriere" "platier recifal" "Detritique" "Recif barriere interne" "D6" 10 8 -999 -999 -999 -999 "William Roman" +"AMP" "AS140085" "SVR" "Petit Astrolabe" NA "Barriere" NA 1 9 7 2014 NA NA "SE" 2 2 NA NA "LM" -19.87637 165.83664 "HR" "AP" "Banc de recif barriere" "platier recifal" "Detritique" "Recif barriere interne" "D7" 10 8 -999 -999 -999 -999 "William Roman" +"AMP" "AS140086" "SVR" "Petit Astrolabe" NA "Barriere" NA 1 9 7 2014 NA NA "SE" 2 2 NA NA "LM" -19.87811 165.83476 "HR" "AP" "Banc lagonaire" "terrasse profonde" "Fond lagonaire" "Recif barriere interne" "SA3" 10 16 -999 -999 -999 -999 "William Roman" +"AMP" "AS140087" "SVR" "Petit Astrolabe" NA "Barriere" NA 1 9 7 2014 NA NA "SE" 2 2 NA NA "LM" -19.88056 165.82449 "HR" "AP" "Banc lagonaire" "terrasse profonde" "Corail vivant" "Recif barriere interne" "LC1" 10 6 -999 -999 -999 -999 "William Roman" +"AMP" "AS140088" "SVR" "Petit Astrolabe" NA "Barriere" NA 1 9 7 2014 NA NA "SE" 2 2 NA NA "LM" -19.88285 165.8271 "HR" "AP" "Banc lagonaire" "terrasse profonde" "Corail vivant" "Recif barriere interne" "D5" 10 18 -999 -999 -999 -999 "William Roman" +"AMP" "AS140089" "SVR" "Petit Astrolabe" NA "Barriere" NA 1 9 7 2014 NA NA "SE" 2 2 NA NA "LM" -19.88747 165.83023 "HR" "AP" "Banc de recif barriere" "platier recifal" "Detritique" "Recif barriere interne" "D3" 10 9 -999 -999 -999 -999 "William Roman" +"AMP" "AS140090" "SVR" "Petit Astrolabe" NA "Barriere" NA 1 9 7 2014 NA NA "SE" 2 2 NA NA "LM" -19.8891 165.82724 "HR" "AP" "Banc lagonaire" "terrasse profonde" "Fond lagonaire" "Recif barriere interne" "SA3" 10 9 -999 -999 -999 -999 "William Roman" +"AMP" "AS140092" "SVR" "Petit Astrolabe" NA "Barriere" NA 1 9 7 2014 NA NA "SE" 1 1 NA NA "LM" -19.88708 165.8239 "HR" "AP" "Banc lagonaire" "terrasse profonde" "Corail vivant" "Recif barriere interne" "LC1" 10 19 -999 -999 -999 -999 "William Roman" +"AMP" "AS140093" "SVR" "Petit Astrolabe" NA "Barriere" NA 1 9 7 2014 NA NA "SE" 1 1 NA NA "LM" -19.88596 165.82838 "HR" "AP" "Banc lagonaire" "terrasse profonde" "Corail vivant" "Recif barriere interne" "D7" 10 19 -999 -999 -999 -999 "William Roman" +"AMP" "AS140094" "SVR" "Petit Astrolabe" NA "Barriere" NA 1 9 7 2014 NA NA "SE" 1 1 NA NA "LM" -19.89867 165.81786 "HR" "AP" "" "" "Corail vivant" "Recif barriere externe" "LC1" 10 8 -999 -999 -999 -999 "William Roman" +"AMP" "AS140095" "SVR" "Petit Astrolabe" NA "Barriere" NA 1 9 7 2014 NA NA "SE" 1 1 NA NA "LM" -19.89889 165.8201 "HR" "AP" "Banc de recif barriere" "front recifal" "Corail vivant" "Recif barriere externe" "LC1" 10 10 -999 -999 -999 -999 "William Roman" +"AMP" "AS140097" "SVR" "Petit Astrolabe" NA "Barriere" NA 1 9 7 2014 NA NA "SE" 1 1 NA NA "LM" -19.89507 165.82761 "HR" "AP" "Banc de recif barriere" "front recifal" "Corail vivant" "Recif barriere externe" "LC1" 10 6 -999 -999 -999 -999 "William Roman" +"AMP" "AS140098" "SVR" "Petit Astrolabe" NA "Barriere" NA 1 9 7 2014 NA NA "SE" 1 1 NA NA "LM" -19.89369 165.82069 "HR" "AP" "Banc de recif barriere" "platier recifal" "Corail vivant" "Recif barriere interne" "D7" 10 13 -999 -999 -999 -999 "William Roman" +"AMP" "AS140099" "SVR" "Petit Astrolabe" NA "Barriere" NA 1 9 7 2014 NA NA "SE" 1 1 NA NA "LM" -19.89348 165.82175 "HR" "AP" "Banc de recif barriere" "platier recifal" "Detritique" "Recif barriere interne" "D1" 10 8 -999 -999 -999 -999 "William Roman" +"AMP" "AS140150" "SVR" "Petit Astrolabe" NA "Barriere" NA 1 9 7 2014 NA NA "SE" 2 2 NA NA "LM" -19.83773 165.84705 "HR" "AP" "Banc de recif barriere" "front recifal" "Corail vivant" "Recif barriere externe" "LC1" 10 10 -999 -999 -999 -999 "William Roman" +"AMP" "AS140151" "SVR" "Petit Astrolabe" NA "Barriere" NA 1 9 7 2014 NA NA "SE" 2 2 NA NA "LM" -19.83661 165.84923 "HR" "AP" "" "" "Corail vivant" "Recif barriere externe" "LC1" 10 10 -999 -999 -999 -999 "William Roman" +"AMP" "AS140152" "SVR" "Petit Astrolabe" NA "Barriere" NA 1 9 7 2014 NA NA "SE" 2 2 NA NA "LM" -19.84052 165.85227 "HR" "AP" "" "" "Corail vivant" "Recif barriere externe" "LC1" 10 6 -999 -999 -999 -999 "William Roman" +"AMP" "AS140153" "SVR" "Petit Astrolabe" NA "Barriere" NA 1 9 7 2014 NA NA "SE" 2 2 NA NA "LM" -19.84248 165.85213 "HR" "AP" "Banc de recif barriere" "front recifal" "Corail vivant" "Recif barriere externe" "LC1" 10 9 -999 -999 -999 -999 "William Roman" +"AMP" "AS140154" "SVR" "Petit Astrolabe" NA "Barriere" NA 1 9 7 2014 NA NA "SE" 2 2 NA NA "LM" -19.84672 165.85333 "HR" "AP" "" "" "Corail vivant" "Recif barriere externe" "LC1" 10 11 -999 -999 -999 -999 "William Roman" +"AMP" "AS140155" "SVR" "Petit Astrolabe" NA "Barriere" NA 1 9 7 2014 NA NA "SE" 2 2 NA NA "LM" -19.8482 165.85458 "HR" "AP" "" "" "Corail vivant" "Recif barriere externe" "LC1" 10 9 -999 -999 -999 -999 "William Roman" +"AMP" "AS140156" "SVR" "Petit Astrolabe" NA "Barriere" NA 1 9 7 2014 NA NA "SE" 2 2 NA NA "LM" -19.85758 165.84753 "HR" "AP" "Banc de recif barriere" "front recifal" "Corail vivant" "Recif barriere externe" "LC1" 10 8 -999 -999 -999 -999 "William Roman" +"AMP" "AS140157" "SVR" "Petit Astrolabe" NA "Barriere" NA 1 9 7 2014 NA NA "SE" 2 2 NA NA "LM" -19.8599 165.84643 "HR" "AP" "Banc de recif barriere" "front recifal" "Corail vivant" "Recif barriere externe" "LC1" 10 7 -999 -999 -999 -999 "William Roman" +"AMP" "AS140158" "SVR" "Petit Astrolabe" NA "Barriere" NA 1 9 7 2014 NA NA "SE" 2 2 NA NA "LM" -19.87943 165.84295 "HR" "AP" "" "" "Corail vivant" "Recif barriere externe" "LC1" 10 9 -999 -999 -999 -999 "William Roman" +"AMP" "AS140159" "SVR" "Petit Astrolabe" NA "Barriere" NA 1 9 7 2014 NA NA "SE" 2 2 NA NA "LM" -19.88238 165.84242 "HR" "AP" "Banc de recif barriere" "front recifal" "Corail vivant" "Recif barriere externe" "LC1" 10 8 -999 -999 -999 -999 "William Roman" +"AMP" "AS140160" "SVR" "Petit Astrolabe" NA "Barriere" NA 1 9 7 2014 NA NA "SE" 2 2 NA NA "LM" -19.88924 165.83827 "HR" "AP" "" "" "Corail vivant" "Recif barriere externe" "LC1" 10 6 -999 -999 -999 -999 "William Roman" +"AMP" "BE13P004" "SVR" "Desmazures" NA "Passe" NA 1 24 6 2013 "14:14" "pluie" NA 1 1 NA NA "LD" -21.37922 159.43827 "HR" "AP" "" "" "Corail vivant" "Passe" "LC1" -999 12 -999 -999 -999 -999 NA +"AMP" "BE13P005" "SVR" "Desmazures" NA "Pente externe" NA 1 24 6 2013 "14:25" "nuage" NA 1 1 NA NA "LD" -21.38995 159.42751 "HR" "AP" "Couronne d atoll" "platier recifal ennoye" "Corail vivant" "Recif barriere interne" "LC1" -999 8 -999 -999 -999 -999 NA +"AMP" "BE13S004" "SVR" "Desmazures" NA "Pente interne" NA 1 24 6 2013 "11:15" "soleil" NA 1 1 NA NA "LD" -21.35132 159.35233 "HR" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Corail vivant" "Recif barriere interne" "LC2" -999 8 -999 -999 -999 -999 NA +"AMP" "BE13S005" "SVR" "Desmazures" NA "Pente interne" NA 1 24 6 2013 "11:20" "soleil" NA 1 1 NA NA "LD" -21.35347 159.35362 "HR" "AP" "Couronne d atoll" "platier recifal" "Detritique" "Recif barriere interne" NA -999 6 -999 -999 -999 -999 NA +"AMP" "BE13S007" "SVR" "Desmazures" NA "Pente interne" NA 1 24 6 2013 "13:09" "pluie" NA 2 1 NA NA "LD" -21.38864 159.39751 "HR" "AP" "Couronne d atoll" "platier recifal ennoye" "Fond lagonaire" "Recif barriere interne" "SA4" -999 8 -999 -999 -999 -999 NA +"AMP" "BE13S009" "SVR" "Caye est" NA "Pente interne" NA 1 24 6 2013 "16:56" "nuage" "0" 0 1 NA NA "LD" -21.42507 159.53867 "HR" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Corail vivant" "Recif barriere interne" "LC2" -999 11 -999 -999 -999 -999 NA +"AMP" "BE13S010" "SVR" "Caye est" NA "Pente interne" NA 1 24 6 2013 "17:02" "nuage" "0" 0 1 NA NA "LD" -21.43102 159.54056 "HR" "AP" "Couronne d atoll" "platier recifal ennoye" "Corail vivant" "Recif barriere interne" "LC1" -999 8 -999 -999 -999 -999 NA +"AMP" "BE13S011" "SVR" "Caye est" NA "Pente interne" NA 1 24 6 2013 "17:28" "nuage" "0" 0 1 NA NA "LD" -21.45395 159.55984 "HR" "AP" "Couronne d atoll" "platier recifal ennoye" "Corail vivant" "Recif barriere interne" "LC1" -999 9 -999 -999 -999 -999 NA +"AMP" "BE13S012" "SVR" "Desmazures" NA "Pente interne" NA 1 24 6 2013 "11:59" "nuage" NA 2 1 NA NA "LD" -21.37585 159.36366 "HR" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Corail vivant" "Recif barriere interne" "LC4" -999 6 -999 -999 -999 -999 NA +"AMP" "BE13S013" "SVR" "Desmazures" NA "Pente interne" NA 1 24 6 2013 "12:01" "nuage" NA 2 1 NA NA "LD" -21.37634 159.36617 "HR" "AP" "Couronne d atoll" "platier recifal" "Corail vivant" "Recif barriere interne" "LC4" -999 3 -999 -999 -999 -999 NA +"AMP" "BE13S015" "SVR" "Caye est" NA "Pente interne" NA 1 24 6 2013 "17:32" "nuage" "0" 0 1 NA NA "LD" -21.45562 159.55672 "HR" "AP" "Couronne d atoll" "platier recifal ennoye" "Corail vivant" "Recif barriere interne" "LC3" -999 6 -999 -999 -999 -999 NA +"AMP" "BE13S016" "SVR" "Recif Bellona Sud" NA "Pente interne" NA 1 25 6 2013 "08:50" "nuage" "0" 0 1 NA NA "LD" -21.5932 159.57921 "HR" "AP" "Couronne d atoll" "platier recifal ennoye" "Corail vivant" "Recif barriere interne" "LC1" -999 25 -999 -999 -999 -999 NA +"AMP" "BE13S018" "SVR" "Recif Bellona Sud" NA "Pente interne" NA 1 25 6 2013 "09:53" "pluie" "0" 0 1 NA NA "LD" -21.64462 159.59425 "HR" "AP" "Couronne d atoll" "platier recifal ennoye" "Corail vivant" "Recif barriere interne" "LC3" -999 27 -999 -999 -999 -999 NA +"AMP" "BE13S019" "SVR" "Recif Bellona Sud" NA "Pente interne" NA 1 25 6 2013 "09:57" "nuage" "0" 0 1 NA NA "LD" -21.64611 159.5934 "HR" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Corail vivant" "Recif barriere interne" "LC5" -999 28 -999 -999 -999 -999 NA +"AMP" "BE13S026" "SVR" "Recif Bellona Sud" NA "Pente interne" NA 1 25 6 2013 "13:57" "nuage" "0" 0 1 NA NA "LD" -21.80007 159.55028 "HR" "AP" "Couronne d atoll" "platier recifal ennoye" "Corail vivant" "Recif barriere interne" "LC3" -999 10 -999 -999 -999 -999 NA +"AMP" "BE13S027" "SVR" "Recif Bellona Sud" NA "Pente interne" NA 1 25 6 2013 "14:03" "nuage" "0" 0 1 NA NA "LD" -21.80159 159.55551 "HR" "AP" "Couronne d atoll" "platier recifal ennoye" "Corail vivant" "Recif barriere interne" "LC1" -999 9 -999 -999 -999 -999 NA +"AMP" "BE13S028" "SVR" "Recif Bellona Sud" NA "Pente interne" NA 1 25 6 2013 "14:22" "nuage" "0" 0 1 NA NA "LD" -21.80249 159.5495 "HR" "AP" "Couronne d atoll" "platier recifal ennoye" "Fond lagonaire" "Recif barriere interne" "SA4" -999 9 -999 -999 -999 -999 NA +"AMP" "BE13S029" "SVR" "Recif Bellona Sud" NA "Pente interne" NA 1 25 6 2013 "14:25" "nuage" NA 1 1 NA NA "LD" -21.80432 159.5499 "HR" "AP" "Couronne d atoll" "platier recifal ennoye" "Fond lagonaire" "Recif barriere interne" "SA3" -999 9 -999 -999 -999 -999 NA +"AMP" "BE13S030" "SVR" "Recif Bellona Sud" NA "Pente interne" NA 1 25 6 2013 "15:12" "nuage" NA 1 1 NA NA "LD" -21.85096 159.54266 "HR" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Fond lagonaire" "Recif barriere interne" "SA3" -999 11 -999 -999 -999 -999 NA +"AMP" "BE13S031" "SVR" "Recif Bellona Sud" NA "Pente interne" NA 1 25 6 2013 "15:15" "nuage" NA 1 1 NA NA "LD" -21.84878 159.54384 "HR" "AP" "Couronne d atoll" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA5" -999 7 -999 -999 -999 -999 NA +"AMP" "BE13S032" "SVR" "Recif Bellona Sud" NA "Pente interne" NA 1 25 6 2013 "15:37" "nuage" NA 1 1 NA NA "LD" -21.86731 159.53661 "HR" "AP" "Couronne d atoll" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" NA -999 2.5 -999 -999 -999 -999 NA +"AMP" "BE13S033" "SVR" "Recif Bellona Sud" NA "Pente interne" NA 1 25 6 2013 "15:42" "nuage" NA 1 1 NA NA "LD" -21.86495 159.53374 "HR" "AP" "Couronne d atoll" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA3" -999 5 -999 -999 -999 -999 NA +"AMP" "BE13S034" "SVR" "Recif Bellona Sud" NA "Pente interne" NA 1 25 6 2013 "16:45" "nuage" NA 1 1 NA NA "LD" -21.88552 159.448 "HR" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Fond lagonaire" "Recif barriere interne" "SA1" -999 8 -999 -999 -999 -999 NA +"AMP" "BE13S035" "SVR" "Recif Bellona Sud" NA "Pente interne" NA 1 25 6 2013 "16:50" "nuage" NA 1 1 NA NA "LD" -21.89212 159.44557 "HR" "AP" "Couronne d atoll" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA1" -999 2.5 -999 -999 -999 -999 NA +"AMP" "BE13S036" "SVR" "Recif Bellona Sud" NA "Pente interne" NA 1 25 6 2013 "17:10" "nuage" NA 1 1 NA NA "LD" -21.88565 159.43498 "HR" "AP" "Couronne d atoll" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA3" -999 3 -999 -999 -999 -999 NA +"AMP" "BE13S037" "SVR" "Recif Bellona Sud" NA "Pente interne" NA 1 25 6 2013 "17:14" "nuage" NA 1 1 NA NA "LD" -21.88403 159.43747 "HR" "AP" "Couronne d atoll" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA3" -999 8 -999 -999 -999 -999 NA +"AMP" "BE13S038" "SVR" "Recif Bellona milieu" NA "Pente interne" NA 1 26 6 2013 "08:38" "soleil" NA 5 2 NA NA "LD" -21.7586 159.32693 "HR" "AP" "Couronne d atoll" "platier recifal ennoye" "Fond lagonaire" "Recif barriere interne" "SA3" -999 20 -999 -999 -999 -999 NA +"AMP" "BE13S039" "SVR" "Recif Bellona milieu" NA "Pente interne" NA 1 26 6 2013 "08:46" "soleil" NA 5 2 NA NA "LD" -21.75801 159.32376 "HR" "AP" "Couronne d atoll" "platier recifal ennoye" "Fond lagonaire" "Recif barriere interne" "SA1" -999 20 -999 -999 -999 -999 NA +"AMP" "BE13S040" "SVR" "Recif Bellona milieu" NA "Pente interne" NA 1 26 6 2013 "10:43" "soleil" NA 5 1 NA NA "LD" -21.58544 159.2583 "HR" "AP" "Couronne d atoll" "platier recifal ennoye" "Corail vivant" "Recif barriere interne" "LC3" -999 16 -999 -999 -999 -999 NA +"AMP" "BE13S041" "SVR" "Recif Bellona milieu" NA "Pente interne" NA 1 26 6 2013 "10:48" "soleil" NA 5 1 NA NA "LD" -21.58799 159.25578 "HR" "AP" "Couronne d atoll" "platier recifal ennoye" "Detritique" "Recif barriere interne" NA -999 20 -999 -999 -999 -999 NA +"AMP" "BE13S042" "SVR" "Recif Bellona milieu" NA "Pente interne" NA 1 26 6 2013 "12:17" "soleil" NA 5 1 NA NA "LD" -21.49534 159.18315 "HR" "AP" "Couronne d atoll" "platier recifal ennoye" "Fond lagonaire" "Recif barriere interne" "SA1" -999 25 -999 -999 -999 -999 NA +"AMP" "BE13S043" "SVR" "Recif Bellona milieu" NA "Pente interne" NA 1 26 6 2013 "12:22" "soleil" NA 5 1 NA NA "LD" -21.49756 159.1837 "HR" "AP" "Couronne d atoll" "platier recifal ennoye" "Fond lagonaire" "Recif barriere interne" "SA4" -999 24 -999 -999 -999 -999 NA +"AMP" "BE13S044" "SVR" "Recif Bellona milieu" NA "Pente interne" NA 1 26 6 2013 "14:03" "soleil" NA 4 1 NA NA "LD" -21.43524 159.02403 "HR" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Corail vivant" "Recif barriere interne" NA -999 7 -999 -999 -999 -999 NA +"AMP" "BE13S045" "SVR" "Recif Bellona milieu" NA "Pente interne" NA 1 26 6 2013 "14:09" "soleil" NA 4 1 NA NA "LD" -21.4388 159.03178 "HR" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Fond lagonaire" "Recif barriere interne" "SA1" -999 16 -999 -999 -999 -999 NA +"AMP" "BE13S046" "SVR" "Recif Bellona milieu" NA "Pente interne" NA 1 26 6 2013 "14:30" "soleil" NA 3 1 NA NA "LD" -21.43916 159.01639 "HR" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Fond lagonaire" "Recif barriere interne" "SA4" -999 13 -999 -999 -999 -999 NA +"AMP" "BE13S047" "SVR" "Recif Bellona milieu" NA "Pente interne" NA 1 26 6 2013 "14:33" "soleil" NA 3 1 NA NA "LD" -21.44014 159.01701 "HR" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Corail vivant" "Recif barriere interne" "LC2" -999 6 -999 -999 -999 -999 NA +"AMP" "BE13S048" "SVR" "Recif Bellona milieu" NA "Pente interne" NA 1 26 6 2013 "14:50" "soleil" NA 3 -999 NA NA "LD" -21.44859 159.01443 "HR" "AP" "Couronne d atoll" "lagon enclave de faro" "Fond lagonaire" "Recif barriere interne" "SA3" -999 3 -999 -999 -999 -999 NA +"AMP" "BE13S049" "SVR" "Recif Bellona milieu" NA "Pente interne" NA 1 26 6 2013 "14:55" "soleil" NA 3 -999 NA NA "LD" -21.45559 159.01288 "HR" "AP" "Couronne d atoll" "platier recifal de faro" "Fond lagonaire" "Recif barriere interne" "SA3" -999 3 -999 -999 -999 -999 NA +"AMP" "BE13S050" "SVR" "Recif Bellona milieu" NA "Pente interne" NA 1 26 6 2013 "15:13" "soleil" NA 3 -999 NA NA "LD" -21.45659 159.00607 "HR" "AP" "Couronne d atoll" "platier recifal de faro" "Corail vivant" "Recif barriere interne" "LC2" -999 2 -999 -999 -999 -999 NA +"AMP" "BE13S052" "SVR" "Caye observatoire" NA "Pente externe" NA 1 27 6 2013 "08:47" "soleil" NA 2 1 NA NA "LD" -21.42166 158.83978 "HR" "AP" "Couronne d atoll" "platier recifal ennoye" "Corail vivant" "Recif barriere interne" "LC2" -999 12 -999 -999 -999 -999 NA +"AMP" "BE13S053" "SVR" "Caye observatoire" NA "Pente externe" NA 1 27 6 2013 "08:57" "soleil" NA 2 1 NA NA "LD" -21.42475 158.84477 "HR" "AP" "Couronne d atoll" "front recifal" "Fond lagonaire" "Recif barriere externe" "SA3" -999 26 -999 -999 -999 -999 NA +"AMP" "BE13S054" "SVR" "Caye observatoire" NA "Pente interne" NA 1 27 6 2013 "09:22" "soleil" NA 2 -999 NA NA "LD" -21.40974 158.84683 "HR" "AP" "Couronne d atoll" "platier recifal ennoye" "Detritique" "Recif barriere interne" NA -999 4 -999 -999 -999 -999 NA +"AMP" "BE13S055" "SVR" "Caye observatoire" NA "Pente interne" NA 1 27 6 2013 "09:27" "soleil" NA 2 -999 NA NA "LD" -21.41235 158.84656 "HR" "AP" "Couronne d atoll" "platier recifal de faro" "Corail vivant" "Recif barriere interne" "LC5" -999 15 -999 -999 -999 -999 NA +"AMP" "BE13S056" "SVR" "Caye observatoire" NA "Pente interne" NA 1 27 6 2013 "09:46" "soleil" NA 2 -999 NA NA "LD" -21.41163 158.85445 "HR" "AP" "Couronne d atoll" "platier recifal de faro" "Corail vivant" "Recif barriere interne" "LC4" -999 4 -999 -999 -999 -999 NA +"AMP" "BE13S057" "SVR" "Caye observatoire" NA "Pente interne" NA 1 27 6 2013 "09:48" "soleil" NA 2 -999 NA NA "LD" -21.41163 158.85387 "HR" "AP" "Couronne d atoll" "platier recifal de faro" "Fond lagonaire" "Recif barriere interne" "SA4" -999 6 -999 -999 -999 -999 NA +"AMP" "BE13S058" "SVR" "Caye observatoire" NA "Pente interne" NA 1 27 6 2013 "11:12" "soleil" NA 2 1 NA NA "LD" -21.42929 158.74193 "HR" "AP" "Couronne d atoll" "platier recifal ennoye" "Corail vivant" "Recif barriere interne" "LC3" -999 21 -999 -999 -999 -999 NA +"AMP" "BE13S059" "SVR" "Caye observatoire" NA "Pente interne" NA 1 27 6 2013 "11:20" "soleil" NA 2 1 NA NA "LD" -21.43382 158.74387 "HR" "AP" "Couronne d atoll" "platier recifal ennoye" "Corail vivant" "Recif barriere interne" "SA4" -999 22 -999 -999 -999 -999 NA +"AMP" "BE13S061" "SVR" "Recif Boody" NA "Pente externe" NA 1 27 6 2013 "15:44" "soleil" NA 2 1 NA NA "LD" -21.025 158.57451 "HR" "AP" "Couronne d atoll" "front recifal" "Fond lagonaire" "Recif barriere externe" "SA3" -999 26 -999 -999 -999 -999 NA +"AMP" "BE13S062" "SVR" "Recif Boody" NA "Pente externe" NA 1 27 6 2013 "15:49" "soleil" NA 1 -999 NA NA "LD" -21.02883 158.57953 "HR" "AP" "Couronne d atoll" "platier recifal ennoye" "Corail vivant" "Recif barriere interne" "LC3" -999 11 -999 -999 -999 -999 NA +"AMP" "BE13S063" "SVR" "Recif Boody" NA "Pente interne" NA 1 27 6 2013 "16:17" "soleil" NA 1 -999 NA NA "LD" -21.01691 158.58334 "HR" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Detritique" "Recif barriere interne" NA -999 5 -999 -999 -999 -999 NA +"AMP" "BE13S064" "SVR" "Recif Boody" NA "Pente interne" NA 1 27 6 2013 "16:20" "nuage" NA 1 -999 NA NA "LD" -21.01843 158.57761 "HR" "AP" "Couronne d atoll" "platier recifal" "Fond lagonaire" "Recif barriere interne" "LC5" -999 5 -999 -999 -999 -999 NA +"AMP" "BE13S065" "SVR" "Recif Boody" NA "Pente interne" NA 1 27 6 2013 "16:46" "nuage" NA 1 -999 NA NA "LD" -20.99429 158.56557 "HR" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Fond lagonaire" "Recif barriere interne" "SA3" -999 5 -999 -999 -999 -999 NA +"AMP" "BE13S066" "SVR" "Recif Boody" NA "Pente interne" NA 1 27 6 2013 "16:49" "nuage" NA 1 -999 NA NA "LD" -20.98964 158.56673 "HR" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Corail vivant" "Recif barriere interne" "SA3" -999 11 -999 -999 -999 -999 NA +"AMP" "BE13S067" "SVR" "Recif Boody" NA "Pente interne" NA 1 27 6 2013 "17:10" "nuage" NA 1 -999 NA NA "LD" -20.92309 158.55757 "HR" "AP" "Lagon d atoll" "lagon profond" "Fond lagonaire" "Recif barriere interne" "SA4" -999 10 -999 -999 -999 -999 NA +"AMP" "BE13S069" "SVR" "Recif Boody" NA "Pente interne" NA 1 27 6 2013 "17:35" "nuage" NA 1 -999 NA NA "LD" -20.98455 158.55434 "HR" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Fond lagonaire" "Recif barriere interne" "SA3" -999 4.5 -999 -999 -999 -999 NA +"AMP" "BE13S070" "SVR" "Recif Boody" NA "Pente interne" NA 1 27 6 2013 "17:39" "nuage" NA 1 -999 NA NA "LD" -20.98567 158.55345 "HR" "AP" "Couronne d atoll" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA3" -999 3 -999 -999 -999 -999 NA +"AMP" "BE13S072" "SVR" "Recif Bellona Nord-ouest" NA "Pente externe" NA 1 28 6 2013 "08:47" "soleil" "0" 0 -999 NA NA "LD" -20.85567 158.48177 "HR" "AP" "Couronne d atoll" "front recifal" "Corail vivant" "Recif barriere externe" "LC2" -999 22 -999 -999 -999 -999 NA +"AMP" "BE13S074" "SVR" "Recif Bellona Nord-ouest" NA "Pente interne" NA 1 28 6 2013 "09:13" "soleil" "0" 0 -999 NA NA "LD" -20.85045 158.49173 "HR" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Fond lagonaire" "Recif barriere interne" "SA3" -999 14 -999 -999 -999 -999 NA +"AMP" "BE13S075" "SVR" "Recif Bellona Nord-ouest" NA "Pente interne" NA 1 28 6 2013 "09:45" "soleil" "0" 0 -999 NA NA "LD" -20.81807 158.46584 "HR" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Corail vivant" "Recif barriere interne" "LC4" -999 8 -999 -999 -999 -999 NA +"AMP" "BE13S076" "SVR" "Recif Bellona Nord-ouest" NA "Pente interne" NA 1 28 6 2013 "09:49" "soleil" "0" 0 -999 NA NA "LD" -20.81481 158.46875 "HR" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Fond lagonaire" "Recif barriere interne" "LC5" -999 13 -999 -999 -999 -999 NA +"AMP" "BE13S077" "SVR" "Recif Bellona Nord-ouest" NA "Pente interne" NA 1 28 6 2013 "12:04" "soleil" NA 1 -999 NA NA "LD" -20.57002 158.5576 "HR" "AP" "Couronne d atoll" "platier recifal ennoye" "Fond lagonaire" "Recif barriere interne" "SA4" -999 29 -999 -999 -999 -999 NA +"AMP" "BE13S078" "SVR" "Recif Bellona Nord-ouest" NA "Pente interne" NA 1 28 6 2013 "12:15" "soleil" NA 1 -999 NA NA "LD" -20.57258 158.55998 "HR" "AP" "Couronne d atoll" "platier recifal ennoye" "Detritique" "Recif barriere interne" NA -999 29 -999 -999 -999 -999 NA +"AMP" "BL120001" "SVR" "Deva" NA "Herbier" NA 1 21 5 2012 NA NA NA 1 2 NA "MD" "PC" -21.53408 165.25207 "HR" "AP" "Recif frangeant de recif barriere cotier" "frangeant diffus" "Fond lagonaire" "Frangeant cotier" NA 6 1.4 -999 -999 -999 -999 "William Roman" +"AMP" "BL120002" "SVR" "Deva" NA "Herbier" NA 1 21 5 2012 NA NA NA 1 2 NA "MD" "PC" -21.54357 165.25778 "HR" "AP" "Recif frangeant de recif barriere cotier" "frangeant diffus" "Fond lagonaire" "Frangeant cotier" NA 6 1.4 -999 -999 -999 -999 "William Roman" +"AMP" "BL120005" "SVR" "Deva" NA "Frangeant" NA 1 20 5 2012 NA NA NA 2 2 NA "MD" "NL" -21.56992 165.26797 "HR" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Frangeant cotier" "SA3" 6 1.8 -999 -999 -999 -999 "William Roman" +"AMP" "BL120006" "SVR" "Deva" NA "Frangeant" NA 1 20 5 2012 NA NA NA 2 2 NA "MD" "NL" -21.57817 165.27565 "HR" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Detritique" "Fond lagonaire" "D5" 7 1.7 -999 -999 -999 -999 "William Roman" +"AMP" "BL120008" "SVR" "Deva" NA "Barriere" NA 1 20 5 2012 NA NA NA 4 2 NA "MM" "NL" -21.56555 165.24957 "HR" "AP" "Complexe de recif barriere cotier" "platier recifal" "Detritique" "Recif barriere interne" "D5" 6 2 -999 -999 -999 -999 "William Roman" +"AMP" "BL120009" "SVR" "Deva" NA "Barriere" NA 1 21 5 2012 NA NA NA 3 2 NA "MD" "PC" -21.57372 165.25268 "HR" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA4" 8 3.5 -999 -999 -999 -999 "William Roman" +"AMP" "BL120010" "SVR" "Deva" NA "Barriere" NA 1 22 5 2012 NA NA NA 2 2 NA "PM" "PC" -21.5827 165.2551 "HR" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA4" 9 4.4 -999 -999 -999 -999 "William Roman" +"AMP" "BL120011" "SVR" "Deva" NA "Barriere" NA 1 22 5 2012 NA NA NA 2 2 NA "PM" "PC" -21.58503 165.26378 "HR" "AP" "Complexe de recif barriere cotier" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA4" 11 2.5 -999 -999 -999 -999 "William Roman" +"AMP" "BL120012" "SVR" "Deva" NA "Barriere" NA 1 22 5 2012 NA NA NA 3 2 NA "MD" "PC" -21.58842 165.27227 "HR" "AP" "Complexe de recif barriere cotier" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA4" 7 2.1 -999 -999 -999 -999 "William Roman" +"AMP" "BL120013" "SVR" "Deva" NA "Barriere" NA 1 19 5 2012 NA NA NA 3 2 NA "MM" "DC" -21.5949 165.28262 "HR" "AP" "Complexe de recif barriere cotier" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA3" 8 1.4 -999 -999 -999 -999 "William Roman" +"AMP" "BL120014" "SVR" "Deva" NA "Barriere" NA 1 19 5 2012 NA NA NA 4 2 NA "MM" "DC" -21.59172 165.29167 "HR" "AP" "Complexe de recif barriere cotier" "platier recifal" "Detritique" "Recif barriere interne" "D7" 7 1.5 -999 -999 -999 -999 "William Roman" +"AMP" "BL120015" "SVR" "Deva" NA "Barriere" NA 1 19 5 2012 NA NA NA 4 2 NA "MM" "DC" -21.59168 165.29795 "HR" "AP" "Complexe de recif barriere cotier" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA3" 8 1.5 -999 -999 -999 -999 "William Roman" +"AMP" "BL120016" "SVR" "Deva" NA "Barriere" NA 1 19 5 2012 NA NA NA 4 2 NA "BM" "DC" -21.595 165.30925 "HR" "AP" "Complexe de recif barriere cotier" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA4" 7 1.8 -999 -999 -999 -999 "William Roman" +"AMP" "BL120017" "SVR" "Deva" NA "Barriere" NA 1 19 5 2012 NA NA NA 4 2 NA "MD" "DC" -21.60502 165.31667 "HR" "AP" "Complexe de recif barriere cotier" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA4" 9 2.9 -999 -999 -999 -999 "William Roman" +"AMP" "BL120018" "SVR" "Deva" NA "Barriere" NA 1 19 5 2012 NA NA NA 4 2 NA "MD" "DC" -21.60577 165.31993 "HR" "AP" "Complexe de recif barriere cotier" "platier recifal" "Detritique" "Recif barriere interne" "D3" 10 2.1 -999 -999 -999 -999 "William Roman" +"AMP" "BL120019" "SVR" "Faille aux requins" NA "Faille aux requins" NA 1 20 5 2012 NA NA NA 2 2 NA "MD" "NL" -21.60848 165.33548 "RE" "AP" "Complexe de recif barriere cotier" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA3" 9 1.6 -999 -999 -999 -999 "William Roman" +"AMP" "BL120020" "SVR" "Faille aux requins" NA "Faille aux requins" NA 1 20 5 2012 NA NA NA 2 2 NA "MD" "NL" -21.60572 165.3363 "RE" "AP" "Complexe de recif barriere cotier" "platier recifal de passe" "Corail vivant" "Recif barriere interne" "LC3" 8 1.5 -999 -999 -999 -999 "William Roman" +"AMP" "BL120021" "SVR" "Faille aux requins" NA "Faille aux requins" NA 1 20 5 2012 NA NA NA 2 2 NA "MD" "NL" -21.60327 165.33597 "RE" "AP" "Complexe de recif barriere cotier" "platier recifal de passe" "Fond lagonaire" "Recif barriere interne" "SA3" 10 2 -999 -999 -999 -999 "William Roman" +"AMP" "BL120022" "SVR" "Faille aux requins" NA "Faille aux requins" NA 1 20 5 2012 NA NA NA 2 2 NA "MD" "NL" -21.60113 165.33597 "RE" "AP" "Complexe de recif barriere cotier" "platier recifal de passe" "Fond lagonaire" "Recif barriere interne" "LC3" 9 2.4 -999 -999 -999 -999 "William Roman" +"AMP" "BL120023" "SVR" "Faille aux requins" NA "Faille aux requins" NA 1 20 5 2012 NA NA NA 2 2 NA "PM" "NL" -21.59817 165.3372 "RE" "AP" "Complexe de recif barriere cotier" "platier recifal de passe" "Detritique" "Recif barriere interne" "D5" 8 1.5 -999 -999 -999 -999 "William Roman" +"AMP" "BL120024" "SVR" "Faille aux requins" NA "Faille aux requins" NA 1 24 5 2012 NA NA NA 3 2 NA "MD" "PC" -21.59788 165.34123 "RE" "AP" "Complexe de recif barriere cotier" "platier recifal de passe" "Detritique" "Recif barriere interne" "D7" 10 1.7 -999 -999 -999 -999 "William Roman" +"AMP" "BL120027" "SVR" "Faille aux requins" NA "Faille aux requins" NA 1 24 5 2012 NA NA NA 3 2 NA "MD" "PC" -21.60813 165.34095 "RE" "AP" "Complexe de recif barriere cotier" "platier recifal de passe" "Detritique" "Recif barriere interne" "D5" 9 1.9 -999 -999 -999 -999 "William Roman" +"AMP" "BL120028" "SVR" "Faille aux requins" NA "Faille aux requins" NA 1 24 5 2012 NA NA NA 3 2 NA "MD" "PC" -21.60125 165.34028 "RE" "AP" "Complexe de recif barriere cotier" "platier recifal de passe" "Detritique" "Recif barriere interne" "D7" 10 2.4 -999 -999 -999 -999 "William Roman" +"AMP" "BL120031" "SVR" "Deva" NA "Frangeant" NA 1 20 5 2012 NA NA NA 2 2 NA "MD" "NL" -21.58732 165.30545 "HR" "AP" "Complexe de recif barriere cotier" "platier recifal intermediaire de recif barriere cotier" "Fond lagonaire" "Frangeant cotier" "SA2" 6 1.6 -999 -999 -999 -999 "William Roman" +"AMP" "BL120032" "SVR" "Deva" NA "Herbier" NA 1 19 5 2012 NA NA NA 4 2 NA "MD" "DC" -21.59125 165.31422 "HR" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Frangeant cotier" "SA3" 7 1.2 -999 -999 -999 -999 "William Roman" +"AMP" "BL120033" "SVR" "Deva" NA "Frangeant" NA 1 20 5 2012 NA NA NA 2 2 NA "MD" "NL" -21.5928 165.325 "HR" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Frangeant cotier" "LC3" 8 1.3 -999 -999 -999 -999 "William Roman" +"AMP" "BL120038" "SVR" "Poe" NA "Barriere" NA 1 21 5 2012 NA NA NA 2 2 NA "BM" "PC" -21.61608 165.35017 "RE" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA3" 8 1.5 -999 -999 -999 -999 "William Roman" +"AMP" "BL120039" "SVR" "Poe" NA "Barriere" NA 1 21 5 2012 NA NA NA 2 2 NA "BM" "PC" -21.62417 165.3579 "RE" "AP" "Complexe de recif barriere cotier" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA4" 13 2 -999 -999 -999 -999 "William Roman" +"AMP" "BL120040" "SVR" "Poe" NA "Barriere" NA 1 22 5 2012 NA NA NA 2 2 NA "MD" "PC" -21.62505 165.36707 "RE" "AP" "Complexe de recif barriere cotier" "platier recifal" "Corail vivant" "Recif barriere interne" "LC3" 13 2.3 -999 -999 -999 -999 "William Roman" +"AMP" "BL120041" "SVR" "Poe" NA "Barriere" NA 1 22 5 2012 NA NA NA 3 2 NA "MD" "PC" -21.62438 165.37853 "RE" "AP" "Complexe de recif barriere cotier" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA4" 10 1.6 -999 -999 -999 -999 "William Roman" +"AMP" "BL120042" "SVR" "Poe" NA "Barriere" NA 1 22 5 2012 NA NA NA 3 2 NA "MD" "PC" -21.62493 165.38838 "RE" "AP" "Complexe de recif barriere cotier" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA4" 7 1.4 -999 -999 -999 -999 "William Roman" +"AMP" "BL120043" "SVR" "Faille aux requins" NA "Faille aux requins" NA 1 24 5 2012 NA NA NA 3 2 NA "PM" "PC" -21.5962 165.34132 "RE" "AP" "Complexe de recif barriere cotier" "platier recifal de passe" "Detritique" "Recif barriere interne" "D7" 8 1.5 -999 -999 -999 -999 "William Roman" +"AMP" "BL120047" "SVR" "Poe" NA "Frangeant" NA 1 23 5 2012 NA NA NA 2 1 NA "MD" "PC" -21.61395 165.37833 "RE" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Frangeant cotier" "SA3" 11 1.3 -999 -999 -999 -999 "William Roman" +"AMP" "BL120048" "SVR" "Poe" NA "Fond lagonaire" NA 1 23 5 2012 NA NA NA 2 1 NA "MD" "PC" -21.61937 165.3876 "RE" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA2" 8 1.3 -999 -999 -999 -999 "William Roman" +"AMP" "BL120049" "SVR" "Poe" NA "Frangeant" NA 1 23 5 2012 NA NA NA 2 1 NA "MD" "PC" -21.63038 165.40528 "RE" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA3" 9 1.6 -999 -999 -999 -999 "William Roman" +"AMP" "BL120050" "SVR" "Poe" NA "Frangeant" NA 1 23 5 2012 NA NA NA 2 1 NA "MD" "PC" -21.62402 165.40048 "RE" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Detritique" "Frangeant cotier" "D7" 7 2.3 -999 -999 -999 -999 "William Roman" +"AMP" "BL120051" "SVR" "Poe" NA "Frangeant" NA 1 23 5 2012 NA NA NA 2 1 NA "MD" "PC" -21.63503 165.41608 "RE" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Detritique" "Fond lagonaire" NA 8 2.2 -999 -999 -999 -999 "William Roman" +"AMP" "BL120052" "SVR" "Poe" NA "Barriere" NA 1 23 5 2012 NA NA NA 2 1 NA "MM" "PC" -21.62935 165.39712 "RE" "AP" "Complexe de recif barriere cotier" "platier recifal" "Fond lagonaire" "Recif barriere interne" NA 15 2.7 -999 -999 -999 -999 "William Roman" +"AMP" "BL120054" "SVR" "Poe" NA "Barriere" NA 1 23 5 2012 NA NA NA 2 1 NA "PM" "PC" -21.6393 165.41737 "RE" "AP" "Complexe de recif barriere cotier" "platier recifal" "Detritique" "Recif barriere interne" "D5" 8 1.8 -999 -999 -999 -999 "William Roman" +"AMP" "BL120055" "SVR" "Deva" NA "Fond lagonaire" NA 1 21 5 2012 NA NA NA 2 2 NA "MD" "PC" -21.55387 165.25158 "HR" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" 11 1.6 -999 -999 -999 -999 "William Roman" +"AMP" "BL120056" "SVR" "Deva" NA "Fond lagonaire" NA 1 21 5 2012 NA NA NA 2 2 NA "MD" "PC" -21.56243 165.25577 "HR" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" 13 2.3 -999 -999 -999 -999 "William Roman" +"AMP" "BL120057" "SVR" "Deva" NA "Fond lagonaire" NA 1 21 5 2012 NA NA NA 3 2 NA "MD" "PC" -21.5713 165.26027 "HR" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA2" 13 2.8 -999 -999 -999 -999 "William Roman" +"AMP" "BL120058" "SVR" "Deva" NA "Fond lagonaire" NA 1 21 5 2012 NA NA NA 3 2 NA "MD" "PC" -21.58183 165.27155 "HR" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA2" 9 2.4 -999 -999 -999 -999 "William Roman" +"AMP" "BL120059" "SVR" "Deva" NA "Fond lagonaire" NA 1 21 5 2012 NA NA NA 3 2 NA "MD" "PC" -21.58333 165.27907 "HR" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA2" 13 2.6 -999 -999 -999 -999 "William Roman" +"AMP" "BL120060" "SVR" "Deva" NA "Fond lagonaire" NA 1 21 5 2012 NA NA NA 3 2 NA "MD" "PC" -21.58913 165.29268 "HR" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA4" 12 1.6 -999 -999 -999 -999 "William Roman" +"AMP" "BL120061" "SVR" "Deva" NA "Fond lagonaire" NA 1 21 5 2012 NA NA NA 3 2 NA "MD" "PC" -21.58913 165.29722 "HR" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA2" 8 1.5 -999 -999 -999 -999 "William Roman" +"AMP" "BL120062" "SVR" "Deva" NA "Barriere" NA 1 19 5 2012 NA NA NA 4 2 NA "BM" "DC" -21.59275 165.30837 "HR" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" NA 10 1.7 -999 -999 -999 -999 "William Roman" +"AMP" "BL120063" "SVR" "Deva" NA "Barriere" NA 1 19 5 2012 NA NA NA 4 2 NA "MD" "DC" -21.59753 165.31725 "HR" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA3" 7 2 -999 -999 -999 -999 "William Roman" +"AMP" "BL120065" "SVR" "Poe" NA "Fond lagonaire" NA 1 19 5 2012 NA NA NA 3 1 NA "MD" "DC" -21.60268 165.33268 "RE" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" 8 1.9 -999 -999 -999 -999 "William Roman" +"AMP" "BL120066" "SVR" "Poe" NA "Fond lagonaire" NA 1 21 5 2012 NA NA NA 2 2 NA "BM" "PC" -21.60403 165.34735 "RE" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" 8 2.1 -999 -999 -999 -999 "William Roman" +"AMP" "BL120067" "SVR" "Poe" NA "Fond lagonaire" NA 1 21 5 2012 NA NA NA 2 2 NA "BM" "PC" -21.61 165.35485 "RE" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA3" 9 1.6 -999 -999 -999 -999 "William Roman" +"AMP" "BL120068" "SVR" "Poe" NA "Fond lagonaire" NA 1 21 5 2012 NA NA NA 2 2 NA "MM" "PC" -21.61657 165.36463 "RE" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA3" 8 1.8 -999 -999 -999 -999 "William Roman" +"AMP" "BL120069" "SVR" "Poe" NA "Fond lagonaire" NA 1 21 5 2012 NA NA NA 2 2 NA "MM" "PC" -21.6184 165.37278 "RE" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA2" 7 1.7 -999 -999 -999 -999 "William Roman" +"AMP" "BL120070" "SVR" "Poe" NA "Fond lagonaire" NA 1 23 5 2012 NA NA NA 2 1 NA "MD" "PC" -21.62097 165.38555 "RE" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA2" 8 1.5 -999 -999 -999 -999 "William Roman" +"AMP" "BL120071" "SVR" "Poe" NA "Fond lagonaire" NA 1 23 5 2012 NA NA NA 2 1 NA "MD" "PC" -21.62832 165.4035 "RE" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA2" 8 1.7 -999 -999 -999 -999 "William Roman" +"AMP" "BL120072" "SVR" "Poe" NA "Frangeant" NA 1 23 5 2012 NA NA NA 2 1 NA "MD" "PC" -21.6311 165.40935 "RE" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Detritique" "Fond lagonaire" "D5" 6 2 -999 -999 -999 -999 "William Roman" +"AMP" "BL120074" "SVR" "Ile Verte" NA "Recif ilot" NA 1 25 5 2012 NA NA NA 2 2 NA "MM" "PC" -21.65675 165.46112 "RE" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "SA3" 8 3.3 -999 -999 -999 -999 "William Roman" +"AMP" "BL120075" "SVR" "Ile Verte" NA "Recif ilot" NA 1 25 5 2012 NA NA NA 2 2 NA "MM" "PC" -21.65835 165.46358 "RE" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "SA4" 6 5 -999 -999 -999 -999 "William Roman" +"AMP" "BL120076" "SVR" "Ile Verte" NA "Recif ilot" NA 1 25 5 2012 NA NA NA 2 2 NA "MM" "PC" -21.66028 165.46208 "RE" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Detritique" "Frangeant ilot" "D5" 7 2.4 -999 -999 -999 -999 "William Roman" +"AMP" "BL12007B" "SVR" "Deva" NA "Barriere" NA 1 21 5 2012 NA NA NA 2 2 NA "MD" "PC" -21.55447 165.2464 "HR" "AP" "Complexe de recif barriere cotier" "platier recifal" "Detritique" "Recif barriere interne" "D7" 9 2.1 -999 -999 -999 -999 "William Roman" +"AMP" "BL120082" "SVR" "Ile Verte" NA "Recif ilot" NA 1 25 5 2012 NA NA NA 2 2 NA "MM" "PC" -21.65765 165.4628 "RE" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "D7" 8 4.5 -999 -999 -999 -999 "William Roman" +"AMP" "BL120085" "SVR" "Ile Verte" NA "Recif ilot" NA 1 25 5 2012 NA NA NA 2 2 NA "MM" "PC" -21.65952 165.46347 "RE" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Detritique" "Frangeant ilot" "D5" 7 4.5 -999 -999 -999 -999 "William Roman" +"AMP" "BL120088" "SVR" "Deva" NA "Barriere" NA 1 20 5 2012 NA NA NA 4 2 NA "BM" "NL" -21.55648 165.2487 "HR" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Detritique" "Recif barriere interne" "D2" 10 2 -999 -999 -999 -999 "William Roman" +"AMP" "BL120089" "SVR" "Deva" NA "Barriere" NA 1 20 5 2012 NA NA NA 4 2 NA "MM" "NL" -21.55893 165.24895 "HR" "AP" "Complexe de recif barriere cotier" "platier recifal" "Detritique" "Recif barriere interne" "D5" 9 2.1 -999 -999 -999 -999 "William Roman" +"AMP" "BL120090" "SVR" "Deva" NA "Barriere" NA 1 21 5 2012 NA NA NA 3 2 NA "MD" "PC" -21.56995 165.25102 "HR" "AP" "Complexe de recif barriere cotier" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA4" 8 3 -999 -999 -999 -999 "William Roman" +"AMP" "BL120091" "SVR" "Deva" NA "Barriere" NA 1 22 5 2012 NA NA NA 2 2 NA "PM" "PC" -21.57958 165.25512 "HR" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA4" 11 4.4 -999 -999 -999 -999 "William Roman" +"AMP" "BL120092" "SVR" "Deva" NA "Barriere" NA 1 22 5 2012 NA NA NA 2 2 NA "PM" "PC" -21.58377 165.25785 "HR" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Detritique" "Recif barriere interne" "D2" 9 2.1 -999 -999 -999 -999 "William Roman" +"AMP" "BL120093" "SVR" "Deva" NA "Barriere" NA 1 22 5 2012 NA NA NA 2 2 NA "PM" "PC" -21.58633 165.26833 "HR" "AP" "Complexe de recif barriere cotier" "platier recifal" "Detritique" "Recif barriere interne" NA 11 3.1 -999 -999 -999 -999 "William Roman" +"AMP" "BL120094" "SVR" "Deva" NA "Barriere" NA 1 22 5 2012 NA NA NA 3 2 NA "MD" "PC" -21.59217 165.27512 "HR" "AP" "Complexe de recif barriere cotier" "platier recifal" "Corail vivant" "Recif barriere interne" "LC3" 8 2.9 -999 -999 -999 -999 "William Roman" +"AMP" "BL120095" "SVR" "Deva" NA "Barriere" NA 1 19 5 2012 NA NA NA 3 2 NA "MM" "DC" -21.59362 165.2869 "HR" "AP" "Complexe de recif barriere cotier" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA4" 8 1.3 -999 -999 -999 -999 "William Roman" +"AMP" "BL120096" "SVR" "Deva" NA "Barriere" NA 1 19 5 2012 NA NA NA 4 2 NA "MM" "DC" -21.59112 165.29393 "HR" "AP" "Complexe de recif barriere cotier" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA3" 8 1.4 -999 -999 -999 -999 "William Roman" +"AMP" "BL120097" "SVR" "Deva" NA "Barriere" NA 1 19 5 2012 NA NA NA 4 2 NA "BM" "DC" -21.59798 165.3071 "HR" "AP" "Complexe de recif barriere cotier" "platier recifal" "Detritique" "Recif barriere interne" "D3" 9 1.6 -999 -999 -999 -999 "William Roman" +"AMP" "BL120098" "SVR" "Deva" NA "Barriere" NA 1 19 5 2012 NA NA NA 4 2 NA "MD" "DC" -21.6036 165.31445 "HR" "AP" "Complexe de recif barriere cotier" "platier recifal" "Detritique" "Recif barriere externe" "D1" 8 2.7 -999 -999 -999 -999 "William Roman" +"AMP" "BL120099" "SVR" "Deva" NA "Barriere" NA 1 19 5 2012 NA NA NA 4 2 NA "MD" "DC" -21.60657 165.32282 "HR" "AP" "Complexe de recif barriere cotier" "platier recifal" "Detritique" "Recif barriere interne" "D3" 9 1.6 -999 -999 -999 -999 "William Roman" +"AMP" "BL120101" "SVR" "Poe" NA "Barriere" NA 1 21 5 2012 NA NA NA 2 2 NA "BM" "PC" -21.62173 165.35298 "RE" "AP" "Complexe de recif barriere cotier" "platier recifal" "Fond lagonaire" "Recif barriere interne" "LC3" 10 2.1 -999 -999 -999 -999 "William Roman" +"AMP" "BL120102" "SVR" "Poe" NA "Barriere" NA 1 22 5 2012 NA NA NA 2 2 NA "MD" "PC" -21.62528 165.36213 "RE" "AP" "Complexe de recif barriere cotier" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA4" 10 2.1 -999 -999 -999 -999 "William Roman" +"AMP" "BL120103" "SVR" "Poe" NA "Barriere" NA 1 22 5 2012 NA NA NA 3 2 NA "MD" "PC" -21.62488 165.37158 "RE" "AP" "Complexe de recif barriere cotier" "platier recifal" "Detritique" "Recif barriere interne" "LC3" 13 2.2 -999 -999 -999 -999 "William Roman" +"AMP" "BL120104" "SVR" "Poe" NA "Barriere" NA 1 22 5 2012 NA NA NA 3 2 NA "MD" "PC" -21.6243 165.38332 "RE" "AP" "Complexe de recif barriere cotier" "platier recifal" "Fond lagonaire" "Recif barriere interne" NA 6 1.5 -999 -999 -999 -999 "William Roman" +"AMP" "BL120105" "SVR" "Poe" NA "Barriere" NA 1 24 5 2012 NA NA NA 2 2 NA "MM" "PC" -21.62772 165.39412 "RE" "AP" "Complexe de recif barriere cotier" "platier recifal" "Detritique" "Recif barriere interne" NA 7 2.1 -999 -999 -999 -999 "William Roman" +"AMP" "BL120106" "SVR" "Poe" NA "Barriere" NA 1 24 5 2012 NA NA NA 2 2 NA "MM" "PC" -21.63182 165.40083 "RE" "AP" "Complexe de recif barriere cotier" "platier recifal" "Detritique" "Recif barriere interne" NA 9 2.5 -999 -999 -999 -999 "William Roman" +"AMP" "BL120107" "SVR" "Poe" NA "Barriere" NA 1 23 5 2012 NA NA NA 2 1 NA "PM" "PC" -21.63808 165.41078 "RE" "AP" "Complexe de recif barriere cotier" "platier recifal" "Detritique" "Recif barriere interne" "D5" 8 1.9 -999 -999 -999 -999 "William Roman" +"AMP" "BL120108" "SVR" "Poe" NA "Barriere" NA 1 23 5 2012 NA NA NA 2 1 NA "MD" "PC" -21.64092 165.42488 "RE" "AP" "Complexe de recif barriere cotier" "platier recifal" "Detritique" "Recif barriere interne" "D3" 6 2 -999 -999 -999 -999 "William Roman" +"AMP" "BL120125" "SVR" "Deva" NA "Fond lagonaire" NA 1 22 5 2012 NA NA NA 2 2 NA "PM" "PC" -21.58658 165.25553 "HR" "AP" "Complexe de recif barriere cotier" "platier recifal" "Detritique" "Recif barriere interne" "D2" 15 2.4 -999 -999 -999 -999 "William Roman" +"AMP" "BL120128" "SVR" "Deva" NA "Barriere" NA 1 19 5 2012 NA NA NA 4 2 NA "BM" "DC" -21.59592 165.30452 "HR" "AP" "Complexe de recif barriere cotier" "platier recifal" "Fond lagonaire" "Recif barriere interne" NA 8 1.5 -999 -999 -999 -999 "William Roman" +"AMP" "BL120129" "SVR" "Deva" NA "Barriere" NA 1 19 5 2012 NA NA NA 4 2 NA "MM" "DC" -21.5932 165.30097 "HR" "AP" "Complexe de recif barriere cotier" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA4" 9 1.6 -999 -999 -999 -999 "William Roman" +"AMP" "BL120130" "SVR" "Poe" NA "Barriere" NA 1 21 5 2012 NA NA NA 2 2 NA "BM" "PC" -21.6143 165.34693 "RE" "AP" "Complexe de recif barriere cotier" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA1" 7 1.6 -999 -999 -999 -999 "William Roman" +"AMP" "BL120131" "SVR" "Faille aux requins" NA "Faille aux requins" NA 1 24 5 2012 NA NA NA 3 2 NA "MD" "PC" -21.61307 165.34405 "RE" "AP" "Complexe de recif barriere cotier" "platier recifal" "Fond lagonaire" "Recif barriere interne" "LC3" 10 1.4 -999 -999 -999 -999 "William Roman" +"AMP" "BL120133" "SVR" "Poe" NA "Frangeant" NA 1 23 5 2012 NA NA NA 2 1 NA "MD" "PC" -21.63433 165.41405 "RE" "AP" "Complexe de recif barriere cotier" "platier recifal intermediaire de recif barriere cotier" "Detritique" "Frangeant cotier" "D6" 8 2.2 -999 -999 -999 -999 "William Roman" +"AMP" "BL120135" "SVR" "Poe" NA "Barriere" NA 1 23 5 2012 NA NA NA 2 1 NA "PM" "PC" -21.6403 165.42077 "RE" "AP" "Complexe de recif barriere cotier" "platier recifal" "Detritique" "Recif barriere interne" "D2" 9 2 -999 -999 -999 -999 "William Roman" +"AMP" "BL120136" "SVR" "Ile Verte" NA "Frangeant" NA 1 25 5 2012 NA NA NA 2 2 NA "PM" "PC" -21.64742 165.46267 "HR" "AP" "Complexe de recif barriere cotier" "chenal" "Detritique" "Frangeant cotier" "D7" 8 4.5 -999 -999 -999 -999 "William Roman" +"AMP" "BL120137" "SVR" "Ile Verte" NA "Barriere" NA 1 25 5 2012 NA NA NA 2 2 NA "MM" "PC" -21.66235 165.45458 "HR" "AP" "Complexe de recif barriere cotier" "platier recifal" "Detritique" "Recif barriere interne" NA 8 2.5 -999 -999 -999 -999 "William Roman" +"AMP" "BL120139" "SVR" "Deva" NA "Barriere" NA 1 19 5 2012 NA NA NA 4 2 NA "MD" "DC" -21.59965 165.31483 "HR" "AP" "Complexe de recif barriere cotier" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA3" 8 2.3 -999 -999 -999 -999 "William Roman" +"AMP" "BL120140" "SVR" "Cap Goulvain" NA "Barriere" NA 1 20 5 2012 NA NA NA 3 2 NA "MD" "NL" -21.54092 165.2451 "HR" "AP" "Complexe de recif barriere cotier" "platier recifal intermediaire de recif barriere cotier" "Corail vivant" "Recif barriere interne" "LC1" 7 3.9 -999 -999 -999 -999 "William Roman" +"AMP" "BL120141" "SVR" "Cap Goulvain" NA "Barriere" NA 1 20 5 2012 NA NA NA 3 2 NA "MD" "NL" -21.54473 165.24307 "HR" "AP" "Complexe de recif barriere cotier" "platier recifal intermediaire de recif barriere cotier" "Detritique" "Recif barriere interne" NA 7 3 -999 -999 -999 -999 "William Roman" +"AMP" "BL120149" "SVR" "Faille aux requins" NA "Faille aux requins" NA 1 19 5 2012 NA NA NA 3 1 NA "MD" "DC" -21.59133 165.3365 "RE" "AP" "Recif frangeant de recif barriere cotier" "frangeant diffus" "Corail vivant" "Frangeant cotier" "LC2" 6 1.3 -999 -999 -999 -999 "William Roman" +"AMP" "BL120150" "SVR" "Faille aux requins" NA "Faille aux requins" NA 1 19 5 2012 NA NA NA 4 2 NA "MD" "DC" -21.5993 165.3382 "RE" "AP" "Complexe de recif barriere cotier" "platier recifal de passe" "Corail vivant" "Passe" "LC3" 10 1.3 -999 -999 -999 -999 "William Roman" +"AMP" "BL120151" "SVR" "Deva" NA "Herbier" NA 1 19 5 2012 NA NA NA 4 2 NA "BM" "DC" -21.58982 165.3137 "HR" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Frangeant cotier" "SA3" 6 1.2 -999 -999 -999 -999 "William Roman" +"AMP" "BL120152" "SVR" "Faille aux requins" NA "Faille aux requins" NA 1 20 5 2012 NA NA NA 2 2 NA "MD" "NL" -21.6091 165.33423 "RE" "AP" "Complexe de recif barriere cotier" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA4" 9 1.5 -999 -999 -999 -999 "William Roman" +"AMP" "BL120154" "SVR" "Deva" NA "Frangeant" NA 1 20 5 2012 NA NA NA 2 2 NA "MD" "NL" -21.59412 165.33323 "HR" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Frangeant cotier" "SA1" 8 1.7 -999 -999 -999 -999 "William Roman" +"AMP" "BL120155" "SVR" "Deva" NA "Frangeant" NA 1 20 5 2012 NA NA NA 2 2 NA "MD" "NL" -21.59255 165.32765 "HR" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Frangeant cotier" "SA1" 6 1.5 -999 -999 -999 -999 "William Roman" +"AMP" "BL120157" "SVR" "Cap Goulvain" NA "Barriere" NA 1 20 5 2012 NA NA NA 3 2 NA "MD" "NL" -21.54617 165.24192 "HR" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA4" 8 6.1 -999 -999 -999 -999 "William Roman" +"AMP" "BL120158" "SVR" "Cap Goulvain" NA "Barriere" NA 1 20 5 2012 NA NA NA 3 2 NA "MD" "NL" -21.53578 165.24398 "HR" "AP" "Complexe de recif barriere cotier" "platier recifal intermediaire de recif barriere cotier" "Fond lagonaire" "Recif barriere interne" "SA3" 7 4.2 -999 -999 -999 -999 "William Roman" +"AMP" "BL120159" "SVR" "Cap Goulvain" NA "Barriere" NA 1 20 5 2012 NA NA NA 3 2 NA "BM" "NL" -21.5474 165.24017 "HR" "AP" "Complexe de recif barriere cotier" "platier recifal" "Detritique" "Recif barriere interne" "D1" 9 3 -999 -999 -999 -999 "William Roman" +"AMP" "BL120161" "SVR" "Cap Goulvain" NA "Barriere" NA 1 20 5 2012 NA NA NA 3 2 NA "BM" "NL" -21.5493 165.24535 "HR" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Detritique" "Recif barriere interne" "D5" 10 1.9 -999 -999 -999 -999 "William Roman" +"AMP" "BL120200" "SVR" "Deva" NA "Fond lagonaire" NA 1 22 5 2012 NA NA NA 2 2 NA "MD" "PC" -21.58668 165.28797 "HR" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA2" 11 2.2 -999 -999 -999 -999 "William Roman" +"AMP" "BL120201" "SVR" "Poe" NA "Frangeant" NA 1 23 5 2012 NA NA NA 2 1 NA "MD" "PC" -21.62385 165.39533 "RE" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Corail vivant" "Fond lagonaire" "LC3" 8 2.3 -999 -999 -999 -999 "William Roman" +"AMP" "BL120204" "SVR" "Faille aux requins" NA "Faille aux requins" NA 1 24 5 2012 NA NA NA 3 2 NA "MD" "PC" -21.61082 165.3413 "RE" "AP" "Complexe de recif barriere cotier" "platier recifal de passe" "Detritique" "Recif barriere interne" NA 8 2 -999 -999 -999 -999 "William Roman" +"AMP" "BL120205" "SVR" "Ile Verte" NA "Barriere" NA 1 25 5 2012 NA NA NA 2 2 NA "PM" "PC" -21.66018 165.4521 "HR" "AP" "Complexe de recif barriere cotier" "platier recifal" "Detritique" "Recif barriere interne" "D5" 8 2 -999 -999 -999 -999 "William Roman" +"AMP" "BL120207" "SVR" "Ile Verte" NA "Frangeant" NA 1 25 5 2012 NA NA NA 2 2 NA "PM" "PC" -21.64927 165.46385 "HR" "AP" "Recif frangeant de recif barriere cotier" "platier recifal" "Detritique" "Frangeant cotier" "D5" 9 2.1 -999 -999 -999 -999 "William Roman" +"AMP" "BL120300" "SVR" "Faille aux requins" NA "Faille aux requins" NA 1 24 5 2012 NA NA NA 3 2 NA "PM" "PC" -21.59762 165.33903 "RE" "AP" "Complexe de recif barriere cotier" "passe" "Detritique" "Passe" "D7" 6 13 -999 -999 -999 -999 "William Roman" +"AMP" "BL12P003" "SVR" "Deva" NA "Frangeant" NA 1 23 5 2012 NA NA NA 1 1 NA "MD" "PC" -21.55188 165.25928 "HR" "AP" "Recif frangeant de recif barriere cotier" "frangeant diffus" "Fond lagonaire" "Frangeant cotier" "SA4" 10 1.7 -999 -999 -999 -999 "William Roman" +"AMP" "BL12P005" "SVR" NA NA NA NA 1 23 5 2012 NA NA NA 1 1 NA "MD" "PC" -21.55903 165.26632 "HR" "AP" "Recif frangeant de recif barriere cotier" "frangeant diffus" "Herbier" "Frangeant cotier" "SG1" 5 1.1 -999 -999 -999 -999 "William Roman" +"AMP" "BL12P006" "SVR" NA NA NA NA 1 23 5 2012 NA NA NA 1 1 NA "MD" "PC" -21.5686 165.27503 "HR" "AP" "Recif frangeant de recif barriere cotier" "frangeant diffus" "Herbier" "Frangeant cotier" "SG2" 6 1.1 -999 -999 -999 -999 "William Roman" +"AMP" "BL12P009" "SVR" NA NA NA NA 1 23 5 2012 NA NA NA 1 1 NA "PM" "PC" -21.5853 165.31077 "HR" "AP" "Recif frangeant de recif barriere cotier" "frangeant diffus" "Herbier" "Frangeant cotier" "SG1" 7 1.2 -999 -999 -999 -999 "William Roman" +"AMP" "BL12P011" "SVR" "Poe" NA "Herbier" NA 1 22 5 2012 NA NA NA 1 1 NA "PM" "PC" -21.61442 165.39762 "RE" "AP" "Complexe de recif barriere cotier" "platier recifal intermediaire de recif barriere cotier" "Herbier" "Frangeant cotier" "SG1" 8 1 -999 -999 -999 -999 "William Roman" +"AMP" "BL12P012" "SVR" "Poe" NA "Herbier" NA 1 22 5 2012 NA NA NA 2 1 NA "PM" "PC" -21.60038 165.36062 "RE" "AP" "Recif frangeant de recif barriere cotier" "frangeant diffus" "Herbier" "Frangeant cotier" "SG1" 7 0.8 -999 -999 -999 -999 "William Roman" +"AMP" "BL12P014" "SVR" "Poe" NA "Frangeant" NA 1 24 5 2012 NA NA NA 1 2 NA "PM" "PC" -21.61817 165.3968 "RE" "AP" "Complexe de recif barriere cotier" "platier recifal intermediaire de recif barriere cotier" "Fond lagonaire" "Frangeant cotier" "SA3" 7 1.1 -999 -999 -999 -999 "William Roman" +"AMP" "BL12P015" "SVR" "Gouaro" NA "Herbier" NA 1 24 5 2012 NA NA NA 2 2 NA "PM" "PC" -21.62038 165.42718 "HR" "AP" "Recif frangeant de recif barriere cotier" "frangeant diffus" "Herbier" "Frangeant cotier" "SG1" 6 1 -999 -999 -999 -999 "William Roman" +"AMP" "BL12P016" "SVR" "Gouaro" NA "Frangeant" NA 1 24 5 2012 NA NA NA 2 2 NA "MD" "PC" -21.63073 165.42442 "HR" "AP" "Complexe de recif barriere cotier" "platier recifal intermediaire de recif barriere cotier" "Detritique" "Frangeant cotier" "D5" 8 1.8 -999 -999 -999 -999 "William Roman" +"AMP" "BL12P017" "SVR" "Gouaro" NA "Frangeant" NA 1 24 5 2012 NA NA NA 2 2 NA "MD" "PC" -21.63598 165.42862 "HR" "AP" "Complexe de recif barriere cotier" "platier recifal intermediaire de recif barriere cotier" "Detritique" "Frangeant cotier" "LC3" 10 2 -999 -999 -999 -999 "William Roman" +"AMP" "BL12P018" "SVR" "Poe" NA "Frangeant" NA 1 24 5 2012 NA NA NA 1 2 NA "MD" "PC" -21.62555 165.41297 "RE" "AP" "Complexe de recif barriere cotier" "platier recifal intermediaire de recif barriere cotier" "Detritique" "Frangeant cotier" "D7" 9 2 -999 -999 -999 -999 "William Roman" +"AMP" "BL12P023" "SVR" "Deva" NA "Fond lagonaire" NA 1 21 5 2012 NA NA NA 3 2 NA "MM" "PC" -21.5982 165.33683 "HR" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA4" 5 1.7 -999 -999 -999 -999 "William Roman" +"AMP" "BL12P034" "SVR" "Poe" NA "Frangeant" NA 1 23 5 2012 NA NA NA 1 1 NA "MD" "PC" -21.5954 165.33488 "RE" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Frangeant cotier" "SA4" 12 2.8 -999 -999 -999 -999 "William Roman" +"AMP" "BL12P044" "SVR" "Poe" NA "Herbier" NA 1 22 5 2012 NA NA NA 2 1 NA "MD" "PC" -21.59895 165.35072 "RE" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Herbier" "Frangeant cotier" "SG3" 9 2.1 -999 -999 -999 -999 "William Roman" +"AMP" "BL12P045" "SVR" "Poe" NA "Herbier" NA 1 22 5 2012 NA NA NA 3 2 NA "MD" "PC" -21.60295 165.3604 "RE" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Herbier" "Frangeant cotier" "SG2" 7 2.3 -999 -999 -999 -999 "William Roman" +"AMP" "BL12P046" "SVR" "Poe" NA "Herbier" NA 1 22 5 2012 NA NA NA 3 2 NA "MD" "PC" -21.60628 165.36852 "RE" "AP" "Recif frangeant de recif barriere cotier" "frangeant diffus" "Herbier" "Frangeant cotier" "SG3" 8 1.4 -999 -999 -999 -999 "William Roman" +"AMP" "BL12P064" "SVR" "Deva" NA "Fond lagonaire" NA 1 21 5 2012 NA NA NA 3 2 NA "BM" "PC" -21.59975 165.32645 "HR" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" 7 2 -999 -999 -999 -999 "William Roman" +"AMP" "BL12P074" "SVR" "Ile Verte" NA "Recif ilot" NA 1 25 5 2012 NA NA NA 2 2 NA "PM" "PC" -21.65683 165.46063 "RE" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "SA3" 8 1.6 -999 -999 -999 -999 "William Roman" +"AMP" "BL12P077" "SVR" "Ile Verte" NA "Recif ilot" NA 1 25 5 2012 NA NA NA 2 2 NA "MM" "PC" -21.6608 165.45745 "RE" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "SA3" 9 1.6 -999 -999 -999 -999 "William Roman" +"AMP" "BL12P078" "SVR" "Ile Verte" NA "Recif ilot" NA 1 25 5 2012 NA NA NA 2 2 NA "MM" "PC" -21.65882 165.45517 "RE" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Detritique" "Frangeant ilot" "LC3" 10 1.6 -999 -999 -999 -999 "William Roman" +"AMP" "BL12P079" "SVR" "Ile Verte" NA "Recif ilot" NA 1 25 5 2012 NA NA NA 2 2 NA "MM" "PC" -21.65695 165.45612 "RE" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Detritique" "Frangeant ilot" "D7" 9 1.6 -999 -999 -999 -999 "William Roman" +"AMP" "BL12P080" "SVR" "Ile Verte" NA "Recif ilot" NA 1 25 5 2012 NA NA NA 2 2 NA "PM" "PC" -21.65598 165.45895 "RE" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "SA3" 9 1.6 -999 -999 -999 -999 "William Roman" +"AMP" "BL12P083" "SVR" "Ile Verte" NA "Recif ilot" NA 1 25 5 2012 NA NA NA 2 2 NA "MM" "PC" -21.65973 165.4562 "RE" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Detritique" "Frangeant ilot" "D7" 9 1.6 -999 -999 -999 -999 "William Roman" +"AMP" "BL12P084" "SVR" "Ile Verte" NA "Recif ilot" NA 1 25 5 2012 NA NA NA 2 2 NA "MM" "PC" -21.65728 165.45328 "RE" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Detritique" "Frangeant ilot" "D5" 8 2 -999 -999 -999 -999 "William Roman" +"AMP" "BL12P086" "SVR" "Ile Verte" NA "Recif ilot" NA 1 25 5 2012 NA NA NA 2 2 NA "MM" "PC" -21.6611 165.45925 "RE" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "SA4" 8 1.6 -999 -999 -999 -999 "William Roman" +"AMP" "BL12P087" "SVR" "Ile Verte" NA "Recif ilot" NA 1 25 5 2012 NA NA NA 2 2 NA "PM" "PC" -21.6539 165.46015 "RE" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "SA4" 8 1.6 -999 -999 -999 -999 "William Roman" +"AMP" "BL12P109" "SVR" "Gouaro" NA "Frangeant" NA 1 24 5 2012 NA NA NA 2 2 NA "PM" "PC" -21.61967 165.43287 "HR" "AP" "Recif frangeant de recif barriere cotier" "frangeant diffus" "Detritique" "Frangeant cotier" NA 5 1.5 -999 -999 -999 -999 "William Roman" +"AMP" "BL12P111" "SVR" "Poe" NA "Herbier" NA 1 22 5 2012 NA NA NA 1 1 NA "MM" "PC" -21.61612 165.40392 "RE" "AP" "Complexe de recif barriere cotier" "platier recifal intermediaire de recif barriere cotier" "Herbier" "Frangeant cotier" "SG2" 7 0.9 -999 -999 -999 -999 "William Roman" +"AMP" "BL12P112" "SVR" "Poe" NA "Herbier" NA 1 22 5 2012 NA NA NA 2 1 NA "PM" "PC" -21.6124 165.38943 "RE" "AP" "Complexe de recif barriere cotier" "platier recifal intermediaire de recif barriere cotier" "Herbier" "Frangeant cotier" "SG2" 8 1 -999 -999 -999 -999 "William Roman" +"AMP" "BL12P113" "SVR" "Poe" NA "Herbier" NA 1 22 5 2012 NA NA NA 2 1 NA "PM" "PC" -21.60873 165.37677 "RE" "AP" "Complexe de recif barriere cotier" "platier recifal intermediaire de recif barriere cotier" "Herbier" "Frangeant cotier" "SG1" 8 1.1 -999 -999 -999 -999 "William Roman" +"AMP" "BL12P115" "SVR" "Poe" NA "Herbier" NA 1 22 5 2012 NA NA NA 2 1 NA "MD" "PC" -21.59867 165.35613 "RE" "AP" "Recif frangeant de recif barriere cotier" "frangeant diffus" "Herbier" "Frangeant cotier" "SG1" 7 1 -999 -999 -999 -999 "William Roman" +"AMP" "BL12P116" "SVR" "Deva" NA "Frangeant" NA 1 21 5 2012 NA NA NA 3 2 NA "BM" "PC" -21.59188 165.32362 "HR" "AP" "Complexe de recif barriere cotier" "platier recifal intermediaire de recif barriere cotier" "Fond lagonaire" "Frangeant cotier" "SA3" 6 1.3 -999 -999 -999 -999 "William Roman" +"AMP" "BL12P122" "SVR" "Poe" NA "Frangeant" NA 1 24 5 2012 NA NA NA 1 2 NA "MD" "PC" -21.62218 165.40795 "RE" "AP" "Complexe de recif barriere cotier" "platier recifal intermediaire de recif barriere cotier" "Fond lagonaire" "Frangeant cotier" "D7" 9 2.3 -999 -999 -999 -999 "William Roman" +"AMP" "BL12P123" "SVR" "Poe" NA "Frangeant" NA 1 24 5 2012 NA NA NA 1 2 NA "MD" "PC" -21.62668 165.4201 "RE" "AP" "Complexe de recif barriere cotier" "platier recifal intermediaire de recif barriere cotier" "Detritique" "Frangeant cotier" "D5" 7 2 -999 -999 -999 -999 "William Roman" +"AMP" "BL12P124" "SVR" "Gouaro" NA "Frangeant" NA 1 24 5 2012 NA NA NA 2 2 NA "MD" "PC" -21.63022 165.43052 "HR" "AP" "Complexe de recif barriere cotier" "platier recifal intermediaire de recif barriere cotier" "Detritique" "Frangeant cotier" "D5" 7 2 -999 -999 -999 -999 "William Roman" +"AMP" "BL12P149" "SVR" "Deva" NA "Frangeant" NA 1 21 5 2012 NA NA NA 3 2 NA "MM" "PC" -21.59628 165.338 "HR" "AP" "Complexe de recif barriere cotier" "platier recifal intermediaire de recif barriere cotier" "Fond lagonaire" "Recif barriere interne" "SA4" 9 2 -999 -999 -999 -999 "William Roman" +"AMP" "BO120001" "SVR" "Baie Port Bouquet" NA NA NA 1 25 6 2012 NA NA "SE" 3 -999 NA "MD" "PC" -21.6554 166.38 "HR" "AP" "Complexe de massif corallien de lagon" "front recifal" "Fond lagonaire" "Frangeant ilot" "SA5" -999 2.5 -999 -999 -999 -999 NA +"AMP" "BO120002" "SVR" "Baie Port Bouquet" NA NA NA 1 25 6 2012 NA NA "SE" 3 -999 NA "PM" "PC" -21.652 166.37588 "HR" "AP" "Complexe de massif corallien de lagon" "front recifal" "Corail vivant" "Frangeant ilot" "LC1" -999 2.5 -999 -999 -999 -999 NA +"AMP" "BO120004" "SVR" "Baie Port Bouquet" NA NA NA 1 25 6 2012 NA NA "SE" 3 -999 NA "MD" "PC" -21.66568 166.39002 "HR" "AP" "Complexe de massif corallien de lagon" "front recifal" "Corail vivant" "Frangeant ilot" "LC2" -999 1.5 -999 -999 -999 -999 NA +"AMP" "BO120007" "SVR" "Baie Port Bouquet" NA NA NA 1 26 6 2012 NA NA "SE" 3 -999 NA "MM" "PC" -21.67785 166.3841 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Frangeant ilot" "SA4" -999 6 -999 -999 -999 -999 NA +"AMP" "BO120008" "SVR" "Baie Port Bouquet" NA NA NA 1 25 6 2012 NA NA "SE" 3 -999 NA "MD" "PC" -21.67642 166.37222 "RE" "AP" "Recif frangeant protege de lagons" "platier recifal" "Fond lagonaire" "Frangeant ilot" "SA5" -999 1.7 -999 -999 -999 -999 NA +"AMP" "BO120009" "SVR" "Baie Port Bouquet" NA NA NA 1 25 6 2012 NA NA "SE" 3 -999 NA "MD" "PC" -21.65843 166.38402 "HR" "AP" "Complexe de massif corallien de lagon" "front recifal" "Fond lagonaire" "Frangeant ilot" "SA4" -999 2.1 -999 -999 -999 -999 NA +"AMP" "BO120011" "SVR" "Baie Port Bouquet" NA NA NA 1 25 6 2012 NA NA "SE" 3 -999 NA "MD" "PC" -21.67778 166.4127 "HR" "AP" "Ile lagonaire" "lagon profond" "Corail vivant" "Frangeant ilot" "LC2" -999 2.4 -999 -999 -999 -999 NA +"AMP" "BO120012" "SVR" "Baie Port Bouquet" NA NA NA 1 25 6 2012 NA NA "SE" 3 -999 NA "MD" "PC" -21.67548 166.4099 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Corail vivant" "Frangeant ilot" "LC1" -999 2 -999 -999 -999 -999 NA +"AMP" "BO120014" "SVR" "Baie Port Bouquet" NA NA NA 1 25 6 2012 NA NA "SE" 3 -999 NA "MM" "PC" -21.65243 166.36162 "HR" "AP" "Complexe de massif corallien de lagon" "front recifal" "Corail vivant" "Frangeant ilot" "LC1" -999 3 -999 -999 -999 -999 NA +"AMP" "BO120015" "SVR" "Baie Port Bouquet" NA NA NA 1 25 6 2012 NA NA "SE" 3 -999 NA "MM" "PC" -21.65135 166.35893 "HR" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Frangeant ilot" "D1" -999 3 -999 -999 -999 -999 NA +"AMP" "BO120016" "SVR" "Baie Port Bouquet" NA NA NA 1 26 6 2012 NA NA "SE" 2 -999 NA "MM" "PC" -21.65455 166.35802 "HR" "AP" "Terre emergee" "terre emergee" "Corail vivant" "Frangeant cotier" "LC2" -999 5.5 -999 -999 -999 -999 NA +"AMP" "BO120019" "SVR" "Ilots" NA NA NA 1 27 6 2012 NA NA "SE" 4 -999 NA "MM" "PQ" -21.7233 166.49938 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Corail vivant" "Frangeant ilot" "LC3" -999 3.6 -999 -999 -999 -999 NA +"AMP" "BO120022" "SVR" "Ilots" NA NA NA 1 27 6 2012 NA NA "SE" 4 -999 NA "MM" "PQ" -21.7486 166.5143 "RE" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Corail vivant" "Frangeant ilot" "LC2" -999 2 -999 -999 -999 -999 NA +"AMP" "BO120024" "SVR" "Ilots" NA NA NA 1 28 6 2012 NA NA "SE" 3 -999 NA "MM" "LM" -21.75807 166.49138 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Detritique" "Frangeant ilot" "D1" -999 1.8 -999 -999 -999 -999 NA +"AMP" "BO120025" "SVR" "Ilots" NA NA NA 1 28 6 2012 NA NA "SE" 3 -999 NA "MM" "LM" -21.75755 166.48998 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Detritique" "Frangeant ilot" "D5" -999 1.7 -999 -999 -999 -999 NA +"AMP" "BO120026" "SVR" "Ilots" NA NA NA 1 27 6 2012 NA NA "SE" 4 -999 NA "MM" "PQ" -21.74743 166.51295 "RE" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Corail vivant" "Frangeant ilot" "LC1" -999 2.5 -999 -999 -999 -999 NA +"AMP" "BO120028" "SVR" "Ilots" NA NA NA 1 27 6 2012 NA NA "SE" 4 -999 NA "MM" "PQ" -21.74547 166.51287 "RE" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Corail vivant" "Frangeant ilot" "LC1" -999 3.6 -999 -999 -999 -999 NA +"AMP" "BO120029" "SVR" "Ilots" NA NA NA 1 27 6 2012 NA NA "SE" 4 -999 NA "MM" "PQ" -21.74645 166.51287 "RE" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Fond lagonaire" "Frangeant ilot" "LC3" -999 2.9 -999 -999 -999 -999 NA +"AMP" "BO120030" "SVR" "Baie Port Bouquet" NA NA NA 1 25 6 2012 NA NA "SE" 3 -999 NA "MD" "PC" -21.674 166.40617 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "SA4" -999 2 -999 -999 -999 -999 NA +"AMP" "BO120031" "SVR" "Baie Port Bouquet" NA NA NA 1 25 6 2012 NA NA "SE" 3 -999 NA "MD" "PC" -21.67225 166.40348 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Corail vivant" "Frangeant ilot" "LC1" -999 1.9 -999 -999 -999 -999 NA +"AMP" "BO120032" "SVR" "Baie Port Bouquet" NA NA NA 1 25 6 2012 NA NA "SE" 3 -999 NA "MD" "PC" -21.6677 166.3925 "HR" "AP" "Complexe de massif corallien de lagon" "front recifal" "Corail vivant" "Frangeant ilot" "LC1" -999 2 -999 -999 -999 -999 NA +"AMP" "BO120033" "SVR" "Ilots" NA NA NA 1 27 6 2012 NA NA "SE" 4 -999 NA "MM" "PQ" -21.74338 166.5113 "RE" "AP" "Ile lagonaire" "lagon profond" "Corail vivant" "Frangeant ilot" "LC1" -999 5 -999 -999 -999 -999 NA +"AMP" "BO120034" "SVR" "Ilots" NA NA NA 1 27 6 2012 NA NA "SE" 4 -999 NA "MM" "PQ" -21.72428 166.50052 "HR" "AP" "Ile lagonaire" "lagon profond" "Detritique" "Frangeant ilot" "D2" -999 3.7 -999 -999 -999 -999 NA +"AMP" "BO120036" "SVR" "Baie Port Bouquet" NA NA NA 1 26 6 2012 NA NA "SE" 3 -999 NA "PM" "PC" -21.67917 166.379 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Frangeant ilot" "SA5" -999 5.9 -999 -999 -999 -999 NA +"AMP" "BO120037" "SVR" "Baie Port Bouquet" NA NA NA 1 26 6 2012 NA NA "SE" 3 -999 NA "MM" "PC" -21.67775 166.38993 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Frangeant ilot" "SA3" -999 7 -999 -999 -999 -999 NA +"AMP" "BO120038" "SVR" "Baie Port Bouquet" NA NA NA 1 26 6 2012 NA NA "SE" 3 -999 NA "MM" "PC" -21.67388 166.39598 "RE" "AP" "Recif frangeant protege de lagons" "platier recifal" "Corail vivant" "Frangeant ilot" "LC2" -999 3 -999 -999 -999 -999 NA +"AMP" "BO120039" "SVR" "Baie Port Bouquet" NA NA NA 1 25 6 2012 NA NA "SE" 3 -999 NA "MD" "PC" -21.66147 166.38647 "HR" "AP" "Complexe de massif corallien de lagon" "front recifal" "Corail vivant" "Frangeant ilot" "LC2" -999 2.1 -999 -999 -999 -999 NA +"AMP" "BO120040" "SVR" "Baie Port Bouquet" NA NA NA 1 25 6 2012 NA NA "SE" 3 -999 NA "MD" "PC" -21.67377 166.38298 "RE" "AP" "Recif frangeant protege de lagons" "platier recifal" "Corail vivant" "Frangeant ilot" "LC2" -999 3.1 -999 -999 -999 -999 NA +"AMP" "BO120041" "SVR" "Baie Port Bouquet" NA NA NA 1 26 6 2012 NA NA "SE" 2 -999 NA "MM" "PC" -21.66308 166.35963 "HR" "AP" "Ile lagonaire" "lagon profond" "Corail vivant" "Frangeant cotier" "LC1" -999 3.4 -999 -999 -999 -999 NA +"AMP" "BO120042" "SVR" "Baie Port Bouquet" NA NA NA 1 26 6 2012 NA NA "SE" 2 -999 NA "MM" "PC" -21.65735 166.36002 "HR" "AP" "Recif frangeant protege de lagons" "platier recifal" "Corail vivant" "Frangeant cotier" "D6" -999 6.6 -999 -999 -999 -999 NA +"AMP" "BO120043" "SVR" "Baie Port Bouquet" NA NA NA 1 25 6 2012 NA NA "SE" 3 -999 NA "MD" "PC" -21.67225 166.37365 "RE" "AP" "Terre emergee" "terre emergee" "Corail vivant" "Frangeant ilot" "LC1" -999 2.3 -999 -999 -999 -999 NA +"AMP" "BO120044" "SVR" "Baie Port Bouquet" NA NA NA 1 25 6 2012 NA NA "SE" 3 -999 NA "MD" "PC" -21.6716 166.3861 "RE" "AP" "Recif frangeant protege de lagons" "platier recifal" "Corail vivant" "Frangeant ilot" "LC3" -999 2.8 -999 -999 -999 -999 NA +"AMP" "BO120045" "SVR" "Ilots" NA NA NA 1 28 6 2012 NA NA "SE" 2 -999 NA "MM" "LM" -21.75467 166.48818 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Corail vivant" "Frangeant ilot" "LC1" -999 4.5 -999 -999 -999 -999 NA +"AMP" "BO120046" "SVR" "Ilots" NA NA NA 1 28 6 2012 NA NA "SE" 2 -999 NA "MM" "LM" -21.75663 166.48867 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "SA3" -999 2.2 -999 -999 -999 -999 NA +"AMP" "BO120047" "SVR" "Baie Port Bouquet" NA NA NA 1 26 6 2012 NA NA "SE" 3 -999 NA "PM" "PC" -21.68168 166.36032 "RE" "AP" "Ile lagonaire" "lagon profond" "Corail vivant" "Recif intermediaire" "LC1" -999 2 -999 -999 -999 -999 NA +"AMP" "BO120050" "SVR" "Baie Port Bouquet" NA NA NA 1 25 6 2012 NA NA "SE" 3 -999 NA "MD" "PC" -21.67355 166.36643 "RE" "AP" "Recif frangeant protege de lagons" "platier recifal" "Corail vivant" "Recif intermediaire" "LC1" -999 3 -999 -999 -999 -999 NA +"AMP" "BO120054" "SVR" "Ilots" NA NA NA 1 27 6 2012 NA NA "SE" 4 -999 NA "PM" "PQ" -21.71137 166.48562 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Corail vivant" "Frangeant ilot" "LC1" -999 2.1 -999 -999 -999 -999 NA +"AMP" "BO120055" "SVR" "Ilots" NA NA NA 1 27 6 2012 NA NA "SE" 4 -999 NA "PM" "PQ" -21.71487 166.48797 "HR" "AP" "Ile lagonaire" "lagon profond" "Corail vivant" "Frangeant ilot" "LC1" -999 5 -999 -999 -999 -999 NA +"AMP" "BO120056" "SVR" "Ilots" NA NA NA 1 27 6 2012 NA NA "SE" 4 -999 NA "PM" "PQ" -21.71575 166.489 "HR" "AP" "Ile lagonaire" "lagon profond" "Corail vivant" "Frangeant ilot" "LC1" -999 4.2 -999 -999 -999 -999 NA +"AMP" "BO120059" "SVR" "Baie Port Bouquet" NA NA NA 1 26 6 2012 NA NA "SE" 3 -999 NA "MM" "PC" -21.67228 166.39738 "HR" "AP" "Recif frangeant protege de lagons" "platier recifal" "Corail vivant" "Frangeant ilot" NA -999 6.8 -999 -999 -999 -999 NA +"AMP" "BO120076" "SVR" "Toupeti frangeant" NA NA NA 1 27 6 2012 NA NA "SE" 4 -999 NA "MD" "PQ" -21.71345 166.43255 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Fond lagonaire" "Recif intermediaire" "SA1" -999 3.7 -999 -999 -999 -999 NA +"AMP" "BO120077" "SVR" "Toupeti frangeant" NA NA NA 1 27 6 2012 NA NA "SE" 4 -999 NA "MD" "PQ" -21.71018 166.43592 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Fond lagonaire" "Recif intermediaire" "SA4" -999 4.9 -999 -999 -999 -999 NA +"AMP" "BO120079" "SVR" "Toupeti frangeant" NA NA NA 1 27 6 2012 NA NA "SE" 4 -999 NA "MD" "PQ" -21.71735 166.4354 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Fond lagonaire" "Recif intermediaire" "SA4" -999 2.7 -999 -999 -999 -999 NA +"AMP" "BO120080" "SVR" "Toupeti frangeant" NA NA NA 1 27 6 2012 NA NA "SE" 4 -999 NA "MD" "PQ" -21.71567 166.43983 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Corail vivant" "Recif intermediaire" "D6" -999 5.2 -999 -999 -999 -999 NA +"AMP" "BO120095" "SVR" "Grand recif Ngoe" NA NA NA 1 28 6 2012 NA NA "SE" 2 -999 NA "MM" "LM" -21.6651 166.50203 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA5" -999 5.3 -999 -999 -999 -999 NA +"AMP" "BO120096" "SVR" "Grand recif Ngoe" NA NA NA 1 28 6 2012 NA NA "SE" 2 -999 NA "MM" "LM" -21.66728 166.50422 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Recif barriere interne" NA -999 2.9 -999 -999 -999 -999 NA +"AMP" "BO120098" "SVR" "Grand recif Ngoe" NA NA NA 1 28 6 2012 NA NA "SE" 2 -999 NA "MM" "LM" -21.6882 166.52353 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA4" -999 6.5 -999 -999 -999 -999 NA +"AMP" "BO120099" "SVR" "Grand recif Ngoe" NA NA NA 1 28 6 2012 NA NA "SE" 2 -999 NA "MM" "LM" -21.70485 166.53697 "HR" "AP" "Complexe de recif barriere multiple" "terrasse externe" "Corail vivant" "Recif barriere interne" "LC3" -999 3 -999 -999 -999 -999 NA +"AMP" "BO120100" "SVR" "Grand recif Ngoe" NA NA NA 1 28 6 2012 NA NA "SE" 2 -999 NA "MM" "LM" -21.7113 166.54162 "HR" "AP" "Complexe de recif barriere multiple" "terrasse externe" "Corail vivant" "Recif barriere interne" "SA4" -999 4.5 -999 -999 -999 -999 NA +"AMP" "BO120101" "SVR" "Grand recif Ngoe" NA NA NA 1 28 6 2012 NA NA "SE" 2 -999 NA "MM" "LM" -21.6779 166.51388 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA1" -999 6.6 -999 -999 -999 -999 NA +"AMP" "BO120102" "SVR" "Grand recif Ngoe" NA NA NA 1 28 6 2012 NA NA "SE" 2 -999 NA "MM" "LM" -21.67407 166.5116 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA3" -999 3.3 -999 -999 -999 -999 NA +"AMP" "BO120201" "SVR" "Baie Port Bouquet" NA NA NA 1 26 6 2012 NA NA "SE" 2 -999 NA "MM" "PC" -21.66292 166.3574 "HR" "AP" "Ile lagonaire" "lagon profond" "Corail vivant" "Frangeant cotier" "LC4" -999 2.6 -999 -999 -999 -999 NA +"AMP" "BO120203" "SVR" "Baie Port Bouquet" NA NA NA 1 26 6 2012 NA NA "SE" 3 -999 NA "MD" "PC" -21.67213 166.37242 "RE" "AP" "Ile lagonaire" "lagon profond" "Detritique" "Frangeant ilot" "D6" -999 8.8 -999 -999 -999 -999 NA +"AMP" "BO120204" "SVR" "Baie Port Bouquet" NA NA NA 1 26 6 2012 NA NA "SE" 3 -999 NA "MD" "PC" -21.67275 166.38398 "RE" "AP" "Recif frangeant protege de lagons" "platier recifal" "Corail vivant" "Frangeant ilot" "LC2" -999 4 -999 -999 -999 -999 NA +"AMP" "BO120205" "SVR" "Baie Port Bouquet" NA NA NA 1 26 6 2012 NA NA "SE" 3 -999 NA "MD" "PC" -21.67402 166.38125 "RE" "AP" "Recif frangeant protege de lagons" "platier recifal" "Corail vivant" "Frangeant ilot" "LC2" -999 3.5 -999 -999 -999 -999 NA +"AMP" "BO120206" "SVR" "Baie Port Bouquet" NA NA NA 1 26 6 2012 NA NA "SE" 3 -999 NA "MD" "PC" -21.68337 166.42427 "HR" "AP" "Ile lagonaire" "lagon profond" "Corail vivant" "Frangeant cotier" "LC1" -999 5 -999 -999 -999 -999 NA +"AMP" "BO120207" "SVR" "Baie Port Bouquet" NA NA NA 1 26 6 2012 NA NA "SE" 3 -999 NA "MD" "PC" -21.68547 166.42465 "HR" "AP" "Ile lagonaire" "lagon profond" "Corail vivant" "Frangeant cotier" "LC1" -999 3.1 -999 -999 -999 -999 NA +"AMP" "BO120209" "SVR" "Baie Port Bouquet" NA NA NA 1 26 6 2012 NA NA "SE" 3 -999 NA "MD" "PC" -21.69097 166.42152 "HR" "AP" "Recif frangeant protege de lagons" "front recifal" "Corail vivant" "Frangeant cotier" "LC2" -999 4.5 -999 -999 -999 -999 NA +"AMP" "BO120210" "SVR" "Ilots" NA NA NA 1 27 6 2012 NA NA "SE" 4 -999 NA "MM" "PQ" -21.74955 166.5157 "RE" "AP" "Ile lagonaire" "lagon profond" "Detritique" "Frangeant ilot" NA -999 3.4 -999 -999 -999 -999 NA +"AMP" "BO120211" "SVR" "Ilots" NA NA NA 1 27 6 2012 NA NA "SE" 4 -999 NA "MM" "PQ" -21.7212 166.49773 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "LC3" -999 5 -999 -999 -999 -999 NA +"AMP" "BO120212" "SVR" "Ilots" NA NA NA 1 27 6 2012 NA NA "SE" 4 -999 NA "PM" "PQ" -21.71297 166.48662 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Corail vivant" "Frangeant ilot" "LC1" -999 3.3 -999 -999 -999 -999 NA +"AMP" "BO120213" "SVR" "Grand recif Ngoe" NA NA NA 1 28 6 2012 NA NA "SE" 2 -999 NA "MM" "LM" -21.69525 166.52773 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA5" -999 2.8 -999 -999 -999 -999 NA +"AMP" "BO120214" "SVR" "Grand recif Ngoe" NA NA NA 1 28 6 2012 NA NA "SE" 2 -999 NA "MM" "LM" -21.69938 166.532 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Recif barriere interne" "D1" -999 2.5 -999 -999 -999 -999 NA +"AMP" "BO120215" "SVR" "Grand recif Ngoe" NA NA NA 1 28 6 2012 NA NA "SE" 2 -999 NA "MM" "LM" -21.70848 166.54007 "HR" "AP" "Complexe de recif barriere multiple" "terrasse externe" "Detritique" "Recif barriere interne" "LC3" -999 2.6 -999 -999 -999 -999 NA +"AMP" "BO120216" "SVR" "Grand recif Ngoe" NA NA NA 1 28 6 2012 NA NA "SE" 2 -999 NA "MM" "LM" -21.71303 166.54235 "HR" "AP" "Complexe de recif barriere multiple" "terrasse externe" "Detritique" "Recif barriere interne" NA -999 6.2 -999 -999 -999 -999 NA +"AMP" "BO12095B" "SVR" "Ilots" NA NA NA 1 27 6 2012 NA NA "SE" 4 -999 NA "PM" "PQ" -21.71967 166.49748 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Corail vivant" "Frangeant ilot" "LC1" -999 7.1 -999 -999 -999 -999 NA +"AMP" "CH13P030" "SVR" "Corne sud" NA "Recif isole" NA 1 29 6 2013 "09:24" "soleil" NA 2 1 NA NA "LD" -19.88122 158.37747 "HR" "AP" "Lagon d atoll" "lagon profond" "Corail vivant" "Recif isole" "LC1" -999 10 -999 -999 -999 -999 NA +"AMP" "CH13P031" "SVR" "Corne sud" NA "Recif isole" NA 1 29 6 2013 "09:41" "soleil" NA 2 1 NA NA "LD" -19.88273 158.3762 "HR" "AP" "Lagon d atoll" "lagon profond" "Corail vivant" "Recif isole" "LC1" -999 10 -999 -999 -999 -999 NA +"AMP" "CH13P032" "SVR" "Corne sud" NA "Recif isole" NA 1 29 6 2013 "10:26" "soleil" NA 2 1 NA NA "LD" -19.86985 158.37647 "HR" "AP" "Lagon d atoll" "lagon profond" "Corail vivant" "Recif isole" "LC1" -999 10 -999 -999 -999 -999 NA +"AMP" "CH13P033" "SVR" "Corne sud" NA "Recif isole" NA 1 29 6 2013 "10:37" "soleil" NA 2 1 NA NA "LD" -19.87143 158.38177 "HR" "AP" "Massif corallien d atoll" "platier recifal ennoye" "Corail vivant" "Recif isole" "LC1" -999 9 -999 -999 -999 -999 NA +"AMP" "CH13P034" "SVR" "Corne sud" NA "Recif isole" NA 1 29 6 2013 "11:15" "soleil" NA 2 1 NA NA "LD" -19.87588 158.40362 "HR" "AP" "Lagon d atoll" "lagon profond" "Corail vivant" "Recif isole" "LC1" -999 18 -999 -999 -999 -999 NA +"AMP" "CH13P036" "SVR" "Corne sud" NA "Pente interne" NA 1 29 6 2013 "12:26" "soleil" NA 2 1 NA NA "LD" -19.8933 158.46607 "HR" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Fond lagonaire" "Recif barriere interne" "SA2" -999 3 -999 -999 -999 -999 NA +"AMP" "CH13P037" "SVR" "Corne sud" NA "Pente interne" NA 1 29 6 2013 "13:32" "soleil" NA 2 1 NA NA "LD" -19.90367 158.46283 "HR" "AP" "Lagon d atoll" "lagon profond" "Corail vivant" "Recif barriere interne" "LC1" -999 6 -999 -999 -999 -999 NA +"AMP" "CH13P038" "SVR" "Corne sud" NA "Pente interne" NA 1 29 6 2013 "13:41" "soleil" NA 2 1 NA NA "LD" -19.9035 158.46263 "HR" "AP" "Lagon d atoll" "lagon profond" "Corail vivant" "Recif barriere interne" "LC1" -999 4 -999 -999 -999 -999 NA +"AMP" "CH13P039" "SVR" "Corne sud" NA "Recif isole" NA 1 29 6 2013 "14:13" "soleil" NA 2 1 NA NA "LD" -19.894 158.44471 "HR" "AP" "Lagon d atoll" "lagon profond" "Corail vivant" "Recif isole" "LC1" -999 12 -999 -999 -999 -999 NA +"AMP" "CH13P040" "SVR" "Corne sud" NA "Recif isole" NA 1 29 6 2013 "14:24" "soleil" NA 2 1 NA NA "LD" -19.88672 158.45078 "HR" "AP" "Lagon d atoll" "lagon profond" "Corail vivant" "Recif isole" "LC1" -999 3.7 -999 -999 -999 -999 NA +"AMP" "CH13P041" "SVR" "Corne sud" NA "Pente interne" NA 1 29 6 2013 "14:55" "soleil" NA 2 1 NA NA "LD" -19.88617 158.46113 "HR" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Corail vivant" "Recif barriere interne" "LC1" -999 25 -999 -999 -999 -999 NA +"AMP" "CH13P042" "SVR" "Corne sud" NA "Pente interne" NA 1 29 6 2013 "15:00" "soleil" NA 2 1 NA NA "LD" -19.8855 158.46082 "HR" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Fond lagonaire" "Recif barriere interne" "SA1" -999 4 -999 -999 -999 -999 NA +"AMP" "CH13P043" "SVR" "Corne sud" NA "Pente interne" NA 1 29 6 2013 "15:34" "soleil" NA 2 1 NA NA "LD" -19.87052 158.45295 "HR" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Corail vivant" "Recif barriere interne" "LC1" -999 4 -999 -999 -999 -999 NA +"AMP" "CH13P047" "SVR" "Recif Ouest" NA "Pente interne" NA 1 30 6 2013 "09:38" "nuage" NA 3 1 NA NA "DQ" -19.7601 158.29568 "HR" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Fond lagonaire" "Recif barriere interne" "SA3" -999 18.5 -999 -999 -999 -999 NA +"AMP" "CH13P048" "SVR" "Barriere ouest" NA "Pente interne" NA 1 30 6 2013 "09:44" "nuage" NA 2 1 NA NA "DQ" -19.7594 158.2951 "HR" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Corail vivant" "Recif barriere interne" "LC1" -999 18 -999 -999 -999 -999 NA +"AMP" "CH13P049" "SVR" "Barriere ouest" NA "Pente interne" NA 1 30 6 2013 "11:12" "nuage" NA 1 1 NA NA "DQ" -19.62372 158.24973 "HR" "AP" "Massif corallien d atoll" "platier recifal ennoye" "Detritique" "Recif barriere interne" "D7" -999 27 -999 -999 -999 -999 NA +"AMP" "CH13P050" "SVR" "Barriere ouest" NA "Pente interne" NA 1 30 6 2013 "11:18" "nuage" "0" 0 -999 NA NA "DQ" -19.62503 158.24783 "HR" "AP" "Massif corallien d atoll" "platier recifal ennoye" "Corail vivant" "Recif barriere interne" "LC2" -999 19.6 -999 -999 -999 -999 NA +"AMP" "CH13P051" "SVR" NA NA "Pente interne" NA 1 30 6 2013 "15:01" "soleil" "0" 0 -999 NA NA "DQ" -19.49913 158.28108 "HR" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Corail vivant" "Recif barriere interne" "LC5" -999 26.6 -999 -999 -999 -999 NA +"AMP" "CH13P052" "SVR" NA NA "Pente interne" NA 1 30 6 2013 "15:07" "soleil" "0" 0 -999 NA NA "DQ" -19.49988 158.28063 "HR" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Corail vivant" "Recif barriere interne" "LC1" -999 10 -999 -999 -999 -999 NA +"AMP" "CH13P053" "SVR" "Barriere ouest" NA "Pente interne" NA 1 30 6 2013 "15:41" "soleil" "0" 0 -999 NA NA "DQ" -19.48672 158.28692 "HR" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Corail vivant" "Recif barriere interne" "LC2" -999 9 -999 -999 -999 -999 NA +"AMP" "CH13P054" "SVR" "Barriere ouest" NA "Pente interne" NA 1 30 6 2013 "15:46" "soleil" "0" 0 -999 NA NA "DQ" -19.48518 158.28692 "HR" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Corail vivant" "Recif barriere interne" "LC2" -999 11.4 -999 -999 -999 -999 NA +"AMP" "CH13P055" "SVR" "Barriere ouest" NA "Pente externe" NA 1 1 7 2013 "09:40" "soleil" NA 1 -999 NA NA "DC" -19.4491 158.26938 "HR" "AP" "Couronne d atoll" "front recifal" "Corail vivant" "Recif barriere externe" "LC1" -999 6 -999 -999 -999 -999 NA +"AMP" "CH13P056" "SVR" "Barriere ouest" NA "Pente externe" NA 1 1 7 2013 "09:50" "soleil" NA 1 -999 NA NA "DC" -19.44698 158.27143 "HR" "AP" "Couronne d atoll" "front recifal" "Corail vivant" "Recif barriere externe" "LC1" -999 5 -999 -999 -999 -999 NA +"AMP" "CH13P057" "SVR" "Barriere ouest" NA "Pente externe" NA 1 1 7 2013 "11:02" "soleil" NA 1 -999 NA NA "DC" -19.3039 158.2716 "HR" "AP" "" "" "Corail vivant" "Recif barriere externe" "LC2" -999 6 -999 -999 -999 -999 NA +"AMP" "CH13P059" "SVR" "Barriere nord-ouest" NA "Pente externe" NA 1 1 7 2013 "13:58" "soleil" NA 2 -999 NA NA "DC" -19.03695 158.43275 "HR" "AP" "Couronne d atoll" "front recifal" "Corail vivant" "Recif barriere externe" "LC1" -999 9 -999 -999 -999 -999 NA +"AMP" "CH13P060" "SVR" "Barriere nord-ouest" NA "Pente externe" NA 1 1 7 2013 "14:07" "soleil" NA 2 -999 NA NA "DC" -19.03738 158.43133 "HR" "AP" "Couronne d atoll" "front recifal" "Corail vivant" "Recif barriere externe" "LC1" -999 7 -999 -999 -999 -999 NA +"AMP" "CH13P061" "SVR" "Bampton nord" NA "Pente externe" NA 1 1 7 2013 "15:30" "soleil" NA 2 -999 NA NA "DC" -19.05815 158.4807 "HR" "AP" "" "" "Corail vivant" "Recif barriere externe" "LC1" -999 9 -999 -999 -999 -999 NA +"AMP" "CH13P063" "SVR" "Bampton nord" NA "Passe" NA 1 1 7 2013 "16:35" "soleil" NA 2 -999 NA NA "DC" -19.10967 158.55555 "HR" "AP" "" "" "Corail vivant" "Passe" "LC1" -999 6 -999 -999 -999 -999 NA +"AMP" "CH13P065" "SVR" "Bampton nord" NA "Pente externe" NA 1 2 7 2013 "08:40" "soleil" NA 1 -999 NA NA "DC" -19.07048 158.66102 "HR" "AP" "" "" "Corail vivant" "Recif barriere externe" "LC1" -999 8 -999 -999 -999 -999 NA +"AMP" "CH13P066" "SVR" "Bampton nord" NA "Pente externe" NA 1 2 7 2013 "08:45" "soleil" NA 1 -999 NA NA "DC" -19.07003 158.66298 "HR" "AP" "" "" "Corail vivant" "Recif barriere externe" "LC1" -999 7 -999 -999 -999 -999 NA +"AMP" "CH13P067" "SVR" NA NA "Pente externe" NA 1 2 7 2013 "09:33" "soleil" NA 1 -999 NA NA "DC" -19.0567 158.70987 "HR" "AP" "" "" "Corail vivant" "Recif barriere externe" "LC2" -999 11 -999 -999 -999 -999 NA +"AMP" "CH13P068" "SVR" NA NA "Pente externe" NA 1 2 7 2013 "09:40" "soleil" NA 1 -999 NA NA "DC" -19.05523 158.70873 "HR" "AP" "" "" "Corail vivant" "Recif barriere externe" "LC1" -999 6 -999 -999 -999 -999 NA +"AMP" "CH13P069" "SVR" NA NA "Pente externe" NA 1 2 7 2013 "10:39" "soleil" NA 1 -999 NA NA "DC" -19.0681 158.77832 "HR" "AP" "" "" "Corail vivant" "Recif barriere externe" "LC2" -999 15.5 -999 -999 -999 -999 NA +"AMP" "CH13P070" "SVR" "Bampton nord" NA "Pente externe" NA 1 2 7 2013 "10:50" "soleil" NA 1 -999 NA NA "DC" -19.07055 158.78277 "HR" "AP" "" "" "Corail vivant" "Recif barriere externe" "LC2" -999 10 -999 -999 -999 -999 NA +"AMP" "CH13P071" "SVR" "La Palette" NA "Pente externe" NA 1 2 7 2013 "16:35" "soleil" NA 1 -999 NA NA "DC" -18.96575 158.92373 "HR" "AP" "Couronne d atoll" "front recifal" "Corail vivant" "Recif barriere externe" "LC1" -999 16 -999 -999 -999 -999 NA +"AMP" "CH13P073" "SVR" "Recif Dumont Urville" NA "Recif profond" NA 1 3 7 2013 "09:02" "soleil" NA 1 2 NA NA "DC" -19.88359 159.00484 "HR" "AP" "Atoll ennoye" "couronne ennoyee" "Corail vivant" "Recif profond" "LC1" -999 16 -999 -999 -999 -999 NA +"AMP" "CH13P074" "SVR" "Recif Dumont Urville" NA "Recif profond" NA 1 3 7 2013 "09:43" "soleil" NA 1 2 NA NA "DC" -19.87988 159.00264 "HR" "AP" "Atoll ennoye" "couronne ennoyee" "Corail vivant" "Recif profond" "LC4" -999 17 -999 -999 -999 -999 NA +"AMP" "CH13P075" "SVR" "Recif Dumont Urville" NA "Recif profond" NA 1 3 7 2013 "09:50" "soleil" NA 1 2 NA NA "DC" -19.8786 159.00549 "HR" "AP" "Atoll ennoye" "couronne ennoyee" "Corail vivant" "Recif profond" "LC2" -999 20 -999 -999 -999 -999 NA +"AMP" "CH13S081" "SVR" "Corne sud" NA "Pente interne" NA 1 29 6 2013 "08:36" "nuage" NA 2 1 NA NA "LD" -19.86601 158.3105 "HR" "AP" "Couronne d atoll" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA3" -999 5 -999 -999 -999 -999 NA +"AMP" "CH13S082" "SVR" "Corne sud" NA "Pente interne" NA 1 29 6 2013 "08:39" "nuage" NA 2 1 NA NA "LD" -19.86341 158.31147 "HR" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Fond lagonaire" "Recif barriere interne" "SA3" -999 8 -999 -999 -999 -999 NA +"AMP" "CH13S083" "SVR" "Corne sud" NA "Pente interne" NA 1 29 6 2013 "09:00" "soleil" NA 2 1 NA NA "LD" -19.88399 158.33106 "HR" "AP" "Couronne d atoll" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA3" -999 3.5 -999 -999 -999 -999 NA +"AMP" "CH13S085" "SVR" "Corne sud" NA "Pente externe" NA 1 29 6 2013 "09:28" "soleil" NA 2 1 NA NA "LD" -19.90252 158.35657 "HR" "AP" "Couronne d atoll" "platier recifal" "Corail vivant" "Recif barriere interne" "LC5" -999 2 -999 -999 -999 -999 NA +"AMP" "CH13S086" "SVR" "Corne sud" NA "Pente interne" NA 1 29 6 2013 "09:42" "soleil" NA 2 1 NA NA "LD" -19.89899 158.35838 "HR" "AP" "Couronne d atoll" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA3" -999 5 -999 -999 -999 -999 NA +"AMP" "CH13S087" "SVR" NA NA "Passe" NA 1 29 6 2013 "10:04" "soleil" NA 2 1 NA NA "LD" -19.90756 158.37111 "HR" "AP" "Couronne d atoll" "platier recifal ennoye" "Fond lagonaire" "Passe" "SA3" -999 8 -999 -999 -999 -999 NA +"AMP" "CH13S088" "SVR" NA NA "Passe" NA 1 29 6 2013 "10:10" "soleil" NA 2 1 NA NA "LD" -19.90909 158.37202 "HR" "AP" "Couronne d atoll" "platier recifal ennoye" "Corail vivant" "Passe" "LC2" -999 15 -999 -999 -999 -999 NA +"AMP" "CH13S090" "SVR" "Corne sud" NA "Passe" NA 1 29 6 2013 "10:27" "soleil" NA 2 1 NA NA "LD" -19.91314 158.37115 "HR" "AP" "Couronne d atoll" "front recifal" "Fond lagonaire" "Recif barriere externe" "LC5" -999 18 -999 -999 -999 -999 NA +"AMP" "CH13S091" "SVR" "Corne sud" NA "Passe" NA 1 29 6 2013 "10:35" "soleil" NA 2 1 NA NA "LD" -19.91688 158.37631 "HR" "AP" "Couronne d atoll" "front recifal" "Corail vivant" "Recif barriere externe" "LC3" -999 20 -999 -999 -999 -999 NA +"AMP" "CH13S092" "SVR" "Corne sud" NA "Passe" NA 1 29 6 2013 "10:56" "soleil" NA 2 1 NA NA "LD" -19.90784 158.3801 "HR" "AP" "Couronne d atoll" "platier recifal" "Corail vivant" "Recif barriere interne" "LC5" -999 8 -999 -999 -999 -999 NA +"AMP" "CH13S093" "SVR" "Corne sud" NA "Passe" NA 1 29 6 2013 "11:01" "soleil" NA 2 1 NA NA "LD" -19.91044 158.37724 "HR" "AP" "Couronne d atoll" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA3" -999 4 -999 -999 -999 -999 NA +"AMP" "CH13S094" "SVR" "Corne sud" NA "Pente interne" NA 1 29 6 2013 "12:38" "soleil" NA 2 1 NA NA "LD" -19.92849 158.4142 "HR" "AP" "Couronne d atoll" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA5" -999 2 -999 -999 -999 -999 NA +"AMP" "CH13S095" "SVR" "Corne sud" NA "Pente interne" NA 1 29 6 2013 "12:42" "soleil" NA 2 1 NA NA "LD" -19.92729 158.41544 "HR" "AP" "Couronne d atoll" "platier recifal" "Corail vivant" "Recif barriere interne" "LC4" -999 4 -999 -999 -999 -999 NA +"AMP" "CH13S096" "SVR" "Corne sud" NA "Pente interne" NA 1 29 6 2013 "13:13" "soleil" NA 2 1 NA NA "LD" -19.95067 158.45818 "HR" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Fond lagonaire" "Recif barriere interne" "SA5" -999 14 -999 -999 -999 -999 NA +"AMP" "CH13S098" "SVR" "Corne sud" NA "Pente interne" NA 1 29 6 2013 "13:17" "soleil" NA 2 1 NA NA "LD" -19.95689 158.45797 "HR" "AP" "Couronne d atoll" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA3" -999 3 -999 -999 -999 -999 NA +"AMP" "CH13S099" "SVR" "Corne sud" NA "Pente interne" NA 1 29 6 2013 "13:38" "soleil" NA 2 1 NA NA "LD" -19.9678 158.4727 "HR" "AP" "Couronne d atoll" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA3" -999 9 -999 -999 -999 -999 NA +"AMP" "CH13S100" "SVR" "Corne sud" NA "Pente interne" NA 1 29 6 2013 "13:56" "soleil" NA 2 1 NA NA "LD" -19.96997 158.47429 "HR" "AP" "Couronne d atoll" "platier recifal" "Corail vivant" "Recif barriere interne" "LC3" -999 4 -999 -999 -999 -999 NA +"AMP" "CH13S101" "SVR" "Corne sud" NA "Pente interne" NA 1 29 6 2013 "14:17" "soleil" NA 2 1 NA NA "LD" -19.93937 158.48089 "HR" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Fond lagonaire" "Recif barriere interne" "SA3" -999 5 -999 -999 -999 -999 NA +"AMP" "CH13S102" "SVR" "Corne sud" NA "Pente interne" NA 1 29 6 2013 "14:22" "soleil" NA 2 1 NA NA "LD" -19.93852 158.48535 "HR" "AP" "Couronne d atoll" "platier recifal" "Fond lagonaire" "Recif barriere interne" "LC5" -999 3 -999 -999 -999 -999 NA +"AMP" "CH13S103" "SVR" "Corne sud" NA "Pente interne" NA 1 29 6 2013 "14:43" "soleil" NA 2 1 NA NA "LD" -19.90802 158.47987 "HR" "AP" "Couronne d atoll" "platier recifal" "Detritique" "Recif barriere interne" NA -999 2 -999 -999 -999 -999 NA +"AMP" "CH13S104" "SVR" "Corne sud" NA "Pente interne" NA 1 29 6 2013 "14:49" "soleil" NA 2 1 NA NA "LD" -19.90982 158.47105 "HR" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Fond lagonaire" "Recif barriere interne" "SA1" -999 20 -999 -999 -999 -999 NA +"AMP" "CH13S105" "SVR" "Corne sud" NA "Pente externe" NA 1 29 6 2013 "15:33" "soleil" NA 2 1 NA NA "LD" -19.83167 158.45501 "HR" "AP" "Couronne d atoll" "front recifal" "Fond lagonaire" "Recif barriere externe" "SA1" -999 15 -999 -999 -999 -999 NA +"AMP" "CH13S106" "SVR" "Corne sud" NA "Pente externe" NA 1 29 6 2013 "15:36" "soleil" NA 2 1 NA NA "LD" -19.83346 158.45203 "HR" "AP" "Couronne d atoll" "front recifal" "Corail vivant" "Recif barriere externe" "LC5" -999 10 -999 -999 -999 -999 NA +"AMP" "CH13S107" "SVR" "Corne sud" NA "Pente externe" NA 1 29 6 2013 "15:53" "soleil" NA 2 1 NA NA "LD" -19.82408 158.44817 "HR" "AP" "Couronne d atoll" "front recifal" "Corail vivant" "Recif barriere externe" "LC3" -999 12 -999 -999 -999 -999 NA +"AMP" "CH13S120" "SVR" "Barriere ouest" NA "Pente interne" NA 1 30 6 2013 "09:29" "nuage" NA 2 1 NA NA "DQ" -19.79729 158.27803 "HR" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Fond lagonaire" "Recif barriere interne" "SA3" -999 10 -999 -999 -999 -999 NA +"AMP" "CH13S121" "SVR" "Barriere ouest" NA "Pente interne" NA 1 30 6 2013 "09:39" "nuage" NA 2 -999 NA NA "DQ" -19.79832 158.27338 "HR" "AP" "Couronne d atoll" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA3" -999 2 -999 -999 -999 -999 NA +"AMP" "CH13S122" "SVR" "Barriere ouest" NA "Pente interne" NA 1 30 6 2013 "09:57" "soleil" NA 2 -999 NA NA "DQ" -19.79355 158.2686 "HR" "AP" "Couronne d atoll" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA3" -999 2 -999 -999 -999 -999 NA +"AMP" "CH13S123" "SVR" "Barriere ouest" NA "Pente interne" NA 1 30 6 2013 "10:00" "soleil" NA 2 -999 NA NA "DQ" -19.79408 158.26637 "HR" "AP" "Couronne d atoll" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA3" -999 2 -999 -999 -999 -999 NA +"AMP" "CH13S124" "SVR" "Barriere ouest" NA "Pente interne" NA 1 30 6 2013 "10:29" "soleil" NA 2 -999 NA NA "DQ" -19.7681 158.26944 "HR" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Fond lagonaire" "Recif barriere interne" "SA1" -999 18 -999 -999 -999 -999 NA +"AMP" "CH13S125" "SVR" "Barriere ouest" NA "Pente interne" NA 1 30 6 2013 "10:35" "soleil" NA 2 -999 NA NA "DQ" -19.76577 158.2681 "HR" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Corail vivant" "Recif barriere interne" "LC1" -999 10 -999 -999 -999 -999 NA +"AMP" "CH13S126" "SVR" "Barriere ouest" NA "Pente interne" NA 1 30 6 2013 "10:57" "soleil" NA 2 -999 NA NA "DQ" -19.7392 158.263 "HR" "AP" "Couronne d atoll" "platier recifal" "Detritique" "Recif barriere interne" NA -999 7 -999 -999 -999 -999 NA +"AMP" "CH13S127" "SVR" "Barriere ouest" NA "Pente interne" NA 1 30 6 2013 "11:08" "soleil" NA 2 -999 NA NA "DQ" -19.73607 158.26712 "HR" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Corail vivant" "Recif barriere interne" "LC5" -999 13 -999 -999 -999 -999 NA +"AMP" "CH13S128" "SVR" "Barriere ouest" NA "Pente interne" NA 1 30 6 2013 "12:03" "soleil" NA 2 -999 NA NA "DQ" -19.68905 158.24399 "HR" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Fond lagonaire" "Recif barriere interne" "SA1" -999 9 -999 -999 -999 -999 NA +"AMP" "CH13S130" "SVR" "Barriere ouest" NA "Pente interne" NA 1 30 6 2013 "12:30" "soleil" NA 2 -999 NA NA "DQ" -19.67176 158.22406 "HR" "AP" "Couronne d atoll" "platier recifal" "Detritique" "Recif barriere interne" NA -999 6 -999 -999 -999 -999 NA +"AMP" "CH13S131" "SVR" "Barriere ouest" NA "Pente interne" NA 1 30 6 2013 "12:36" "soleil" NA 2 -999 NA NA "DQ" -19.67157 158.2228 "HR" "AP" "Couronne d atoll" "platier recifal" "Corail vivant" "Recif barriere interne" "LC5" -999 6 -999 -999 -999 -999 NA +"AMP" "CH13S132" "SVR" "Barriere ouest" NA "Pente externe" NA 1 30 6 2013 "14:05" "soleil" NA 2 -999 NA NA "DQ" -19.62607 158.19752 "HR" "AP" "Couronne d atoll" "front recifal" "Corail vivant" "Recif barriere externe" "LC1" -999 18 -999 -999 -999 -999 NA +"AMP" "CH13S133" "SVR" "Barriere ouest" NA "Pente externe" NA 1 30 6 2013 "14:19" "soleil" NA 2 1 NA NA "DQ" -19.63048 158.19765 "HR" "AP" "Couronne d atoll" "front recifal" "Corail vivant" "Recif barriere externe" "LC5" -999 9 -999 -999 -999 -999 NA +"AMP" "CH13S135" "SVR" "Barriere ouest" NA "Pente externe" NA 1 30 6 2013 "15:08" "soleil" NA 2 1 NA NA "DQ" -19.53257 158.23281 "HR" "AP" "Couronne d atoll" "front recifal" "Fond lagonaire" "Recif barriere externe" "SA3" -999 14 -999 -999 -999 -999 NA +"AMP" "CH13S136" "SVR" "Barriere ouest" NA "Pente interne" NA 1 30 6 2013 "15:12" "soleil" NA 2 1 NA NA "DQ" -19.53274 158.2356 "HR" "AP" "Couronne d atoll" "platier recifal" "Detritique" "Recif barriere interne" NA -999 4 -999 -999 -999 -999 NA +"AMP" "CH13S138" "SVR" "Barriere ouest" NA "Pente interne" NA 1 30 6 2013 "15:34" "soleil" NA 2 1 NA NA "DQ" -19.52935 158.23893 "HR" "AP" "Couronne d atoll" "platier recifal" "Detritique" "Recif barriere interne" "D1" -999 2 -999 -999 -999 -999 NA +"AMP" "CH13S140" "SVR" "Barriere ouest" NA "Pente interne" NA 1 30 6 2013 "16:08" "soleil" NA 2 1 NA NA "DQ" -19.49237 158.26188 "HR" "AP" "Couronne d atoll" "platier recifal ennoye" "Fond lagonaire" "Recif barriere interne" "SA3" -999 9 -999 -999 -999 -999 NA +"AMP" "CH13S141" "SVR" "Barriere ouest" NA "Pente interne" NA 1 1 7 2013 "07:52" "nuage" NA 1 -999 NA NA "DC" -19.4422 158.28621 "HR" "AP" "Couronne d atoll" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA3" -999 4 -999 -999 -999 -999 NA +"AMP" "CH13S142" "SVR" "Barriere ouest" NA "Pente interne" NA 1 1 7 2013 "07:57" "nuage" NA 1 -999 NA NA "DC" -19.44154 158.28206 "HR" "AP" "Couronne d atoll" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA3" -999 3 -999 -999 -999 -999 NA +"AMP" "CH13S143" "SVR" "Barriere ouest" NA "Pente externe" NA 1 1 7 2013 "08:39" "soleil" "0" 0 -999 NA NA "DC" -19.41791 158.28415 "HR" "AP" "Couronne d atoll" "platier recifal" "Detritique" "Recif barriere interne" NA -999 3 -999 -999 -999 -999 NA +"AMP" "CH13S144" "SVR" "Barriere ouest" NA "Pente externe" NA 1 1 7 2013 "08:44" "soleil" "0" 0 -999 NA NA "DC" -19.41518 158.28529 "HR" "AP" "Couronne d atoll" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA3" -999 4 -999 -999 -999 -999 NA +"AMP" "CH13S145" "SVR" "Barriere ouest" NA "Pente interne" NA 1 1 7 2013 "09:14" "soleil" "0" 0 -999 NA NA "DC" -19.36367 158.30557 "HR" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Detritique" "Recif barriere interne" NA -999 10 -999 -999 -999 -999 NA +"AMP" "CH13S146" "SVR" "Barriere ouest" NA "Pente interne" NA 1 1 7 2013 "09:19" "soleil" "0" 0 -999 NA NA "DC" -19.36861 158.3083 "HR" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Corail vivant" "Recif barriere interne" "LC5" -999 16 -999 -999 -999 -999 NA +"AMP" "CH13S147" "SVR" "Barriere ouest" NA "Pente interne" NA 1 1 7 2013 "09:46" "soleil" "0" 0 -999 NA NA "DC" -19.32082 158.3089 "HR" "AP" "Couronne d atoll" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA3" -999 6 -999 -999 -999 -999 NA +"AMP" "CH13S148" "SVR" "Barriere ouest" NA "Pente interne" NA 1 1 7 2013 "09:51" "soleil" "0" 0 -999 NA NA "DC" -19.31721 158.30519 "HR" "AP" "Couronne d atoll" "platier recifal" "Corail vivant" "Recif barriere interne" "LC6" -999 5 -999 -999 -999 -999 NA +"AMP" "CH13S149" "SVR" "Barriere nord-ouest" NA "Pente interne" NA 1 1 7 2013 "10:28" "soleil" "0" 0 -999 NA NA "DC" -19.26705 158.32788 "HR" "AP" "Couronne d atoll" "platier recifal" "Detritique" "Recif barriere interne" NA -999 4 -999 -999 -999 -999 NA +"AMP" "CH13S150" "SVR" "Barriere nord-ouest" NA "Pente interne" NA 1 1 7 2013 "10:32" "soleil" "0" 0 -999 NA NA "DC" -19.26605 158.325 "HR" "AP" "Couronne d atoll" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA3" -999 4 -999 -999 -999 -999 NA +"AMP" "CH13S151" "SVR" "Barriere nord-ouest" NA "Pente interne" NA 1 1 7 2013 "11:16" "soleil" "0" 0 1 NA NA "DC" -19.22572 158.35562 "HR" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Corail vivant" "Recif barriere interne" "LC5" -999 11 -999 -999 -999 -999 NA +"AMP" "CH13S152" "SVR" "Barriere nord-ouest" NA "Pente interne" NA 1 1 7 2013 "11:20" "soleil" "0" 0 -999 NA NA "DC" -19.22135 158.35452 "HR" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Fond lagonaire" "Recif barriere interne" "SA3" -999 9 -999 -999 -999 -999 NA +"AMP" "CH13S153" "SVR" "Barriere nord-ouest" NA "Pente interne" NA 1 1 7 2013 "11:47" "soleil" "0" 0 -999 NA NA "DC" -19.16123 158.37515 "HR" "AP" "Couronne d atoll" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA3" -999 3 -999 -999 -999 -999 NA +"AMP" "CH13S154" "SVR" "Barriere nord-ouest" NA "Pente interne" NA 1 1 7 2013 "11:51" "soleil" "0" 0 -999 NA NA "DC" -19.16165 158.37167 "HR" "AP" "Couronne d atoll" "platier recifal" "Detritique" "Recif barriere interne" "SA5" -999 3 -999 -999 -999 -999 NA +"AMP" "CH13S155" "SVR" "Barriere nord-ouest" NA "Pente externe" NA 1 1 7 2013 "12:29" "soleil" "0" 0 -999 NA NA "DC" -19.11152 158.37144 "HR" "AP" "Couronne d atoll" "front recifal" "Fond lagonaire" "Recif barriere externe" "SA5" -999 16 -999 -999 -999 -999 NA +"AMP" "CH13S156" "SVR" "Barriere nord-ouest" NA "Pente externe" NA 1 1 7 2013 "12:48" "soleil" "0" 0 -999 NA NA "DC" -19.11205 158.36305 "HR" "AP" "" "" "Corail vivant" "Recif barriere externe" "LC1" -999 16 -999 -999 -999 -999 NA +"AMP" "CH13S157" "SVR" "Barriere nord-ouest" NA "Pente interne" NA 1 1 7 2013 "13:40" "soleil" NA 1 -999 NA NA "DC" -19.05875 158.43628 "HR" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Fond lagonaire" "Recif barriere interne" "SA1" -999 9 -999 -999 -999 -999 NA +"AMP" "CH13S158" "SVR" "Barriere nord-ouest" NA "Pente interne" NA 1 1 7 2013 "13:43" "soleil" "0" 0 -999 NA NA "DC" -19.06126 158.43677 "HR" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Fond lagonaire" "Recif barriere interne" "SA5" -999 6 -999 -999 -999 -999 NA +"AMP" "CH13S159" "SVR" "Bampton nord" NA "Pente interne" NA 1 1 7 2013 "14:05" "soleil" "0" 0 -999 NA NA "DC" -19.07146 158.48175 "HR" "AP" "Couronne d atoll" "platier recifal" "Corail vivant" "Recif barriere interne" "LC5" -999 3 -999 -999 -999 -999 NA +"AMP" "CH13S160" "SVR" "Bampton nord" NA "Pente interne" NA 1 1 7 2013 "14:07" "soleil" "0" 0 -999 NA NA "DC" -19.06964 158.48051 "HR" "AP" "Couronne d atoll" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA5" -999 6 -999 -999 -999 -999 NA +"AMP" "CH13S162" "SVR" "Bampton nord" NA "Pente externe" NA 1 1 7 2013 "14:40" "soleil" "0" 0 -999 NA NA "DC" -19.11359 158.54855 "HR" "AP" "Couronne d atoll" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA3" -999 6 -999 -999 -999 -999 NA +"AMP" "CH13S163" "SVR" "Bampton nord" NA "Pente externe" NA 1 1 7 2013 "15:11" "nuage" NA 1 -999 NA NA "DC" -19.12192 158.60109 "HR" "AP" "Couronne d atoll" "platier recifal" "Corail vivant" "Recif barriere externe" "LC5" -999 4 -999 -999 -999 -999 NA +"AMP" "CH13S165" "SVR" "Bampton nord" NA "Pente interne" NA 1 1 7 2013 "16:14" "soleil" NA 4 -999 NA NA "DC" -19.09616 158.65114 "HR" "AP" "Couronne d atoll" "platier recifal" "Corail vivant" "Recif barriere interne" "LC6" -999 7 -999 -999 -999 -999 NA +"AMP" "CH13S171" "SVR" "Bampton nord" NA "Pente interne" NA 1 2 7 2013 "07:46" "soleil" NA 2 1 NA NA "DC" -19.09641 158.65251 "HR" "AP" "Couronne d atoll" "platier recifal" "Corail vivant" "Recif barriere interne" "LC5" -999 16 -999 -999 -999 -999 NA +"AMP" "CH13S172" "SVR" "Bampton nord" NA "Pente interne" NA 1 2 7 2013 "08:08" "soleil" NA 2 1 NA NA "DC" -19.08017 158.68166 "HR" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Fond lagonaire" "Recif barriere interne" "SA3" -999 9 -999 -999 -999 -999 NA +"AMP" "CH13S175" "SVR" "Bampton nord" NA "Pente externe" NA 1 2 7 2013 "08:40" "soleil" NA 2 1 NA NA "DC" -19.05575 158.72998 "HR" "AP" "Couronne d atoll" "platier recifal" "Detritique" "Recif barriere externe" NA -999 4 -999 -999 -999 -999 NA +"AMP" "CH13S176" "SVR" "Bampton nord" NA "Pente externe" NA 1 2 7 2013 "09:11" "soleil" NA 2 1 NA NA "DC" -19.07068 158.77649 "HR" "AP" "Couronne d atoll" "front recifal" "Corail vivant" "Recif barriere externe" "SA5" -999 9 -999 -999 -999 -999 NA +"AMP" "CH13S178" "SVR" "Bampton nord" NA "Pente externe" NA 1 2 7 2013 "09:40" "soleil" NA 2 1 NA NA "DC" -19.07203 158.82515 "HR" "AP" "Couronne d atoll" "front recifal" "Fond lagonaire" "Recif barriere externe" "SA5" -999 4 -999 -999 -999 -999 NA +"AMP" "CH13S180" "SVR" "Bampton nord" NA "Passe" NA 1 2 7 2013 "10:22" "soleil" NA 2 1 NA NA "DC" -19.03402 158.87971 "HR" "AP" "Couronne d atoll" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA1" -999 3 -999 -999 -999 -999 NA +"AMP" "CH13S181" "SVR" "Bampton nord" NA "Passe" NA 1 2 7 2013 "10:26" "soleil" NA 2 1 NA NA "DC" -19.0367 158.88072 "HR" "AP" "Couronne d atoll" "platier recifal" "Detritique" "Recif barriere interne" "SA4" -999 2.5 -999 -999 -999 -999 NA +"AMP" "CH13S182" "SVR" "Bampton nord" NA "Passe" NA 1 2 7 2013 "10:47" "soleil" NA 2 1 NA NA "DC" -19.03495 158.91197 "HR" "AP" "Couronne d atoll" "passe" "Corail vivant" "Passe" "LC4" -999 13 -999 -999 -999 -999 NA +"AMP" "CH13S183" "SVR" "Bampton nord" NA "Passe" NA 1 2 7 2013 "10:53" "soleil" NA 2 1 NA NA "DC" -19.03622 158.91457 "HR" "AP" "Lagon d atoll" "lagon profond" "Corail vivant" "Passe" "LC1" -999 9 -999 -999 -999 -999 NA +"AMP" "CH13S184" "SVR" "La Palette" NA "Pente interne" NA 1 2 7 2013 "11:16" "soleil" NA 2 1 NA NA "DC" -19.0169 158.9296 "HR" "AP" "Couronne d atoll" "platier recifal" "Corail vivant" "Recif barriere interne" "LC4" -999 3 -999 -999 -999 -999 NA +"AMP" "CH13S185" "SVR" "La Palette" NA "Pente interne" NA 1 2 7 2013 "11:18" "soleil" NA 2 1 NA NA "DC" -19.01105 158.93489 "HR" "AP" "Couronne d atoll" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA3" -999 2.5 -999 -999 -999 -999 NA +"AMP" "CH13S186" "SVR" "La Palette" NA "Pente interne" NA 1 2 7 2013 "11:40" "soleil" NA 2 1 NA NA "DC" -18.99569 158.92546 "HR" "AP" "Couronne d atoll" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA3" -999 5 -999 -999 -999 -999 NA +"AMP" "CH13S187" "SVR" "La Palette" NA "Pente interne" NA 1 2 7 2013 "11:42" "soleil" NA 2 1 NA NA "DC" -18.9969 158.92278 "HR" "AP" "Couronne d atoll" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA3" -999 6 -999 -999 -999 -999 NA +"AMP" "CH13S188" "SVR" "La Palette" NA "Pente interne" NA 1 2 7 2013 "12:03" "soleil" NA 2 1 NA NA "DC" -18.97728 158.92021 "HR" "AP" "Couronne d atoll" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA3" -999 3.5 -999 -999 -999 -999 NA +"AMP" "CH13S189" "SVR" "La Palette" NA "Pente interne" NA 1 2 7 2013 "12:05" "soleil" NA 2 1 NA NA "DC" -18.98129 158.9175 "HR" "AP" "Couronne d atoll" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA1" -999 9.5 -999 -999 -999 -999 NA +"AMP" "CH13S190" "SVR" "La Palette" NA "Passe" NA 1 2 7 2013 "16:17" "soleil" NA 2 1 NA NA "DC" -19.0557 158.97443 "HR" "AP" "Couronne d atoll" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA3" -999 4 -999 -999 -999 -999 NA +"AMP" "CH13S191" "SVR" "La Palette" NA "Passe" NA 1 2 7 2013 "16:21" "soleil" NA 2 1 NA NA "DC" -19.05643 158.97627 "HR" "AP" "Couronne d atoll" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA4" -999 5 -999 -999 -999 -999 NA +"AMP" "CH13S192" "SVR" "La Palette" NA "Passe" NA 1 2 7 2013 "16:55" "soleil" NA 3 -999 NA NA "DC" -19.08731 159.00189 "HR" "AP" "Couronne d atoll" "platier recifal" "Detritique" "Recif barriere interne" NA -999 5 -999 -999 -999 -999 NA +"AMP" "CH13S193" "SVR" "La Palette" NA "Passe" NA 1 2 7 2013 "17:01" "soleil" NA 3 -999 NA NA "DC" -19.08855 159.00133 "HR" "AP" "Couronne d atoll" "platier recifal" "Detritique" "Recif barriere interne" NA -999 4 -999 -999 -999 -999 NA +"AMP" "CH13S194" "SVR" "La Palette" NA "Pente interne" NA 1 2 7 2013 "17:37" "soleil" NA 3 -999 NA NA "DC" -19.12218 159.02579 "HR" "AP" "Couronne d atoll" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA3" -999 4 -999 -999 -999 -999 NA +"AMP" "CH13S195" "SVR" "La Palette" NA "Pente interne" NA 1 2 7 2013 "17:42" "soleil" NA 3 -999 NA NA "DC" -19.12167 159.02475 "HR" "AP" "Couronne d atoll" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA3" -999 3 -999 -999 -999 -999 NA +"AMP" "CS130001" "SVR" "Ilot Mato" NA "Frangeant ilot" NA 1 27 9 2013 "13:24" "soleil" "ENE" 5 4 NA "PM" "DQ" -22.55121 166.78958 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Frangeant ilot" "D5" -999 9 -999 -999 -999 -999 NA +"AMP" "CS130003" "SVR" "Ilot Mato" NA "Recif lagonaire isole" NA 1 27 9 2013 "12:49" "soleil" "ENE" 5 4 NA "PM" "DQ" -22.56465 166.79614 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Corail vivant" "Recif intermediaire" "LC4" -999 6 -999 -999 -999 -999 NA +"AMP" "CS130005" "SVR" "Ilot Puemba" NA "Frangeant ilot" NA 1 27 9 2013 "12:04" "soleil" "ENE" 4 4 NA "PM" "DQ" -22.53203 166.82684 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse profonde" "Corail vivant" "Frangeant ilot" "LC5" -999 12 -999 -999 -999 -999 NA +"AMP" "CS130007" "SVR" "Recif Ia" NA "Recif lagonaire isole" NA 1 27 9 2013 "11:20" "soleil" "ENE" 4 4 NA "MM" "DQ" -22.55253 166.85097 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Fond lagonaire" "Recif intermediaire" "SA3" -999 10 -999 -999 -999 -999 NA +"AMP" "CS130008" "SVR" "Recif Ia" NA "Recif lagonaire isole" NA 1 27 9 2013 "11:08" "soleil" "ENE" 4 4 NA "MM" "DQ" -22.56649 166.84407 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Corail vivant" "Recif intermediaire" "LC5" -999 3 -999 -999 -999 -999 NA +"AMP" "CS130009" "SVR" "Ilot Ieroue" NA "Frangeant ilot" NA 1 27 9 2013 "10:24" "soleil" "NE" 3 2 NA "MM" "DQ" -22.60607 166.82471 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Corail vivant" "Frangeant ilot" "LC5" -999 10 -999 -999 -999 -999 NA +"AMP" "CS130010" "SVR" "Ilot Ieroue" NA "Recif lagonaire isole" NA 1 27 9 2013 "10:31" "soleil" "ENE" 4 4 NA "MM" "DQ" -22.6078 166.83199 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Corail vivant" "Recif intermediaire" "LC5" -999 7 -999 -999 -999 -999 NA +"AMP" "CS130011" "SVR" "Ilot Uatio" NA "Recif lagonaire isole" NA 1 27 9 2013 "07:33" "soleil" "NE" 3 2 NA "BM" "DQ" -22.70619 166.79312 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Corail vivant" "Frangeant ilot" "LC3" -999 6 -999 -999 -999 -999 NA +"AMP" "CS130013" "SVR" "Ilot Uaterembi" NA "Recif lagonaire isole" NA 1 27 9 2013 "08:52" "soleil" "NE" 3 2 NA "MM" "DQ" -22.68533 166.82043 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal ennoye" "Detritique" "Recif intermediaire" NA -999 6 -999 -999 -999 -999 NA +"AMP" "CS130014" "SVR" "Ilot Uaterembi" NA "Frangeant ilot" NA 1 27 9 2013 "09:02" "soleil" "NE" 3 2 NA "MM" "DQ" -22.6796 166.8087 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse profonde" "Corail vivant" "Frangeant ilot" "LC6" -999 10 -999 -999 -999 -999 NA +"AMP" "CS130015" "SVR" "Ilot Nge" NA "Frangeant ilot" NA 1 26 9 2013 "16:03" "soleil" "NE" 3 2 NA "MD" "LD" -22.69387 166.84822 "HR" "AP" "Complexe de massif corallien de lagon" "front recifal" "Corail vivant" "Frangeant ilot" "LC1" -999 5 -999 -999 -999 -999 NA +"AMP" "CS130016" "SVR" "Ilot Nge" NA "Frangeant ilot" NA 1 26 9 2013 "15:58" "soleil" "NE" 3 2 NA "MD" "LD" -22.69657 166.85616 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Corail vivant" "Frangeant ilot" "LC2" -999 7 -999 -999 -999 -999 NA +"AMP" "CS130017" "SVR" "Recif Purembi" NA "Recif lagonaire isole" NA 1 26 9 2013 "14:53" "soleil" "NE" 2 2 NA "MD" "LD" -22.64985 166.90541 "HR" "AP" "Complexe de massif corallien de mers interieures" "terrasse peu profonde" "Fond lagonaire" "Recif intermediaire" "SA3" -999 3 -999 -999 -999 -999 NA +"AMP" "CS130018" "SVR" "Recif Purembi" NA "Recif lagonaire isole" NA 1 26 9 2013 "14:29" "soleil" "NE" 2 2 NA "MD" "LD" -22.65505 166.9064 "HR" "AP" "Complexe de massif corallien de mers interieures" "platier recifal" "Corail vivant" "Passe" "LC4" -999 4 -999 -999 -999 -999 NA +"AMP" "CS130019" "SVR" NA NA "Recif lagonaire isole" NA 1 26 9 2013 "15:25" "soleil" "NE" 3 2 NA "MD" "LD" -22.68029 166.89664 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Corail vivant" "Recif intermediaire" "LC2" -999 11 -999 -999 -999 -999 NA +"AMP" "CS130020" "SVR" NA NA "Recif lagonaire isole" NA 1 26 9 2013 "15:32" "soleil" "NE" 3 2 NA "MD" "LD" -22.69225 166.89694 "HR" "AP" "Complexe de massif corallien de lagon" "lagon enclave a champ de constructions coralliennes" "Corail vivant" "Recif intermediaire" "LC5" -999 8 -999 -999 -999 -999 NA +"AMP" "CS130021" "SVR" "Recif Neokumbi" NA "Fond lagonaire" NA 1 20 9 2013 "13:59" "nuage" "SE" 3 2 NA "BM" "LD" -22.7557 166.71069 "HR" "AP" "Ile lagonaire" "lagon profond" "Corail vivant" "Recif barriere interne" "LC4" -999 5 -999 -999 -999 -999 NA +"AMP" "CS130023" "SVR" "Recif Neokumbi" NA "Pente interne" NA 1 20 9 2013 "13:34" "nuage" NA 3 2 NA "BM" "LD" -22.77255 166.72441 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA1" -999 10 -999 -999 -999 -999 NA +"AMP" "CS130025" "SVR" "Recif Neokumbi" NA "Pente interne" NA 1 20 9 2013 "13:19" "soleil" NA 3 2 NA "BM" "LD" -22.77901 166.73123 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA3" -999 6 -999 -999 -999 -999 NA +"AMP" "CS130027" "SVR" "Recif Umbei" NA "Pente interne" NA 1 20 9 2013 "09:36" "soleil" "ESE" 3 2 NA "MD" "LD" -22.85575 166.80911 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Corail vivant" "Recif barriere interne" "LC5" -999 6 -999 -999 -999 -999 NA +"AMP" "CS130029" "SVR" "Recif Neokouie" NA "Pente interne" NA 1 20 9 2013 "12:00" "soleil" "ESE" 3 2 NA "MD" "LD" -22.82341 166.77275 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA1" -999 13 -999 -999 -999 -999 NA +"AMP" "CS130031" "SVR" "Recif Neokouie" NA "Pente interne" NA 1 20 9 2013 "12:39" "soleil" "SE" 3 2 NA "MD" "LD" -22.81188 166.76044 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA1" -999 11 -999 -999 -999 -999 NA +"AMP" "CS130033" "SVR" "Recif Ie" NA "Pente interne" NA 1 20 9 2013 "09:27" "soleil" "ESE" 3 2 NA "MD" "LD" -22.87506 166.82227 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA1" -999 12 -999 -999 -999 -999 NA +"AMP" "CS130035" "SVR" "Recif Garanhua" NA "Pente interne" NA 1 20 9 2013 "08:55" "soleil" "ESE" 3 2 NA "MD" "LD" -22.89155 166.83647 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Recif barriere interne" NA -999 6 -999 -999 -999 -999 NA +"AMP" "CS130037" "SVR" "Recif Garanhua" NA "Pente interne" NA 1 20 9 2013 "08:29" "soleil" "ESE" 3 2 NA "MD" "LD" -22.9124 166.84808 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Recif barriere interne" "D7" -999 11 -999 -999 -999 -999 NA +"AMP" "CS130039" "SVR" "Recif Garanhua" NA "Passe" NA 1 20 9 2013 "08:18" "soleil" "ESE" 3 2 NA "MD" "LD" -22.91297 166.8627 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Corail vivant" "Recif barriere interne" "LC6" -999 8 -999 -999 -999 -999 NA +"AMP" "CS130042" "SVR" "Ilot Kouare" NA "Recif lagonaire isole" NA 1 25 9 2013 "14:35" "soleil" "SSE" 1 1 NA "MD" "LD" -22.77936 166.82495 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Corail vivant" "Recif intermediaire" "LC4" -999 10 -999 -999 -999 -999 NA +"AMP" "CS130043" "SVR" "Ilot Kouare" NA "Recif lagonaire isole" NA 1 25 9 2013 "14:06" "soleil" "SSE" 1 1 NA "MD" "LD" -22.77667 166.81329 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Corail vivant" "Recif intermediaire" "LC5" -999 4 -999 -999 -999 -999 NA +"AMP" "CS130044" "SVR" "Ilot Kouare" NA "Frangeant ilot" NA 1 25 9 2013 "13:42" "soleil" "SSE" 1 1 NA "MD" "LD" -22.77323 166.79747 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Corail vivant" "Frangeant ilot" "LC5" -999 7 -999 -999 -999 -999 NA +"AMP" "CS130045" "SVR" "Ilot Kouare" NA "Recif lagonaire isole" NA 1 25 9 2013 "13:20" "soleil" "SSE" 1 1 NA "MD" "LD" -22.77983 166.79422 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Recif intermediaire" NA -999 8 -999 -999 -999 -999 NA +"AMP" "CS130046" "SVR" "Ilot Kouare" NA "Recif lagonaire isole" NA 1 25 9 2013 "12:57" "soleil" "SSE" 1 1 NA "MD" "LD" -22.78851 166.79965 "HR" "AP" "Complexe de massif corallien de lagon" "front recifal" "Corail vivant" "Recif intermediaire" "LC2" -999 6 -999 -999 -999 -999 NA +"AMP" "CS130047" "SVR" NA NA "Recif lagonaire isole" NA 1 25 9 2013 "15:14" "soleil" "SSE" 1 1 NA "MD" "LD" -22.808 166.8111 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Corail vivant" "Recif intermediaire" "LC5" -999 5 -999 -999 -999 -999 NA +"AMP" "CS130050" "SVR" "Recif Tootira" NA "Recif lagonaire isole" NA 1 25 9 2013 "16:24" "soleil" "SSE" 1 1 NA "MD" "LD" -22.76707 166.87622 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Corail vivant" "Recif intermediaire" "LC5" -999 2 -999 -999 -999 -999 NA +"AMP" "CS130054" "SVR" "Ilot Mbore" NA "Frangeant ilot" NA 1 26 9 2013 "07:50" "soleil" "0" 0 0 NA "MM" "LD" -22.80248 166.9147 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Corail vivant" "Frangeant ilot" "SA3" -999 13 -999 -999 -999 -999 NA +"AMP" "CS130055" "SVR" "Ilot Mbore" NA "Recif lagonaire isole" NA 1 26 9 2013 "07:55" "soleil" "0" 0 0 NA "MM" "LD" -22.79659 166.9211 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Corail vivant" "Recif intermediaire" "LC6" -999 11 -999 -999 -999 -999 NA +"AMP" "CS130060" "SVR" "Ilot Tere" NA "Recif lagonaire isole" NA 1 25 9 2013 "15:46" "soleil" "SSE" 1 1 NA "MD" "LD" -22.7931 166.84464 "HR" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Recif intermediaire" "D7" -999 4 -999 -999 -999 -999 NA +"AMP" "CS130064" "SVR" "Recif Nogumatiugi" NA "Pente interne" NA 1 19 9 2013 "15:03" "soleil" "NE" 3 2 NA "MM" "PL" -22.93609 166.90732 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA3" -999 13 -999 -999 -999 -999 NA +"AMP" "CS130065" "SVR" "Recif Nogumatiugi" NA "Pente externe" NA 1 19 9 2013 "08:21" "soleil" "NE" 3 2 NA "MM" "PL" -22.93533 166.89656 "HR" "AP" "Complexe de recif barriere externe" "front recifal" "Corail vivant" "Recif barriere externe" "LC2" -999 9 -999 -999 -999 -999 NA +"AMP" "CS130066" "SVR" "Recif Nogumatiugi" NA "Pente interne" NA 1 19 9 2013 "16:22" "soleil" "NE" 3 2 NA "MM" "PL" -22.95135 166.91286 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA3" -999 2 -999 -999 -999 -999 NA +"AMP" "CS130068" "SVR" "Recif Nogumatiugi" NA "Pente interne" NA 1 19 9 2013 "13:55" "soleil" "NE" 3 2 NA "MM" "PL" -22.9709 166.93752 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA3" -999 13 -999 -999 -999 -999 NA +"AMP" "CS130069" "SVR" "Recif Nogumatiugi" NA "Pente externe" NA 1 19 9 2013 "09:45" "soleil" "NE" 3 2 NA "MM" "PL" -22.97569 166.92628 "HR" "AP" "Complexe de recif barriere externe" "front recifal" "Corail vivant" "Recif barriere externe" "LC1" -999 15 -999 -999 -999 -999 NA +"AMP" "CS130070" "SVR" "Recif Nogumatiugi" NA "Pente interne" NA 1 19 9 2013 "13:28" "soleil" "NE" 3 2 NA "MM" "PL" -22.98359 166.94968 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA2" -999 3 -999 -999 -999 -999 NA +"AMP" "CS130071" "SVR" "Recif Nogumatiugi" NA "Pente externe" NA 1 19 9 2013 "08:26" "soleil" "NE" 3 2 NA "MD" "PL" -22.99533 166.94604 "HR" "AP" "Complexe de recif barriere externe" "front recifal" "Corail vivant" "Recif barriere externe" "LC1" -999 17 -999 -999 -999 -999 NA +"AMP" "CS130072" "SVR" "Recif Nogumatiugi" NA "Pente interne" NA 1 19 9 2013 "12:20" "soleil" "NE" 3 1 NA "BM" "PL" -22.99912 166.96102 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Corail vivant" "Recif barriere interne" NA -999 3 -999 -999 -999 -999 NA +"AMP" "CS130074" "SVR" "Recif Cimenia" NA "Pente interne" NA 1 19 9 2013 "11:06" "soleil" "NE" 3 1 NA "MD" "PL" -23.00774 166.98964 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA3" -999 3 -999 -999 -999 -999 NA +"AMP" "CS130075" "SVR" "Recif Nogumatiugi" NA "Pente externe" NA 1 19 9 2013 "10:26" "soleil" "NE" 3 2 NA "MM" "PL" -23.01656 166.9791 "HR" "AP" "" "" "Corail vivant" "Recif barriere externe" "LC1" -999 22 -999 -999 -999 -999 NA +"AMP" "CS130077" "SVR" "Recif Nogumatiugi" NA "Recif lagonaire isole" NA 1 19 9 2013 "10:25" "soleil" "NE" 3 2 NA "MD" "PL" -23.01337 167.00319 "HR" "AP" "Complexe de recif barriere imbrique" "front recifal ou terrasse" "Fond lagonaire" "Passe" NA -999 13 -999 -999 -999 -999 NA +"AMP" "CS130079" "SVR" "Recif Cimenia" NA "Fond lagonaire" NA 1 19 9 2013 "11:40" "soleil" "NE" 3 1 NA "MD" "PL" -22.99517 166.97784 "HR" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA3" -999 9 -999 -999 -999 -999 NA +"AMP" "CS130080" "SVR" "Recif Nogumatiugi" NA "Pente interne" NA 1 19 9 2013 "12:30" "soleil" "NE" 3 1 NA "BM" "PL" -22.99036 166.95686 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA1" -999 16 -999 -999 -999 -999 NA +"AMP" "CS130081" "SVR" "Recif Nogumatiugi" NA "Pente externe" NA 1 19 9 2013 "08:58" "soleil" "NE" 3 2 NA "MM" "PL" -22.9532 166.90274 "HR" "AP" "" "" "Corail vivant" "Recif barriere externe" "LC1" -999 13 -999 -999 -999 -999 NA +"AMP" "CS130082" "SVR" "Recif Nogumatiugi" NA "Pente interne" NA 1 19 9 2013 "14:22" "soleil" "NE" 3 2 NA "MM" "PL" -22.96041 166.92392 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA3" -999 3 -999 -999 -999 -999 NA +"AMP" "CS130083" "SVR" "Recif Nogumatiugi" NA "Fond lagonaire" NA 1 19 9 2013 "10:15" "soleil" "NE" 3 2 NA "MD" "PL" -23.01459 167.01726 "HR" "AP" "Ile lagonaire" "lagon profond" "Corail vivant" "Passe" "LC4" -999 15 -999 -999 -999 -999 NA +"AMP" "CS130084" "SVR" "Recif Cimenia" NA "Recif lagonaire isole" NA 1 19 9 2013 "11:52" "soleil" "NE" 3 1 NA "MD" "PL" -22.98714 166.98018 "HR" "AP" "Complexe de recif barriere imbrique" "terrasse peu profonde" "Algueraie" "Recif intermediaire" "SA2" -999 3 -999 -999 -999 -999 NA +"AMP" "CS130085" "SVR" "Recif Cimenia" NA "Recif lagonaire isole" NA 1 18 9 2013 "14:16" "soleil" "NE" 3 2 NA "MM" "LM" -22.97055 166.97797 "HR" "AP" "Complexe de recif barriere imbrique" "front recifal ou terrasse" "Fond lagonaire" "Recif intermediaire" "SA3" -999 13 -999 -999 -999 -999 NA +"AMP" "CS130086" "SVR" "Recif Cimenia" NA "Fond lagonaire" NA 1 18 9 2013 "14:45" "soleil" "NE" 3 2 NA "MM" "LM" -22.95685 166.97769 "HR" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA3" -999 22 -999 -999 -999 -999 NA +"AMP" "CS130087" "SVR" "Recif Cimenia" NA "Fond lagonaire" NA 1 18 9 2013 "14:55" "soleil" "NE" 3 2 NA "MM" "LM" -22.94703 166.9727 "HR" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA5" -999 23 -999 -999 -999 -999 NA +"AMP" "CS130089" "SVR" "Recif Cimenia" NA "Fond lagonaire" NA 1 18 9 2013 "15:58" "soleil" "NE" 3 2 NA "MM" "LM" -22.90582 166.96228 "HR" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA3" -999 22 -999 -999 -999 -999 NA +"AMP" "CS130090" "SVR" "Recif Cimenia" NA "Fond lagonaire" NA 1 18 9 2013 "08:30" "soleil" "NE" 3 2 NA "MM" "LM" -22.88748 166.96848 "HR" "AP" "Ile lagonaire" "lagon profond" "Corail vivant" "Fond lagonaire" "LC4" -999 6 -999 -999 -999 -999 NA +"AMP" "CS130091" "SVR" "Recif Cimenia" NA "Recif lagonaire isole" NA 1 18 9 2013 "08:15" "soleil" "NE" 3 2 NA "MM" "LM" -22.87778 166.97881 "HR" "AP" "Complexe de recif barriere imbrique" "front recifal ou terrasse" "Corail vivant" "Fond lagonaire" "LC4" -999 6 -999 -999 -999 -999 NA +"AMP" "CS130092" "SVR" "Recif Cimenia" NA "Recif lagonaire isole" NA 1 18 9 2013 "11:15" "soleil" "NE" 2 1 NA "MM" "LM" -22.87748 166.95901 "HR" "AP" "Complexe de recif barriere imbrique" "pinacle de recif barriere" "Fond lagonaire" "Recif intermediaire" "SA3" -999 7 -999 -999 -999 -999 NA +"AMP" "CS130093" "SVR" "Recif Cimenia" NA "Recif lagonaire isole" NA 1 18 9 2013 "11:42" "soleil" "NE" 2 1 NA "MM" "LM" -22.86766 166.96867 "HR" "AP" "Complexe de recif barriere imbrique" "terrasse peu profonde" "Corail vivant" "Recif intermediaire" NA -999 13 -999 -999 -999 -999 NA +"AMP" "CS130094" "SVR" "Recif Cimenia" NA "Recif lagonaire isole" NA 1 18 9 2013 "12:58" "soleil" "NE" 3 2 NA "MM" "LM" -22.92507 166.94969 "HR" "AP" "Complexe de recif barriere imbrique" "platier recifal" "Corail vivant" "Recif intermediaire" "LC4" -999 5 -999 -999 -999 -999 NA +"AMP" "CS130095" "SVR" "Recif Cimenia" NA "Recif lagonaire isole" NA 1 18 9 2013 "13:08" "soleil" "NE" 3 2 NA "MM" "LM" -22.93517 166.95274 "HR" "AP" "Complexe de recif barriere imbrique" "terrasse peu profonde" "Fond lagonaire" "Recif intermediaire" "SA5" -999 4 -999 -999 -999 -999 NA +"AMP" "CS130096" "SVR" "Recif Cimenia" NA "Recif lagonaire isole" NA 1 18 9 2013 "13:29" "soleil" "NE" 3 2 NA "MM" "LM" -22.94666 166.96066 "HR" "AP" "Complexe de recif barriere imbrique" "terrasse peu profonde" "Fond lagonaire" "Recif intermediaire" "SA1" -999 13 -999 -999 -999 -999 NA +"AMP" "CS130097" "SVR" "Recif Cimenia" NA "Recif lagonaire isole" NA 1 18 9 2013 "13:36" "soleil" "NE" 3 2 NA "MM" "LM" -22.95602 166.97128 "HR" "AP" "Complexe de recif barriere imbrique" "terrasse peu profonde" "Fond lagonaire" "Recif intermediaire" "SA5" -999 4 -999 -999 -999 -999 NA +"AMP" "CS130098" "SVR" "Recif Cimenia" NA "Recif lagonaire isole" NA 1 18 9 2013 "14:06" "soleil" "NE" 3 2 NA "MM" "LM" -22.96847 166.97282 "HR" "AP" "Complexe de recif barriere imbrique" "terrasse peu profonde" "Fond lagonaire" "Recif intermediaire" "SA3" -999 8 -999 -999 -999 -999 NA +"AMP" "CS130099" "SVR" "Ilot Koko" NA "Frangeant ilot" NA 1 18 9 2013 "10:02" "soleil" "NE" 2 2 NA "MM" "LM" -22.88428 166.93593 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse profonde" "Fond lagonaire" "Recif intermediaire" "SA3" -999 15 -999 -999 -999 -999 NA +"AMP" "CS130100" "SVR" "Recif Cimenia" NA "Recif lagonaire isole" NA 1 18 9 2013 "11:07" "soleil" "NE" 2 1 NA "MM" "LM" -22.87806 166.95026 "HR" "AP" "Complexe de recif barriere imbrique" "pinacle de recif barriere" "Detritique" "Recif intermediaire" "SA5" -999 4 -999 -999 -999 -999 NA +"AMP" "CS130101" "SVR" "Ilot Koko" NA "Frangeant ilot" NA 1 18 9 2013 "10:12" "soleil" "NE" 2 1 NA "MM" "LM" -22.88118 166.93484 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse profonde" "Fond lagonaire" "Frangeant ilot" "SA5" -999 9 -999 -999 -999 -999 NA +"AMP" "CS130103" "SVR" "Recif Cimenia" NA "Recif lagonaire isole" NA 1 18 9 2013 "08:55" "soleil" "NE" 3 2 NA "MM" "LM" -22.89894 166.97452 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Recif intermediaire" NA -999 6 -999 -999 -999 -999 NA +"AMP" "CS130104" "SVR" "Recif Cimenia" NA "Recif lagonaire isole" NA 1 18 9 2013 "09:35" "soleil" "NE" 3 2 NA "MM" "LM" -22.89978 166.95685 "HR" "AP" "Complexe de recif barriere imbrique" "platier recifal" "Fond lagonaire" "Recif intermediaire" "SA3" -999 8 -999 -999 -999 -999 NA +"AMP" "CS130108" "SVR" "Recif Tiukuru" NA "Pente interne" NA 1 17 9 2013 "15:25" "soleil" "SE" 3 2 NA "MM" "LM" -22.90359 167.05869 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Corail vivant" "Recif barriere interne" "LC4" -999 9 -999 -999 -999 -999 NA +"AMP" "CS130109" "SVR" "Recif Tiukuru" NA "Pente interne" NA 1 17 9 2013 "15:41" "soleil" "SE" 3 2 NA "MM" "LM" -22.91107 167.05853 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Corail vivant" "Recif barriere interne" "LC5" -999 9 -999 -999 -999 -999 NA +"AMP" "CS130110" "SVR" "Recif Ngedembi" NA "Pente interne" NA 1 17 9 2013 "16:31" "soleil" "SE" 1 1 NA "MM" "LM" -22.96225 167.04413 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Recif barriere interne" NA -999 5 -999 -999 -999 -999 NA +"AMP" "CS130111" "SVR" "Recif Ngedembi" NA "Pente interne" NA 1 17 9 2013 "16:25" "soleil" "SE" 1 1 NA "MM" "LM" -22.96651 167.04129 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA1" -999 5 -999 -999 -999 -999 NA +"AMP" "CS130112" "SVR" "Recif Ngedembi" NA "Fond lagonaire" NA 1 17 9 2013 "16:02" "soleil" "SE" 1 1 NA "MM" "LM" -22.96763 167.03604 "HR" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Recif barriere interne" "SA1" -999 16 -999 -999 -999 -999 NA +"AMP" "CS130113" "SVR" "Recif Ngedembi" NA "Fond lagonaire" NA 1 17 9 2013 "15:57" "soleil" "SE" 2 1 NA "MM" "LM" -22.97318 167.03339 "HR" "AP" "Ile lagonaire" "lagon profond" "Corail vivant" "Recif barriere interne" "LC6" -999 3 -999 -999 -999 -999 NA +"AMP" "CS130115" "SVR" "Recif Ndunekunie" NA "Pente interne" NA 1 17 9 2013 "13:52" "soleil" "SE" 3 2 NA "MM" "LM" -22.87234 167.06024 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Recif barriere interne" "SA5" -999 10 -999 -999 -999 -999 NA +"AMP" "CS130116" "SVR" "Recif Ndunekunie" NA "Pente interne" NA 1 17 9 2013 "13:47" "soleil" "SE" 3 2 NA "MM" "LM" -22.86673 167.05983 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA3" -999 10 -999 -999 -999 -999 NA +"AMP" "CS130117" "SVR" "Recif Kuta" NA "Pente interne" NA 1 17 9 2013 "12:45" "soleil" "SE" 3 2 NA "MM" "LM" -22.87032 167.04472 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Corail vivant" "Recif intermediaire" "LC6" -999 4.5 -999 -999 -999 -999 NA +"AMP" "CS130118" "SVR" "Recif Ungeueto" NA "Fond lagonaire" NA 1 17 9 2013 "14:35" "soleil" "SE" 3 2 NA "MM" "LM" -22.88745 167.04332 "HR" "AP" "Ile lagonaire" "lagon profond" "Corail vivant" "Fond lagonaire" "LC2" -999 11 -999 -999 -999 -999 NA +"AMP" "CS130120" "SVR" "Recif Tiukuru" NA "Pente interne" NA 1 17 9 2013 "16:15" "soleil" "SE" 3 2 NA "MM" "LM" -22.92428 167.05716 "HR" "AP" "Complexe de recif barriere externe" "platier recifal ennoye" "Corail vivant" "Recif barriere interne" "LC4" -999 6 -999 -999 -999 -999 NA +"AMP" "CS130123" "SVR" "Recif Tiukuru" NA "Pente externe" NA 1 17 9 2013 "13:24" "soleil" "ESE" 1 1 NA "MM" "LM" -22.87545 167.06969 "HR" "AP" "Complexe de recif barriere externe" "front recifal" "Corail vivant" "Recif barriere externe" "LC4" -999 9 -999 -999 -999 -999 NA +"AMP" "CS130124" "SVR" "Recif Ndunekunie" NA "Pente externe" NA 1 17 9 2013 "13:11" "soleil" "ESE" 1 1 NA "MM" "LM" -22.86677 167.06866 "HR" "AP" "Complexe de recif barriere externe" "front recifal" "Corail vivant" "Recif barriere externe" "LC4" -999 7 -999 -999 -999 -999 NA +"AMP" "CS130125" "SVR" "Recif Tironhua" NA "Pente externe" NA 1 26 9 2013 "08:57" "soleil" "0" 0 0 NA "MM" "LD" -22.82084 167.0313 "HR" "AP" "Complexe de recif barriere externe" "front recifal" "Corail vivant" "Recif barriere externe" "LC1" -999 9 -999 -999 -999 -999 NA +"AMP" "CS130126" "SVR" "Recif Tironhua" NA "Pente externe" NA 1 26 9 2013 "09:00" "soleil" "0" 0 0 NA "MM" "LD" -22.81605 167.03105 "HR" "AP" "Complexe de recif barriere externe" "front recifal" "Corail vivant" "Recif barriere externe" "LC1" -999 8 -999 -999 -999 -999 NA +"AMP" "CS130127" "SVR" "Recif Tironhua" NA "Pente externe" NA 1 26 9 2013 "09:30" "soleil" "0" 0 0 NA "MM" "LD" -22.80914 167.02769 "HR" "AP" "Complexe de recif barriere externe" "front recifal" "Fond lagonaire" "Recif barriere externe" "SA3" -999 14 -999 -999 -999 -999 NA +"AMP" "CS130128" "SVR" "Recif Tironhua" NA "Pente externe" NA 1 26 9 2013 "09:36" "soleil" "0" 0 0 NA "MM" "LD" -22.80578 167.02617 "HR" "AP" "Complexe de recif barriere externe" "front recifal" "Corail vivant" "Recif barriere externe" "LC1" -999 7 -999 -999 -999 -999 NA +"AMP" "CS130129" "SVR" "Recif Tironhua" NA "Pente externe" NA 1 26 9 2013 "10:16" "soleil" "0" 0 0 NA "MM" "LD" -22.78645 167.0201 "HR" "AP" "Complexe de recif barriere externe" "front recifal" "Corail vivant" "Recif barriere externe" "LC2" -999 9 -999 -999 -999 -999 NA +"AMP" "CS130130" "SVR" "Recif Tironhua" NA "Pente externe" NA 1 26 9 2013 "10:25" "soleil" "0" 0 0 NA "MM" "LD" -22.78088 167.01698 "HR" "AP" "Complexe de recif barriere externe" "front recifal" "Corail vivant" "Recif barriere externe" "LC1" -999 10 -999 -999 -999 -999 NA +"AMP" "CS130131" "SVR" "Recif Tironhua" NA "Pente externe" NA 1 26 9 2013 "10:58" "soleil" "0" 0 0 NA "MM" "LD" -22.75265 167.00764 "HR" "AP" "Complexe de recif barriere externe" "front recifal" "Corail vivant" "Recif barriere externe" "LC2" -999 9 -999 -999 -999 -999 NA +"AMP" "CS130132" "SVR" "Recif Kanre" NA "Pente externe" NA 1 26 9 2013 "11:09" "soleil" "0" 0 0 NA "PM" "LD" -22.73453 167.00716 "HR" "AP" "" "" "Corail vivant" "Recif barriere externe" "D3" -999 18 -999 -999 -999 -999 NA +"AMP" "CS130133" "SVR" NA NA "Recif lagonaire isole" NA 1 26 9 2013 "08:43" "soleil" "0" 0 0 NA "MM" "LD" -22.7936 166.97154 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Corail vivant" "Recif intermediaire" "LC2" -999 6 -999 -999 -999 -999 NA +"AMP" "CS130134" "SVR" NA NA "Recif lagonaire isole" NA 1 26 9 2013 "08:53" "soleil" "0" 0 0 NA "MM" "LD" -22.79896 166.97382 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Fond lagonaire" "Recif intermediaire" "SA3" -999 8 -999 -999 -999 -999 NA +"AMP" "CS130135" "SVR" NA NA "Recif lagonaire isole" NA 1 26 9 2013 "09:19" "soleil" "NE" 1 1 NA "MM" "LD" -22.79983 166.98895 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Corail vivant" "Recif intermediaire" "LC2" -999 4 -999 -999 -999 -999 NA +"AMP" "CS130136" "SVR" NA NA "Recif lagonaire isole" NA 1 26 9 2013 "09:24" "soleil" "NE" 1 1 NA "MM" "LD" -22.80016 166.94149 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Fond lagonaire" "Recif intermediaire" "SA5" -999 13 -999 -999 -999 -999 NA +"AMP" "CS130137" "SVR" NA NA "Recif lagonaire isole" NA 1 26 9 2013 "11:11" "soleil" "NE" 2 2 NA "PM" "LD" -22.75415 166.9843 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Corail vivant" "Recif intermediaire" "LC6" -999 9 -999 -999 -999 -999 NA +"AMP" "CS130138" "SVR" "Ilot Totea" NA "Frangeant ilot" NA 1 26 9 2013 "12:14" "soleil" "NE" 2 2 NA "MD" "LD" -22.7166 166.9747 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Corail vivant" "Frangeant ilot" "LC5" -999 5 -999 -999 -999 -999 NA +"AMP" "CS130139" "SVR" "Ilot Totea" NA "Frangeant ilot" NA 1 26 9 2013 "12:10" "soleil" "NE" 2 2 NA "PM" "LD" -22.71794 166.97882 "HR" "AP" "Complexe de massif corallien de lagon" "front recifal" "Fond lagonaire" "Frangeant ilot" "LC5" -999 11 -999 -999 -999 -999 NA +"AMP" "CS130140" "SVR" "Recif Tiendi" NA "Fond lagonaire" NA 1 26 9 2013 "11:36" "soleil" "NE" 2 2 NA "PM" "LD" -22.73199 166.9667 "HR" "AP" "Ile lagonaire" "lagon profond" "Corail vivant" "Fond lagonaire" "LC6" -999 5 -999 -999 -999 -999 NA +"AMP" "CS130141" "SVR" "Recif Ua" NA "Pente interne" NA 1 26 9 2013 "13:25" "soleil" "NE" 2 2 NA "MD" "LD" -22.70333 166.99422 "HR" "AP" "Complexe de recif barriere externe" "platier recifal" "Corail vivant" "Recif intermediaire" "LC2" -999 4 -999 -999 -999 -999 NA +"AMP" "CS130142" "SVR" "Recif Ua" NA "Passe" NA 1 26 9 2013 "13:19" "soleil" "NE" 2 2 NA "MD" "LD" -22.69536 166.99106 "HR" "AP" "Complexe de recif barriere externe" "platier recifal" "Corail vivant" "Recif barriere interne" "LC1" -999 8 -999 -999 -999 -999 NA +"AMP" "CS130143" "SVR" "Recif Tironhua" NA "Pente interne" NA 1 26 9 2013 "10:49" "soleil" "NE" 2 2 NA "MM" "LD" -22.76941 167.00652 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Corail vivant" "Recif barriere interne" "LC5" -999 9 -999 -999 -999 -999 NA +"AMP" "CS130144" "SVR" "Recif Tironhua" NA "Fond lagonaire" NA 1 26 9 2013 "10:16" "soleil" "NE" 2 2 NA "MM" "LD" -22.79521 167.01477 "HR" "AP" "Ile lagonaire" "lagon profond" "Corail vivant" "Fond lagonaire" "LC5" -999 14 -999 -999 -999 -999 NA +"AMP" "CS130145" "SVR" "Recif Tironhua" NA "Pente interne" NA 1 26 9 2013 "09:53" "soleil" "NE" 1 1 NA "MM" "LD" -22.81272 167.02173 "HR" "AP" "Complexe de recif barriere externe" "platier recifal" "Corail vivant" "Recif barriere interne" "LC4" -999 12 -999 -999 -999 -999 NA +"AMP" "CS130146" "SVR" "Recif Tironhua" NA "Pente interne" NA 1 26 9 2013 "09:46" "soleil" "NE" 1 1 NA "MM" "LD" -22.81891 167.02518 "HR" "AP" "Complexe de recif barriere externe" "platier recifal ennoye" "Detritique" "Recif barriere interne" "SA5" -999 10 -999 -999 -999 -999 NA +"AMP" "CS130302" "SVR" "Recif Tiukuru" NA "Pente interne" NA 1 17 9 2013 "16:30" "soleil" "SE" 3 2 NA "MM" "LM" -22.94475 167.05211 "HR" "AP" "Complexe de recif barriere externe" "platier recifal ennoye" "Detritique" "Recif barriere interne" "D1" -999 9 -999 -999 -999 -999 NA +"AMP" "CS130303" "SVR" "Recif Cimenia" NA "Recif lagonaire isole" NA 1 18 9 2013 "15:35" "soleil" "NE" 3 2 NA "MM" "LM" -22.91913 166.95923 "HR" "AP" "Complexe de recif barriere imbrique" "front recifal ou terrasse" "Fond lagonaire" "Recif intermediaire" "SA3" -999 11 -999 -999 -999 -999 NA +"AMP" "CS130304" "SVR" "Recif Cimenia" NA "Fond lagonaire" NA 1 18 9 2013 "16:04" "soleil" "NE" 3 2 NA "MM" "LM" -22.90158 166.96225 "HR" "AP" "Ile lagonaire" "lagon profond" "Corail vivant" "Fond lagonaire" "LC4" -999 13 -999 -999 -999 -999 NA +"AMP" "CS130305" "SVR" "Recif Cimenia" NA "Recif lagonaire isole" NA 1 18 9 2013 "16:36" "soleil" "NE" 3 2 NA "MM" "LM" -22.90357 166.9552 "HR" "AP" "Complexe de recif barriere imbrique" "platier recifal" "Corail vivant" "Recif intermediaire" "LC6" -999 13 -999 -999 -999 -999 NA +"AMP" "CS130306" "SVR" "Recif Nogumatiugi" NA "Pente interne" NA 1 19 9 2013 "13:33" "soleil" "NE" 3 2 NA "MM" "PL" -22.98318 166.94604 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA3" -999 3 -999 -999 -999 -999 NA +"AMP" "CS130307" "SVR" "Recif Nogumatiugi" NA "Pente interne" NA 1 19 9 2013 "14:00" "soleil" "NE" 3 2 NA "MM" "PL" -22.97087 166.93698 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Corail vivant" "Recif barriere interne" "LC5" -999 3 -999 -999 -999 -999 NA +"AMP" "CS130308" "SVR" "Recif Nogumatiugi" NA "Pente interne" NA 1 19 9 2013 "14:28" "soleil" "NE" 3 2 NA "MM" "PL" -22.95669 166.92384 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA3" -999 14 -999 -999 -999 -999 NA +"AMP" "CS130309" "SVR" "Recif Nogumatiugi" NA "Pente interne" NA 1 19 9 2013 "15:07" "soleil" "NE" 3 2 NA "MM" "PL" -22.93594 166.90419 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Recif barriere interne" "SA5" -999 5 -999 -999 -999 -999 NA +"AMP" "CS130310" "SVR" "Recif Umadu" NA "Pente externe" NA 1 19 9 2013 "15:43" "soleil" "NE" 3 2 NA "MM" "PL" -22.9284 166.88683 "HR" "AP" "" "" "Corail vivant" "Recif barriere externe" "LC1" -999 15 -999 -999 -999 -999 NA +"AMP" "CS130311" "SVR" "Recif Nogumatiugi" NA "Pente interne" NA 1 19 9 2013 "16:26" "soleil" "NE" 3 2 NA "MM" "PL" -22.95057 166.91476 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Algueraie" "Recif barriere interne" "MA2" -999 4 -999 -999 -999 -999 NA +"AMP" "CS130313" "SVR" "Recif Garanhua" NA "Pente interne" NA 1 20 9 2013 "09:02" "soleil" "ESE" 3 2 NA "MD" "LD" -22.88627 166.83139 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Corail vivant" "Recif barriere interne" "LC6" -999 5 -999 -999 -999 -999 NA +"AMP" "CS130314" "SVR" "Recif Ie" NA "Passe" NA 1 20 9 2013 "09:35" "soleil" "ESE" 3 2 NA "MD" "LD" -22.86963 166.81775 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Recif barriere interne" NA -999 3 -999 -999 -999 -999 NA +"AMP" "CS130315" "SVR" "Recif Umbei" NA "Pente interne" NA 1 20 9 2013 "10:03" "soleil" "ESE" 3 2 NA "MD" "LD" -22.84989 166.8067 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA3" -999 19 -999 -999 -999 -999 NA +"AMP" "CS130316" "SVR" "Recif Neokouie" NA "Passe" NA 1 20 9 2013 "12:11" "soleil" "ESE" 3 2 NA "MD" "LD" -22.82482 166.78481 "HR" "AP" "Ile lagonaire" "lagon profond" "Corail vivant" "Recif barriere interne" "LC6" -999 14 -999 -999 -999 -999 NA +"AMP" "CS130317" "SVR" "Recif Neokouie" NA "Pente interne" NA 1 20 9 2013 "12:44" "soleil" "SE" 3 2 NA "MD" "LD" -22.80947 166.75493 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA3" -999 4 -999 -999 -999 -999 NA +"AMP" "CS130318" "SVR" "Recif Neokumbi" NA "Pente interne" NA 1 20 9 2013 "14:05" "nuage" "SE" 3 2 NA "MM" "LD" -22.75452 166.70343 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Corail vivant" "Recif barriere interne" "LC2" -999 4 -999 -999 -999 -999 NA +"AMP" "CS130400" "SVR" NA NA "Recif lagonaire isole" NA 1 26 9 2013 "08:14" "soleil" "0" 0 0 NA "MM" "LD" -22.79239 166.92465 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Fond lagonaire" "Recif intermediaire" "SA3" -999 11 -999 -999 -999 -999 NA +"AMP" "CS130401" "SVR" NA NA "Recif lagonaire isole" NA 1 26 9 2013 "08:19" "soleil" "0" 0 0 NA "MM" "LD" -22.78932 166.92557 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Recif intermediaire" "SA3" -999 11 -999 -999 -999 -999 NA +"AMP" "CS130402" "SVR" "Recif Tironhua" NA "Pente interne" NA 1 26 9 2013 "10:24" "soleil" "NE" 2 2 NA "MM" "LD" -22.7917 167.00911 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Recif barriere interne" "SA5" -999 10 -999 -999 -999 -999 NA +"AMP" "CS130403" "SVR" "Recif Tironhua" NA "Fond lagonaire" NA 1 26 9 2013 "10:45" "soleil" "NE" 2 2 NA "MM" "LD" -22.77461 167.00787 "HR" "AP" "Ile lagonaire" "lagon profond" "Corail vivant" "Recif barriere interne" "SA5" -999 11 -999 -999 -999 -999 NA +"AMP" "CS130404" "SVR" NA NA "Recif lagonaire isole" NA 1 26 9 2013 "11:16" "soleil" "NE" 2 2 NA "PM" "LD" -22.74955 166.98654 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Corail vivant" "Recif intermediaire" "LC5" -999 9 -999 -999 -999 -999 NA +"AMP" "CS130405" "SVR" "Recif Kanre" NA "Pente interne" NA 1 26 9 2013 "11:46" "soleil" "NE" 2 2 NA "PM" "LD" -22.72308 167.00041 "HR" "AP" "Complexe de recif barriere externe" "platier recifal ennoye" "Detritique" "Recif barriere interne" NA -999 19 -999 -999 -999 -999 NA +"AMP" "CS130406" "SVR" NA NA "Recif lagonaire isole" NA 1 26 9 2013 "14:02" "soleil" "NE" 2 2 NA "MD" "LD" -22.66814 166.9426 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal ennoye" "Detritique" "Recif intermediaire" NA -999 10 -999 -999 -999 -999 NA +"AMP" "CS130407" "SVR" "Recif Purembi" NA "Recif lagonaire isole" NA 1 26 9 2013 "14:49" "soleil" "NE" 2 2 NA "MD" "LD" -22.64754 166.90668 "HR" "AP" "Complexe de massif corallien de mers interieures" "terrasse peu profonde" "Fond lagonaire" "Recif intermediaire" "SA3" -999 6 -999 -999 -999 -999 NA +"AMP" "CS130900" "SVR" "Recif Tiukuru" NA "Pente externe" NA 1 17 9 2013 "14:00" "soleil" "SE" 2 1 NA "MM" "LM" -22.89355 167.0758 "HR" "AP" "" "" "Corail vivant" "Recif barriere externe" "LC1" -999 10 -999 -999 -999 -999 NA +"AMP" "CS130901" "SVR" "Recif Tiukuru" NA "Pente externe" NA 1 17 9 2013 "14:10" "soleil" "SE" 2 1 NA "MM" "LM" -22.90299 167.06943 "HR" "AP" "" "" "Corail vivant" "Recif barriere externe" "LC1" -999 15 -999 -999 -999 -999 NA +"AMP" "CS130902" "SVR" "Recif Cimenia" NA "Recif lagonaire isole" NA 1 18 9 2013 "09:00" "soleil" "NE" 3 2 NA "MM" "LM" -22.89935 166.97206 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal ennoye" "Corail vivant" "Fond lagonaire" "LC4" -999 5 -999 -999 -999 -999 NA +"AMP" "CS130903" "SVR" "Ilot Koko" NA "Recif lagonaire isole" NA 1 18 9 2013 "10:33" "soleil" "NE" 2 1 NA "MM" "LM" -22.87423 166.93648 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Fond lagonaire" "Recif intermediaire" "SA3" -999 3 -999 -999 -999 -999 NA +"AMP" "CS130904" "SVR" "Ilot Koko" NA "Recif lagonaire isole" NA 1 18 9 2013 "10:40" "soleil" "NE" 2 1 NA "MM" "LM" -22.87031 166.93175 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Fond lagonaire" "Recif intermediaire" "SA3" -999 4 -999 -999 -999 -999 NA +"AMP" "CS130906" "SVR" "Recif Cimenia" NA "Recif lagonaire isole" NA 1 19 9 2013 "11:15" "soleil" "NE" 3 1 NA "MD" "PL" -23.00107 166.98512 "HR" "AP" "Complexe de recif barriere imbrique" "terrasse peu profonde" "Fond lagonaire" "Recif intermediaire" "SA3" -999 3 -999 -999 -999 -999 NA +"AMP" "CS130920" "SVR" "Ilot Kouare" NA "Recif lagonaire isole" NA 1 26 9 2013 "13:41" "soleil" "0" 0 0 NA "MD" "LD" -22.78006 166.81859 "HR" "AP" "Complexe de massif corallien de lagon" "front recifal" "Corail vivant" "Recif intermediaire" "LC1" -999 6 -999 -999 -999 -999 NA +"AMP" "CS130921" "SVR" "Ilot Kouare" NA "Recif lagonaire isole" NA 1 26 9 2013 "13:49" "soleil" "NE" 1 1 NA "MD" "LD" -22.78494 166.8098 "HR" "AP" "Complexe de massif corallien de lagon" "front recifal" "Corail vivant" "Recif intermediaire" "LC6" -999 11 -999 -999 -999 -999 NA +"AMP" "CS130922" "SVR" "Ilot Kouare" NA "Recif lagonaire isole" NA 1 26 9 2013 "14:19" "soleil" "NE" 1 1 NA "MD" "LD" -22.78923 166.78606 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal ennoye" "Corail vivant" "Recif intermediaire" "LC2" -999 5 -999 -999 -999 -999 NA +"AMP" "CS130923" "SVR" "Ilot Kouare" NA "Recif lagonaire isole" NA 1 26 9 2013 "14:25" "soleil" "NE" 1 1 NA "MD" "LD" -22.78653 166.78915 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Corail vivant" "Recif intermediaire" NA -999 16 -999 -999 -999 -999 NA +"AMP" "CS130924" "SVR" "Ilot Uatio" NA "Frangeant ilot" NA 1 26 9 2013 "15:20" "soleil" "NE" 1 1 NA "MD" "LD" -22.71393 166.79517 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Corail vivant" "Frangeant ilot" "LC1" -999 4 -999 -999 -999 -999 NA +"AMP" "CS130925" "SVR" "Ilot Uatio" NA "Frangeant ilot" NA 1 26 9 2013 "15:30" "soleil" "NE" 1 1 NA "MD" "LD" -22.71295 166.80003 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Corail vivant" "Frangeant ilot" "LC1" -999 6 -999 -999 -999 -999 NA +"AMP" "CS130926" "SVR" "Ilot Ua" NA "Frangeant ilot" NA 1 26 9 2013 "15:55" "soleil" "NE" 1 1 NA "MD" "LD" -22.71196 166.80542 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Corail vivant" "Frangeant ilot" "LC4" -999 7 -999 -999 -999 -999 NA +"AMP" "CS130927" "SVR" "Ilot Ua" NA "Frangeant ilot" NA 1 26 9 2013 "16:03" "soleil" "NE" 1 1 NA "MD" "LD" -22.71316 166.81393 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "SA3" -999 10 -999 -999 -999 -999 NA +"AMP" "CS130950" "SVR" "Ilot Ua" NA "Frangeant ilot" NA 1 27 9 2013 "07:20" "soleil" "NE" 3 2 NA "BM" "DQ" -22.70906 166.80682 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Corail vivant" "Frangeant ilot" "LC5" -999 5 -999 -999 -999 -999 NA +"AMP" "CS130951" "SVR" "Ilot Gi" NA "Recif lagonaire isole" NA 1 27 9 2013 "08:10" "soleil" "NE" 3 2 NA "MM" "DQ" -22.72217 166.84755 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse profonde" "Detritique" "Frangeant ilot" "D6" -999 4 -999 -999 -999 -999 NA +"AMP" "CS130952" "SVR" "Ilot Gi" NA "Frangeant ilot" NA 1 27 9 2013 "08:16" "soleil" "NE" 3 2 NA "MM" "DQ" -22.72531 166.8493 "HR" "AP" "Complexe de massif corallien de lagon" "front recifal" "Corail vivant" "Frangeant ilot" "LC5" -999 13 -999 -999 -999 -999 NA +"AMP" "CS130953" "SVR" "Recif Puakue" NA "Recif lagonaire isole" NA 1 27 9 2013 "09:34" "soleil" "NE" 3 2 NA "MM" "DQ" -22.64137 166.78233 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Recif intermediaire" "LC5" -999 9 -999 -999 -999 -999 NA +"AMP" "CS130954" "SVR" "Recif Puakue" NA "Recif lagonaire isole" NA 1 27 9 2013 "09:43" "soleil" "NE" 3 2 NA "MM" "DQ" -22.64212 166.77948 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Corail vivant" "Recif intermediaire" "LC6" -999 13 -999 -999 -999 -999 NA +"AMP" "CS13Z101" "SVR" "Ilot Ndo" NA "Frangeant ilot" NA 1 26 9 2013 "12:43" "soleil" "NE" 2 2 NA "MD" "LD" -22.68689 166.97415 "HR" "AP" "Complexe de massif corallien de lagon" "front recifal" "Corail vivant" "Frangeant ilot" "LC1" -999 5 -999 -999 -999 -999 NA +"AMP" "CS13Z104" "SVR" "Ilot Ndo" NA "Frangeant ilot" NA 1 26 9 2013 "12:47" "soleil" "NE" 2 2 NA "MD" "LD" -22.68627 166.97275 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Corail vivant" "Frangeant ilot" "LC4" -999 5 -999 -999 -999 -999 NA +"AMP" "CS13Z106" "SVR" "Recif Purembi" NA "Recif lagonaire isole" NA 1 26 9 2013 "14:22" "soleil" "NE" 2 2 NA "MD" "LD" -22.6522 166.91838 "HR" "AP" "Complexe de massif corallien de mers interieures" "platier recifal" "Corail vivant" "Recif barriere interne" "LC5" -999 2 -999 -999 -999 -999 NA +"AMP" "CS13Z107" "SVR" NA NA "Recif lagonaire isole" NA 1 26 9 2013 "13:56" "soleil" "NE" 2 2 NA "MD" "LD" -22.66359 166.944 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal ennoye" "Corail vivant" "Recif intermediaire" "LC3" -999 9 -999 -999 -999 -999 NA +"AMP" "CS13Z205" "SVR" "Recif Cimenia" NA "Recif lagonaire isole" NA 1 18 9 2013 "09:30" "soleil" "NE" 3 2 NA "MM" "LM" -22.89991 166.95808 "HR" "AP" "Complexe de recif barriere imbrique" "terrasse peu profonde" "Fond lagonaire" "Recif intermediaire" "SA3" -999 6 -999 -999 -999 -999 NA +"AMP" "CS13Z209" "SVR" "Recif Cimenia" NA "Recif lagonaire isole" NA 1 18 9 2013 "11:50" "soleil" "NE" 1 1 NA "MM" "LM" -22.86373 166.97212 "HR" "AP" "Complexe de recif barriere imbrique" "platier recifal" "Fond lagonaire" "Recif intermediaire" NA -999 3 -999 -999 -999 -999 NA +"AMP" "EN150001" "SVR" "Grand Guilbert" NA "Pente externe" NA 1 27 6 2015 NA NA "ESE" 5 4 NA NA "LM" -18.04173 163.05162 "RN" "AP" "Couronne d atoll" "front recifal" "Corail vivant" "Recif barriere externe" "LC2" 10 12 -999 -999 -999 -999 NA +"AMP" "EN150002" "SVR" "Grand Guilbert" NA "Pente interne" NA 1 27 6 2015 NA NA "ESE" 5 4 NA NA "LM" -18.03964 163.08771 "RN" "AP" "Lagon d atoll" "lagon peu profond d atoll" "Fond lagonaire" "Fond lagonaire" "D7" 10 5 -999 -999 -999 -999 NA +"AMP" "EN150003" "SVR" "Huon" NA "Pente externe" NA 1 30 6 2015 NA NA "E" 6 4 NA NA "LM" -18.06478 162.82668 "RN" "AP" "Couronne d atoll" "front recifal" "Detritique" "Recif barriere externe" "D5" 10 13 -999 -999 -999 -999 NA +"AMP" "EN150006" "SVR" "Huon" NA "Pente interne" NA 1 30 6 2015 NA NA "E" 6 4 NA NA "LM" -18.20941 162.92863 "RN" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Detritique" "Recif barriere interne" "D6" 10 9 -999 -999 -999 -999 NA +"AMP" "EN150007" "SVR" "Huon" NA "Pente interne" NA 1 29 6 2015 NA NA "ESE" 6 4 NA NA "LM" -17.93287 162.89796 "RN" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Fond lagonaire" "Recif barriere interne" "SA1" 10 7 -999 -999 -999 -999 NA +"AMP" "EN150008" "SVR" "Huon" NA "Pente interne" NA 1 30 6 2015 NA NA "E" 6 2 NA NA "LM" -18.04177 162.9574 "RN" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Fond lagonaire" "Recif barriere interne" "SA2" 10 6 -999 -999 -999 -999 NA +"AMP" "EN150009" "SVR" "Merite" NA "Pente externe" NA 1 27 6 2015 NA NA "ESE" 5 4 NA NA "LM" -18.21045 162.98701 "RN" "AP" "Couronne d atoll" "front recifal" "Corail vivant" "Recif barriere externe" "LC3" 10 12 -999 -999 -999 -999 NA +"AMP" "EN150010" "SVR" "Merite" NA "Pente interne" NA 1 27 6 2015 NA NA "ESE" 5 4 NA NA "LM" -18.20043 163.01643 "RN" "AP" "Lagon d atoll" "lagon peu profond d atoll" "Detritique" "Fond lagonaire" "D3" 10 7 -999 -999 -999 -999 NA +"AMP" "EN150011" "SVR" "Pelotas" NA "Pente externe" NA 1 25 6 2015 NA NA "SE" 4 2 NA NA "LM" -18.58873 163.19017 "RN" "AP" "Couronne d atoll" "front recifal" "Corail vivant" "Recif barriere externe" "LC1" 10 12 -999 -999 -999 -999 NA +"AMP" "EN150012" "SVR" "Pelotas" NA "Pente externe" NA 1 25 6 2015 NA NA "SE" 4 2 NA NA "LM" -18.5427 163.22704 "RN" "AP" "Couronne d atoll" "front recifal" "Corail vivant" "Recif barriere externe" "LC3" 10 4 -999 -999 -999 -999 NA +"AMP" "EN150013" "SVR" "Pelotas" NA "Pente interne" NA 1 25 6 2015 NA NA "SE" 5 4 NA NA "LM" -18.57368 163.24208 "RN" "AP" "Lagon d atoll" "lagon peu profond d atoll" "Detritique" "Recif barriere interne" "D1" 10 6 -999 -999 -999 -999 NA +"AMP" "EN150014" "SVR" "Petit Guilbert" NA "Pente externe" NA 1 27 6 2015 NA NA "ESE" 5 4 NA NA "LM" -18.00208 163.11093 "RN" "AP" "Couronne d atoll" "platier recifal" "Corail vivant" "Recif barriere interne" "LC1" 10 5 -999 -999 -999 -999 NA +"AMP" "EN150016" "SVR" "Surprise" NA "Pente interne" NA 1 24 6 2015 NA NA "SE" 4 4 NA "MM" "LM" -18.4878 163.0986 "RN" "AP" "Couronne d atoll" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA3" 10 8.5 -999 -999 -999 -999 NA +"AMP" "EN150017" "SVR" "Surprise" NA "Pente interne" NA 1 24 6 2015 NA NA "SE" 4 4 NA "PM" "LM" -18.43734 163.22151 "RN" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Fond lagonaire" "Recif barriere interne" "SA3" 10 6 -999 -999 -999 -999 NA +"AMP" "EN150018" "SVR" "Surprise" NA "Pente interne" NA 1 24 6 2015 NA NA "SE" 4 4 NA "MD" "LM" -18.37336 163.177 "RN" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Fond lagonaire" "Recif barriere interne" NA 10 7.5 -999 -999 -999 -999 NA +"AMP" "EN150020" "SVR" "Surprise" NA "Pente externe" NA 1 25 6 2015 NA NA "SE" 4 4 NA NA "LM" -18.49749 163.10439 "RN" "AP" "Couronne d atoll" "front recifal" "Corail vivant" "Recif barriere externe" "LC1" 10 19 -999 -999 -999 -999 NA +"AMP" "EN150022" "SVR" "Surprise" NA "Pente externe" NA 1 25 6 2015 NA NA "SE" 4 4 NA NA "LM" -18.49455 163.09665 "RN" "AP" "Couronne d atoll" "front recifal" "Corail vivant" "Recif barriere externe" "LC1" 10 19 -999 -999 -999 -999 NA +"AMP" "EN150023" "SVR" "Surprise" NA "Pente externe" NA 1 25 6 2015 NA NA "SE" 3 2 NA NA "LM" -18.4719 163.03679 "RN" "AP" "Couronne d atoll" "front recifal" "Corail vivant" "Recif barriere externe" NA 10 9 -999 -999 -999 -999 NA +"AMP" "EN150027" "SVR" "Surprise" NA "Pente externe" NA 1 26 6 2015 NA NA "E" 3 2 NA NA "LM" -18.34893 162.96819 "RN" "AP" "Couronne d atoll" "front recifal" "Corail vivant" "Recif barriere externe" "LC1" 10 6 -999 -999 -999 -999 NA +"AMP" "EN150028" "SVR" "Surprise" NA "Pente interne" NA 1 26 6 2015 NA NA "SE" 4 4 NA NA "LM" -18.29988 163.01508 "RN" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Corail vivant" "Recif barriere interne" "LC1" 10 10.5 -999 -999 -999 -999 NA +"AMP" "EN150029" "SVR" "Portail" NA "Patate isolee" NA 1 1 7 2015 NA NA "SE" 4 4 NA NA "LM" -18.47939 162.85538 "RN" "AP" "Banc lagonaire" "terrasse lagonaire peu profonde a champ de constructions coralliennes" "Fond lagonaire" "Recif barriere interne" "SA3" 10 11 -999 -999 -999 -999 NA +"AMP" "EN150030" "SVR" "Portail" NA "Pente externe" NA 1 1 7 2015 NA NA "SE" 4 4 NA NA "LM" -18.45867 162.83791 "RN" "AP" "Banc de recif barriere" "front recifal" "Corail vivant" "Recif barriere externe" "LC1" 10 6 -999 -999 -999 -999 NA +"AMP" "EN150032" "SVR" "Pelotas" NA "Pente externe" NA 1 25 6 2015 NA NA "SE" 4 2 NA NA "LM" -18.57678 163.20815 "RN" "AP" "Couronne d atoll" "front recifal" "Corail vivant" "Recif barriere externe" "LC1" 10 11 -999 -999 -999 -999 NA +"AMP" "EN150033" "SVR" "Merite" NA "Pente externe" NA 1 27 6 2015 NA NA "ESE" 5 4 NA NA "LM" -18.1935 162.99567 "RN" "AP" "Couronne d atoll" "front recifal" "Corail vivant" "Recif barriere externe" "LC5" 10 13 -999 -999 -999 -999 NA +"AMP" "EN150040" "SVR" "Grand Guilbert" NA "Pente interne" NA 1 27 6 2015 NA NA "ESE" 5 4 NA NA "LM" -18.02374 163.0598 "RN" "AP" "Couronne d atoll" "front recifal" "Detritique" "Recif barriere interne" "D3" 10 18.5 -999 -999 -999 -999 NA +"AMP" "EN150041" "SVR" "Merite" NA "Pente interne" NA 1 27 6 2015 NA NA "ESE" 5 4 NA NA "LM" -18.19946 163.01548 "RN" "AP" "Lagon d atoll" "lagon peu profond d atoll" "Detritique" "Fond lagonaire" "D7" 10 4.5 -999 -999 -999 -999 NA +"AMP" "EN150045" "SVR" "Pelotas" NA "Pente interne" NA 1 25 6 2015 NA NA "SE" 4 4 NA NA "LM" -18.58045 163.20651 "RN" "AP" "Couronne d atoll" "front recifal" "Corail vivant" "Recif barriere interne" "D7" 10 9 -999 -999 -999 -999 NA +"AMP" "EN150046" "SVR" "Pelotas" NA "Pente interne" NA 1 25 6 2015 NA NA "SE" 5 4 NA NA "LM" -18.60647 163.19853 "RN" "AP" "Lagon d atoll" "lagon peu profond d atoll" "Detritique" "Recif barriere interne" "D5" 10 9 -999 -999 -999 -999 NA +"AMP" "EN150049" "SVR" "Pelotas" NA "Pente interne" NA 1 25 6 2015 NA NA "SE" 5 4 NA NA "LM" -18.57467 163.24141 "RN" "AP" "Lagon d atoll" "lagon peu profond d atoll" "Fond lagonaire" "Recif barriere interne" "SA3" 10 6 -999 -999 -999 -999 NA +"AMP" "EN150054" "SVR" "Portail" NA "Patate isolee" NA 1 1 7 2015 NA NA "SE" 4 4 NA NA "LM" -18.49428 162.85976 "RN" "AP" "Banc lagonaire" "terrasse lagonaire peu profonde a champ de constructions coralliennes" "Fond lagonaire" "Recif barriere interne" "D7" 10 9 -999 -999 -999 -999 NA +"AMP" "EN150060" "SVR" "Portail" NA "Pente externe" NA 1 1 7 2015 NA NA "SE" 4 4 NA NA "LM" -18.47551 162.84146 "RN" "AP" "Banc de recif barriere" "front recifal" "Corail vivant" "Recif barriere externe" "LC1" 10 8 -999 -999 -999 -999 NA +"AMP" "EN150061" "SVR" "Portail" NA "Patate isolee" NA 1 1 7 2015 NA NA "SE" 4 4 NA NA "LM" -18.48158 162.85593 "RN" "AP" "Banc lagonaire" "terrasse lagonaire peu profonde a champ de constructions coralliennes" "Detritique" "Recif barriere interne" "D7" 10 11 -999 -999 -999 -999 NA +"AMP" "EN150062" "SVR" "Petit Guilbert" NA "Pente interne" NA 1 27 6 2015 NA NA "ESE" 5 4 NA NA "LM" -18.0092 163.11536 "RN" "AP" "Lagon d atoll" "lagon peu profond d atoll" "Fond lagonaire" "Fond lagonaire" "SA3" 10 5.5 -999 -999 -999 -999 NA +"AMP" "EN150064" "SVR" "Grand Guilbert" NA "Pente interne" NA 1 27 6 2015 NA NA "ESE" 5 4 NA NA "LM" -18.02882 163.08875 "RN" "AP" "Lagon d atoll" "lagon peu profond d atoll" "Detritique" "Fond lagonaire" "D5" 10 3 -999 -999 -999 -999 NA +"AMP" "EN150065" "SVR" "Grand Guilbert" NA "Pente interne" NA 1 27 6 2015 NA NA "ESE" 5 4 NA NA "LM" -18.02869 163.08463 "RN" "AP" "Lagon d atoll" "lagon peu profond d atoll" "Fond lagonaire" "Fond lagonaire" "SA3" 10 9 -999 -999 -999 -999 NA +"AMP" "EN150066" "SVR" "Merite" NA "Pente externe" NA 1 27 6 2015 NA NA "ESE" 5 4 NA NA "LM" -18.19646 162.99324 "RN" "AP" "Couronne d atoll" "front recifal" "Corail vivant" "Recif barriere externe" "LC5" 10 14 -999 -999 -999 -999 NA +"AMP" "EN150067" "SVR" "Merite" NA "Pente externe" NA 1 27 6 2015 NA NA "ESE" 5 4 NA NA "LM" -18.2137 162.98755 "RN" "AP" "Couronne d atoll" "front recifal" "Detritique" "Recif barriere externe" "D5" 10 13 -999 -999 -999 -999 NA +"AMP" "EN150068" "SVR" "Merite" NA "Pente interne" NA 1 27 6 2015 NA NA "ESE" 5 4 NA NA "LM" -18.21325 163.00253 "RN" "AP" "Lagon d atoll" "lagon peu profond d atoll" "Fond lagonaire" "Fond lagonaire" "SA3" 10 9 -999 -999 -999 -999 NA +"AMP" "EN150070" "SVR" "Merite" NA "Pente interne" NA 1 27 6 2015 NA NA "ESE" 5 4 NA NA "LM" -18.21522 163.006 "RN" "AP" "Lagon d atoll" "lagon peu profond d atoll" "Fond lagonaire" "Recif barriere interne" NA 10 4.5 -999 -999 -999 -999 NA +"AMP" "EN150071" "SVR" "Surprise" NA "Pente interne" NA 1 26 6 2015 NA NA "SE" 4 4 NA NA "LM" -18.29574 163.01776 "RN" "AP" "Couronne d atoll" "platier recifal" "Corail vivant" "Recif barriere interne" "LC5" 10 7 -999 -999 -999 -999 NA +"AMP" "EN150072" "SVR" "Surprise" NA "Pente interne" NA 1 24 6 2015 NA NA "SE" 4 4 NA "MM" "LM" -18.30608 163.07198 "RN" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Fond lagonaire" "Recif barriere interne" "SA3" 10 12.5 -999 -999 -999 -999 NA +"AMP" "EN150076" "SVR" "Surprise" NA "Pente interne" NA 1 24 6 2015 NA NA "SE" 4 4 NA "MD" "LM" -18.34162 163.11833 "RN" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Detritique" "Recif barriere interne" "D7" 10 9 -999 -999 -999 -999 NA +"AMP" "EN150077" "SVR" "Surprise" NA "Pente interne" NA 1 24 6 2015 NA NA "SE" 4 4 NA "MD" "LM" -18.37566 163.1825 "RN" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Fond lagonaire" "Recif barriere interne" "SA3" 10 11 -999 -999 -999 -999 NA +"AMP" "EN150079" "SVR" "Surprise" NA "Pente interne" NA 1 24 6 2015 NA NA "SE" 4 4 NA "MD" "LM" -18.4012 163.20523 "RN" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Fond lagonaire" "Recif barriere interne" "SA1" 10 9 -999 -999 -999 -999 NA +"AMP" "EN150080" "SVR" "Surprise" NA "Pente interne" NA 1 24 6 2015 NA NA "SE" 4 4 NA "MD" "LM" -18.40287 163.20355 "RN" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Fond lagonaire" "Recif barriere interne" "SA1" 10 11 -999 -999 -999 -999 NA +"AMP" "EN150081" "SVR" "Surprise" NA "Pente interne" NA 1 24 6 2015 NA NA "SE" 4 4 NA "PM" "LM" -18.43822 163.22243 "RN" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Detritique" "Recif barriere interne" "D7" 10 9 -999 -999 -999 -999 NA +"AMP" "EN150084" "SVR" "Surprise" NA "Pente interne" NA 1 24 6 2015 NA NA "SE" 4 4 NA "PM" "LM" -18.48931 163.22075 "RN" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Detritique" "Recif barriere interne" "D7" 10 6 -999 -999 -999 -999 NA +"AMP" "EN150087" "SVR" "Surprise" NA "Pente interne" NA 1 24 6 2015 NA NA "SE" 4 4 NA "MM" "LM" -18.51038 163.19341 "RN" "AP" "Couronne d atoll" "platier recifal ennoye" "Corail vivant" "Recif barriere interne" "LC5" 10 12 -999 -999 -999 -999 NA +"AMP" "EN150090" "SVR" "Surprise" NA "Pente interne" NA 1 24 6 2015 NA NA "SE" 4 4 NA "MM" "LM" -18.49532 163.1192 "RN" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Corail vivant" "Recif barriere interne" "D7" 10 10 -999 -999 -999 -999 NA +"AMP" "EN150091" "SVR" "Surprise" NA "Pente interne" NA 1 24 6 2015 NA NA "SE" 4 4 NA "MM" "LM" -18.4877 163.0986 "RN" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Fond lagonaire" "Recif barriere interne" "SA5" 10 9.5 -999 -999 -999 -999 NA +"AMP" "EN150093" "SVR" "Surprise" NA "Pente externe" NA 1 26 6 2015 NA NA "E" 3 2 NA NA "LM" -18.3163 162.96814 "RN" "AP" "Couronne d atoll" "front recifal" "Corail vivant" "Recif barriere externe" "LC1" 10 9 -999 -999 -999 -999 NA +"AMP" "EN150094" "SVR" "Surprise" NA "Pente externe" NA 1 25 6 2015 NA NA "SE" 4 2 NA NA "LM" -18.47719 163.04836 "RN" "AP" "Couronne d atoll" "front recifal" "Corail vivant" "Recif barriere externe" "LC1" 10 10 -999 -999 -999 -999 NA +"AMP" "EN150099" "SVR" "Surprise" NA "Pente interne" NA 1 26 6 2015 NA NA "SE" 4 4 NA NA "LM" -18.29022 163.04457 "RN" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Fond lagonaire" "Recif barriere interne" "SA3" 10 9 -999 -999 -999 -999 NA +"AMP" "EN150100" "SVR" "Surprise" NA "Pente interne" NA 1 26 6 2015 NA NA "SE" 4 4 NA NA "LM" -18.32122 162.9772 "RN" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Corail vivant" "Recif barriere interne" "LC2" 10 12 -999 -999 -999 -999 NA +"AMP" "EN150101" "SVR" "Surprise" NA "Pente interne" NA 1 26 6 2015 NA NA "SE" 4 4 NA NA "LM" -18.31637 162.98022 "RN" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Corail vivant" "Recif barriere interne" "LC3" 10 12 -999 -999 -999 -999 NA +"AMP" "EN150103" "SVR" "Huon" NA "Pente interne" NA 1 30 6 2015 NA NA "E" 6 4 NA NA "LM" -18.21156 162.92578 "RN" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Fond lagonaire" "Recif barriere interne" "SA3" 10 10 -999 -999 -999 -999 NA +"AMP" "EN150105" "SVR" "Huon" NA "Pente externe" NA 1 30 6 2015 NA NA "E" 6 4 NA NA "LM" -18.20408 162.84517 "RN" "AP" "Couronne d atoll" "front recifal" "Corail vivant" "Recif barriere externe" "LC1" 10 7 -999 -999 -999 -999 NA +"AMP" "EN150108" "SVR" "Huon" NA "Pente externe" NA 1 30 6 2015 NA NA "E" 6 4 NA NA "LM" -18.19315 162.84082 "RN" "AP" "Couronne d atoll" "front recifal" "Corail vivant" "Recif barriere externe" "LC1" 10 10 -999 -999 -999 -999 NA +"AMP" "EN150115" "SVR" "Huon" NA "Pente externe" NA 1 30 6 2015 NA NA "E" 6 4 NA NA "LM" -18.08949 162.81807 "RN" "AP" "Couronne d atoll" "front recifal" "Corail vivant" "Recif barriere externe" "LC1" 10 9 -999 -999 -999 -999 NA +"AMP" "EN150116" "SVR" "Huon" NA "Pente externe" NA 1 30 6 2015 NA NA "E" 6 4 NA NA "LM" -18.0922 162.81583 "RN" "AP" "Couronne d atoll" "front recifal" "Corail vivant" "Recif barriere externe" "LC1" 10 5 -999 -999 -999 -999 NA +"AMP" "EN150119" "SVR" "Huon" NA "Pente externe" NA 1 29 6 2015 NA NA "ESE" 6 4 NA NA "LM" -17.94511 162.89265 "RN" "AP" "Couronne d atoll" "passe" "Corail vivant" "Recif barriere externe" "LC1" 10 6 -999 -999 -999 -999 NA +"AMP" "EN150120" "SVR" "Huon" NA "Pente interne" NA 1 29 6 2015 NA NA "ESE" 6 4 NA NA "LM" -17.93004 162.89783 "RN" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Detritique" "Recif barriere interne" "D1" 10 9 -999 -999 -999 -999 NA +"AMP" "EN150121" "SVR" "Huon" NA "Pente externe" NA 1 29 6 2015 NA NA "ESE" 6 4 NA NA "LM" -17.97514 162.89491 "RN" "AP" "Couronne d atoll" "front recifal" "Corail vivant" "Recif barriere externe" "LC1" 10 10 -999 -999 -999 -999 NA +"AMP" "EN150122" "SVR" "Huon" NA "Pente interne" NA 1 29 6 2015 NA NA "ESE" 6 4 NA NA "LM" -17.96907 162.92258 "RN" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Fond lagonaire" "Recif barriere interne" "SA3" 10 3.5 -999 -999 -999 -999 NA +"AMP" "EN150123" "SVR" "Huon" NA "Pente interne" NA 1 29 6 2015 NA NA "ESE" 6 4 NA NA "LM" -17.96503 162.92261 "RN" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Fond lagonaire" "Recif barriere interne" "SA1" 10 5 -999 -999 -999 -999 NA +"AMP" "EN150125" "SVR" "Huon" NA "Pente interne" NA 1 29 6 2015 NA NA "ESE" 6 4 NA NA "LM" -17.99705 162.94583 "RN" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Detritique" "Recif barriere interne" "SA5" 10 7 -999 -999 -999 -999 NA +"AMP" "EN150126" "SVR" "Huon" NA "Pente interne" NA 1 29 6 2015 NA NA "ESE" 6 4 NA NA "LM" -17.99803 162.94577 "RN" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Fond lagonaire" "Recif barriere interne" "SA1" 10 10 -999 -999 -999 -999 NA +"AMP" "EN150129" "SVR" "Huon" NA "Pente interne" NA 1 28 6 2015 NA NA "ESE" 5 4 NA NA "LM" -18.07985 162.946 "RN" "AP" "Couronne d atoll" "platier recifal" "Detritique" "Recif barriere interne" NA 10 9 -999 -999 -999 -999 NA +"AMP" "EN150131" "SVR" "Huon" NA "Pente interne" NA 1 28 6 2015 NA NA "ESE" 5 4 NA NA "LM" -18.07431 162.94341 "RN" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Fond lagonaire" "Recif barriere interne" "SA3" 10 10 -999 -999 -999 -999 NA +"AMP" "EN150132" "SVR" "Huon" NA "Pente interne" NA 1 28 6 2015 NA NA "ESE" 5 4 NA NA "LM" -18.11081 162.93353 "RN" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Fond lagonaire" "Recif barriere interne" "SA3" 10 4 -999 -999 -999 -999 NA +"AMP" "EN150133" "SVR" "Huon" NA "Pente interne" NA 1 28 6 2015 NA NA "ESE" 5 4 NA NA "LM" -18.13977 162.92653 "RN" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Detritique" "Recif barriere interne" NA 10 11 -999 -999 -999 -999 NA +"AMP" "EN150135" "SVR" "Huon" NA "Pente interne" NA 1 28 6 2015 NA NA "ESE" 5 4 NA NA "LM" -18.1387 162.9278 "RN" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Detritique" "Recif barriere interne" NA 10 7 -999 -999 -999 -999 NA +"AMP" "EN150136" "SVR" "Huon" NA "Patate isolee" NA 1 28 6 2015 NA NA "ESE" 5 4 NA NA "LM" -18.15353 162.9129 "RN" "AP" "Lagon d atoll" "lagon profond" "Detritique" "Recif isole" NA 10 9 -999 -999 -999 -999 NA +"AMP" "EN150137" "SVR" "Huon" NA "Patate isolee" NA 1 28 6 2015 NA NA "ESE" 5 4 NA NA "LM" -18.15233 162.89328 "RN" "AP" "Lagon d atoll" "lagon profond" "Corail vivant" "Recif isole" "LC1" 10 6 -999 -999 -999 -999 NA +"AMP" "EN150138" "SVR" "Huon" NA "Patate isolee" NA 1 28 6 2015 NA NA "ESE" 5 4 NA NA "LM" -18.15065 162.90456 "RN" "AP" "Lagon d atoll" "lagon profond" "Corail vivant" "Recif isole" "LC1" 10 6 -999 -999 -999 -999 NA +"AMP" "EN150139" "SVR" "Huon" NA "Patate isolee" NA 1 28 6 2015 NA NA "ESE" 5 4 NA NA "LM" -18.13332 162.88388 "RN" "AP" "Lagon d atoll" "lagon profond" "Corail vivant" "Recif isole" "LC3" 10 3 -999 -999 -999 -999 NA +"AMP" "EN150140" "SVR" "Huon" NA "Patate isolee" NA 1 28 6 2015 NA NA "ESE" 5 4 NA NA "LM" -18.11894 162.88625 "RN" "AP" "Lagon d atoll" "lagon profond" "Corail vivant" "Recif isole" "LC2" 10 3 -999 -999 -999 -999 NA +"AMP" "EN150141" "SVR" "Huon" NA "Patate isolee" NA 1 28 6 2015 NA NA "ESE" 5 4 NA NA "LM" -18.14799 162.89651 "RN" "AP" "Lagon d atoll" "lagon profond" "Corail vivant" "Recif isole" NA 10 2 -999 -999 -999 -999 NA +"AMP" "EN150142" "SVR" "Huon" NA "Pente interne" NA 1 28 6 2015 NA NA "ESE" 5 4 NA NA "LM" -18.08888 162.93848 "RN" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Fond lagonaire" "Recif barriere interne" "SA5" 10 10 -999 -999 -999 -999 NA +"AMP" "EN150144" "SVR" "Huon" NA "Pente interne" NA 1 28 6 2015 NA NA "ESE" 5 4 NA NA "LM" -18.10803 162.93369 "RN" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Detritique" "Recif barriere interne" NA 10 9 -999 -999 -999 -999 NA +"AMP" "EN150145" "SVR" "Huon" NA "Pente interne" NA 1 28 6 2015 NA NA "ESE" 5 4 NA NA "LM" -18.08324 162.94057 "RN" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Detritique" "Recif barriere interne" NA 10 9 -999 -999 -999 -999 NA +"AMP" "EN150150" "SVR" "Surprise" NA "Pente interne" NA 1 24 6 2015 NA NA "SE" 4 4 NA "MD" "LM" -18.3385 163.11829 "RN" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Detritique" "Recif barriere interne" NA 10 4 -999 -999 -999 -999 NA +"AMP" "EN150151" "SVR" "Surprise" NA "Pente externe" NA 1 26 6 2015 NA NA "E" 3 2 NA NA "LM" -18.28941 163.00766 "RN" "AP" "Couronne d atoll" "front recifal" "Fond lagonaire" "Recif barriere externe" "LC5" 10 14 -999 -999 -999 -999 NA +"AMP" "EN150152" "SVR" "Grand Guilbert" NA "Pente interne" NA 1 27 6 2015 NA NA "ESE" 5 4 NA NA "LM" -18.03887 163.08795 "RN" "AP" "Lagon d atoll" "lagon peu profond d atoll" "Fond lagonaire" "Fond lagonaire" "D6" 10 5 -999 -999 -999 -999 NA +"AMP" "EN150153" "SVR" "Petit Guilbert" NA "Pente interne" NA 1 27 6 2015 NA NA "ESE" 5 4 NA NA "LM" -18.00892 163.1189 "RN" "AP" "Lagon d atoll" "lagon peu profond d atoll" "Fond lagonaire" "Fond lagonaire" "SA3" 10 4.5 -999 -999 -999 -999 NA +"AMP" "EN150154" "SVR" "Grand Guilbert" NA "Pente externe" NA 1 27 6 2015 NA NA "ESE" 5 4 NA NA "LM" -18.04511 163.05212 "RN" "AP" "Couronne d atoll" "front recifal" "Corail vivant" "Recif barriere externe" "D5" 10 16 -999 -999 -999 -999 NA +"AMP" "EN150155" "SVR" "Petit Guilbert" NA "Pente externe" NA 1 27 6 2015 NA NA "ESE" 5 4 NA NA "LM" -17.99862 163.11093 "RN" "AP" "Couronne d atoll" "front recifal" "Corail vivant" "Recif barriere externe" "LC1" 10 4 -999 -999 -999 -999 NA +"AMP" "EN150200" "SVR" "Pelotas" NA "Pente interne" NA 1 25 6 2015 NA NA "SE" 5 4 NA NA "LM" -18.60323 163.20039 "RN" "AP" "Lagon d atoll" "lagon peu profond d atoll" "Corail vivant" "Recif barriere interne" "LC1" 10 11 -999 -999 -999 -999 NA +"AMP" "EN150202" "SVR" "Surprise" NA "Pente interne" NA 1 26 6 2015 NA NA "SE" 4 4 NA NA "LM" -18.29022 163.04761 "RN" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Corail vivant" "Recif barriere interne" "LC3" 10 9 -999 -999 -999 -999 NA +"AMP" "EN150250" "SVR" "Surprise" NA "Pente externe" NA 1 26 6 2015 NA NA "E" 3 2 NA NA "LM" -18.34423 162.96448 "RN" "AP" "Couronne d atoll" "front recifal" "Corail vivant" "Recif barriere externe" "LC1" 10 9 -999 -999 -999 -999 NA +"AMP" "EN150251" "SVR" "Surprise" NA "Pente externe" NA 1 26 6 2015 NA NA "E" 3 2 NA NA "LM" -18.28652 163.01158 "RN" "AP" "Couronne d atoll" "front recifal" "Corail vivant" "Recif barriere externe" "LC1" 10 11 -999 -999 -999 -999 NA +"AMP" "EN150252" "SVR" "Surprise" NA "Pente externe" NA 1 26 6 2015 NA NA "NE" 3 4 NA NA "LM" -18.27775 163.04919 "RN" "AP" "Couronne d atoll" "front recifal" "Corail vivant" "Recif barriere externe" "LC1" 10 10 -999 -999 -999 -999 NA +"AMP" "EN150253" "SVR" "Grand Guilbert" NA "Pente interne" NA 1 27 6 2015 NA NA "ESE" 5 4 NA NA "LM" -18.02284 163.06075 "RN" "AP" "Couronne d atoll" "platier recifal" "Detritique" "Recif barriere interne" "D7" 10 14 -999 -999 -999 -999 NA +"AMP" "EN150300" "SVR" "Huon" NA "Patate isolee" NA 1 28 6 2015 NA NA "ESE" 5 4 NA NA "LM" -18.11704 162.8821 "RN" "AP" "Lagon d atoll" "lagon profond" "Detritique" "Recif isole" NA 10 3.5 -999 -999 -999 -999 NA +"AMP" "EN150301" "SVR" "Huon" NA "Pente externe" NA 1 29 6 2015 NA NA "ESE" 6 4 NA NA "LM" -17.96929 162.89357 "RN" "AP" "Couronne d atoll" "front recifal" "Corail vivant" "Recif barriere externe" "LC1" 10 11 -999 -999 -999 -999 NA +"AMP" "EN150302" "SVR" "Huon" NA "Pente externe" NA 1 29 6 2015 NA NA "ESE" 6 4 NA NA "LM" -17.93559 162.89218 "RN" "AP" "Couronne d atoll" "front recifal" "Corail vivant" "Recif barriere externe" "LC1" 10 7 -999 -999 -999 -999 NA +"AMP" "EN150303" "SVR" "Huon" NA "Pente externe" NA 1 29 6 2015 NA NA "ESE" 6 4 NA NA "LM" -17.92821 162.89418 "RN" "AP" "Couronne d atoll" "front recifal" "Corail vivant" "Recif barriere externe" "LC3" 10 16 -999 -999 -999 -999 NA +"AMP" "EN150305" "SVR" "Huon" NA "Pente interne" NA 1 30 6 2015 NA NA "E" 6 4 NA NA "LM" -18.21522 162.92276 "RN" "AP" "Lagon d atoll" "pente interne (de lagon d atoll)" "Fond lagonaire" "Recif barriere interne" "SA3" 10 7 -999 -999 -999 -999 NA +"AMP" "EN150307" "SVR" "Huon" NA "Pente externe" NA 1 30 6 2015 NA NA "E" 6 4 NA NA "LM" -18.12802 162.81447 "RN" "AP" "Couronne d atoll" "front recifal" "Corail vivant" "Recif barriere externe" "LC1" 10 12 -999 -999 -999 -999 NA +"AMP" "EN150308" "SVR" "Huon" NA "Pente externe" NA 1 30 6 2015 NA NA "E" 6 4 NA NA "LM" -18.12611 162.81584 "RN" "AP" "Couronne d atoll" "front recifal" "Detritique" "Recif barriere externe" "D3" 10 9 -999 -999 -999 -999 NA +"AMP" "EN150309" "SVR" "Huon" NA "Pente externe" NA 1 30 6 2015 NA NA "E" 6 4 NA NA "LM" -18.16575 162.8248 "RN" "AP" "Couronne d atoll" "front recifal" "Corail vivant" "Recif barriere externe" "LC1" 10 7 -999 -999 -999 -999 NA +"AMP" "EN150310" "SVR" "Portail" NA "Patate isolee" NA 1 1 7 2015 NA NA "SE" 4 4 NA NA "LM" -18.49346 162.86002 "RN" "AP" "Banc lagonaire" "terrasse lagonaire peu profonde a champ de constructions coralliennes" "Fond lagonaire" "Recif barriere interne" "SA1" 10 9.5 -999 -999 -999 -999 NA +"AMP" "EN150311" "SVR" "Portail" NA "Patate isolee" NA 1 1 7 2015 NA NA "SE" 4 4 NA NA "LM" -18.46909 162.84698 "RN" "AP" "Banc lagonaire" "terrasse lagonaire peu profonde a champ de constructions coralliennes" "Detritique" "Recif barriere interne" "D7" 10 12 -999 -999 -999 -999 NA +"AMP" "EN150312" "SVR" "Portail" NA "Patate isolee" NA 1 1 7 2015 NA NA "SE" 4 4 NA NA "LM" -18.47182 162.84607 "RN" "AP" "Banc de recif barriere" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA3" 10 6.5 -999 -999 -999 -999 NA +"AMP" "EN150313" "SVR" "Portail" NA "Patate isolee" NA 1 1 7 2015 NA NA "SE" 4 4 NA NA "LM" -18.4673 162.84436 "RN" "AP" "Banc lagonaire" "terrasse lagonaire peu profonde a champ de constructions coralliennes" "Fond lagonaire" "Recif barriere interne" "SA3" 10 6 -999 -999 -999 -999 NA +"AMP" "EN150350" "SVR" "Huon" NA "Pente externe" NA 1 30 6 2015 NA NA "E" 6 4 NA NA "LM" -18.06839 162.82437 "RN" "AP" "Couronne d atoll" "front recifal" "Corail vivant" "Recif barriere externe" "LC1" 10 8 -999 -999 -999 -999 NA +"AMP" "EN150351" "SVR" "Huon" NA "Pente externe" NA 1 30 6 2015 NA NA "E" 6 4 NA NA "LM" -18.20013 162.84283 "RN" "AP" "Couronne d atoll" "front recifal" "Corail vivant" "Recif barriere externe" "LC1" 10 6 -999 -999 -999 -999 NA +"AMP" "EN150352" "SVR" "Huon" NA "Pente externe" NA 1 30 6 2015 NA NA "E" 6 4 NA NA "LM" -18.18924 162.83954 "RN" "AP" "Couronne d atoll" "front recifal" "Corail vivant" "Recif barriere externe" "LC1" 10 6 -999 -999 -999 -999 NA +"AMP" "EN150400" "SVR" "Portail" NA "Pente externe" NA 1 1 7 2015 NA NA "SE" 4 4 NA NA "LM" -18.46245 162.83798 "RN" "AP" "Banc de recif barriere" "front recifal" "Corail vivant" "Recif barriere externe" "LC1" 10 8 -999 -999 -999 -999 NA +"AMP" "GN130001" "SVR" "Ilot Maitre" NA "Recif ilot" NA 1 2 12 2013 NA NA "O" 2 2 NA "MD" "NL" -22.32995 166.41037 "RE" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Fond lagonaire" "Frangeant ilot" "SA3" -999 3 -999 -999 -999 -999 NA +"AMP" "GN130002" "SVR" "Ilot Maitre" NA "Recif ilot" NA 1 2 12 2013 NA NA "O" 2 2 NA "MD" "NL" -22.33118 166.40771 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Corail vivant" "Frangeant ilot" "LC5" -999 5 -999 -999 -999 -999 NA +"AMP" "GN130003" "SVR" "Ilot Maitre" NA "Recif ilot" NA 1 2 12 2013 NA NA "O" 2 2 NA "MD" "NL" -22.33344 166.4064 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "SA3" -999 4 -999 -999 -999 -999 NA +"AMP" "GN130004" "SVR" "Ilot Maitre" NA "Recif ilot" NA 1 2 12 2013 NA NA "O" 2 2 NA "MD" "NL" -22.32701 166.41199 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "SA3" -999 4 -999 -999 -999 -999 NA +"AMP" "GN130005" "SVR" "Ilot Maitre" NA "Recif ilot" NA 1 2 12 2013 NA NA "O" 2 2 NA "MD" "NL" -22.33245 166.405 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Herbier" "Frangeant ilot" "SG3" -999 6 -999 -999 -999 -999 NA +"AMP" "GN130007" "SVR" "Seche Croissant" NA "Recif intermediaire" NA 1 2 12 2013 NA NA "NE" 1 1 NA "PM" "NL" -22.32686 166.37057 "RP" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Recif intermediaire" NA -999 4 -999 -999 -999 -999 NA +"AMP" "GN130008" "SVR" "Seche Croissant" NA "Recif intermediaire" NA 1 2 12 2013 NA NA "O" 2 1 NA "PM" "NL" -22.32921 166.3768 "RP" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Corail vivant" "Recif intermediaire" "SA5" -999 9 -999 -999 -999 -999 NA +"AMP" "GN130010" "SVR" "Goeland" NA "Recif ilot" NA 1 4 12 2013 NA NA "O" 1 0 NA "PM" "NL" -22.37468 166.37814 "RP" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "SA3" -999 3 -999 -999 -999 -999 NA +"AMP" "GN130011" "SVR" "Goeland" NA "Recif ilot" NA 1 4 12 2013 NA NA "O" 1 0 NA "PM" "NL" -22.37333 166.37427 "HR" "AP" "Ile lagonaire" "lagon profond" "Corail vivant" "Fond lagonaire" NA -999 7 -999 -999 -999 -999 NA +"AMP" "GN130012" "SVR" "Goeland" NA "Recif ilot" NA 1 4 12 2013 NA NA "O" 1 0 NA "PM" "NL" -22.37555 166.37445 "HR" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" NA -999 6 -999 -999 -999 -999 NA +"AMP" "GN130013" "SVR" "Goeland" NA "Recif ilot" NA 1 4 12 2013 NA NA "O" 1 0 NA "MD" "NL" -22.39913 166.38889 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Fond lagonaire" "Frangeant ilot" "SA3" -999 7 -999 -999 -999 -999 NA +"AMP" "GN130014" "SVR" "Goeland" NA "Recif ilot" NA 1 4 12 2013 NA NA "O" 1 0 NA "PM" "NL" -22.37506 166.38098 "RP" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Algueraie" "Frangeant ilot" "MA2" -999 1.8 -999 -999 -999 -999 NA +"AMP" "GN130015" "SVR" "Crouy" NA "Recif intermediaire" NA 1 4 12 2013 NA NA "O" 1 0 NA "PM" "NL" -22.34993 166.3506 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Recif intermediaire" "SA3" -999 8 -999 -999 -999 -999 NA +"AMP" "GN130016" "SVR" "Crouy" NA "Recif intermediaire" NA 1 4 12 2013 NA NA "O" 1 0 NA "PM" "NL" -22.35322 166.3483 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Recif intermediaire" NA -999 3 -999 -999 -999 -999 NA +"AMP" "GN130017" "SVR" "Crouy" NA "Recif intermediaire" NA 1 4 12 2013 NA NA "O" 1 0 NA "MM" "NL" -22.36482 166.33615 "HR" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA2" -999 11 -999 -999 -999 -999 NA +"AMP" "GN130018" "SVR" "Crouy" NA "Recif intermediaire" NA 1 4 12 2013 NA NA "O" 1 0 NA "MM" "NL" -22.36902 166.35774 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Recif intermediaire" "SA3" -999 6 -999 -999 -999 -999 NA +"AMP" "GN130019" "SVR" "Crouy" NA "Recif intermediaire" NA 1 4 12 2013 NA NA "O" 1 0 NA "PM" "NL" -22.36091 166.36153 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Fond lagonaire" "Recif intermediaire" "SA3" -999 3 -999 -999 -999 -999 NA +"AMP" "GN130021" "SVR" "Lange" NA "Recif ilot" NA 1 9 12 2013 NA NA "SE" 3 2 NA "MD" "LM" -22.17264 166.26427 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Frangeant ilot" "SG1" -999 11 -999 -999 -999 -999 NA +"AMP" "GN130022" "SVR" "Lange" NA "Recif ilot" NA 1 9 12 2013 NA NA "SE" 3 2 NA "MD" "LM" -22.17377 166.26413 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Algueraie" "Frangeant ilot" "MA3" -999 3 -999 -999 -999 -999 NA +"AMP" "GN130023" "SVR" "Lange" NA "Recif ilot" NA 1 9 12 2013 NA NA "SE" 3 2 NA "MD" "LM" -22.17605 166.26657 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Fond lagonaire" "Frangeant ilot" "SA3" -999 4 -999 -999 -999 -999 NA +"AMP" "GN130025" "SVR" "Recif de Prony" NA "Recif intermediaire" NA 1 11 12 2013 NA NA "SE" 3 2 NA "MM" "LM" -22.26716 166.33195 "HR" "AP" "Complexe de massif corallien de lagon" "front recifal" "Fond lagonaire" "Recif intermediaire" "SA5" -999 5 -999 -999 -999 -999 NA +"AMP" "GN130026" "SVR" "Recif de Prony" NA "Recif intermediaire" NA 1 11 12 2013 NA NA "SE" 3 2 NA "PM" "LM" -22.26166 166.33409 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Algueraie" "Recif intermediaire" "MA1" -999 5 -999 -999 -999 -999 NA +"AMP" "GN130027" "SVR" "Recif de Prony" NA "Recif intermediaire" NA 1 11 12 2013 NA NA "SE" 3 2 NA "PM" "LM" -22.26231 166.33321 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Recif intermediaire" "SA4" -999 4 -999 -999 -999 -999 NA +"AMP" "GN130028" "SVR" "Recif de Prony" NA "Recif intermediaire" NA 1 11 12 2013 NA NA "SE" 3 2 NA "MM" "LM" -22.26422 166.32883 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Corail vivant" "Recif intermediaire" "LC1" -999 4 -999 -999 -999 -999 NA +"AMP" "GN130029" "SVR" "Crouy" NA "Recif intermediaire" NA 1 4 12 2013 NA NA "O" 1 0 NA "MM" "NL" -22.36217 166.34129 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Recif intermediaire" "SA3" -999 5 -999 -999 -999 -999 NA +"AMP" "GN130030" "SVR" "Goeland" NA "Recif ilot" NA 1 4 12 2013 NA NA "O" 1 0 NA "MD" "NL" -22.38055 166.38857 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Detritique" "Frangeant ilot" NA -999 7 -999 -999 -999 -999 NA +"AMP" "GN130031" "SVR" "Ilot Maitre" NA "Recif ilot" NA 1 2 12 2013 NA NA "O" 2 2 NA "MD" "NL" -22.33016 166.40695 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Herbier" "Frangeant ilot" NA -999 7 -999 -999 -999 -999 NA +"AMP" "GN130032" "SVR" "Ilot Maitre" NA "Recif ilot" NA 1 2 12 2013 NA NA "O" 2 2 NA "MD" "NL" -22.34627 166.41121 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Herbier" "Frangeant ilot" "SG3" -999 8 -999 -999 -999 -999 NA +"AMP" "GN130033" "SVR" "Ilot Maitre" NA "Recif ilot" NA 1 2 12 2013 NA NA "O" 2 2 NA "MD" "NL" -22.34649 166.41261 "RE" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Frangeant ilot" NA -999 6 -999 -999 -999 -999 NA +"AMP" "GN130034" "SVR" "Ilot Maitre" NA "Recif ilot" NA 1 2 12 2013 NA NA "O" 2 1 NA "MD" "NL" -22.32833 166.42052 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Frangeant ilot" NA -999 5 -999 -999 -999 -999 NA +"AMP" "GN130035" "SVR" "Ilot Maitre" NA "Recif ilot" NA 1 2 12 2013 NA NA "O" 2 1 NA "MD" "NL" -22.34214 166.42717 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Corail vivant" "Frangeant ilot" "LC5" -999 5 -999 -999 -999 -999 NA +"AMP" "GN130036" "SVR" "Ilot Maitre" NA "Recif ilot" NA 1 2 12 2013 NA NA "O" 2 2 NA "MD" "NL" -22.34402 166.42671 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Frangeant ilot" NA -999 9 -999 -999 -999 -999 NA +"AMP" "GN130037" "SVR" "Ilot Maitre" NA "Recif ilot" NA 1 2 12 2013 NA NA "O" 2 1 NA "MD" "NL" -22.33004 166.42235 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Fond lagonaire" "Frangeant ilot" NA -999 7 -999 -999 -999 -999 NA +"AMP" "GN130038" "SVR" "Seche Croissant" NA "Recif intermediaire" NA 1 2 12 2013 NA NA "NE" 1 1 NA "PM" "NL" -22.32852 166.36771 "RP" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Herbier" "Recif intermediaire" "SG2" -999 10 -999 -999 -999 -999 NA +"AMP" "GN130039" "SVR" "Seche Croissant" NA "Recif intermediaire" NA 1 2 12 2013 NA NA "O" 2 1 NA "PM" "NL" -22.32693 166.37506 "RP" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Algueraie" "Recif intermediaire" "MA3" -999 7 -999 -999 -999 -999 NA +"AMP" "GN130040" "SVR" "Seche Croissant" NA "Recif intermediaire" NA 1 2 12 2013 NA NA "NE" 1 1 NA "PM" "NL" -22.32379 166.36359 "RP" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Corail vivant" "Recif intermediaire" "LC2" -999 3 -999 -999 -999 -999 NA +"AMP" "GN130041" "SVR" "Seche Croissant" NA "Recif intermediaire" NA 1 2 12 2013 NA NA "NE" 1 1 NA "PM" "NL" -22.32363 166.36127 "RP" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Recif intermediaire" "SG1" -999 12 -999 -999 -999 -999 NA +"AMP" "GN130042" "SVR" "Goeland" NA "Recif ilot" NA 1 4 12 2013 NA NA "O" 1 0 NA "MD" "NL" -22.38173 166.38982 "HR" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Frangeant ilot" "SA2" -999 11 -999 -999 -999 -999 NA +"AMP" "GN130043" "SVR" "Crouy" NA "Recif intermediaire" NA 1 4 12 2013 NA NA "O" 1 0 NA "PM" "NL" -22.35633 166.36496 "HR" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA3" -999 12 -999 -999 -999 -999 NA +"AMP" "GN130044" "SVR" "Goeland" NA "Recif ilot" NA 1 4 12 2013 NA NA "O" 1 0 NA "MD" "NL" -22.40292 166.39067 "HR" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA1" -999 8 -999 -999 -999 -999 NA +"AMP" "GN130045" "SVR" "Crouy" NA "Recif intermediaire" NA 1 4 12 2013 NA NA "O" 1 0 NA "MM" "NL" -22.37227 166.35612 "HR" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA2" -999 11 -999 -999 -999 -999 NA +"AMP" "GN130046" "SVR" "Recif de Prony" NA "Recif intermediaire" NA 1 11 12 2013 NA NA "SE" 3 2 NA "MM" "LM" -22.26869 166.33296 "HR" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Recif intermediaire" "MA3" -999 23 -999 -999 -999 -999 NA +"AMP" "GN130047" "SVR" "Recif de Prony" NA "Recif intermediaire" NA 1 11 12 2013 NA NA "SE" 3 2 NA "MM" "LM" -22.26502 166.32674 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Corail vivant" "Recif intermediaire" "LC1" -999 6 -999 -999 -999 -999 NA +"AMP" "GN130048" "SVR" "Lange" NA "Recif ilot" NA 1 9 12 2013 NA NA "SE" 3 2 NA "MD" "LM" -22.17466 166.2672 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Herbier" "Frangeant ilot" "SG2" -999 10 -999 -999 -999 -999 NA +"AMP" "GN130057" "SVR" "Laregnere" NA "Recif ilot" NA 1 10 12 2013 NA NA "SE" 3 2 NA "PM" "LM" -22.33091 166.33708 "RE" "AP" "Ile lagonaire" "lagon profond" "Corail vivant" "Fond lagonaire" "LC3" -999 8 -999 -999 -999 -999 NA +"AMP" "GN130058" "SVR" "Laregnere" NA "Recif ilot" NA 1 5 12 2013 NA NA "S" 1 0 NA "MM" "NL" -22.32559 166.33269 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Corail vivant" "Frangeant ilot" "LC1" -999 4 -999 -999 -999 -999 NA +"AMP" "GN130059" "SVR" "Laregnere" NA "Recif ilot" NA 1 5 12 2013 NA NA "S" 1 0 NA "MM" "NL" -22.3243 166.33328 "RE" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG3" -999 10 -999 -999 -999 -999 NA +"AMP" "GN130060" "SVR" "Laregnere" NA "Recif ilot" NA 1 5 12 2013 NA NA "S" 1 0 NA "MM" "NL" -22.32611 166.32732 "RE" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Corail vivant" "Frangeant ilot" "LC2" -999 4 -999 -999 -999 -999 NA +"AMP" "GN130061" "SVR" "Laregnere" NA "Recif ilot" NA 1 5 12 2013 NA NA "S" 1 0 NA "MM" "NL" -22.32407 166.32895 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Herbier" "Frangeant ilot" "SG2" -999 5 -999 -999 -999 -999 NA +"AMP" "GN130062" "SVR" "Laregnere" NA "Recif ilot" NA 1 5 12 2013 NA NA "S" 1 0 NA "MM" "NL" -22.324 166.32591 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Herbier" "Frangeant ilot" "SG1" -999 6 -999 -999 -999 -999 NA +"AMP" "GN130063" "SVR" "Laregnere" NA "Recif ilot" NA 1 5 12 2013 NA NA "S" 1 0 NA "MM" "NL" -22.32591 166.32368 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "SA3" -999 4 -999 -999 -999 -999 NA +"AMP" "GN130064" "SVR" "Laregnere" NA "Recif ilot" NA 1 5 12 2013 NA NA "S" 1 0 NA "MM" "NL" -22.32297 166.32404 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Herbier" "Frangeant ilot" "SG2" -999 5 -999 -999 -999 -999 NA +"AMP" "GN130065" "SVR" "Laregnere" NA "Recif ilot" NA 1 10 12 2013 NA NA "SE" 3 2 NA "PM" "LM" -22.33118 166.33078 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Fond lagonaire" "Frangeant ilot" NA -999 9 -999 -999 -999 -999 NA +"AMP" "GN130066" "SVR" "Laregnere" NA "Recif ilot" NA 1 10 12 2013 NA NA "SE" 3 2 NA "PM" "LM" -22.33072 166.32384 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Corail vivant" "Frangeant ilot" "LC3" -999 9 -999 -999 -999 -999 NA +"AMP" "GN130067" "SVR" "Laregnere" NA "Recif ilot" NA 1 10 12 2013 NA NA "SE" 3 2 NA "PM" "LM" -22.33156 166.31577 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Corail vivant" "Frangeant ilot" "LC5" -999 8 -999 -999 -999 -999 NA +"AMP" "GN130069" "SVR" "Laregnere" NA "Recif ilot" NA 1 5 12 2013 NA NA "S" 1 0 NA "PM" "NL" -22.32638 166.31847 "RE" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Corail vivant" "Frangeant ilot" "LC5" -999 4 -999 -999 -999 -999 NA +"AMP" "GN130070" "SVR" "Laregnere" NA "Recif ilot" NA 1 5 12 2013 NA NA "S" 1 0 NA "PM" "NL" -22.32483 166.3199 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "SA4" -999 3 -999 -999 -999 -999 NA +"AMP" "GN130071" "SVR" "Laregnere" NA "Recif ilot" NA 1 5 12 2013 NA NA "S" 1 0 NA "PM" "NL" -22.32381 166.3228 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Herbier" "Frangeant ilot" "SG2" -999 6 -999 -999 -999 -999 NA +"AMP" "GN130072" "SVR" "Laregnere" NA "Recif ilot" NA 1 5 12 2013 NA NA "S" 1 0 NA "PM" "NL" -22.3243 166.31573 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Herbier" "Frangeant ilot" "SG1" -999 6 -999 -999 -999 -999 NA +"AMP" "GN130073" "SVR" "Laregnere" NA "Recif ilot" NA 1 5 12 2013 NA NA "S" 1 0 NA "PM" "NL" -22.32591 166.31383 "RE" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Corail vivant" "Frangeant ilot" "LC5" -999 6 -999 -999 -999 -999 NA +"AMP" "GN130074" "SVR" "Laregnere" NA "Recif ilot" NA 1 5 12 2013 NA NA "S" 2 1 NA "PM" "NL" -22.32585 166.31084 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Herbier" "Frangeant ilot" "SG1" -999 10 -999 -999 -999 -999 NA +"AMP" "GN130075" "SVR" "Laregnere" NA "Recif ilot" NA 1 5 12 2013 NA NA "S" 2 1 NA "PM" "NL" -22.32512 166.3092 "RE" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG1" -999 11 -999 -999 -999 -999 NA +"AMP" "GN130076" "SVR" "Laregnere" NA "Recif ilot" NA 1 5 12 2013 NA NA "S" 1 0 NA "MM" "NL" -22.32089 166.32552 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Herbier" "Frangeant ilot" "SG2" -999 9 -999 -999 -999 -999 NA +"AMP" "GN130077" "SVR" "Laregnere" NA "Recif ilot" NA 1 5 12 2013 NA NA "S" 1 0 NA "MM" "NL" -22.31933 166.32353 "RE" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Frangeant ilot" "SG1" -999 12 -999 -999 -999 -999 NA +"AMP" "GN130078" "SVR" "Laregnere" NA "Recif ilot" NA 1 5 12 2013 NA NA "S" 1 0 NA "MM" "NL" -22.32094 166.32156 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Algueraie" "Frangeant ilot" "MA2" -999 3 -999 -999 -999 -999 NA +"AMP" "GN130079" "SVR" "Laregnere" NA "Recif ilot" NA 1 5 12 2013 NA NA "S" 1 0 NA "MM" "NL" -22.32149 166.31992 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Algueraie" "Frangeant ilot" "MA1" -999 5 -999 -999 -999 -999 NA +"AMP" "GN130080" "SVR" "Laregnere" NA "Recif ilot" NA 1 5 12 2013 NA NA "S" 1 0 NA "PM" "NL" -22.31907 166.31696 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG1" -999 10 -999 -999 -999 -999 NA +"AMP" "GN130081" "SVR" "Laregnere" NA "Recif ilot" NA 1 5 12 2013 NA NA "S" 1 0 NA "PM" "NL" -22.32267 166.31485 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Herbier" "Frangeant ilot" "SG1" -999 9 -999 -999 -999 -999 NA +"AMP" "GN130082" "SVR" "Laregnere" NA "Recif ilot" NA 1 5 12 2013 NA NA "S" 2 1 NA "MD" "NL" -22.32927 166.30342 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG1" -999 11 -999 -999 -999 -999 NA +"AMP" "GN130083" "SVR" "Laregnere" NA "Recif ilot" NA 1 5 12 2013 NA NA "S" 2 1 NA "MD" "NL" -22.32754 166.3056 "RE" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG1" -999 15 -999 -999 -999 -999 NA +"AMP" "GN130084" "SVR" "Laregnere" NA "Recif ilot" NA 1 5 12 2013 NA NA "S" 2 1 NA "MD" "NL" -22.32506 166.30444 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG2" -999 10 -999 -999 -999 -999 NA +"AMP" "GN130085" "SVR" "Laregnere" NA "Recif ilot" NA 1 5 12 2013 NA NA "S" 2 1 NA "MD" "NL" -22.33033 166.30614 "RE" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG3" -999 12 -999 -999 -999 -999 NA +"AMP" "GN130086" "SVR" "Laregnere" NA "Recif ilot" NA 1 5 12 2013 NA NA "S" 2 1 NA "MD" "NL" -22.33543 166.29634 "HR" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA1" -999 16 -999 -999 -999 -999 NA +"AMP" "GN130087" "SVR" "Laregnere" NA "Recif ilot" NA 1 5 12 2013 NA NA "S" 2 1 NA "MD" "NL" -22.32906 166.30104 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Algueraie" "Recif intermediaire" "MA2" -999 8 -999 -999 -999 -999 NA +"AMP" "GN130088" "SVR" "Laregnere" NA "Recif ilot" NA 1 5 12 2013 NA NA "S" 2 1 NA "MD" "NL" -22.33038 166.3018 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Herbier" "Recif intermediaire" "SG1" -999 9 -999 -999 -999 -999 NA +"AMP" "GN130089" "SVR" "Laregnere" NA "Recif ilot" NA 1 5 12 2013 NA NA "S" 2 1 NA "MD" "NL" -22.33006 166.29408 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Fond lagonaire" "Recif intermediaire" "SA3" -999 14 -999 -999 -999 -999 NA +"AMP" "GN130090" "SVR" "Laregnere" NA "Recif ilot" NA 1 5 12 2013 NA NA "S" 2 1 NA "MD" "NL" -22.3263 166.29961 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Herbier" "Recif intermediaire" "MA4" -999 6 -999 -999 -999 -999 NA +"AMP" "GN130091" "SVR" "Laregnere" NA "Recif ilot" NA 1 5 12 2013 NA NA "S" 2 1 NA "MD" "NL" -22.32939 166.29916 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Corail vivant" "Recif intermediaire" "LC3" -999 5 -999 -999 -999 -999 NA +"AMP" "GN130092" "SVR" "Laregnere" NA "Recif ilot" NA 1 5 12 2013 NA NA "S" 2 1 NA "MD" "NL" -22.3277 166.29765 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Corail vivant" "Recif intermediaire" "LC5" -999 3.5 -999 -999 -999 -999 NA +"AMP" "GN130093" "SVR" "Laregnere" NA "Recif ilot" NA 1 5 12 2013 NA NA "S" 2 1 NA "MD" "NL" -22.32764 166.29587 "HR" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA3" -999 12 -999 -999 -999 -999 NA +"AMP" "GN130094" "SVR" "Laregnere" NA "Recif ilot" NA 1 5 12 2013 NA NA "S" 2 1 NA "MD" "NL" -22.32424 166.29652 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG1" -999 15 -999 -999 -999 -999 NA +"AMP" "GN130095" "SVR" "Laregnere" NA "Recif ilot" NA 1 5 12 2013 NA NA "S" 2 1 NA "MD" "NL" -22.32183 166.30261 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG1" -999 11 -999 -999 -999 -999 NA +"AMP" "GN130096" "SVR" "Laregnere" NA "Recif ilot" NA 1 5 12 2013 NA NA "S" 1 1 NA "PM" "NL" -22.31994 166.31151 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG2" -999 12 -999 -999 -999 -999 NA +"AMP" "GN130097" "SVR" "Lagon Signal Laregnere" NA "Fond lagonaire" NA 1 11 12 2013 NA NA "SE" 3 2 NA "MM" "LM" -22.31424 166.31273 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG2" -999 13 -999 -999 -999 -999 NA +"AMP" "GN130098" "SVR" "Lagon Signal Laregnere" NA "Fond lagonaire" NA 1 11 12 2013 NA NA "SE" 3 2 NA "MM" "LM" -22.31455 166.30815 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "MA3" -999 13 -999 -999 -999 -999 NA +"AMP" "GN130099" "SVR" "Lagon Signal Laregnere" NA "Fond lagonaire" NA 1 11 12 2013 NA NA "SE" 3 2 NA "MM" "LM" -22.31389 166.30296 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG2" -999 16 -999 -999 -999 -999 NA +"AMP" "GN130101" "SVR" "Lagon Signal Laregnere" NA "Fond lagonaire" NA 1 11 12 2013 NA NA "SE" 3 2 NA "MM" "LM" -22.31107 166.30157 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG1" -999 16 -999 -999 -999 -999 NA +"AMP" "GN130102" "SVR" "Lagon Signal Laregnere" NA "Fond lagonaire" NA 1 11 12 2013 NA NA "SE" 3 2 NA "MM" "LM" -22.3086 166.30856 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG2" -999 14 -999 -999 -999 -999 NA +"AMP" "GN130103" "SVR" "Lagon Signal Laregnere" NA "Fond lagonaire" NA 1 11 12 2013 NA NA "SE" 3 2 NA "MM" "LM" -22.30848 166.30501 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG1" -999 16 -999 -999 -999 -999 NA +"AMP" "GN130104" "SVR" "Lagon Signal Laregnere" NA "Fond lagonaire" NA 1 11 12 2013 NA NA "SE" 3 2 NA "MM" "LM" -22.31257 166.29413 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG3" -999 20 -999 -999 -999 -999 NA +"AMP" "GN130105" "SVR" "Ilot Signal" NA "Fond lagonaire" NA 1 3 12 2013 NA NA "SO" 1 2 NA "MD" "NL" -22.30801 166.29483 "RE" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG1" -999 16 -999 -999 -999 -999 NA +"AMP" "GN130106" "SVR" "Recif Senez" NA "Recif intermediaire" NA 1 11 12 2013 NA NA "SE" 3 2 NA "MM" "LM" -22.29505 166.33331 "HR" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" NA -999 8 -999 -999 -999 -999 NA +"AMP" "GN130107" "SVR" "Recif Senez" NA "Recif intermediaire" NA 1 11 12 2013 NA NA "SE" 3 2 NA "MM" "LM" -22.29623 166.3331 "HR" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA3" -999 9 -999 -999 -999 -999 NA +"AMP" "GN130108" "SVR" "Recif Senez" NA "Recif intermediaire" NA 1 11 12 2013 NA NA "SE" 3 2 NA "MM" "LM" -22.29654 166.3316 "HR" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "LC6" -999 9 -999 -999 -999 -999 NA +"AMP" "GN130110" "SVR" "Recif Senez" NA "Recif intermediaire" NA 1 11 12 2013 NA NA "SE" 3 2 NA "MM" "LM" -22.29386 166.3326 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Recif intermediaire" "SG1" -999 11 -999 -999 -999 -999 NA +"AMP" "GN130111" "SVR" "Ilot Signal" NA "Recif ilot" NA 1 3 12 2013 NA NA "SO" 1 2 NA "MD" "NL" -22.30241 166.29892 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA4" -999 9 -999 -999 -999 -999 NA +"AMP" "GN130112" "SVR" "Ilot Signal" NA "Fond lagonaire" NA 1 3 12 2013 NA NA "SO" 1 1 NA "MD" "NL" -22.29907 166.30092 "RE" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA2" -999 11 -999 -999 -999 -999 NA +"AMP" "GN130113" "SVR" "Ilot Signal" NA "Fond lagonaire" NA 1 3 12 2013 NA NA "SO" 1 1 NA "MD" "NL" -22.29858 166.29956 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" NA -999 8 -999 -999 -999 -999 NA +"AMP" "GN130114" "SVR" "Ilot Signal" NA "Recif ilot" NA 1 3 12 2013 NA NA "SO" 1 2 NA "MD" "NL" -22.30664 166.29367 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Corail vivant" "Frangeant ilot" NA -999 9 -999 -999 -999 -999 NA +"AMP" "GN130115" "SVR" "Ilot Signal" NA "Fond lagonaire" NA 1 3 12 2013 NA NA "SO" 1 2 NA "MD" "NL" -22.30393 166.28842 "RE" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG1" -999 21 -999 -999 -999 -999 NA +"AMP" "GN130116" "SVR" "Ilot Signal" NA "Fond lagonaire" NA 1 3 12 2013 NA NA "SO" 1 2 NA "MD" "NL" -22.30343 166.28979 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Fond lagonaire" "Frangeant ilot" "SA2" -999 15 -999 -999 -999 -999 NA +"AMP" "GN130117" "SVR" "Ilot Signal" NA "Fond lagonaire" NA 1 3 12 2013 NA NA "SO" 1 2 NA "MD" "NL" -22.29974 166.28702 "RE" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG3" -999 7 -999 -999 -999 -999 NA +"AMP" "GN130118" "SVR" "Ilot Signal" NA "Recif ilot" NA 1 3 12 2013 NA NA "SO" 1 2 NA "MD" "NL" -22.29945 166.28911 "RE" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Corail vivant" "Frangeant ilot" NA -999 20 -999 -999 -999 -999 NA +"AMP" "GN130119" "SVR" "Ilot Signal" NA "Fond lagonaire" NA 1 3 12 2013 NA NA "0" 0 1 NA "PM" "NL" -22.29662 166.28783 "RE" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG1" -999 15 -999 -999 -999 -999 NA +"AMP" "GN130120" "SVR" "Ilot Signal" NA "Recif ilot" NA 1 3 12 2013 NA NA "SO" 1 1 NA "PM" "NL" -22.29649 166.28967 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "SA3" -999 7 -999 -999 -999 -999 NA +"AMP" "GN130121" "SVR" "Ilot Signal" NA "Recif ilot" NA 1 3 12 2013 NA NA "0" 0 1 NA "PM" "NL" -22.29501 166.29045 "RE" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Corail vivant" "Frangeant ilot" "LC5" -999 6 -999 -999 -999 -999 NA +"AMP" "GN130122" "SVR" "Ilot Signal" NA "Fond lagonaire" NA 1 3 12 2013 NA NA "0" 0 1 NA "PM" "NL" -22.29548 166.28981 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Herbier" "Frangeant ilot" "SG2" -999 8 -999 -999 -999 -999 NA +"AMP" "GN130123" "SVR" "Ilot Signal" NA "Recif ilot" NA 1 3 12 2013 NA NA "0" 0 1 NA "PM" "NL" -22.29467 166.29054 "RE" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Fond lagonaire" "Frangeant ilot" "SA5" -999 6 -999 -999 -999 -999 NA +"AMP" "GN130124" "SVR" "Ilot Signal" NA "Fond lagonaire" NA 1 3 12 2013 NA NA "0" 0 1 NA "PM" "NL" -22.29404 166.28967 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Herbier" "Frangeant ilot" "SG1" -999 11 -999 -999 -999 -999 NA +"AMP" "GN130125" "SVR" "Ilot Signal" NA "Fond lagonaire" NA 1 3 12 2013 NA NA "0" 0 1 NA "PM" "NL" -22.29493 166.28866 "RE" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG1" -999 17 -999 -999 -999 -999 NA +"AMP" "GN130126" "SVR" "Ilot Signal" NA "Fond lagonaire" NA 1 3 12 2013 NA NA "0" 0 1 NA "PM" "NL" -22.2931 166.29929 "RE" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG1" -999 13 -999 -999 -999 -999 NA +"AMP" "GN130127" "SVR" "Ilot Signal" NA "Fond lagonaire" NA 1 3 12 2013 NA NA "0" 0 1 NA "PM" "NL" -22.29285 166.29134 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "SA1" -999 5 -999 -999 -999 -999 NA +"AMP" "GN130128" "SVR" "Ilot Signal" NA "Fond lagonaire" NA 1 3 12 2013 NA NA "SO" 1 1 NA "PM" "NL" -22.29191 166.29179 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Algueraie" "Frangeant ilot" "MA2" -999 5 -999 -999 -999 -999 NA +"AMP" "GN130129" "SVR" "Ilot Signal" NA "Recif ilot" NA 1 3 12 2013 NA NA "SO" 1 1 NA "PM" "NL" -22.29315 166.29297 "RE" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Frangeant ilot" NA -999 5 -999 -999 -999 -999 NA +"AMP" "GN130130" "SVR" "Ilot Signal" NA "Recif ilot" NA 1 3 12 2013 NA NA "SO" 1 1 NA "MD" "NL" -22.29558 166.29674 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Corail vivant" "Frangeant ilot" NA -999 6 -999 -999 -999 -999 NA +"AMP" "GN130131" "SVR" "Mbe Kouen" NA "Recif ilot" NA 1 12 12 2013 NA NA "S" 2 2 NA "MM" "LM" -22.26729 166.21542 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Recif intermediaire" "SA3" -999 7 -999 -999 -999 -999 NA +"AMP" "GN130132" "SVR" "Mbe Kouen" NA "Recif ilot" NA 1 12 12 2013 NA NA "S" 2 2 NA "MM" "LM" -22.26779 166.22273 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Fond lagonaire" "D6" -999 7 -999 -999 -999 -999 NA +"AMP" "GN130133" "SVR" "Mbe Kouen" NA "Recif ilot" NA 1 12 12 2013 NA NA "S" 2 2 NA "MM" "LM" -22.2668 166.22614 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" -999 11 -999 -999 -999 -999 NA +"AMP" "GN130134" "SVR" "Mbe Kouen" NA "Recif ilot" NA 1 12 12 2013 NA NA "S" 2 2 NA "PM" "LM" -22.26756 166.22913 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Herbier" "Fond lagonaire" "SG3" -999 10 -999 -999 -999 -999 NA +"AMP" "GN130135" "SVR" "Recif Mbe Kouen" NA "Recif intermediaire" NA 1 12 12 2013 NA NA "S" 2 2 NA "PM" "LM" -22.26562 166.23108 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Detritique" "Recif intermediaire" "D6" -999 6 -999 -999 -999 -999 NA +"AMP" "GN130136" "SVR" "Recif Mbe Kouen" NA "Recif intermediaire" NA 1 12 12 2013 NA NA "S" 2 2 NA "MM" "LM" -22.25247 166.23257 "HR" "AP" "Complexe de massif corallien de lagon" "front recifal" "Fond lagonaire" "Recif intermediaire" "SA4" -999 8 -999 -999 -999 -999 NA +"AMP" "GN130137" "SVR" "Mbe Kouen" NA "Recif ilot" NA 1 12 12 2013 NA NA "S" 2 2 NA "MM" "LM" -22.2595 166.22516 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Algueraie" "Frangeant ilot" "MA3" -999 6 -999 -999 -999 -999 NA +"AMP" "GN130138" "SVR" "Mbe Kouen" NA "Recif ilot" NA 1 12 12 2013 NA NA "S" 2 2 NA "MM" "LM" -22.25974 166.22726 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" -999 11 -999 -999 -999 -999 NA +"AMP" "GN130139" "SVR" "Recif Mbe Kouen" NA "Recif intermediaire" NA 1 12 12 2013 NA NA "S" 2 2 NA "MM" "LM" -22.2546 166.22737 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Corail vivant" "Recif intermediaire" "LC3" -999 4 -999 -999 -999 -999 NA +"AMP" "GN130140" "SVR" "Recif Mbe Kouen" NA "Recif intermediaire" NA 1 12 12 2013 NA NA "S" 2 2 NA "MM" "LM" -22.2513 166.22366 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Corail vivant" "Recif intermediaire" "LC4" -999 7 -999 -999 -999 -999 NA +"AMP" "GN130141" "SVR" "Mbo" NA "Recif ilot" NA 1 6 12 2013 NA NA "SO" 1 1 NA "PM" "NL" -22.24965 166.2249 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Herbier" "Fond lagonaire" "SG1" -999 11 -999 -999 -999 -999 NA +"AMP" "GN130142" "SVR" "Mbo" NA "Recif ilot" NA 1 6 12 2013 NA NA "SO" 1 1 NA "PM" "NL" -22.24442 166.23524 "HR" "AP" "Complexe de massif corallien de lagon" "front recifal" "Fond lagonaire" "Frangeant ilot" "SA4" -999 7 -999 -999 -999 -999 NA +"AMP" "GN130143" "SVR" "Mbo" NA "Recif ilot" NA 1 6 12 2013 NA NA "SO" 1 1 NA "PM" "NL" -22.24165 166.2325 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Frangeant ilot" "D3" -999 6 -999 -999 -999 -999 NA +"AMP" "GN130144" "SVR" "Mbo" NA "Recif ilot" NA 1 6 12 2013 NA NA "SO" 1 1 NA "MD" "NL" -22.23924 166.22739 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Fond lagonaire" "Frangeant ilot" "SA4" -999 8 -999 -999 -999 -999 NA +"AMP" "GN130145" "SVR" "Mbo" NA "Recif ilot" NA 1 6 12 2013 NA NA "SO" 1 1 NA "MD" "NL" -22.24033 166.22295 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Fond lagonaire" "Frangeant ilot" NA -999 7 -999 -999 -999 -999 NA +"AMP" "GN130146" "SVR" "Mbo" NA "Recif ilot" NA 1 6 12 2013 NA NA "SO" 1 1 NA "PM" "NL" -22.24279 166.22174 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Corail vivant" "Frangeant ilot" "LC2" -999 6 -999 -999 -999 -999 NA +"AMP" "GN130147" "SVR" "Mbo" NA "Recif ilot" NA 1 6 12 2013 NA NA "SO" 1 1 NA "PM" "NL" -22.24528 166.2236 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "SA3" -999 7 -999 -999 -999 -999 NA +"AMP" "GN130148" "SVR" "Mbo" NA "Recif ilot" NA 1 6 12 2013 NA NA "SO" 1 1 NA "PM" "NL" -22.2478 166.2287 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Frangeant ilot" "D1" -999 6 -999 -999 -999 -999 NA +"AMP" "GN130149" "SVR" "Mbe Kouen" NA "Recif ilot" NA 1 12 12 2013 NA NA "S" 2 2 NA "MM" "LM" -22.26383 166.22154 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Corail vivant" "Frangeant ilot" "LC5" -999 4 -999 -999 -999 -999 NA +"AMP" "GN130150" "SVR" "Mbe Kouen" NA "Recif ilot" NA 1 12 12 2013 NA NA "S" 2 2 NA "MM" "LM" -22.26178 166.2238 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Fond lagonaire" "Frangeant ilot" "SA3" -999 4 -999 -999 -999 -999 NA +"AMP" "GN130151" "SVR" "Mbe Kouen" NA "Recif ilot" NA 1 12 12 2013 NA NA "S" 2 2 NA "MM" "LM" -22.26336 166.22543 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Fond lagonaire" "Frangeant ilot" "SA3" -999 5 -999 -999 -999 -999 NA +"AMP" "GN130152" "SVR" "Mbe Kouen" NA "Recif ilot" NA 1 12 12 2013 NA NA "S" 2 2 NA "MM" "LM" -22.26539 166.21704 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Fond lagonaire" "Recif intermediaire" "SA3" -999 3 -999 -999 -999 -999 NA +"AMP" "GN130153" "SVR" "Recif Mbe Kouen" NA "Recif intermediaire" NA 1 12 12 2013 NA NA "S" 2 2 NA "PM" "LM" -22.26401 166.23547 "HR" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Recif intermediaire" "D2" -999 5 -999 -999 -999 -999 NA +"AMP" "GN130154" "SVR" "Laregnere" NA "Recif ilot" NA 1 5 12 2013 NA NA "S" 1 0 NA "PM" "NL" -22.32521 166.31902 "RE" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Herbier" "Frangeant ilot" "SG1" -999 4 -999 -999 -999 -999 NA +"AMP" "GN130155" "SVR" "Laregnere" NA "Recif ilot" NA 1 5 12 2013 NA NA "S" 1 0 NA "PM" "NL" -22.32534 166.3174 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Herbier" "Frangeant ilot" "SG3" -999 5 -999 -999 -999 -999 NA +"AMP" "GN130156" "SVR" "Laregnere" NA "Recif ilot" NA 1 5 12 2013 NA NA "S" 1 0 NA "PM" "NL" -22.32516 166.31645 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "SA3" -999 6 -999 -999 -999 -999 NA +"AMP" "GN130157" "SVR" "Ilot Signal" NA "Fond lagonaire" NA 1 3 12 2013 NA NA "SO" 1 2 NA "MD" "NL" -22.30311 166.3002 "RE" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG2" -999 18 -999 -999 -999 -999 NA +"AMP" "GN130158" "SVR" "Ilot Signal" NA "Fond lagonaire" NA 1 3 12 2013 NA NA "SO" 1 1 NA "MD" "NL" -22.29424 166.29738 "RE" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG1" -999 16 -999 -999 -999 -999 NA +"AMP" "GN130159" "SVR" "Laregnere" NA "Recif ilot" NA 1 10 12 2013 NA NA "SE" 3 2 NA "PM" "LM" -22.33318 166.31583 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA1" -999 12 -999 -999 -999 -999 NA +"AMP" "GN130160" "SVR" "Laregnere" NA "Recif ilot" NA 1 10 12 2013 NA NA "SE" 3 2 NA "PM" "LM" -22.33287 166.32385 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA1" -999 13 -999 -999 -999 -999 NA +"AMP" "GN130161" "SVR" "Laregnere" NA "Recif ilot" NA 1 10 12 2013 NA NA "SE" 3 2 NA "PM" "LM" -22.33386 166.33145 "RE" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA3" -999 13 -999 -999 -999 -999 NA +"AMP" "GN130162" "SVR" "Laregnere" NA "Recif ilot" NA 1 10 12 2013 NA NA "SE" 3 2 NA "PM" "LM" -22.33085 166.33926 "RE" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG1" -999 13 -999 -999 -999 -999 NA +"AMP" "GN130163" "SVR" "Laregnere" NA "Recif ilot" NA 1 5 12 2013 NA NA "S" 2 1 NA "MD" "NL" -22.33411 166.29672 "HR" "AP" "Complexe de massif corallien de lagon" "front recifal" "Corail vivant" "Recif intermediaire" "LC1" -999 4 -999 -999 -999 -999 NA +"AMP" "GN130164" "SVR" "Recif Senez" NA "Recif intermediaire" NA 1 11 12 2013 NA NA "SE" 3 2 NA "MM" "LM" -22.29576 166.33115 "HR" "AP" "Complexe de massif corallien de lagon" "front recifal" "Corail vivant" "Recif intermediaire" "LC5" -999 3 -999 -999 -999 -999 NA +"AMP" "GN130165" "SVR" "Recif Senez" NA "Recif intermediaire" NA 1 11 12 2013 NA NA "SE" 3 2 NA "MM" "LM" -22.29586 166.33429 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG2" -999 12 -999 -999 -999 -999 NA +"AMP" "GN130166" "SVR" "Recif Senez" NA "Recif intermediaire" NA 1 11 12 2013 NA NA "SE" 3 2 NA "MM" "LM" -22.2931 166.33362 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "MA3" -999 14 -999 -999 -999 -999 NA +"AMP" "GN130169" "SVR" "Recif Mbe Kouen" NA "Recif intermediaire" NA 1 12 12 2013 NA NA "S" 2 2 NA "MM" "LM" -22.25374 166.21069 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Recif intermediaire" "SA3" -999 5 -999 -999 -999 -999 NA +"AMP" "GN130170" "SVR" "Recif Mbe Kouen" NA "Recif intermediaire" NA 1 12 12 2013 NA NA "S" 2 2 NA "MM" "LM" -22.25747 166.21002 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA3" -999 6 -999 -999 -999 -999 NA +"AMP" "GN130171" "SVR" "Lagon Mba Mbo" NA "Fond lagonaire" NA 1 6 12 2013 NA NA "0" 0 0 NA "PM" "NL" -22.23467 166.21405 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SG3" -999 11 -999 -999 -999 -999 NA +"AMP" "GN130172" "SVR" "Lagon Mba Mbo" NA "Fond lagonaire" NA 1 6 12 2013 NA NA "0" 0 0 NA "PM" "NL" -22.22866 166.21495 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" NA -999 10 -999 -999 -999 -999 NA +"AMP" "GN130173" "SVR" "Ilot Signal" NA "Recif ilot" NA 1 3 12 2013 NA NA "0" 0 1 NA "PM" "NL" -22.29399 166.29099 "RE" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Corail vivant" "Frangeant ilot" "LC2" -999 5 -999 -999 -999 -999 NA +"AMP" "GN130174" "SVR" "Mbe Kouen" NA "Recif ilot" NA 1 12 12 2013 NA NA "S" 2 2 NA "MM" "LM" -22.26333 166.2211 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Herbier" "Frangeant ilot" "SG1" -999 6 -999 -999 -999 -999 NA +"AMP" "GN130175" "SVR" "Mbe Kouen" NA "Recif ilot" NA 1 12 12 2013 NA NA "S" 2 2 NA "MM" "LM" -22.26104 166.22301 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Herbier" "Frangeant ilot" "SG2" -999 7 -999 -999 -999 -999 NA +"AMP" "GN130176" "SVR" "Mbe Kouen" NA "Recif ilot" NA 1 12 12 2013 NA NA "S" 2 2 NA "MM" "LM" -22.26413 166.21577 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Recif intermediaire" "SA1" -999 6 -999 -999 -999 -999 NA +"AMP" "GN130177" "SVR" "Recif Mbe Kouen" NA "Recif intermediaire" NA 1 12 12 2013 NA NA "S" 2 2 NA "PM" "LM" -22.26404 166.23712 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Herbier" "Fond lagonaire" "SG2" -999 14 -999 -999 -999 -999 NA +"AMP" "GN130178" "SVR" "Recif Mbe Kouen" NA "Recif intermediaire" NA 1 12 12 2013 NA NA "S" 2 2 NA "MM" "LM" -22.25228 166.23427 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Corail vivant" "Fond lagonaire" NA -999 10 -999 -999 -999 -999 NA +"AMP" "GN130179" "SVR" "Recif Mbe Kouen" NA "Recif intermediaire" NA 1 12 12 2013 NA NA "S" 2 2 NA "PM" "LM" -22.27061 166.23535 "HR" "AP" "Complexe de massif corallien de lagon" "front recifal" "Fond lagonaire" "Recif intermediaire" "LC5" -999 7 -999 -999 -999 -999 NA +"AMP" "GN130180" "SVR" "Recif Mbe Kouen" NA "Recif intermediaire" NA 1 12 12 2013 NA NA "S" 2 2 NA "PM" "LM" -22.27043 166.23721 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" -999 12 -999 -999 -999 -999 NA +"AMP" "GN130181" "SVR" "Mbo" NA "Recif ilot" NA 1 6 12 2013 NA NA "SO" 1 1 NA "MD" "NL" -22.24139 166.23027 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Corail vivant" "Frangeant ilot" "LC3" -999 3 -999 -999 -999 -999 NA +"AMP" "GN130182" "SVR" "Mbo" NA "Recif ilot" NA 1 6 12 2013 NA NA "SO" 1 1 NA "MD" "NL" -22.24006 166.22688 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Frangeant ilot" "D1" -999 2 -999 -999 -999 -999 NA +"AMP" "GN130183" "SVR" "Mbo" NA "Recif ilot" NA 1 6 12 2013 NA NA "SO" 1 1 NA "MD" "NL" -22.24146 166.22191 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" NA -999 5 -999 -999 -999 -999 NA +"AMP" "GN130184" "SVR" "Mba" NA "Recif ilot" NA 1 6 12 2013 NA NA "0" 0 0 NA "MM" "NL" -22.21374 166.1964 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Corail vivant" "Frangeant ilot" "LC4" -999 5 -999 -999 -999 -999 NA +"AMP" "GN130185" "SVR" "Mba" NA "Recif ilot" NA 1 6 12 2013 NA NA "0" 0 0 NA "MM" "NL" -22.21252 166.19504 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "SA3" -999 9 -999 -999 -999 -999 NA +"AMP" "GN130186" "SVR" "Mba" NA "Recif ilot" NA 1 6 12 2013 NA NA "0" 0 0 NA "MM" "NL" -22.21225 166.19998 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Corail vivant" "Frangeant ilot" "LC5" -999 6 -999 -999 -999 -999 NA +"AMP" "GN130187" "SVR" "Mba" NA "Recif ilot" NA 1 6 12 2013 NA NA "0" 0 0 NA "MM" "NL" -22.21071 166.20001 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Herbier" "Frangeant ilot" "SG1" -999 12 -999 -999 -999 -999 NA +"AMP" "GN130188" "SVR" "Mba" NA "Recif ilot" NA 1 6 12 2013 NA NA "0" 0 0 NA "PM" "NL" -22.21589 166.20587 "HR" "AP" "Complexe de massif corallien de lagon" "front recifal" "Fond lagonaire" "Frangeant ilot" "SA5" -999 9 -999 -999 -999 -999 NA +"AMP" "GN130189" "SVR" "Mba" NA "Recif ilot" NA 1 6 12 2013 NA NA "0" 0 0 NA "PM" "NL" -22.21463 166.20601 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Herbier" "Frangeant ilot" "SG2" -999 10 -999 -999 -999 -999 NA +"AMP" "GN130190" "SVR" "Mba" NA "Recif ilot" NA 1 6 12 2013 NA NA "0" 0 0 NA "MM" "NL" -22.22107 166.20802 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Corail vivant" "Frangeant ilot" "LC3" -999 6 -999 -999 -999 -999 NA +"AMP" "GN130191" "SVR" "Mba" NA "Recif ilot" NA 1 6 12 2013 NA NA "0" 0 0 NA "MM" "NL" -22.2219 166.21072 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Herbier" "Fond lagonaire" "SG1" -999 10 -999 -999 -999 -999 NA +"AMP" "GN130192" "SVR" "Mba" NA "Recif ilot" NA 1 6 12 2013 NA NA "0" 0 0 NA "MM" "NL" -22.22085 166.20181 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Corail vivant" "Frangeant ilot" "LC5" -999 7 -999 -999 -999 -999 NA +"AMP" "GN130193" "SVR" "Mba" NA "Recif ilot" NA 1 6 12 2013 NA NA "0" 0 0 NA "MM" "NL" -22.22173 166.201 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Herbier" "Frangeant ilot" "SG2" -999 11 -999 -999 -999 -999 NA +"AMP" "GN130195" "SVR" "Pandanus" NA "Recif ilot" NA 1 9 12 2013 NA NA "SE" 3 2 NA "PM" "LM" -22.19611 166.23834 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Corail vivant" "Frangeant ilot" "LC3" -999 4 -999 -999 -999 -999 NA +"AMP" "GN130196" "SVR" "Pandanus" NA "Recif ilot" NA 1 9 12 2013 NA NA "SE" 3 2 NA "PM" "LM" -22.19589 166.24043 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Fond lagonaire" "Frangeant ilot" "SA4" -999 6 -999 -999 -999 -999 NA +"AMP" "GN130197" "SVR" "Pandanus" NA "Recif ilot" NA 1 9 12 2013 NA NA "SE" 3 2 NA "PM" "LM" -22.19548 166.23608 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Fond lagonaire" "Frangeant ilot" "SA3" -999 4 -999 -999 -999 -999 NA +"AMP" "GN130199" "SVR" "Pandanus" NA "Recif ilot" NA 1 9 12 2013 NA NA "SE" 3 2 NA "PM" "LM" -22.19442 166.24063 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Herbier" "Frangeant ilot" "SG1" -999 6 -999 -999 -999 -999 NA +"AMP" "GN130200" "SVR" "Pandanus" NA "Recif ilot" NA 1 9 12 2013 NA NA "SE" 3 2 NA "MM" "LM" -22.20245 166.2402 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Frangeant ilot" "SG1" -999 12 -999 -999 -999 -999 NA +"AMP" "GN130201" "SVR" "Pandanus" NA "Recif ilot" NA 1 9 12 2013 NA NA "SE" 3 2 NA "MM" "LM" -22.20123 166.23936 "HR" "AP" "Complexe de massif corallien de lagon" "front recifal" "Corail vivant" "Frangeant ilot" "SA5" -999 9 -999 -999 -999 -999 NA +"AMP" "GN130202" "SVR" "Pandanus" NA "Recif ilot" NA 1 9 12 2013 NA NA "SE" 3 2 NA "PM" "LM" -22.19287 166.24843 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Herbier" "Frangeant ilot" "SG1" -999 6 -999 -999 -999 -999 NA +"AMP" "GN130203" "SVR" "Pandanus" NA "Recif ilot" NA 1 9 12 2013 NA NA "SE" 3 2 NA "MM" "LM" -22.19988 166.25642 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "SA3" -999 4 -999 -999 -999 -999 NA +"AMP" "GN130204" "SVR" "Pandanus" NA "Recif ilot" NA 1 9 12 2013 NA NA "SE" 3 2 NA "MM" "LM" -22.20016 166.25813 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "SA4" -999 3 -999 -999 -999 -999 NA +"AMP" "GN130205" "SVR" "Pandanus" NA "Recif ilot" NA 1 9 12 2013 NA NA "SE" 3 2 NA "MM" "LM" -22.20763 166.26276 "HR" "AP" "Complexe de massif corallien de lagon" "front recifal" "Herbier" "Frangeant ilot" "SG1" -999 9 -999 -999 -999 -999 NA +"AMP" "GN130206" "SVR" "Pandanus" NA "Recif ilot" NA 1 9 12 2013 NA NA "SE" 3 2 NA "MM" "LM" -22.20554 166.26077 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Herbier" "Frangeant ilot" "SG2" -999 11 -999 -999 -999 -999 NA +"AMP" "GN130207" "SVR" "Lange" NA "Recif ilot" NA 1 9 12 2013 NA NA "SE" 3 2 NA "PM" "LM" -22.18101 166.25809 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG1" -999 11 -999 -999 -999 -999 NA +"AMP" "GN130208" "SVR" "Lange" NA "Recif ilot" NA 1 9 12 2013 NA NA "SE" 3 2 NA "PM" "LM" -22.18237 166.25864 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG1" -999 12 -999 -999 -999 -999 NA +"AMP" "GN130209" "SVR" "Canard" NA "Recif ilot" NA 1 4 12 2013 NA NA "O" 1 0 NA "MD" "NL" -22.31163 166.43434 "RE" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Corail vivant" "Frangeant ilot" "LC1" -999 3 -999 -999 -999 -999 NA +"AMP" "GN130210" "SVR" "Canard" NA "Recif ilot" NA 1 4 12 2013 NA NA "O" 1 0 NA "MD" "NL" -22.3117 166.43433 "RE" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Fond lagonaire" "Frangeant ilot" "SA3" -999 5 -999 -999 -999 -999 NA +"AMP" "GN130211" "SVR" "Canard" NA "Recif ilot" NA 1 4 12 2013 NA NA "O" 1 0 NA "MD" "NL" -22.31443 166.435 "RE" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Corail vivant" "Frangeant ilot" "LC2" -999 1.5 -999 -999 -999 -999 NA +"AMP" "GN130213" "SVR" "Canard" NA "Recif ilot" NA 1 4 12 2013 NA NA "O" 1 0 NA "MD" "NL" -22.31083 166.43365 "RE" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Frangeant ilot" "SG1" -999 7 -999 -999 -999 -999 NA +"AMP" "GN130214" "SVR" "Canard" NA "Recif ilot" NA 1 4 12 2013 NA NA "O" 1 0 NA "MD" "NL" -22.31067 166.43469 "RE" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Frangeant ilot" "SG1" -999 6 -999 -999 -999 -999 NA +"AMP" "GN130215" "SVR" "Canard" NA "Recif ilot" NA 1 4 12 2013 NA NA "O" 1 0 NA "MD" "NL" -22.31508 166.43579 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Corail vivant" "Frangeant ilot" "LC5" -999 6 -999 -999 -999 -999 NA +"AMP" "GN130216" "SVR" "Canard" NA "Recif ilot" NA 1 4 12 2013 NA NA "O" 1 0 NA "MD" "NL" -22.31328 166.4388 "RE" "AP" "Ile lagonaire" "lagon profond" "Corail vivant" "Frangeant ilot" "LC1" -999 6 -999 -999 -999 -999 NA +"AMP" "GN130217" "SVR" "Goeland" NA "Recif ilot" NA 1 4 12 2013 NA NA "O" 1 0 NA "PM" "NL" -22.38994 166.37622 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Fond lagonaire" "Frangeant ilot" "SA4" -999 2 -999 -999 -999 -999 NA +"AMP" "GN130218" "SVR" "Goeland" NA "Recif ilot" NA 1 4 12 2013 NA NA "O" 1 0 NA "MD" "NL" -22.39703 166.37712 "HR" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA3" -999 6 -999 -999 -999 -999 NA +"AMP" "GN130219" "SVR" "Ilot Sable" NA "Recif intermediaire" NA 1 6 12 2013 NA NA "0" 0 0 NA "MM" "NL" -22.2486 166.26814 "HR" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA4" -999 7 -999 -999 -999 -999 NA +"AMP" "GN130220" "SVR" "Ilot Sable" NA "Recif intermediaire" NA 1 6 12 2013 NA NA "0" 0 0 NA "MM" "NL" -22.2486 166.27094 "HR" "AP" "Ile lagonaire" "lagon profond" "Detritique" "Fond lagonaire" NA -999 7 -999 -999 -999 -999 NA +"AMP" "GN130221" "SVR" "Ilot Signal" NA "Fond lagonaire" NA 1 3 12 2013 NA NA "SO" 1 2 NA "MD" "NL" -22.29132 166.27803 "RE" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG2" -999 20 -999 -999 -999 -999 NA +"AMP" "GN130222" "SVR" "Ilot Signal" NA "Recif ilot" NA 1 3 12 2013 NA NA "SO" 1 2 NA "MD" "NL" -22.29405 166.27641 "RE" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG2" -999 19 -999 -999 -999 -999 NA +"AMP" "GN130223" "SVR" "Seche Croissant" NA "Recif intermediaire" NA 1 2 12 2013 NA NA "O" 2 2 NA "MD" "NL" -22.33242 166.3842 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal ennoye" "Algueraie" "Recif intermediaire" "SA4" -999 6 -999 -999 -999 -999 NA +"AMP" "GN130224" "SVR" "Seche Croissant" NA "Recif intermediaire" NA 1 2 12 2013 NA NA "O" 2 2 NA "MD" "NL" -22.33074 166.38051 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal ennoye" "Detritique" "Recif intermediaire" "D1" -999 6 -999 -999 -999 -999 NA +"AMP" "GN130225" "SVR" "Pandanus" NA "Recif ilot" NA 1 9 12 2013 NA NA "SE" 3 2 NA "PM" "LM" -22.19028 166.24974 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG3" -999 11 -999 -999 -999 -999 NA +"AMP" "GN130500" "SVR" "Ilot Maitre" NA "Recif ilot" NA 1 2 12 2013 NA NA "O" 2 1 NA "MD" "NL" -22.33246 166.41388 "RE" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Herbier" "Frangeant ilot" "SG1" -999 1.5 -999 -999 -999 -999 NA +"AMP" "GN130501" "SVR" "Ilot Maitre" NA "Recif ilot" NA 1 2 12 2013 NA NA "O" 2 1 NA "MD" "NL" -22.33415 166.41275 "RE" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Herbier" "Frangeant ilot" "SG1" -999 1.5 -999 -999 -999 -999 NA +"AMP" "GN130503" "SVR" "Laregnere" NA "Recif ilot" NA 1 5 12 2013 NA NA "S" 1 0 NA "MD" "NL" -22.327 166.31728 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Fond lagonaire" "Frangeant ilot" "LC3" -999 2 -999 -999 -999 -999 NA +"AMP" "GN130504" "SVR" "Laregnere" NA "Recif ilot" NA 1 5 12 2013 NA NA "S" 1 0 NA "MD" "NL" -22.32868 166.31827 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Corail vivant" "Frangeant ilot" "LC1" -999 2 -999 -999 -999 -999 NA +"AMP" "GN130505" "SVR" "Laregnere" NA "Recif ilot" NA 1 5 12 2013 NA NA "S" 1 0 NA "MD" "NL" -22.3285 166.31993 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Fond lagonaire" "Frangeant ilot" "LC3" -999 2 -999 -999 -999 -999 NA +"AMP" "GN130506" "SVR" "Mbo" NA "Recif ilot" NA 1 6 12 2013 NA NA "SO" 1 1 NA "MD" "NL" -22.244 166.22864 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Fond lagonaire" "Frangeant ilot" "SA5" -999 2 -999 -999 -999 -999 NA +"AMP" "GN130510" "SVR" "Lagon Mba Mbo" NA "Fond lagonaire" NA 1 12 12 2013 NA NA "S" 2 2 NA "MM" "LM" -22.22279 166.21605 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Herbier" "Fond lagonaire" "SG1" -999 9 -999 -999 -999 -999 NA +"AMP" "GN130511" "SVR" "Lagon Mba Mbo" NA "Fond lagonaire" NA 1 12 12 2013 NA NA "S" 2 2 NA "MM" "LM" -22.22716 166.20927 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Algueraie" "Fond lagonaire" "MA2" -999 9 -999 -999 -999 -999 NA +"AMP" "GN130512" "SVR" "Lagon Mba Mbo" NA "Fond lagonaire" NA 1 12 12 2013 NA NA "S" 2 2 NA "MM" "LM" -22.23186 166.19957 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA5" -999 8 -999 -999 -999 -999 NA +"AMP" "GN130513" "SVR" "Lagon Mba Mbo" NA "Fond lagonaire" NA 1 12 12 2013 NA NA "S" 2 2 NA "MM" "LM" -22.24291 166.20731 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Algueraie" "Fond lagonaire" "MA2" -999 9 -999 -999 -999 -999 NA +"AMP" "GN130514" "SVR" "Lagon Mba Mbo" NA "Fond lagonaire" NA 1 12 12 2013 NA NA "S" 2 2 NA "MM" "LM" -22.24045 166.21098 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" -999 10 -999 -999 -999 -999 NA +"AMP" "GN130515" "SVR" "Lagon Mba Mbo" NA "Fond lagonaire" NA 1 12 12 2013 NA NA "S" 2 2 NA "MM" "LM" -22.23674 166.21745 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Herbier" "Fond lagonaire" "SG1" -999 10 -999 -999 -999 -999 NA +"AMP" "GN130516" "SVR" "Recif Mbe Kouen" NA "Recif intermediaire" NA 1 12 12 2013 NA NA "S" 2 2 NA "MM" "LM" -22.25386 166.20938 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Recif intermediaire" "SA3" -999 6 -999 -999 -999 -999 NA +"AMP" "GN130517" "SVR" "Pandanus" NA "Recif ilot" NA 1 13 12 2013 NA NA "SO" 1 1 NA "MM" "LM" -22.19576 166.23795 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Detritique" "Frangeant ilot" NA -999 4 -999 -999 -999 -999 NA +"AMP" "GN130518" "SVR" "Pandanus" NA "Recif ilot" NA 1 13 12 2013 NA NA "SO" 1 1 NA "MM" "LM" -22.19447 166.23738 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Herbier" "Frangeant ilot" "SG1" -999 6 -999 -999 -999 -999 NA +"AMP" "GN130519" "SVR" "Lange" NA "Recif ilot" NA 1 13 12 2013 NA NA "SO" 1 1 NA "MM" "LM" -22.17433 166.25784 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Fond lagonaire" "Frangeant ilot" "SA3" -999 3 -999 -999 -999 -999 NA +"AMP" "GN130520" "SVR" "Lange" NA "Recif ilot" NA 1 13 12 2013 NA NA "SO" 1 1 NA "MM" "LM" -22.17561 166.25902 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Fond lagonaire" "Frangeant ilot" NA -999 1.5 -999 -999 -999 -999 NA +"AMP" "GN130521" "SVR" "Lange" NA "Recif ilot" NA 1 13 12 2013 NA NA "SO" 1 1 NA "MM" "LM" -22.17524 166.26089 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Herbier" "Frangeant ilot" "SG1" -999 2 -999 -999 -999 -999 NA +"AMP" "GN130522" "SVR" "Lange" NA "Recif ilot" NA 1 13 12 2013 NA NA "SO" 1 1 NA "MM" "LM" -22.17393 166.26067 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Herbier" "Frangeant ilot" "SG3" -999 3 -999 -999 -999 -999 NA +"AMP" "GN130523" "SVR" "Maa" NA "Frangeant" NA 1 13 12 2013 NA NA "SO" 2 2 NA "MM" "LM" -22.2159 166.32565 "HR" "AP" "Ile lagonaire" "lagon profond" "Detritique" "Frangeant cotier" "D7" -999 4 -999 -999 -999 -999 NA +"AMP" "GN130524" "SVR" "Maa" NA "Frangeant" NA 1 13 12 2013 NA NA "SO" 2 2 NA "MM" "LM" -22.21686 166.32693 "HR" "AP" "Ile lagonaire" "lagon profond" "Detritique" "Frangeant cotier" "D5" -999 4 -999 -999 -999 -999 NA +"AMP" "GN130526" "SVR" "Kuendu" NA "Frangeant" NA 1 13 12 2013 NA NA "SO" 2 2 NA "MM" "LM" -22.25878 166.38632 "HR" "AP" "Ile lagonaire" "lagon profond" "Detritique" "Frangeant cotier" NA -999 4 -999 -999 -999 -999 NA +"AMP" "HI120001" "SVR" "Dongan Hienga" NA "Barriere" "Donga Hienga" 1 29 8 2012 NA NA "0" 0 -999 NA "MM" "PC" -20.62927 165.06783 "HR" "AP" "Complexe de recif barriere externe" "front recifal" "Detritique" "Recif barriere externe" "D5" 5 11.5 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120002" "SVR" "Dongan Hienga" NA "Barriere" "Donga Hienga" 1 29 8 2012 NA NA "0" 0 -999 NA "MM" "PC" -20.62537 165.06052 "HR" "AP" "Complexe de recif barriere externe" "front recifal" "Detritique" "Recif barriere externe" "D2" 5 7.5 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120003" "SVR" "Dongan Hienga" NA "Barriere" "Donga Hienga" 1 29 8 2012 NA NA "0" 0 -999 NA "MM" "PC" -20.61933 165.05182 "HR" "AP" "Complexe de recif barriere externe" "front recifal" "Detritique" "Recif barriere externe" NA 5 4.3 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120004" "SVR" "Recif Kaun" NA "Barriere" "Recif Kaun et Douok" 1 30 8 2012 NA NA "0" 0 -999 NA "MM" "PC" -20.60521 165.03685 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA1" 5 4 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120005" "SVR" "Recif Kaun" NA "Barriere" "Recif Kaun et Douok" 1 30 8 2012 NA NA NA 1 -999 NA "MM" "PC" -20.59871 165.03685 "HR" "AP" "Complexe de recif barriere externe" "platier recifal" "Detritique" "Recif barriere interne" "D1" 5 2.2 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120006" "SVR" "Recif Kaun" NA "Barriere" "Recif Kaun et Douok" 1 30 8 2012 NA NA NA 1 -999 NA "MM" "PC" -20.5955 165.0284 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" NA 5 4 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120007" "SVR" "Recif Kaun" NA "Barriere" "Recif Kaun et Douok" 1 30 8 2012 NA NA NA 1 -999 NA "MM" "PC" -20.59088 165.02484 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Recif barriere interne" "D2" 5 4 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120008" "SVR" "Recif Kaun" NA "Barriere" "Recif Kaun et Douok" 1 30 8 2012 NA NA NA 3 -999 NA "MD" "PC" -20.586 165.022 "HR" "AP" "Complexe de recif barriere externe" "platier recifal" "Detritique" "Recif barriere interne" "D2" 5 2.5 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120009" "SVR" "Recif Kaun" NA "Barriere" "Recif Kaun et Douok" 1 30 8 2012 NA NA NA 3 -999 NA "MD" "PC" -20.58187 165.01817 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Recif barriere interne" "D2" 5 2.9 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120010" "SVR" "Recif Kaun" NA "Barriere" "Recif Kaun et Douok" 1 30 8 2012 NA NA NA 3 -999 NA "MD" "PC" -20.57387 165.01381 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Recif barriere interne" "D6" 5 2.4 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120011" "SVR" "Recif Kaun" NA "Barriere" "Recif Kaun et Douok" 1 30 8 2012 NA NA NA 3 -999 NA "MD" "PC" -20.56953 165.01166 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Recif barriere interne" "D5" 5 2.3 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120012" "SVR" "Recif Kaun" NA "Barriere" "Recif Kaun et Douok" 1 30 8 2012 NA NA NA 3 -999 NA "MD" "PC" -20.5688 165.00468 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA3" 5 4.3 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120013" "SVR" "Recif Kaun" NA "Barriere" "Recif Kaun et Douok" 1 30 8 2012 NA NA NA 3 -999 NA "MD" "PC" -20.57083 165.00137 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Recif barriere interne" "D7" 5 8.8 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120014" "SVR" "Dongan Hiengu" NA "Barriere - dessus patate" "Dongan Hiengu HR Dohimen" 1 29 8 2012 NA NA NA 2 -999 NA "MM" "PC" -20.63457 165.08882 "HR" "AP" "Complexe de recif barriere externe" "passe" "Detritique" "Passe" "D7" 5 2.9 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120015" "SVR" "Dongan Hiengu" NA "Barriere" "Dongan Hiengu HR Dohimen" 1 29 8 2012 NA NA "0" 0 -999 NA "MM" "PC" -20.63212 165.0926 "HR" "AP" "Complexe de recif barriere externe" "front recifal" "Detritique" "Recif barriere externe" "D1" 5 9.6 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120016" "SVR" "Recif Doiman" NA "Barriere" "Do himen Recif Doiman" 1 27 8 2012 NA NA NA 1 -999 NA "MM" "PC" -20.58843 165.14688 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Recif barriere interne" "D7" 5 5 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120017" "SVR" "Recif Doiman" NA "Barriere" "Do himen Recif Doiman" 1 27 8 2012 NA NA NA 1 -999 NA "MM" "PC" -20.58762 165.15032 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Recif barriere interne" "D5" 5 4.5 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120018" "SVR" "Recif Doiman" NA "Barriere" "Do himen Recif Doiman" 1 27 8 2012 NA NA NA 1 -999 NA "MM" "PC" -20.5894 165.15683 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Recif barriere interne" "D7" 5 6 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120019" "SVR" "Recif Mengalia" NA "Barriere" "Grand recif Mengalia" 1 27 8 2012 NA NA NA 1 -999 NA "MM" "PC" -20.60143 165.18973 "HR" "AP" "Complexe de recif barriere externe" "platier recifal" "Detritique" "Recif barriere interne" "D5" 5 3 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120020" "SVR" "Recif Mengalia" NA "Barriere" "Grand recif Mengalia" 1 28 8 2012 NA NA "0" 0 -999 NA "MM" "PC" -20.60518 165.19772 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA3" 5 2.5 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120021" "SVR" "Recif Mengalia" NA "Barriere" "Grand recif Mengalia" 1 28 8 2012 NA NA "0" 0 -999 NA "MM" "PC" -20.60812 165.20655 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Recif barriere interne" "D7" 5 3 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120023" "SVR" "Recif Douok" NA "Barriere" "Recif Kaun et Douok" 1 30 8 2012 NA NA NA 3 -999 NA "MD" "PC" -20.58274 164.99144 "HR" "AP" "Complexe de recif barriere externe" "front recifal" "Detritique" "Recif barriere externe" "D7" 5 7.7 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120024" "SVR" "Recif Douok" NA "Barriere" "Recif Kaun et Douok" 1 30 8 2012 NA NA NA 3 -999 NA "MD" "PC" -20.58077 164.99525 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Recif barriere interne" "D7" 5 11 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120025" "SVR" "Ilot Hienghene" NA "Ilot intermediaire" "ilot Hienghene et Tiguit" 1 29 8 2012 NA NA NA 1 -999 NA "MM" "PC" -20.62745 164.94044 "HR" "AP" "Complexe de recif barriere imbrique" "terrasse peu profonde" "Detritique" "Frangeant ilot" "D7" 5 2 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120026" "SVR" "Ilot Hienghene" NA "Ilot intermediaire" "ilot Hienghene et Tiguit" 1 29 8 2012 NA NA NA 1 -999 NA "MM" "PC" -20.62455 164.94514 "HR" "AP" "Complexe de recif barriere imbrique" "terrasse peu profonde" "Detritique" "Frangeant ilot" NA 5 4 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120027" "SVR" "Ilot Hienghene" NA "Ilot intermediaire" "ilot Hienghene et Tiguit" 1 29 8 2012 NA NA "0" 0 -999 NA "MM" "PC" -20.61814 164.94957 "HR" "AP" "Complexe de recif barriere imbrique" "terrasse peu profonde" "Detritique" "Frangeant ilot" "D7" 5 4 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120028" "SVR" "Ilot Tiguit" NA "Ilot intermediaire" "ilot Hienghene et Tiguit" 1 29 8 2012 NA NA "0" 0 -999 NA "MM" "PC" -20.62631 164.92255 "HR" "AP" "Complexe de recif barriere imbrique" "terrasse peu profonde" "Detritique" "Frangeant ilot" "LC5" 5 3 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120029" "SVR" "Ilot de sable" NA "Recif intermediaire" "Thabap" 1 30 8 2012 NA NA NA 1 -999 NA "MD" "PC" -20.6118 164.89499 "RC" "AP" "Complexe de recif barriere imbrique" "front recifal ou terrasse" "Detritique" "Recif barriere externe" "D5" 5 7 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120030" "SVR" "Ilot Hiengabat" NA "Ilot intermediaire" "ilot Hiengabat" 1 29 8 2012 NA NA "0" 0 -999 NA "MM" "PC" -20.63896 164.98717 "HR" "AP" "Complexe de recif barriere imbrique" "front recifal ou terrasse" "Detritique" "Frangeant ilot" "LC3" 5 2 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120032" "SVR" "Ilot Hiengabat" NA "Ilot intermediaire" "ilot Hiengabat" 1 29 8 2012 NA NA "0" 0 -999 NA "MM" "PC" -20.63416 164.98088 "HR" "AP" "Complexe de recif barriere imbrique" "front recifal ou terrasse" "Fond lagonaire" "Frangeant ilot" "SA5" 5 15 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120033" "SVR" "Dongan Hienga" NA "Barriere" "Donga Hienga" 1 31 8 2012 NA NA NA 3 -999 NA "md" "PC" -20.63106 165.05017 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA3" 5 8.2 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120034" "SVR" "Recif Kaun" NA "Barriere" "Recif Kaun et Douok" 1 31 8 2012 NA NA NA 3 -999 NA "MD" "PC" -20.59742 165.02466 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA3" 5 6.5 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120035" "SVR" "Recif Kaun" NA "Barriere" "Recif Kaun et Douok" 1 31 8 2012 NA NA NA 3 -999 NA "MD" "PC" -20.5844 165.01834 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA1" 5 11.7 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120036" "SVR" "Recif Kaun" NA "Barriere" "Recif Kaun et Douok" 1 30 8 2012 NA NA NA 3 -999 NA "MD" "PC" -20.57309 165.00351 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA1" 5 10.7 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120037" "SVR" "Recif Kaun" NA "Barriere" "Recif Kaun et Douok" 1 30 8 2012 NA NA NA 3 -999 NA "MD" "PC" -20.56582 165.0009 "HR" "AP" "Complexe de recif barriere externe" "platier recifal" "Detritique" "Recif barriere interne" "D1" 5 8 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120039" "SVR" "Dongan Hienga" NA "Barriere" "Donga Hienga" 1 29 8 2012 NA NA "0" 0 -999 NA "MM" "PC" -20.63428 165.06425 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Recif barriere interne" "D2" 5 4 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120040" "SVR" "Dongan Hienga" NA "Barriere" "Donga Hienga" 1 29 8 2012 NA NA "0" 0 -999 NA "MM" "PC" -20.63252 165.06003 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Recif barriere interne" "D1" 5 5 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120041" "SVR" "Dongan Hienga" NA "Barriere" "Donga Hienga" 1 29 8 2012 NA NA "0" 0 -999 NA "MM" "PC" -20.63108 165.0538 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Recif barriere interne" "D1" 5 5 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120042" "SVR" "Dongan Hienga" NA "Barriere" "Donga Hienga" 1 29 8 2012 NA NA "0" 0 -999 NA "MM" "PC" -20.6246 165.04845 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Recif barriere interne" "SA5" 5 8.5 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120045" "SVR" "Recif Mengalia" NA "Barriere" "Grand recif Mengalia" 1 28 8 2012 NA NA "0" 0 -999 NA "MM" "PC" -20.6101 165.20357 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA3" 5 5 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120046" "SVR" "Recif Mengalia" NA "Barriere" "Grand recif Mengalia" 1 28 8 2012 NA NA "0" 0 -999 NA "MM" "PC" -20.6142 165.21148 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Recif barriere interne" "D7" 5 15 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120047" "SVR" "Recif Mengalia" NA "Barriere" "Grand recif Mengalia" 1 28 8 2012 NA NA "0" 0 -999 NA "MM" "PC" -20.61498 165.22152 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA1" 5 5 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120048" "SVR" "Dongan Hiengu" NA "Barriere" "Dongan Hiengu HR Dohimen" 1 29 8 2012 NA NA "0" 0 -999 NA "MM" "PC" -20.63852 165.10353 "HR" "AP" "Complexe de recif barriere externe" "front recifal" "Detritique" "Passe" "D5" 5 10 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120050" "SVR" "Ilot Hienghene" NA "Ilot intermediaire" "ilot Hienghene et Tiguit" 1 29 8 2012 NA NA NA 1 -999 NA "MM" "PC" -20.62961 164.93912 "HR" "AP" "Complexe de recif barriere imbrique" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "SA3" 5 8 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120051" "SVR" "Ilot Hienghene" NA "Fond lagonaire" "ilot Hienghene et Tiguit" 1 29 8 2012 NA NA NA 1 -999 NA "MM" "PC" -20.63104 164.92924 "HR" "AP" "Ile lagonaire" "lagon profond" "Detritique" "Fond lagonaire" "D2" 5 10 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120053" "SVR" "Ilot de sable" NA "Ilot intermediaire" "ilot Hienghene et Tiguit" 1 30 8 2012 NA NA "0" 0 -999 NA "MD" "PC" -20.62377 164.91226 "HR" "AP" "Complexe de recif barriere imbrique" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "SA4" 5 11 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120055" "SVR" "Ilot de sable" NA "Recif intermediaire" "Thabap" 1 30 8 2012 NA NA NA 1 -999 NA "MD" "PC" -20.62068 164.89563 "RC" "AP" "Complexe de recif barriere imbrique" "terrasse peu profonde" "Detritique" "Frangeant ilot" "D7" 5 6 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120058" "SVR" "Recif Pidanain" NA "Ilot intermediaire" "Yeega" 1 29 8 2012 NA NA "0" 0 -999 NA "MM" "PC" -20.65748 165.01956 "RE" "AP" "Complexe de recif barriere imbrique" "front recifal ou terrasse" "Detritique" "Frangeant ilot" "D7" 5 10 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120060" "SVR" "Ilot Hiengabat" NA "Ilot intermediaire" "ilot Hiengabat" 1 28 8 2012 NA NA NA 1 -999 NA "MM" "PC" -20.63664 164.9778 "HR" "AP" "Complexe de recif barriere imbrique" "platier recifal" "Detritique" "Frangeant ilot" "D5" 5 9 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120064" "SVR" "Hienga" NA "Barriere" "ilot Hienga HR Yeega" 1 31 8 2012 NA NA NA 3 -999 NA "MD" "PC" -20.66691 165.06207 "HR" "AP" "Complexe de recif barriere imbrique" "passe" "Detritique" "Fond lagonaire" "D2" 5 15 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120067" "SVR" "Recif Mengalia" NA "Barriere" "Grand recif Mengalia" 1 28 8 2012 NA NA "0" 0 -999 NA "MM" "PC" -20.61173 165.23058 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Recif barriere interne" "D6" 5 3 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120068" "SVR" "Recif Mengalia" NA "Barriere" "Grand recif Mengalia" 1 28 8 2012 NA NA "0" 0 -999 NA "MM" "PC" -20.61282 165.22447 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Recif barriere interne" "D7" 5 4 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120069" "SVR" "Recif Mengalia" NA "Barriere" "Grand recif Mengalia" 1 28 8 2012 NA NA "0" 0 -999 NA "MM" "PC" -20.61133 165.21578 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Recif barriere interne" "D6" 5 4 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120070" "SVR" "Recif Mengalia" NA "Barriere" "Grand recif Mengalia" 1 28 8 2012 NA NA "0" 0 -999 NA "MM" "PC" -20.61597 165.22497 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Recif barriere interne" "SA3" 5 6 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120086" "SVR" "Dongan Hiengu" NA "Barriere - bas tombant" "Dongan Hiengu HR Dohimen" 1 29 8 2012 NA NA NA 2 -999 NA "MM" "PC" -20.63758 165.09212 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Recif barriere interne" "D7" 5 10.5 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120088" "SVR" "Recif Doiman" NA "Barriere" "Do himen Recif Doiman" 1 27 8 2012 NA NA NA 1 -999 NA "MM" "PC" -20.59582 165.1745 "RE" "AP" "Complexe de recif barriere externe" "platier recifal" "Detritique" "Recif barriere interne" NA 5 3 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120089" "SVR" "Recif Mengalia" NA "Barriere" "Grand recif Mengalia" 1 27 8 2012 NA NA NA 1 -999 NA "MM" "PC" -20.60022 165.1831 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Recif barriere interne" "D7" 5 3 -999 -999 -999 -999 NA +"AMP" "HI120093" "SVR" "Recif Doiman" NA "Barriere" "Do himen Recif Doiman" 1 27 8 2012 NA NA NA 1 -999 NA "MM" "PC" -20.59058 165.16377 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Recif barriere interne" "D1" 5 4.3 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120094" "SVR" "Recif Doiman" NA "Barriere" "Do himen Recif Doiman" 1 27 8 2012 NA NA NA 1 -999 NA "MM" "PC" -20.59122 165.1405 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Recif barriere interne" "D2" 5 5 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120095" "SVR" "Dongan Hiengu" NA "Barriere - bas tombant" "Dongan Hiengu HR Dohimen" 1 29 8 2012 NA NA NA 2 -999 NA "MM" "PC" -20.63563 165.08959 "HR" "AP" "Complexe de recif barriere externe" "passe" "Detritique" "Passe" "D5" 5 16 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120096" "SVR" "Dongan Hienga" NA "Barriere" "Donga Hienga" 1 29 8 2012 NA NA "0" 0 -999 NA "MM" "PC" -20.63072 165.07088 "HR" "AP" "Complexe de recif barriere externe" "front recifal" "Detritique" "Recif barriere externe" "D5" 5 12.6 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120097" "SVR" "Ilot Hienga" NA "Ilot intermediaire" "ilot Hienga HR Yeega" 1 28 8 2012 NA NA NA 1 -999 NA "MD" "PC" -20.66176 165.05658 "HR" "AP" "Complexe de recif barriere imbrique" "front recifal ou terrasse" "Detritique" "Frangeant ilot" "LC3" 5 4 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120098" "SVR" "Ilot Hienga" NA "Ilot intermediaire" "Yeega" 1 28 8 2012 NA NA NA 1 -999 NA "MM" "PC" -20.65985 165.05153 "RE" "AP" "Complexe de recif barriere imbrique" "platier recifal" "Detritique" "Frangeant ilot" "D7" 5 5 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120099" "SVR" "Recif Pidanain" NA "Ilot intermediaire" "Yeega" 1 28 8 2012 NA NA NA 1 -999 NA "MM" "PC" -20.65924 165.02286 "RE" "AP" "Complexe de recif barriere imbrique" "platier recifal" "Detritique" "Frangeant ilot" "D5" 5 6 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120100" "SVR" "Recif Pidanain" NA "Ilot intermediaire" "Yeega" 1 28 8 2012 NA NA NA 1 -999 NA "MM" "PC" -20.66073 165.02032 "RE" "AP" "Complexe de recif barriere imbrique" "terrasse peu profonde" "Detritique" "Frangeant ilot" "D1" 5 3 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120103" "SVR" "Ilot Hiengabat" NA "Ilot intermediaire" "ilot Hiengabat" 1 28 8 2012 NA NA NA 1 -999 NA "MM" "PC" -20.64888 164.98625 "HR" "AP" "Complexe de recif barriere imbrique" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "SA3" 5 4 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120116" "SVR" "Frangeant" NA "Frangeant" "cote Hienghene Koulnoue" 1 31 8 2012 NA NA NA 3 -999 NA "MD" "PC" -20.67966 164.97547 "HR" "AP" "Recif frangeant protege de lagons" "platier recifal" "Detritique" "Frangeant cotier" "D6" 5 11 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120130" "SVR" "Ilot Hienga" NA "Ilot intermediaire" "Yeega" 1 27 8 2012 NA NA NA 1 -999 NA "MM" "PC" -20.66328 165.04729 "RE" "AP" "Complexe de recif barriere imbrique" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "SA5" 5 11 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120136" "SVR" "Frangeant" NA "Frangeant" "cote N Hienghene" 1 30 8 2012 NA NA NA 2 -999 NA "MD" "PC" -20.64356 164.91257 "HR" "AP" "Recif frangeant protege de lagons" "platier recifal" "Detritique" "Frangeant cotier" "D5" 5 4 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120139" "SVR" "Frangeant" NA "Frangeant" "cote N Hienghene" 1 30 8 2012 NA NA NA 1 -999 NA "MD" "PC" -20.63544 164.89803 "HR" "AP" "Recif frangeant protege de lagons" "platier recifal" "Fond lagonaire" "Frangeant cotier" "SA3" 5 4 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120140" "SVR" "Ilot de sable" NA "Recif intermediaire" "Thabap" 1 30 8 2012 NA NA NA 1 -999 NA "MD" "PC" -20.62285 164.89888 "RC" "AP" "Complexe de recif barriere imbrique" "terrasse peu profonde" "Detritique" "Frangeant ilot" "D2" 5 2 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120141" "SVR" "Ilot Hienga" NA "Ilot intermediaire" "Yeega" 1 27 8 2012 NA NA NA 1 -999 NA "MM" "PC" -20.65969 165.04126 "RE" "AP" "Complexe de recif barriere imbrique" "recif barriere ennoye profond" "Detritique" "Recif intermediaire" "D7" 5 16 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120144" "SVR" "Ilot Hienga" NA "Fond lagonaire" "Yeega" 1 29 8 2012 NA NA "0" 0 -999 NA "MD" "PC" -20.66364 165.03625 "RE" "AP" "Complexe de recif barriere imbrique" "passe" "Fond lagonaire" "Fond lagonaire" "SA3" 5 19 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120146" "SVR" "Ilot Hienga" NA "Fond lagonaire" "Yeega" 1 29 8 2012 NA NA "0" 0 -999 NA "MD" "PC" -20.66298 165.01532 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA3" 5 19 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120147" "SVR" "Recif Pidanain" NA "Fond lagonaire" "Yeega" 1 28 8 2012 NA NA NA 1 -999 NA "MM" "PC" -20.6577 165.01228 "RE" "AP" "Complexe de recif barriere imbrique" "passe" "Fond lagonaire" "Fond lagonaire" "SA1" 5 20 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120148" "SVR" "Dongan Hiengu" NA "Barriere" "Dongan Hiengu HR Dohimen" 1 29 8 2012 NA NA "0" 0 -999 NA "MM" "PC" -20.64142 165.09772 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA3" 5 5 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120149" "SVR" "Recif Doiman" NA "Barriere" "Do himen Recif Doiman" 1 27 8 2012 NA NA NA 1 -999 NA "MM" "PC" -20.58962 165.14988 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA3" 5 6.5 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120150" "SVR" "Recif Doiman" NA "Barriere" "Do himen Recif Doiman" 1 27 8 2012 NA NA NA 1 -999 NA "MM" "PC" -20.59398 165.16853 "RE" "AP" "Complexe de recif barriere externe" "platier recifal" "Detritique" "Recif barriere interne" "D2" 5 3 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120156" "SVR" "Les Charpentiers" NA "Recif les charpentiers" "Les Charpentiers" 1 27 8 2012 NA NA NA 1 -999 NA "MM" "PC" -20.68562 165.02916 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse profonde" "Detritique" "Recif intermediaire" NA 5 8 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120158" "SVR" "Les Charpentiers" NA "Recif les charpentiers" "Les Charpentiers" 1 27 8 2012 NA NA NA 1 -999 NA "MM" "PC" -20.68737 165.0334 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse profonde" "Detritique" "Recif intermediaire" "D6" 5 13 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120160" "SVR" "Les Charpentiers" NA "Recif les charpentiers" "Les Charpentiers" 1 27 8 2012 NA NA NA 1 -999 NA "MM" "PC" -20.68736 165.036 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse profonde" "Detritique" "Recif intermediaire" "D5" 5 6 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120162" "SVR" "Ilot Hienga" NA "Ilot intermediaire" "ilot Hienga HR Yeega" 1 27 8 2012 NA NA NA 1 -999 NA "MM" "PC" -20.66583 165.05562 "HR" "AP" "Complexe de recif barriere imbrique" "terrasse peu profonde" "Corail vivant" "Frangeant ilot" "LC5" 5 3 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120163" "SVR" "Ilot Hienga" NA "Ilot intermediaire" "Yeega" 1 27 8 2012 NA NA NA 1 -999 NA "MM" "PC" -20.66011 165.05273 "RE" "AP" "Complexe de recif barriere imbrique" "platier recifal" "Corail vivant" "Frangeant ilot" "LC5" 5 4 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120168" "SVR" "Recif Pidanain" NA "Ilot intermediaire" "Yeega" 1 29 8 2012 NA NA "0" 0 -999 NA "MD" "PC" -20.65882 165.01808 "RE" "AP" "Complexe de recif barriere imbrique" "passe" "Detritique" "Frangeant ilot" "D5" 5 5 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120169" "SVR" "Ilot Hienghene" NA "Fond lagonaire" "ilot Hienghene et Tiguit" 1 29 8 2012 NA NA NA 1 -999 NA "MM" "PC" -20.6268 164.95154 "HR" "AP" "Ile lagonaire" "lagon profond" "Detritique" "Fond lagonaire" "D5" 5 5 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120170" "SVR" "Ilot Hienghene" NA "Ilot intermediaire" "ilot Hienghene et Tiguit" 1 29 8 2012 NA NA "0" 0 -999 NA "MM" "PC" -20.62194 164.935 "HR" "AP" "Complexe de recif barriere imbrique" "platier recifal" "Detritique" "Frangeant ilot" "SA5" 5 4 -999 -999 -999 -999 NA +"AMP" "HI120171" "SVR" "Ilot Hienghene" NA "Ilot intermediaire" "ilot Hienghene et Tiguit" 1 29 8 2012 NA NA "0" 0 -999 NA "MM" "PC" -20.6192 164.93739 "HR" "AP" "Complexe de recif barriere imbrique" "lagon enclave" "Detritique" "Frangeant ilot" "D5" 5 7 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120172" "SVR" "Ilot Hienghene" NA "Ilot intermediaire" "ilot Hienghene et Tiguit" 1 29 8 2012 NA NA "0" 0 -999 NA "MM" "PC" -20.6239 164.92984 "HR" "AP" "Complexe de recif barriere imbrique" "platier recifal ennoye" "Detritique" "Frangeant ilot" "D7" 5 6 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120173" "SVR" "Ilot Tiguit" NA "Ilot intermediaire" "ilot Hienghene et Tiguit" 1 29 8 2012 NA NA "0" 0 -999 NA "MM" "PC" -20.62065 164.92151 "HR" "AP" "Complexe de recif barriere imbrique" "front recifal ou terrasse" "Detritique" "Recif barriere externe" "D5" 5 12 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120174" "SVR" "Ilot Tiguit" NA "Ilot intermediaire" "ilot Hienghene et Tiguit" 1 29 8 2012 NA NA "0" 0 -999 NA "MM" "PC" -20.62468 164.91535 "HR" "AP" "Complexe de recif barriere imbrique" "terrasse peu profonde" "Detritique" "Frangeant ilot" "D2" 5 5 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120175" "SVR" "Ilot de sable" NA "Recif intermediaire" "Thabap" 1 30 8 2012 NA NA NA 1 -999 NA "MD" "PC" -20.61153 164.90121 "RC" "AP" "Complexe de recif barriere imbrique" "front recifal ou terrasse" "Corail vivant" "Recif barriere externe" "LC2" 5 5 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120176" "SVR" "Ilot de sable" NA "Recif intermediaire" "Thabap" 1 30 8 2012 NA NA NA 1 -999 NA "MD" "PC" -20.61958 164.89665 "RC" "AP" "Complexe de recif barriere imbrique" "terrasse peu profonde" "Detritique" "Frangeant ilot" "D1" 5 1.5 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120178" "SVR" "Frangeant" NA "Frangeant" "cote Hienghene Koulnoue" 1 31 8 2012 NA NA NA 1 -999 NA "MD" "PC" -20.69579 164.9998 "HR" "AP" "Ile lagonaire" "lagon profond" "Detritique" "Frangeant cotier" "SA5" 5 4 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120180" "SVR" "Frangeant" NA "Frangeant" "cote Hienghene Koulnoue" 1 31 8 2012 NA NA NA 2 -999 NA "MD" "PC" -20.69018 164.99171 "HR" "AP" "Recif frangeant protege de lagons" "platier recifal" "Detritique" "Frangeant cotier" NA 5 3 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120181" "SVR" "Frangeant" NA "Frangeant" "cote Hienghene Koulnoue" 1 31 8 2012 NA NA NA 2 -999 NA "MD" "PC" -20.68586 164.98517 "HR" "AP" "Recif frangeant protege de lagons" "platier recifal" "Detritique" "Frangeant cotier" NA 5 3 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120183" "SVR" "Ilot Hiengabat" NA "Recif intermediaire" "ilot Hiengabat" 1 31 8 2012 NA NA NA 3 -999 NA "MM" "PC" -20.65378 164.99719 "HR" "AP" "Complexe de recif barriere imbrique" "recif barriere ennoye profond" "Fond lagonaire" "Recif intermediaire" "SA3" 5 12 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120201" "SVR" "Recif Doiman" NA "Barriere" "Do himen Recif Doiman" 1 27 8 2012 NA NA NA 1 -999 NA "MM" "PC" -20.59 165.135 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Recif barriere interne" "D2" 5 4.5 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120204" "SVR" "Recif Doiman" NA "Barriere" "Do himen Recif Doiman" 1 28 8 2012 NA NA "0" 0 -999 NA "MM" "PC" -20.58528 165.1663 "RE" "AP" "Complexe de recif barriere externe" "front recifal" "Corail vivant" "Recif barriere externe" "LC1" 5 13.8 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120205" "SVR" "Recif Doiman" NA "Barriere" "Do himen Recif Doiman" 1 28 8 2012 NA NA "0" 0 -999 NA "MM" "PC" -20.58207 165.15513 "RE" "AP" "Complexe de recif barriere externe" "front recifal" "Corail vivant" "Recif barriere externe" "LC2" 5 4.3 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120210" "SVR" "Dongan Hiengu" NA "Barriere - dessus patate" "Dongan Hiengu HR Dohimen" 1 29 8 2012 NA NA NA 2 -999 NA "MM" "PC" -20.6332 165.08912 "HR" "AP" "Complexe de recif barriere externe" "passe" "Detritique" "Passe" "D7" 5 2.5 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120211" "SVR" "Dongan Hiengu" NA "Barriere - bas tombant" "Dongan Hiengu HR Dohimen" 1 29 8 2012 NA NA NA 2 -999 NA "MM" "PC" -20.632 165.091 "HR" "AP" "Complexe de recif barriere externe" "platier recifal" "Detritique" "Recif barriere externe" "D2" 5 16.6 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HI120212" "SVR" "Dongan Hienga" NA "Passe" "Donga Hienga" 1 29 8 2012 NA NA "0" 0 -999 NA "MM" "PC" -20.61568 165.04673 "HR" "AP" "Complexe de recif barriere externe" "platier recifal ennoye" "Detritique" "Recif barriere interne" "D2" 5 6.8 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "HU140031" "SVR" "Hunter" NA NA NA 3 3 7 2014 "08:09" NA "SE" 2 2 NA "MM" "LM" -22.39302 172.09004 "HR" "AP" "" "" "Detritique" "Frangeant oceanique" NA 10 7 -999 -999 -999 -999 "William Roman" +"AMP" "HU140032" "SVR" "Hunter" NA NA NA 3 3 7 2014 "08:20" NA "SE" 2 2 NA "MM" "LM" -22.39446 172.09077 "HR" "AP" "" "" "Detritique" "Frangeant oceanique" NA 10 15 -999 -999 -999 -999 "William Roman" +"AMP" "HU140033" "SVR" "Hunter" NA NA NA 3 3 7 2014 "08:40" NA "SE" 2 2 NA "PM" "LM" -22.39038 172.0894 "HR" "AP" "" "" "Corail vivant" "Frangeant oceanique" "LC3" 10 12 -999 -999 -999 -999 "William Roman" +"AMP" "HU140034" "SVR" "Hunter" NA NA NA 3 3 7 2014 "09:01" NA "SE" 2 2 NA "PM" "LM" -22.38964 172.08797 "HR" "AP" "" "" "Detritique" "Frangeant oceanique" NA 10 13 -999 -999 -999 -999 "William Roman" +"AMP" "HU140035" "SVR" "Hunter" NA NA NA 3 3 7 2014 "09:15" NA "SE" 2 2 NA "PM" "LM" -22.38981 172.08551 "HR" "AP" "" "" "Detritique" "Frangeant oceanique" NA 10 15 -999 -999 -999 -999 "William Roman" +"AMP" "HU140036" "SVR" "Hunter" NA NA NA 3 3 7 2014 "09:40" NA "SE" 2 2 NA "PM" "LM" -22.39074 172.08377 "HR" "AP" "" "" "Corail vivant" "Frangeant oceanique" "LC3" 10 11 -999 -999 -999 -999 "William Roman" +"AMP" "KO070051" "SVR" NA NA "Fond lagonaire" "faible" 1 5 12 2007 NA NA NA -999 -999 NA "MD" "DC" -21.06514 164.67511 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" -999 1.1 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070056" "SVR" NA NA "Fond lagonaire" "faible" 1 4 12 2007 NA NA NA -999 -999 NA "PM" "DC" -21.06938 164.67505 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA1" -999 2.4 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070068" "SVR" NA NA "Frangeant" "faible" 1 4 12 2007 NA NA NA -999 -999 NA "MM" "DC" -21.07558 164.68788 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA3" -999 2.2 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070069" "SVR" NA NA "Fond lagonaire" "faible" 1 4 12 2007 NA NA NA -999 -999 NA "MM" "DC" -21.07333 164.68443 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" -999 1.4 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070070" "SVR" NA NA "Fond lagonaire" "faible" 1 4 12 2007 NA NA NA -999 -999 NA "MM" "DC" -21.07405 164.67992 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" -999 1.5 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070073" "SVR" NA NA "Frangeant" "faible" 1 4 12 2007 NA NA NA -999 -999 NA "MM" "DC" -21.07845 164.68956 "RC" "AP" "Recif frangeant de recif barriere cotier" "frangeant diffus" "Fond lagonaire" "Frangeant cotier" "SA1" -999 1.4 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070082" "SVR" NA NA "Frangeant" "faible" 1 4 12 2007 NA NA NA -999 -999 NA "MM" "DC" -21.08303 164.68973 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" -999 1.4 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070083" "SVR" NA NA "Fond lagonaire" "faible" 1 4 12 2007 NA NA NA -999 -999 NA "MM" "DC" -21.08321 164.68481 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" -999 1.9 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070084" "SVR" NA NA "Barriere" "faible" 1 4 12 2007 NA NA NA -999 -999 NA "MM" "DC" -21.08278 164.68121 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Detritique" "Fond lagonaire" "D2" -999 2.6 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070085" "SVR" NA NA "Barriere" "faible" 1 4 12 2007 NA NA NA -999 -999 NA "MM" "DC" -21.08815 164.68559 "RC" "AP" "Complexe de recif barriere cotier" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA1" -999 2.7 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070086" "SVR" NA NA "Fond lagonaire" "faible" 1 4 12 2007 NA NA NA -999 -999 NA "MM" "DC" -21.08747 164.68991 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" -999 1.8 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070087" "SVR" NA NA "Frangeant" "faible" 1 4 12 2007 NA NA NA -999 -999 NA "MM" "DC" -21.08782 164.69389 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA3" -999 1.3 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070093" "SVR" NA NA "Fond lagonaire" "faible" 1 4 12 2007 NA NA NA -999 -999 NA "MM" "DC" -21.0922 164.69925 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" -999 1.1 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070095" "SVR" NA NA "Barriere" "faible" 1 4 12 2007 NA NA NA -999 -999 NA "MM" "DC" -21.09159 164.68991 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" -999 1.6 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070099" "SVR" NA NA "Fond lagonaire" "faible" 1 4 12 2007 NA NA NA -999 -999 NA "MM" "DC" -21.09673 164.69424 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" -999 0.9 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070100" "SVR" NA NA "Barriere" "faible" 1 4 12 2007 NA NA NA -999 -999 NA "MM" "DC" -21.09616 164.68964 "RC" "AP" "Complexe de recif barriere cotier" "platier recifal" "Detritique" "Recif barriere interne" "D6" -999 1.1 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070101" "SVR" NA NA "Barriere" "faible" 1 4 12 2007 NA NA NA -999 -999 NA "MM" "DC" -21.10102 164.68941 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA3" -999 1.3 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070102" "SVR" NA NA "Fond lagonaire" "faible" 1 4 12 2007 NA NA NA -999 -999 NA "MM" "DC" -21.10119 164.69424 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" -999 1.4 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070103" "SVR" NA NA "Fond lagonaire" "faible" 1 4 12 2007 NA NA NA -999 -999 NA "MM" "DC" -21.10099 164.6992 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" -999 1.3 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070107" "SVR" NA NA "Frangeant" "faible" 1 4 12 2007 NA NA NA -999 -999 NA "MM" "DC" -21.10582 164.70367 "RC" "AP" "Recif frangeant de recif barriere cotier" "platier recifal" "Fond lagonaire" "Frangeant cotier" "SA3" -999 0.9 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070108" "SVR" NA NA "Fond lagonaire" "faible" 1 4 12 2007 NA NA NA -999 -999 NA "MM" "DC" -21.10586 164.69908 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" -999 1.3 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070109" "SVR" NA NA "Fond lagonaire" "faible" 1 4 12 2007 NA NA NA -999 -999 NA "MM" "DC" -21.10586 164.69446 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" -999 1.6 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070110" "SVR" NA NA "Fond lagonaire" "faible" 1 4 12 2007 NA NA NA -999 -999 NA "MM" "DC" -21.10579 164.68959 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Detritique" "Fond lagonaire" "SA4" -999 2.1 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070111" "SVR" NA NA "Fond lagonaire" "faible" 1 3 12 2007 NA NA NA -999 -999 NA "MM" "DC" -21.11025 164.68851 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Detritique" "Fond lagonaire" "D7" -999 1.5 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070112" "SVR" NA NA "Fond lagonaire" "faible" 1 3 12 2007 NA NA NA -999 -999 NA "MM" "DC" -21.1103 164.69455 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" -999 1.5 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070113" "SVR" NA NA "Herbier" "faible" 1 3 12 2007 NA NA NA -999 -999 NA "MM" "DC" -21.11031 164.69916 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Herbier" "Fond lagonaire" "SG1" -999 1.5 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070114" "SVR" NA NA "Herbier" "faible" 1 3 12 2007 NA NA NA -999 -999 NA "MM" "DC" -21.11035 164.70399 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Herbier" "Fond lagonaire" "SG2" -999 1.5 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070116" "SVR" NA NA "Frangeant" "faible" 1 3 12 2007 NA NA NA -999 -999 NA "MM" "DC" -21.11494 164.70877 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA3" -999 1.5 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070117" "SVR" NA NA "Fond lagonaire" "faible" 1 3 12 2007 NA NA NA -999 -999 NA "MM" "DC" -21.11502 164.70438 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA5" -999 1.5 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070118" "SVR" NA NA "Herbier" "faible" 1 3 12 2007 NA NA NA -999 -999 NA "MM" "DC" -21.11492 164.69902 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Herbier" "Fond lagonaire" "SG1" -999 1.5 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070119" "SVR" NA NA "Fond lagonaire" "faible" 1 3 12 2007 NA NA NA -999 -999 NA "MM" "DC" -21.11487 164.69429 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" -999 1.5 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070120" "SVR" NA NA "Barriere" "faible" 1 3 12 2007 NA NA NA -999 -999 NA "MM" "DC" -21.11494 164.68973 "RC" "AP" "" "" "Fond lagonaire" "Recif barriere interne" "SA4" -999 1.5 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070121" "SVR" NA NA "Fond lagonaire" "faible" 1 3 12 2007 NA NA NA -999 -999 NA "MD" "DC" -21.11923 164.70882 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA3" -999 1.5 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070122" "SVR" NA NA "Fond lagonaire" "faible" 1 3 12 2007 NA NA NA -999 -999 NA "MM" "DC" -21.11694 164.69284 "RC" "AP" "" "" "Fond lagonaire" "Recif barriere interne" "SA1" -999 1.5 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070123" "SVR" NA NA "Fond lagonaire" "faible" 1 3 12 2007 NA NA NA -999 -999 NA "PM" "DC" -21.11827 164.70061 "RC" "AP" "" "" "Fond lagonaire" "Recif barriere interne" "SA3" -999 1.5 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070124" "SVR" NA NA "Barriere" "faible" 1 4 12 2007 NA NA NA -999 -999 NA "BM" "DC" -21.10594 164.68741 "RC" "AP" "Complexe de recif barriere cotier" "platier recifal" "Detritique" "Recif barriere interne" "D6" -999 1.9 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070127" "SVR" NA NA "Fond lagonaire" "faible" 1 5 12 2007 NA NA NA -999 -999 NA "BM" "DC" -21.12383 164.71164 "HR" "AP" "Complexe de recif barriere externe" "passe" "Detritique" "Passe" "D1" -999 2.9 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070129" "SVR" NA NA "Passe" "pas" 1 5 12 2007 NA NA NA -999 -999 NA "MM" "DC" -21.13117 164.70966 "HR" "AP" "Complexe de recif barriere externe" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA3" -999 4.3 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070131" "SVR" NA NA "Passe" "pas" 1 5 12 2007 NA NA NA -999 -999 NA "MM" "DC" -21.13464 164.71162 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA3" -999 2.6 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070132" "SVR" NA NA "Barriere" "pas" 1 5 12 2007 NA NA NA -999 -999 NA "MM" "DC" -21.13885 164.71094 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA3" -999 3.6 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070133" "SVR" NA NA "Barriere" "pas" 1 5 12 2007 NA NA NA -999 -999 NA "MM" "DC" -21.14282 164.71455 "HR" "AP" "Complexe de recif barriere externe" "platier recifal" "Detritique" "Recif barriere interne" "D2" -999 1.9 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070134" "SVR" NA NA "Barriere" "pas" 1 6 12 2007 NA NA NA -999 -999 NA "MM" "DC" -21.14761 164.7132 "HR" "AP" "Complexe de recif barriere externe" "platier recifal" "Detritique" "Recif barriere interne" "D1" -999 2.7 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070135" "SVR" NA NA "Barriere" "pas" 1 5 12 2007 NA NA NA -999 -999 NA "MM" "DC" -21.15124 164.71729 "HR" "AP" "Complexe de recif barriere externe" "platier recifal" "Detritique" "Recif barriere interne" "D2" -999 3.4 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070136" "SVR" NA NA "Barriere" "pas" 1 5 12 2007 NA NA NA -999 -999 NA "MM" "DC" -21.15579 164.71967 "HR" "AP" "Complexe de recif barriere externe" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA3" -999 2.6 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070138" "SVR" NA NA "Barriere" "pas" 1 5 12 2007 NA NA NA -999 -999 NA "MM" "DC" -21.16028 164.72147 "HR" "AP" "Complexe de recif barriere externe" "platier recifal" "Detritique" "Recif barriere interne" "SA5" -999 3.6 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070139" "SVR" NA NA "Barriere" "pas" 1 5 12 2007 NA NA NA -999 -999 NA "MM" "DC" -21.16483 164.72336 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Fond lagonaire" "D2" -999 2.4 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070141" "SVR" NA NA "Barriere" "pas" 1 5 12 2007 NA NA NA -999 -999 NA "MM" "DC" -21.17542 164.7224 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Fond lagonaire" NA -999 3.1 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070142" "SVR" NA NA "Barriere" "pas" 1 5 12 2007 NA NA NA -999 -999 NA "MM" "DC" -21.18059 164.72208 "HR" "AP" "Complexe de recif barriere externe" "platier recifal" "Detritique" "Recif barriere interne" "D1" -999 2.6 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070143" "SVR" NA NA "Barriere" "pas" 1 5 12 2007 NA NA NA -999 -999 NA "MM" "DC" -21.18216 164.72772 "HR" "AP" "Complexe de recif barriere externe" "platier recifal" "Detritique" "Recif barriere interne" "D1" -999 3 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070144" "SVR" NA NA "Barriere" "pas" 1 5 12 2007 NA NA NA -999 -999 NA "MM" "DC" -21.18286 164.73308 "HR" "AP" "Complexe de recif barriere externe" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA3" -999 3.5 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070145" "SVR" NA NA "Barriere" "pas" 1 5 12 2007 NA NA NA -999 -999 NA "MM" "DC" -21.184 164.73853 "HR" "AP" "Complexe de recif barriere externe" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA5" -999 3.1 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070146" "SVR" NA NA "Barriere" "pas" 1 5 12 2007 NA NA NA -999 -999 NA "MD" "DC" -21.18704 164.74272 "HR" "AP" "Complexe de recif barriere externe" "platier recifal" "Detritique" "Recif barriere interne" "D1" -999 2.8 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070147" "SVR" NA NA "Barriere" "pas" 1 6 12 2007 NA NA NA -999 -999 NA "MD" "DC" -21.18979 164.74684 "HR" "AP" "Complexe de recif barriere externe" "platier recifal" "Detritique" "Recif barriere interne" "D1" -999 2.4 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070148" "SVR" NA NA "Fond lagonaire" "pas" 1 6 12 2007 NA NA NA -999 -999 NA "MD" "DC" -21.18392 164.74693 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA2" -999 2.6 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070149" "SVR" NA NA "Fond lagonaire" "pas" 1 6 12 2007 NA NA NA -999 -999 NA "MD" "DC" -21.17534 164.72792 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" -999 3.2 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070150" "SVR" NA NA "Fond lagonaire" "pas" 1 6 12 2007 NA NA NA -999 -999 NA "MD" "DC" -21.17523 164.73331 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA2" -999 3.2 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070151" "SVR" NA NA "Fond lagonaire" "pas" 1 6 12 2007 NA NA NA -999 -999 NA "MD" "DC" -21.1752 164.73865 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" -999 4.4 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070152" "SVR" NA NA "Barriere" "pas" 1 6 12 2007 NA NA NA -999 -999 NA "MD" "DC" -21.17504 164.74394 "HR" "AP" "Complexe de recif barriere imbrique" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA2" -999 1.6 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070153" "SVR" NA NA "Barriere" "pas" 1 6 12 2007 NA NA NA -999 -999 NA "MD" "DC" -21.16482 164.74382 "HR" "AP" "Complexe de recif barriere imbrique" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA2" -999 2.8 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070154" "SVR" NA NA "Fond lagonaire" "pas" 1 6 12 2007 NA NA NA -999 -999 NA "MD" "DC" -21.16441 164.73622 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" -999 4.2 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070155" "SVR" NA NA "Fond lagonaire" "pas" 1 6 12 2007 NA NA NA -999 -999 NA "MD" "DC" -21.16436 164.72881 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" -999 2.2 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070156" "SVR" NA NA "Barriere" "pas" 1 6 12 2007 NA NA NA -999 -999 NA "MD" "DC" -21.15531 164.72888 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Corail vivant" "Fond lagonaire" "LC5" -999 4.2 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070157" "SVR" NA NA "Barriere" "pas" 1 6 12 2007 NA NA NA -999 -999 NA "MD" "DC" -21.15494 164.7361 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" -999 3.6 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070158" "SVR" NA NA "Fond lagonaire" "pas" 1 6 12 2007 NA NA NA -999 -999 NA "MD" "DC" -21.15473 164.74301 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA2" -999 4 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070159" "SVR" NA NA "Fond lagonaire" "pas" 1 6 12 2007 NA NA NA -999 -999 NA "MM" "DC" -21.15466 164.74991 "HR" "AP" "Complexe de recif barriere imbrique" "platier recifal" "Fond lagonaire" "Recif intermediaire" "SA1" -999 3.7 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070161" "SVR" NA NA "Fond lagonaire" "pas" 1 6 12 2007 NA NA NA -999 -999 NA "MM" "DC" -21.14735 164.73671 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" -999 4.4 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070162" "SVR" NA NA "Fond lagonaire" "pas" 1 6 12 2007 NA NA NA -999 -999 NA "MM" "DC" -21.1478 164.72945 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" -999 5.1 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070164" "SVR" NA NA "Barriere" "pas" 1 6 12 2007 NA NA NA -999 -999 NA "MM" "DC" -21.13897 164.71823 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" -999 3 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070165" "SVR" NA NA "Fond lagonaire" "pas" 1 6 12 2007 NA NA NA -999 -999 NA "MM" "DC" -21.13895 164.72566 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" -999 6.8 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070166" "SVR" NA NA "Fond lagonaire" "pas" 1 6 12 2007 NA NA NA -999 -999 NA "MM" "DC" -21.13868 164.73447 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA2" -999 5.1 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070169" "SVR" NA NA "Fond lagonaire" "pas" 1 6 12 2007 NA NA NA -999 -999 NA "MM" "DC" -21.13063 164.72707 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" -999 8.5 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070170" "SVR" NA NA "Barriere" "pas" 1 6 12 2007 NA NA NA -999 -999 NA "MM" "DC" -21.13065 164.72044 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA3" -999 7.1 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070172" "SVR" NA NA "Fond lagonaire" "pas" 1 7 12 2007 NA NA NA -999 -999 NA "MD" "DC" -21.17511 164.75179 "HR" "AP" "Complexe de recif barriere imbrique" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA2" -999 1.6 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070173" "SVR" NA NA "Fond lagonaire" "pas" 1 7 12 2007 NA NA NA -999 -999 NA "MD" "DC" -21.17469 164.76003 "HR" "AP" "Complexe de recif barriere imbrique" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" -999 2.4 -999 -999 -999 -999 "Guilpart" +"AMP" "KO070174" "SVR" NA NA "Fond lagonaire" "pas" 1 7 12 2007 NA NA NA -999 -999 NA "MD" "DC" -21.16389 164.75366 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA2" -999 4.1 -999 -999 -999 -999 "Guilpart" +"AMP" "KO080001" "SVR" NA NA "Barriere" "fort" 1 20 2 2008 NA NA NA -999 -999 NA "MD" "LM" -21.04689 164.62271 "RC" "AP" "Complexe de recif barriere cotier" "platier recifal" "Detritique" "Recif barriere interne" "D6" -999 2.1 -999 -999 -999 -999 "Guilpart" +"AMP" "KO080003" "SVR" NA NA "Fond lagonaire" "pas" 1 22 2 2008 NA NA NA -999 -999 NA "MM" "LD" -21.18904 164.77612 "HR" "AP" "Complexe de recif barriere imbrique" "front recifal ou terrasse" "Fond lagonaire" "Recif intermediaire" "SA2" -999 4.2 -999 -999 -999 -999 "Guilpart" +"AMP" "KO080004" "SVR" NA NA "Recif intermediaire" "fort" 1 20 2 2008 NA NA NA -999 -999 NA "MM" "LM" -21.04108 164.65234 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" -999 2.6 -999 -999 -999 -999 "Guilpart" +"AMP" "KO080005" "SVR" NA NA "Fond lagonaire" "fort" 1 20 2 2008 NA NA NA -999 -999 NA "MM" "LM" -21.04293 164.64203 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" -999 2 -999 -999 -999 -999 "Guilpart" +"AMP" "KO080006" "SVR" NA NA "Fond lagonaire" "fort" 1 20 2 2008 NA NA NA -999 -999 NA "MM" "LM" -21.0426 164.63264 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA3" -999 3.2 -999 -999 -999 -999 "Guilpart" +"AMP" "KO080007" "SVR" NA NA "Barriere" "fort" 1 20 2 2008 NA NA NA -999 -999 NA "MD" "LM" -21.04245 164.6246 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA2" -999 1.5 -999 -999 -999 -999 "Guilpart" +"AMP" "KO080008" "SVR" NA NA "Barriere" "fort" 1 20 2 2008 NA NA NA -999 -999 NA "MD" "LM" -21.03814 164.62219 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA4" -999 1.5 -999 -999 -999 -999 "Guilpart" +"AMP" "KO080011" "SVR" NA NA "Fond lagonaire" "fort" 1 20 2 2008 NA NA NA -999 -999 NA "MM" "LM" -21.03376 164.65198 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde a champ de constructions coralliennes" "Fond lagonaire" "Recif intermediaire" "SA2" -999 5.1 -999 -999 -999 -999 "Guilpart" +"AMP" "KO080012" "SVR" NA NA "Recif intermediaire" "fort" 1 20 2 2008 NA NA NA -999 -999 NA "MM" "LM" -21.03386 164.64255 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde a champ de constructions coralliennes" "Fond lagonaire" "Recif intermediaire" "SA2" -999 2.5 -999 -999 -999 -999 "Guilpart" +"AMP" "KO080013" "SVR" NA NA "Recif intermediaire" "fort" 1 20 2 2008 NA NA NA -999 -999 NA "MD" "LM" -21.03365 164.63284 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde a champ de constructions coralliennes" "Fond lagonaire" "Recif intermediaire" "SA4" -999 3.8 -999 -999 -999 -999 "Guilpart" +"AMP" "KO080014" "SVR" NA NA "Barriere" "fort" 1 20 2 2008 NA NA NA -999 -999 NA "MD" "LM" -21.03457 164.62125 "RC" "AP" "Complexe de recif barriere cotier" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA2" -999 1.8 -999 -999 -999 -999 "Guilpart" +"AMP" "KO080015" "SVR" NA NA "Fond lagonaire" "fort" 1 18 2 2008 NA NA NA -999 -999 NA "MM" "LM" -21.02938 164.63762 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde a champ de constructions coralliennes" "Fond lagonaire" "Recif intermediaire" "SA5" -999 2.6 -999 -999 -999 -999 "Guilpart" +"AMP" "KO080016" "SVR" NA NA "Recif intermediaire" "fort" 1 18 2 2008 NA NA NA -999 -999 NA "MD" "LM" -21.02923 164.6472 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde a champ de constructions coralliennes" "Fond lagonaire" "Recif intermediaire" "SA2" -999 2.7 -999 -999 -999 -999 "Guilpart" +"AMP" "KO080017" "SVR" NA NA "Fond lagonaire" "fort" 1 18 2 2008 NA NA NA -999 -999 NA "MM" "LM" -21.02959 164.62756 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA3" -999 5.7 -999 -999 -999 -999 "Guilpart" +"AMP" "KO080018" "SVR" NA NA "Barriere" "fort" 1 18 2 2008 NA NA NA -999 -999 NA "MM" "LM" -21.02942 164.61761 "RC" "AP" "Complexe de recif barriere cotier" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA1" -999 1.9 -999 -999 -999 -999 "Guilpart" +"AMP" "KO080021" "SVR" NA NA "Recif intermediaire" "fort" 1 18 2 2008 NA NA NA -999 -999 NA "MD" "LM" -21.02473 164.65172 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Recif intermediaire" "SA3" -999 6.6 -999 -999 -999 -999 "Guilpart" +"AMP" "KO080022" "SVR" NA NA "Recif intermediaire" "fort" 1 18 2 2008 NA NA NA -999 -999 NA "BM" "LM" -21.02453 164.64168 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Corail vivant" "Recif intermediaire" "LC4" -999 7.4 -999 -999 -999 -999 "Guilpart" +"AMP" "KO080023" "SVR" NA NA "Fond lagonaire" "fort" 1 18 2 2008 NA NA NA -999 -999 NA "MM" "LM" -21.02476 164.63287 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde a champ de constructions coralliennes" "Detritique" "Recif intermediaire" NA -999 3 -999 -999 -999 -999 "Guilpart" +"AMP" "KO080024" "SVR" NA NA "Fond lagonaire" "fort" 1 18 2 2008 NA NA NA -999 -999 NA "MM" "LM" -21.02459 164.62268 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA3" -999 4.2 -999 -999 -999 -999 "Guilpart" +"AMP" "KO080026" "SVR" NA NA "Fond lagonaire" "fort" 1 18 2 2008 NA NA NA -999 -999 NA "MM" "LM" -21.02064 164.62756 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Corail vivant" "Fond lagonaire" "LC4" -999 3.2 -999 -999 -999 -999 "Guilpart" +"AMP" "KO080027" "SVR" NA NA "Fond lagonaire" "fort" 1 18 2 2008 NA NA NA -999 -999 NA "MM" "LM" -21.02056 164.63771 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Corail vivant" "Fond lagonaire" "LC6" -999 5.1 -999 -999 -999 -999 "Guilpart" +"AMP" "KO080028" "SVR" NA NA "Fond lagonaire" "fort" 1 18 2 2008 NA NA NA -999 -999 NA "MM" "LM" -21.02052 164.61832 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA2" -999 2.3 -999 -999 -999 -999 "Guilpart" +"AMP" "KO080029" "SVR" NA NA "Barriere" "fort" 1 18 2 2008 NA NA NA -999 -999 NA "MM" "LM" -21.01997 164.61118 "RC" "AP" "Complexe de recif barriere cotier" "bassin residuel" "Fond lagonaire" "Recif barriere interne" "SA2" -999 2.3 -999 -999 -999 -999 "Guilpart" +"AMP" "KO080031" "SVR" NA NA "Frangeant" "fort" 1 18 2 2008 NA NA NA -999 -999 NA "MD" "LM" -21.01537 164.66148 "RC" "AP" "Recif frangeant de recif barriere cotier" "frangeant diffus" "Fond lagonaire" "Frangeant cotier" "SA2" -999 2.4 -999 -999 -999 -999 "Guilpart" +"AMP" "KO080033" "SVR" NA NA "Fond lagonaire" "fort" 1 18 2 2008 NA NA NA -999 -999 NA "MM" "LM" -21.01595 164.63275 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Detritique" "Fond lagonaire" "D3" -999 5.5 -999 -999 -999 -999 "Guilpart" +"AMP" "KO080034" "SVR" NA NA "Fond lagonaire" "fort" 1 18 2 2008 NA NA NA -999 -999 NA "MM" "LM" -21.01537 164.62381 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA3" -999 4.7 -999 -999 -999 -999 "Guilpart" +"AMP" "KO080035" "SVR" NA NA "Fond lagonaire" "fort" 1 18 2 2008 NA NA NA -999 -999 NA "MM" "LM" -21.01561 164.61386 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA2" -999 1.5 -999 -999 -999 -999 "Guilpart" +"AMP" "KO080037" "SVR" NA NA "Fond lagonaire" "fort" 1 19 2 2008 NA NA NA -999 -999 NA "MM" "LM" -21.01166 164.61829 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA2" -999 2.4 -999 -999 -999 -999 "Guilpart" +"AMP" "KO080038" "SVR" NA NA "Fond lagonaire" "fort" 1 19 2 2008 NA NA NA -999 -999 NA "MD" "LM" -21.01021 164.62039 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" -999 1.9 -999 -999 -999 -999 "Guilpart" +"AMP" "KO080042" "SVR" NA NA "Fond lagonaire" "fort" 1 19 2 2008 NA NA NA -999 -999 NA "MM" "LM" -21.00673 164.62323 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA2" -999 3.2 -999 -999 -999 -999 "Guilpart" +"AMP" "KO080043" "SVR" NA NA "Barriere" "fort" 1 19 2 2008 NA NA NA -999 -999 NA "MD" "LM" -21.00639 164.61336 "RC" "AP" "Complexe de recif barriere cotier" "platier recifal" "Detritique" "Recif barriere interne" "D2" -999 1.3 -999 -999 -999 -999 "Guilpart" +"AMP" "KO080044" "SVR" NA NA "Recif intermediaire" "fort" 1 19 2 2008 NA NA NA -999 -999 NA "MD" "LM" -20.99333 164.62961 "HR" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA4" -999 1.6 -999 -999 -999 -999 "Guilpart" +"AMP" "KO080055" "SVR" NA NA "Herbier" "faible" 1 21 2 2008 NA NA NA -999 -999 NA "MD" "PL" -20.9837 164.6133 "HR" "AP" "Complexe de recif barriere externe" "passe" "Fond lagonaire" "Recif barriere interne" NA -999 7.5 -999 -999 -999 -999 "Guilpart" +"AMP" "KO080057" "SVR" NA NA "Fond lagonaire" "fort" 1 19 2 2008 NA NA NA -999 -999 NA "MM" "LM" -21.00674 164.61812 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Detritique" "Fond lagonaire" "D2" -999 1.4 -999 -999 -999 -999 "Guilpart" +"AMP" "KO080181" "SVR" NA NA "Fond lagonaire" "faible" 1 20 2 2008 NA NA NA -999 -999 NA "MD" "LM" -21.06116 164.67123 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA3" -999 1.6 -999 -999 -999 -999 "Guilpart" +"AMP" "KO080183" "SVR" NA NA "Barriere" "faible" 1 20 2 2008 NA NA NA -999 -999 NA "MD" "LM" -21.06152 164.66086 "RC" "AP" "Complexe de recif barriere cotier" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA4" -999 1.9 -999 -999 -999 -999 "Guilpart" +"AMP" "KO080184" "SVR" NA NA "Barriere" "faible" 1 20 2 2008 NA NA NA -999 -999 NA "MD" "LM" -21.06006 164.65764 "RC" "AP" "Complexe de recif barriere cotier" "platier recifal" "Detritique" "Recif barriere interne" "SA5" -999 2 -999 -999 -999 -999 "Guilpart" +"AMP" "KO080185" "SVR" NA NA "Fond lagonaire" "faible" 1 20 2 2008 NA NA NA -999 -999 NA "MD" "LM" -21.05626 164.67068 "RC" "AP" "Complexe de recif barriere cotier" "lagon enclave" "Fond lagonaire" "Fond lagonaire" "MA4" -999 3 -999 -999 -999 -999 "Guilpart" +"AMP" "KO080187" "SVR" NA NA "Fond lagonaire" "faible" 1 20 2 2008 NA NA NA -999 -999 NA "MM" "LM" -21.05639 164.66124 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" -999 1.4 -999 -999 -999 -999 "Guilpart" +"AMP" "KO080189" "SVR" NA NA "Barriere" "fort" 1 20 2 2008 NA NA NA -999 -999 NA "MD" "LM" -21.05626 164.65167 "RC" "AP" "Complexe de recif barriere cotier" "platier recifal" "Corail vivant" "Recif barriere interne" "LC5" -999 2 -999 -999 -999 -999 "Guilpart" +"AMP" "KO080192" "SVR" NA NA "Recif intermediaire" "faible" 1 20 2 2008 NA NA NA -999 -999 NA "MM" "LM" -21.0518 164.6617 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Recif intermediaire" "SA3" -999 2 -999 -999 -999 -999 "Guilpart" +"AMP" "KO080194" "SVR" NA NA "Recif intermediaire" "fort" 1 20 2 2008 NA NA NA -999 -999 NA "MD" "LM" -21.05133 164.65166 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA2" -999 1.7 -999 -999 -999 -999 "Guilpart" +"AMP" "KO080196" "SVR" NA NA "Barriere" "fort" 1 20 2 2008 NA NA NA -999 -999 NA "MD" "LM" -21.05118 164.64172 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Detritique" "Fond lagonaire" "D2" -999 1.7 -999 -999 -999 -999 "Guilpart" +"AMP" "KO080197" "SVR" NA NA "Barriere" "fort" 1 20 2 2008 NA NA NA -999 -999 NA "MD" "LM" -21.05198 164.63693 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Detritique" "Recif barriere interne" "D4" -999 2.2 -999 -999 -999 -999 "Guilpart" +"AMP" "KO080199" "SVR" NA NA "Barriere" "fort" 1 20 2 2008 NA NA NA -999 -999 NA "MD" "LM" -21.05229 164.63226 "RC" "AP" "Complexe de recif barriere cotier" "platier recifal" "Detritique" "Recif barriere interne" "D6" -999 1.6 -999 -999 -999 -999 "Guilpart" +"AMP" "KO080201" "SVR" NA NA "Barriere" "fort" 1 20 2 2008 NA NA NA -999 -999 NA "MD" "LM" -21.05078 164.62422 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Detritique" "Fond lagonaire" "D2" -999 1.5 -999 -999 -999 -999 "Guilpart" +"AMP" "KO08go02" "SVR" NA NA "Fond lagonaire" "pas" 1 22 2 2008 NA NA NA -999 -999 NA "MM" "LD" -21.17977 164.77592 "HR" "AP" "Complexe de recif barriere imbrique" "front recifal ou terrasse" "Fond lagonaire" "Recif intermediaire" "SA1" -999 4 -999 -999 -999 -999 "Guilpart" +"AMP" "KO08go04" "SVR" NA NA "Fond lagonaire" "pas" 1 22 2 2008 NA NA NA -999 -999 NA "MM" "LD" -21.19445 164.77823 "HR" "AP" "Complexe de recif barriere imbrique" "front recifal ou terrasse" "Fond lagonaire" "Recif barriere interne" "SA3" -999 5.5 -999 -999 -999 -999 "Guilpart" +"AMP" "KO08go05" "SVR" NA NA "Fond lagonaire" "pas" 1 22 2 2008 NA NA NA -999 -999 NA "MM" "LD" -21.20723 164.77248 "HR" "AP" "Complexe de recif barriere imbrique" "front recifal ou terrasse" "Detritique" "Recif barriere interne" "SA5" -999 4.1 -999 -999 -999 -999 "Guilpart" +"AMP" "KO08go13" "SVR" NA NA "Fond lagonaire" "pas" 1 22 2 2008 NA NA NA -999 -999 NA "MD" "LD" -21.24102 164.77524 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA3" -999 3.6 -999 -999 -999 -999 "Guilpart" +"AMP" "KO08go14" "SVR" NA NA "Recif intermediaire" "pas" 1 22 2 2008 NA NA NA -999 -999 NA "PM" "LD" -21.24012 164.76489 "HR" "AP" "Complexe de recif barriere externe" "platier recifal" "Detritique" "Recif barriere interne" "D2" -999 3.1 -999 -999 -999 -999 "Guilpart" +"AMP" "KO08go15" "SVR" NA NA "Recif intermediaire" "pas" 1 22 2 2008 NA NA NA -999 -999 NA "MD" "LD" -21.24049 164.76944 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA3" -999 2.6 -999 -999 -999 -999 "Guilpart" +"AMP" "KO08go16" "SVR" NA NA "Recif intermediaire" "pas" 1 22 2 2008 NA NA NA -999 -999 NA "MD" "LD" -21.24368 164.77383 "HR" "AP" "Complexe de recif barriere externe" "platier recifal" "Detritique" "Recif barriere interne" "D1" -999 3.3 -999 -999 -999 -999 "Guilpart" +"AMP" "KO08go19" "SVR" NA NA "Recif intermediaire" "pas" 1 22 2 2008 NA NA NA -999 -999 NA "MD" "LD" -21.25277 164.78437 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Recif barriere interne" "D5" -999 3.1 -999 -999 -999 -999 "Guilpart" +"AMP" "KO08Pm02" "SVR" NA NA "Recif intermediaire" "faible" 1 21 2 2008 NA NA NA -999 -999 NA "MD" "PL" -20.97939 164.61046 "HR" "AP" "Complexe de recif barriere externe" "lagon enclave" "Detritique" "Recif barriere interne" "SA4" -999 1.8 -999 -999 -999 -999 "Guilpart" +"AMP" "KO08Pm03" "SVR" NA NA "Recif intermediaire" "faible" 1 21 2 2008 NA NA NA -999 -999 NA "MD" "PL" -20.97393 164.60641 "HR" "AP" "Complexe de recif barriere imbrique" "platier recifal" "Fond lagonaire" "Recif intermediaire" "SA3" -999 1.6 -999 -999 -999 -999 "Guilpart" +"AMP" "KO08Pm04" "SVR" NA NA "Fond lagonaire" "faible" 1 21 2 2008 NA NA NA -999 -999 NA "MD" "PL" -20.98351 164.60634 "HR" "AP" "Complexe de recif barriere externe" "lagon enclave" "Detritique" "Recif barriere interne" "D7" -999 1.9 -999 -999 -999 -999 "Guilpart" +"AMP" "KO08Pm05" "SVR" NA NA "Fond lagonaire" "faible" 1 21 2 2008 NA NA NA -999 -999 NA "PM" "PL" -20.99693 164.60088 "HR" "AP" "Complexe de recif barriere externe" "lagon enclave" "Detritique" "Recif barriere interne" "D7" -999 2 -999 -999 -999 -999 "Guilpart" +"AMP" "KO08Pm06" "SVR" NA NA "Fond lagonaire" "faible" 1 21 2 2008 NA NA NA -999 -999 NA "MD" "PL" -20.98784 164.60149 "HR" "AP" "Complexe de recif barriere externe" "lagon enclave" "Fond lagonaire" "Recif barriere interne" "SA2" -999 2.5 -999 -999 -999 -999 "Guilpart" +"AMP" "KO08Pm07" "SVR" NA NA "Recif intermediaire" "faible" 1 21 2 2008 NA NA NA -999 -999 NA "MD" "PL" -20.97873 164.60136 "HR" "AP" "Complexe de recif barriere externe" "lagon enclave a champ de constructions coralliennes" "Fond lagonaire" "Recif intermediaire" "SA3" -999 1.6 -999 -999 -999 -999 "Guilpart" +"AMP" "KO08Pm09" "SVR" NA NA "Fond lagonaire" "faible" 1 21 2 2008 NA NA NA -999 -999 NA "MD" "PL" -20.98347 164.59596 "HR" "AP" "Complexe de recif barriere externe" "lagon enclave" "Detritique" "Recif barriere interne" "D7" -999 1.7 -999 -999 -999 -999 "Guilpart" +"AMP" "KO08Pm11" "SVR" NA NA "Barriere" "faible" 1 21 2 2008 NA NA NA -999 -999 NA "MD" "PL" -20.99742 164.59059 "HR" "AP" "Complexe de recif barriere externe" "lagon enclave" "Detritique" "Recif barriere interne" "D5" -999 2.4 -999 -999 -999 -999 "Guilpart" +"AMP" "KO08Pm12" "SVR" NA NA "Recif intermediaire" "faible" 1 21 2 2008 NA NA NA -999 -999 NA "MD" "PL" -20.988 164.59135 "HR" "AP" "Complexe de recif barriere externe" "lagon enclave" "Fond lagonaire" "Recif barriere interne" "SA2" -999 1.8 -999 -999 -999 -999 "Guilpart" +"AMP" "KO08Pm13" "SVR" NA NA "Recif intermediaire" "faible" 1 21 2 2008 NA NA NA -999 -999 NA "MD" "PL" -20.97894 164.59154 "HR" "AP" "Complexe de recif barriere externe" "lagon enclave a champ de constructions coralliennes" "Fond lagonaire" "Recif intermediaire" "SA3" -999 3.7 -999 -999 -999 -999 "Guilpart" +"AMP" "KO08Pm17" "SVR" NA NA "Fond lagonaire" "faible" 1 21 2 2008 NA NA NA -999 -999 NA "MD" "PL" -20.98286 164.58549 "HR" "AP" "Complexe de recif barriere externe" "lagon enclave" "Fond lagonaire" "Recif intermediaire" "SA3" -999 2.1 -999 -999 -999 -999 "Guilpart" +"AMP" "KO08Pm18" "SVR" NA NA "Barriere" "faible" 1 21 2 2008 NA NA NA -999 -999 NA "MD" "PL" -20.99445 164.58405 "HR" "AP" "Complexe de recif barriere externe" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA3" -999 2.8 -999 -999 -999 -999 "Guilpart" +"AMP" "KO08Pm19" "SVR" NA NA "Fond lagonaire" "faible" 1 21 2 2008 NA NA NA -999 -999 NA "MD" "PL" -20.98772 164.58172 "HR" "AP" "Complexe de recif barriere externe" "lagon enclave" "Fond lagonaire" "Recif barriere interne" "SA2" -999 2.2 -999 -999 -999 -999 "Guilpart" +"AMP" "KO08Pm20" "SVR" NA NA "Recif intermediaire" "faible" 1 21 2 2008 NA NA NA -999 -999 NA "MD" "PL" -20.97848 164.58226 "HR" "AP" "Complexe de recif barriere externe" "platier recifal" "Fond lagonaire" "Recif intermediaire" "SA2" -999 1.5 -999 -999 -999 -999 "Guilpart" +"AMP" "KO130002" "SVR" NA NA "Barriere" "pas" 1 6 6 2013 NA NA "O" 2 1 NA "MD" "DC" -21.18234 164.72951 "HR" "AP" "Complexe de recif barriere externe" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA3" -999 3 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130003" "SVR" NA NA "Barriere" "pas" 1 6 6 2013 NA NA "O" 3 2 NA "MM" "DC" -21.17467 164.72243 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA3" -999 6 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130004" "SVR" NA NA "Barriere" "pas" 1 6 6 2013 NA NA "O" 3 2 NA "MM" "DC" -21.17043 164.72189 "HR" "AP" "Complexe de recif barriere externe" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA3" -999 5 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130005" "SVR" NA NA "Barriere" "pas" 1 7 6 2013 NA NA "SE" 3 2 NA "MD" "DC" -21.13963 164.71077 "HR" "AP" "Complexe de recif barriere externe" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA3" -999 4.5 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130006" "SVR" NA NA "Recif intermediaire" "pas" 1 6 6 2013 NA NA "O" 3 3 NA "BM" "DC" -21.20371 164.77554 "HR" "AP" "Complexe de recif barriere imbrique" "front recifal ou terrasse" "Fond lagonaire" "Recif barriere interne" "SA3" -999 6 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130007" "SVR" NA NA "Barriere" "pas" 1 6 6 2013 NA NA "O" 3 3 NA "MD" "DC" -21.20366 164.7753 "HR" "AP" "Complexe de recif barriere imbrique" "front recifal ou terrasse" "Fond lagonaire" "Recif barriere interne" "SA3" -999 4.5 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130009" "SVR" NA NA "Recif intermediaire" "pas" 1 6 6 2013 NA NA "O" 2 3 NA "BM" "DC" -21.18884 164.77713 "HR" "AP" "Complexe de recif barriere imbrique" "front recifal ou terrasse" "Fond lagonaire" "Recif intermediaire" "SA1" -999 5 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130010" "SVR" NA NA "Recif intermediaire" "pas" 1 6 6 2013 NA NA "O" 2 3 NA "MD" "DC" -21.18017 164.77565 "HR" "AP" "Complexe de recif barriere imbrique" "front recifal ou terrasse" "Fond lagonaire" "Recif intermediaire" "SA1" -999 3 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130011" "SVR" NA NA "Recif intermediaire" "pas" 1 6 6 2013 NA NA "O" 2 3 NA "MD" "DC" -21.17698 164.77598 "HR" "AP" "Complexe de recif barriere imbrique" "front recifal ou terrasse" "Fond lagonaire" "Recif intermediaire" "SA3" -999 2 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130013" "SVR" NA NA "Barriere" "pas" 1 6 6 2013 NA NA "O" 2 2 NA "MD" "DC" -21.15298 164.71848 "HR" "AP" "Complexe de recif barriere externe" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA3" -999 2 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130015" "SVR" NA NA "Fond lagonaire" "pas" 1 6 6 2013 NA NA "O" 3 2 NA "BM" "DC" -21.17204 164.75668 "HR" "AP" "Complexe de recif barriere imbrique" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA3" -999 2 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130016" "SVR" NA NA "Fond lagonaire" "pas" 1 6 6 2013 NA NA "O" 3 2 NA "MD" "DC" -21.17345 164.7592 "HR" "AP" "Complexe de recif barriere imbrique" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA5" -999 1 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130017" "SVR" NA NA "Fond lagonaire" "pas" 1 6 6 2013 NA NA "O" 3 2 NA "BM" "DC" -21.17585 164.73853 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" -999 4.5 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130018" "SVR" NA NA "Fond lagonaire" "pas" 1 6 6 2013 NA NA "O" 3 2 NA "MM" "DC" -21.17546 164.73355 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA3" -999 6 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130019" "SVR" NA NA "Barriere" "pas" 1 6 6 2013 NA NA "O" 2 2 NA "MD" "DC" -21.15708 164.75159 "HR" "AP" "Complexe de recif barriere imbrique" "terrasse peu profonde" "Fond lagonaire" "Recif intermediaire" "SA3" -999 4 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130020" "SVR" NA NA "Barriere" "pas" 1 6 6 2013 NA NA "O" 2 2 NA "MD" "DC" -21.15312 164.74908 "HR" "AP" "Complexe de recif barriere imbrique" "platier recifal" "Fond lagonaire" "Recif intermediaire" "SA5" -999 3.5 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130021" "SVR" NA NA "Barriere" "pas" 1 7 6 2013 NA NA "SE" 3 2 NA "MD" "DC" -21.12569 164.73509 "HR" "AP" "Complexe de recif barriere imbrique" "platier recifal" "Fond lagonaire" "Recif intermediaire" "SA3" -999 5 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130023" "SVR" NA NA "Fond lagonaire" "pas" 1 6 6 2013 NA NA "O" 2 2 NA "MD" "DC" -21.162 164.74556 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA2" -999 4 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130024" "SVR" NA NA "Fond lagonaire" "pas" 1 6 6 2013 NA NA "O" 2 2 NA "MD" "DC" -21.16439 164.73787 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" -999 4.5 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130025" "SVR" NA NA "Fond lagonaire" "pas" 1 6 6 2013 NA NA "O" 2 2 NA "MD" "DC" -21.15515 164.73448 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" -999 4 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130026" "SVR" NA NA "Fond lagonaire" "pas" 1 6 6 2013 NA NA "O" 2 2 NA "MD" "DC" -21.15548 164.72737 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" -999 3 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130027" "SVR" NA NA "Fond lagonaire" "pas" 1 6 6 2013 NA NA "O" 3 3 NA "MM" "DC" -21.14665 164.73633 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" -999 7 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130029" "SVR" NA NA "Fond lagonaire" "pas" 1 6 6 2013 NA NA "O" 2 2 NA "MD" "DC" -21.13827 164.72607 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA2" -999 9 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130030" "SVR" NA NA "Fond lagonaire" "pas" 1 6 6 2013 NA NA "O" 2 2 NA "MD" "DC" -21.13903 164.71937 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" -999 1.5 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130031" "SVR" NA NA "Barriere" "pas" 1 7 6 2013 NA NA "SE" 3 2 NA "MD" "DC" -21.13789 164.73332 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Corail vivant" "Fond lagonaire" "LC5" -999 5 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130032" "SVR" NA NA "Barriere" "pas" 1 7 6 2013 NA NA "SE" 3 2 NA "MD" "DC" -21.13932 164.73965 "HR" "AP" "Complexe de recif barriere imbrique" "terrasse peu profonde" "Detritique" "Fond lagonaire" NA -999 4 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130034" "SVR" NA NA "Herbier" "faible" 1 7 6 2013 NA NA "SE" 3 2 NA "MD" "DC" -21.11845 164.70509 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Herbier" "Fond lagonaire" "SG1" -999 1.3 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130035" "SVR" NA NA "Passe" "pas" 1 7 6 2013 NA NA "SE" 3 2 NA "MD" "DC" -21.13213 164.7123 "HR" "AP" "Complexe de recif barriere externe" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA3" -999 4 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130036" "SVR" NA NA "Passe" "faible" 1 7 6 2013 NA NA "SE" 3 2 NA "MD" "DC" -21.13073 164.70839 "HR" "AP" "Complexe de recif barriere externe" "platier recifal" "Corail vivant" "Recif barriere interne" "SA5" -999 4 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130038" "SVR" NA NA "Herbier" "faible" 1 7 6 2013 NA NA "SE" 3 2 NA "MD" "DC" -21.11602 164.70427 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Herbier" "Fond lagonaire" "SG1" -999 1 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130041" "SVR" NA NA "Recif intermediaire" "pas" 1 6 6 2013 NA NA "O" 2 2 NA "MD" "DC" -21.15632 164.78006 "HR" "AP" "Complexe de recif barriere imbrique" "front recifal ou terrasse" "Detritique" "Recif intermediaire" "D3" -999 2.5 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130045" "SVR" NA NA "Recif intermediaire" "pas" 1 6 6 2013 NA NA "O" 1 1 NA "MD" "DC" -21.11988 164.76456 "HR" "AP" "Complexe de recif barriere imbrique" "front recifal ou terrasse" "Fond lagonaire" "Recif intermediaire" "D7" -999 3 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130046" "SVR" NA NA "Recif intermediaire" "pas" 1 6 6 2013 NA NA "O" 1 1 NA "MD" "DC" -21.11924 164.75986 "HR" "AP" "Complexe de recif barriere imbrique" "front recifal ou terrasse" "Fond lagonaire" "Recif intermediaire" "SA2" -999 3 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130048" "SVR" NA NA "Recif intermediaire" "pas" 1 6 6 2013 NA NA "O" 1 1 NA "MD" "DC" -21.11096 164.77802 "HR" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA4" -999 3 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130053" "SVR" NA NA "Barriere" "faible" 1 7 6 2013 NA NA "SE" 3 2 NA "MD" "DC" -21.11484 164.69034 "RC" "AP" "" "" "Fond lagonaire" "Recif barriere interne" "SA1" -999 2 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130054" "SVR" NA NA "Fond lagonaire" "faible" 1 7 6 2013 NA NA "SE" 2 2 NA "BM" "DC" -21.10826 164.6873 "RC" "AP" "Complexe de recif barriere cotier" "platier recifal" "Fond lagonaire" "Recif barriere interne" NA -999 3 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130055" "SVR" NA NA "Barriere" "faible" 1 7 6 2013 NA NA "SE" 2 2 NA "BM" "DC" -21.10654 164.68837 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" NA -999 3 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130056" "SVR" NA NA "Barriere" "faible" 1 7 6 2013 NA NA "SE" 2 1 NA "MD" "DC" -21.09016 164.68781 "RC" "AP" "Complexe de recif barriere cotier" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA1" -999 2.5 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130057" "SVR" NA NA "Barriere" "faible" 1 7 6 2013 NA NA "SE" 2 1 NA "MD" "DC" -21.08472 164.68533 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA3" -999 1.5 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130059" "SVR" NA NA "Barriere" "faible" 1 7 6 2013 NA NA "SE" 1 1 NA "MD" "DC" -21.06569 164.66768 "RC" "AP" "Complexe de recif barriere cotier" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA3" -999 3 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130063" "SVR" NA NA "Barriere" "fort" 1 8 6 2013 NA NA "SE" 3 2 NA "MD" "NL" -21.04903 164.62193 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Detritique" "Recif barriere interne" "D7" -999 4 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130064" "SVR" NA NA "Barriere" "fort" 1 8 6 2013 NA NA "SE" 3 2 NA "MD" "NL" -21.04018 164.62123 "RC" "AP" "Complexe de recif barriere cotier" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA1" -999 3 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130067" "SVR" NA NA "Barriere" "fort" 1 8 6 2013 NA NA "SE" 4 2 NA "MM" "NL" -21.01225 164.61214 "RC" "AP" "Complexe de recif barriere cotier" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA1" -999 2 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130069" "SVR" NA NA "Fond lagonaire" "fort" 1 8 6 2013 NA NA "SE" 4 2 NA "MM" "NL" -21.0282 164.62984 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" -999 4 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130070" "SVR" NA NA "Fond lagonaire" "fort" 1 8 6 2013 NA NA "SE" 4 2 NA "MM" "NL" -21.02891 164.63167 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Corail vivant" "Fond lagonaire" "LC6" -999 9 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130071" "SVR" NA NA "Fond lagonaire" "fort" 1 8 6 2013 NA NA "SE" 4 2 NA "BM" "NL" -21.02861 164.63129 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Corail vivant" "Fond lagonaire" "LC5" -999 7 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130072" "SVR" NA NA "Fond lagonaire" "fort" 1 8 6 2013 NA NA "SE" 4 2 NA "MM" "NL" -21.02882 164.63383 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde a champ de constructions coralliennes" "Fond lagonaire" "Recif intermediaire" "SA3" -999 9 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130073" "SVR" NA NA "Recif intermediaire" "fort" 1 8 6 2013 NA NA "SE" 3 1 NA "MD" "NL" -21.0337 164.64238 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde a champ de constructions coralliennes" "Fond lagonaire" "Recif intermediaire" "SA3" -999 3 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130074" "SVR" NA NA "Frangeant" "faible" 1 8 6 2013 NA NA "SE" 2 2 NA "MD" "NL" -21.10561 164.70367 "RC" "AP" "Recif frangeant de recif barriere cotier" "platier recifal" "Fond lagonaire" "Frangeant cotier" "SA3" -999 1 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130075" "SVR" NA NA "Fond lagonaire" "faible" 1 8 6 2013 NA NA "SE" 2 2 NA "MD" "NL" -21.10505 164.69958 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "MA4" -999 2 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130076" "SVR" NA NA "Frangeant" "faible" 1 7 6 2013 NA NA "SE" 2 2 NA "BM" "DC" -21.10006 164.69873 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" -999 1 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130077" "SVR" NA NA "Fond lagonaire" "faible" 1 7 6 2013 NA NA "SE" 2 2 NA "BM" "DC" -21.10076 164.69368 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" -999 1.5 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130079" "SVR" NA NA "Fond lagonaire" "faible" 1 7 6 2013 NA NA "SE" 2 1 NA "MD" "DC" -21.09215 164.69533 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" -999 3 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130080" "SVR" NA NA "Frangeant" "faible" 1 7 6 2013 NA NA "SE" 2 1 NA "MD" "DC" -21.08785 164.69356 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" -999 1.5 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130081" "SVR" NA NA "Frangeant" "faible" 1 7 6 2013 NA NA "SE" 1 1 NA "MD" "DC" -21.08825 164.69113 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" -999 2 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130082" "SVR" NA NA "Barriere" "faible" 1 7 6 2013 NA NA "SE" 2 1 NA "MD" "DC" -21.08842 164.68781 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA3" -999 3 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130083" "SVR" NA NA "Barriere" "faible" 1 7 6 2013 NA NA "SE" 3 2 NA "MD" "DC" -21.11458 164.69391 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" -999 1.5 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130084" "SVR" NA NA "Fond lagonaire" "faible" 1 8 6 2013 NA NA "SE" 2 2 NA "MD" "NL" -21.11032 164.69916 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Herbier" "Fond lagonaire" "SG1" -999 2 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130085" "SVR" NA NA "Fond lagonaire" "faible" 1 7 6 2013 NA NA "SE" 2 2 NA "MD" "DC" -21.11034 164.6942 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" -999 3 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130087" "SVR" NA NA "Barriere" "faible" 1 7 6 2013 NA NA "SE" 1 1 NA "MD" "DC" -21.07227 164.68008 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" -999 1.5 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130088" "SVR" NA NA "Frangeant" "faible" 1 8 6 2013 NA NA "SE" 2 2 NA "MD" "NL" -21.07913 164.68988 "RC" "AP" "Recif frangeant de recif barriere cotier" "frangeant diffus" "Fond lagonaire" "Frangeant cotier" "SA1" -999 1.5 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130089" "SVR" NA NA "Fond lagonaire" "faible" 1 7 6 2013 NA NA "SE" 1 1 NA "MD" "DC" -21.07717 164.6864 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" -999 1.2 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130092" "SVR" NA NA "Barriere" "faible" 1 8 6 2013 NA NA "SE" 2 1 NA "MD" "NL" -21.06615 164.66991 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" -999 1.6 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130093" "SVR" NA NA "Barriere" "faible" 1 8 6 2013 NA NA "SE" 2 2 NA "MD" "NL" -21.05987 164.65759 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA3" -999 1 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130094" "SVR" NA NA "Fond lagonaire" "faible" 1 8 6 2013 NA NA "SE" 2 1 NA "MD" "NL" -21.06149 164.67029 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" -999 2 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130095" "SVR" NA NA "Fond lagonaire" "faible" 1 8 6 2013 NA NA "SE" 1 1 NA "MD" "NL" -21.05615 164.67052 "RC" "AP" "Complexe de recif barriere cotier" "lagon enclave" "Fond lagonaire" "Fond lagonaire" "SA1" -999 3.5 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130097" "SVR" NA NA "Recif intermediaire" "faible" 1 8 6 2013 NA NA "SE" 2 1 NA "MD" "NL" -21.05174 164.66208 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Recif intermediaire" "SA3" -999 3 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130098" "SVR" NA NA "Barriere" "fort" 1 8 6 2013 NA NA "SE" 2 1 NA "MD" "NL" -21.05674 164.6519 "RC" "AP" "Complexe de recif barriere cotier" "platier recifal" "Corail vivant" "Recif barriere interne" "LC2" -999 3 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130099" "SVR" NA NA "Barriere" "fort" 1 8 6 2013 NA NA "SE" 3 2 NA "MD" "NL" -21.05128 164.64568 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Corail vivant" "Fond lagonaire" "SA5" -999 2 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130100" "SVR" NA NA "Barriere" "fort" 1 8 6 2013 NA NA "SE" 3 2 NA "MD" "NL" -21.04885 164.6239 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" -999 4 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130101" "SVR" NA NA "Barriere" "fort" 1 8 6 2013 NA NA "SE" 3 2 NA "MD" "NL" -21.0386 164.62225 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA3" -999 3 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130102" "SVR" NA NA "Recif intermediaire" "fort" 1 8 6 2013 NA NA "SE" 3 1 NA "MD" "NL" -21.0288 164.64589 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde a champ de constructions coralliennes" "Fond lagonaire" "Recif intermediaire" "SA1" -999 4.5 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130103" "SVR" NA NA "Recif intermediaire" "fort" 1 8 6 2013 NA NA "SE" 2 1 NA "MD" "NL" -21.04104 164.65233 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" -999 3 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130107" "SVR" NA NA "Fond lagonaire" "faible" 1 8 6 2013 NA NA "SE" 1 1 NA "MD" "NL" -21.05204 164.67339 "RC" "AP" "Complexe de recif barriere cotier" "lagon enclave" "Fond lagonaire" "Fond lagonaire" "SA1" -999 6.5 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130108" "SVR" NA NA "Recif intermediaire" "faible" 1 8 6 2013 NA NA "SE" 1 1 NA "MD" "NL" -21.04808 164.67313 "RC" "AP" "Complexe de recif barriere cotier" "lagon enclave" "Corail vivant" "Recif intermediaire" "LC4" -999 3 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130110" "SVR" NA NA "Frangeant" "fort" 1 8 6 2013 NA NA "SE" 4 2 NA "MD" "NL" -21.01808 164.65611 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde a champ de constructions coralliennes" "Corail vivant" "Recif intermediaire" "LC4" -999 3 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130112" "SVR" NA NA "Fond lagonaire" "fort" 1 8 6 2013 NA NA "SE" 4 2 NA "MD" "NL" -21.03478 164.62909 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Corail vivant" "Fond lagonaire" "LC5" -999 6 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130113" "SVR" NA NA "Fond lagonaire" "fort" 1 8 6 2013 NA NA "SE" 4 2 NA "MD" "NL" -21.03297 164.63023 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA5" -999 6.5 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130120" "SVR" NA NA "Recif intermediaire" "fort" 1 8 6 2013 NA NA "SE" 2 2 NA "MD" "NL" -21.01125 164.64987 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde a champ de constructions coralliennes" "Fond lagonaire" "Recif intermediaire" NA -999 3 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130129" "SVR" NA NA "Recif intermediaire" "fort" 1 9 6 2013 NA NA "SE" 3 2 NA "MD" "PC" -20.98993 164.63356 "HR" "AP" "Complexe de massif corallien de lagon" "front recifal" "Corail vivant" "Recif intermediaire" "LC2" -999 5 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO13012B" "SVR" NA NA "Barriere" "pas" 1 7 6 2013 NA NA "SE" 3 2 NA "MD" "DC" -21.14292 164.71367 "HR" "AP" "Complexe de recif barriere externe" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA3" -999 2 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130130" "SVR" NA NA "Recif intermediaire" "fort" 1 9 6 2013 NA NA "SE" 3 2 NA "MD" "PC" -20.98892 164.63225 "HR" "AP" "Complexe de massif corallien de lagon" "front recifal" "Fond lagonaire" "Recif intermediaire" "LC5" -999 2 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130131" "SVR" NA NA "Recif intermediaire" "fort" 1 9 6 2013 NA NA "SE" 3 2 NA "MD" "PC" -20.98888 164.6246 "HR" "AP" "Ile lagonaire" "lagon profond" "Corail vivant" "Recif intermediaire" "LC4" -999 6 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130132" "SVR" NA NA "Recif intermediaire" "faible" 1 9 6 2013 NA NA "SE" 2 2 NA "MM" "PC" -20.96662 164.6008 "HR" "AP" "Complexe de recif barriere imbrique" "platier recifal" "Corail vivant" "Recif intermediaire" "LC5" -999 2.5 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130133" "SVR" NA NA "Recif intermediaire" "faible" 1 9 6 2013 NA NA "SE" 2 2 NA "MM" "PC" -20.96213 164.59384 "HR" "AP" "Complexe de recif barriere imbrique" "terrasse peu profonde" "Corail vivant" "Recif intermediaire" "LC2" -999 5 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130135" "SVR" NA NA "Recif intermediaire" "faible" 1 9 6 2013 NA NA "SE" 2 2 NA "MM" "PC" -20.95295 164.58583 "HR" "AP" "Complexe de recif barriere imbrique" "terrasse peu profonde" "Fond lagonaire" "Recif intermediaire" "SA1" -999 5 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130138" "SVR" NA NA "Recif intermediaire" "fort" 1 9 6 2013 NA NA "SE" 3 2 NA "MD" "PC" -20.98396 164.6295 "HR" "AP" "Ile lagonaire" "lagon profond" "Corail vivant" "Fond lagonaire" "LC2" -999 4.5 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130139" "SVR" NA NA "Recif intermediaire" "fort" 1 9 6 2013 NA NA "SE" 3 2 NA "MD" "PC" -20.99661 164.63202 "HR" "AP" "Ile lagonaire" "lagon profond" "Corail vivant" "Fond lagonaire" "LC4" -999 6.5 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130140" "SVR" NA NA "Recif intermediaire" "fort" 1 9 6 2013 NA NA "SE" 3 2 NA "MD" "PC" -20.99509 164.62466 "HR" "AP" "Ile lagonaire" "lagon profond" "Detritique" "Fond lagonaire" NA -999 5 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130144" "SVR" NA NA "Recif intermediaire" "faible" 1 9 6 2013 NA NA "SE" 3 2 NA "MM" "PC" -20.98748 164.59341 "HR" "AP" "Complexe de recif barriere externe" "lagon enclave" "Fond lagonaire" "Recif barriere interne" "SA1" -999 1 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130146" "SVR" NA NA "Recif intermediaire" "faible" 1 9 6 2013 NA NA "SE" 3 2 NA "MM" "PC" -20.98215 164.58014 "HR" "AP" "Complexe de recif barriere externe" "lagon enclave" "Fond lagonaire" "Recif intermediaire" "SA1" -999 2 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130147" "SVR" NA NA "Recif intermediaire" "faible" 1 9 6 2013 NA NA "SE" 3 2 NA "MM" "PC" -20.98272 164.57916 "HR" "AP" "Complexe de recif barriere externe" "lagon enclave" "Fond lagonaire" "Recif intermediaire" "SA1" -999 2.5 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130148" "SVR" NA NA "Barriere" "faible" 1 9 6 2013 NA NA "SE" 3 2 NA "MM" "PC" -20.98825 164.5903 "HR" "AP" "Complexe de recif barriere externe" "lagon enclave" "Fond lagonaire" "Recif barriere interne" "SA1" -999 1 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130151" "SVR" NA NA "Barriere" "pas" 1 10 6 2013 NA NA "SE" 2 2 NA "MD" "PC" -20.94496 164.42932 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA1" -999 7 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130152" "SVR" NA NA "Barriere" "pas" 1 10 6 2013 NA NA "SE" 2 2 NA "MD" "PC" -20.95738 164.42683 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Corail vivant" "Recif barriere interne" "SA3" -999 14 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130153" "SVR" NA NA "Barriere" "pas" 1 10 6 2013 NA NA "SE" 2 2 NA "MD" "PC" -20.95505 164.42503 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA1" -999 7 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130154" "SVR" NA NA "Barriere" "pas" 1 10 6 2013 NA NA "SE" 2 2 NA "MD" "PC" -20.98067 164.43643 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA3" -999 10 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130155" "SVR" NA NA "Barriere" "pas" 1 10 6 2013 NA NA "SE" 2 2 NA "MD" "PC" -20.97971 164.43291 "HR" "AP" "Complexe de recif barriere externe" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA4" -999 5 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130156" "SVR" NA NA "Barriere" "pas" 1 10 6 2013 NA NA "SE" 2 2 NA "MD" "PC" -20.99378 164.43863 "HR" "AP" "Complexe de recif barriere externe" "platier recifal" "Detritique" "Recif barriere interne" "D5" -999 4 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130157" "SVR" NA NA "Barriere" "pas" 1 10 6 2013 NA NA "SE" 2 2 NA "MD" "PC" -20.9917 164.44365 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA1" -999 6 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130160" "SVR" NA NA "Barriere" "faible" 1 10 6 2013 NA NA "SE" 2 2 NA "MD" "PC" -21.00572 164.47458 "HR" "AP" "Complexe de recif barriere externe" "platier recifal" "Corail vivant" "Recif barriere interne" "LC5" -999 4 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130161" "SVR" NA NA "Barriere" "faible" 1 10 6 2013 NA NA "SE" 2 2 NA "MD" "PC" -21.00112 164.47902 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde a champ de constructions coralliennes" "Fond lagonaire" "Recif barriere interne" "SA3" -999 7 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130165" "SVR" NA NA "Barriere" "faible" 1 10 6 2013 NA NA "SE" 2 2 NA "MD" "PC" -20.9974 164.50786 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde a champ de constructions coralliennes" "Corail vivant" "Recif barriere interne" "LC5" -999 6 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130166" "SVR" NA NA "Barriere" "faible" 1 10 6 2013 NA NA "SE" 2 2 NA "MD" "PC" -20.99624 164.50923 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde a champ de constructions coralliennes" "Fond lagonaire" "Recif barriere interne" "SA3" -999 4.5 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130170" "SVR" NA NA "Barriere" "faible" 1 9 6 2013 NA NA "SE" 3 2 NA "MM" "PC" -20.9818 164.55157 "HR" "AP" "Complexe de recif barriere externe" "lagon enclave" "Fond lagonaire" "Recif barriere interne" "SA3" -999 1 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130171" "SVR" NA NA "Barriere" "faible" 1 9 6 2013 NA NA "SE" 3 2 NA "MM" "PC" -20.98222 164.55421 "HR" "AP" "Complexe de recif barriere externe" "lagon enclave" "Fond lagonaire" "Recif barriere interne" "SA1" -999 1 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130173" "SVR" NA NA "Frangeant" "faible" 1 9 6 2013 NA NA "SE" 2 2 NA "MM" "PC" -20.94887 164.53333 "HR" "AP" "Recif frangeant protege de lagons" "platier recifal" "Detritique" "Frangeant cotier" NA -999 5.5 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130174" "SVR" NA NA "Frangeant" "pas" 1 10 6 2013 NA NA "SE" 3 1 NA "MD" "PC" -20.94263 164.5136 "HR" "AP" "Recif frangeant protege de lagons" "platier recifal" "Corail vivant" "Frangeant cotier" "LC4" -999 4.5 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130175" "SVR" NA NA "Frangeant" "pas" 1 10 6 2013 NA NA "SE" 3 1 NA "MD" "PC" -20.94156 164.51256 "HR" "AP" "Recif frangeant protege de lagons" "platier recifal" "Corail vivant" "Frangeant cotier" "LC6" -999 3 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130176" "SVR" NA NA "Frangeant" "pas" 1 10 6 2013 NA NA "SE" 2 1 NA "MD" "PC" -20.9216 164.49597 "HR" "AP" "Recif frangeant protege de lagons" "platier recifal" "Corail vivant" "Frangeant cotier" "LC2" -999 4 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130177" "SVR" NA NA "Frangeant" "pas" 1 10 6 2013 NA NA "SE" 2 1 NA "MD" "PC" -20.91743 164.50061 "HR" "AP" "Recif frangeant protege de lagons" "platier recifal" "Corail vivant" "Frangeant cotier" "LC4" -999 3 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130180" "SVR" NA NA "Frangeant" "pas" 1 10 6 2013 NA NA "SE" 2 1 NA "MD" "PC" -20.92383 164.51601 "HR" "AP" "Recif frangeant protege de lagons" "platier recifal" "Herbier" "Frangeant cotier" "SG3" -999 1.5 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130182" "SVR" NA NA "Frangeant" "faible" 1 10 6 2013 NA NA "SE" 2 1 NA "MD" "PC" -20.92467 164.53712 "HR" "AP" "Recif frangeant protege de lagons" "platier recifal" "Herbier" "Frangeant cotier" "SG1" -999 1.2 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130185" "SVR" NA NA "Frangeant" "faible" 1 10 6 2013 NA NA "SE" 2 1 NA "MD" "PC" -20.91797 164.5578 "HR" "AP" "Recif frangeant protege de lagons" "platier recifal" "Fond lagonaire" "Frangeant cotier" NA -999 2 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130194" "SVR" NA NA "Recif intermediaire" "faible" 1 9 6 2013 NA NA "SE" 2 2 NA "MM" "PC" -20.94469 164.54646 "HR" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Recif intermediaire" NA -999 5 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130202" "SVR" NA NA "Barriere" "faible" 1 7 6 2013 NA NA "SE" 2 2 NA "MD" "DC" -21.11529 164.69138 "RC" "AP" "" "" "Fond lagonaire" "Recif barriere interne" "SA3" -999 2 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130203" "SVR" NA NA "Frangeant" "faible" 1 8 6 2013 NA NA "SE" 2 2 NA "MD" "NL" -21.07226 164.68494 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" -999 2 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130204" "SVR" NA NA "Frangeant" "faible" 1 8 6 2013 NA NA "SE" 2 2 NA "MD" "NL" -21.0738 164.68597 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" -999 1 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130205" "SVR" NA NA "Fond lagonaire" "fort" 1 8 6 2013 NA NA "SE" 3 2 NA "MD" "NL" -21.0466 164.63994 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA3" -999 6 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130206" "SVR" NA NA "Barriere" "fort" 1 8 6 2013 NA NA "SE" 4 2 NA "MM" "NL" -21.03018 164.61996 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA1" -999 1.5 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130207" "SVR" NA NA "Barriere" "fort" 1 9 6 2013 NA NA "SE" 2 2 NA "MM" "PC" -21.0193 164.6068 "RC" "AP" "Complexe de recif barriere cotier" "platier recifal" "Detritique" "Recif barriere interne" NA -999 2 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130208" "SVR" NA NA "Barriere" "fort" 1 9 6 2013 NA NA "SE" 2 2 NA "MM" "PC" -21.01426 164.60971 "RC" "AP" "Complexe de recif barriere cotier" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA3" -999 2 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130209" "SVR" NA NA "Recif intermediaire" "faible" 1 9 6 2013 NA NA "SE" 2 2 NA "MM" "PC" -20.95147 164.5816 "HR" "AP" "Complexe de recif barriere imbrique" "terrasse peu profonde" "Fond lagonaire" "Recif intermediaire" "SA1" -999 4 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130210" "SVR" NA NA "Recif intermediaire" "faible" 1 9 6 2013 NA NA "SE" 3 2 NA "MM" "PC" -20.96522 164.5443 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde a champ de constructions coralliennes" "Fond lagonaire" "Fond lagonaire" "SA1" -999 3 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130211" "SVR" NA NA "Recif intermediaire" "faible" 1 9 6 2013 NA NA "SE" 3 2 NA "MM" "PC" -20.96922 164.53388 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde a champ de constructions coralliennes" "Fond lagonaire" "Fond lagonaire" "SA3" -999 3 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130212" "SVR" NA NA "Barriere" "faible" 1 9 6 2013 NA NA "SE" 3 2 NA "MM" "PC" -20.97709 164.55511 "HR" "AP" "Complexe de recif barriere externe" "lagon enclave" "Fond lagonaire" "Recif intermediaire" "SA1" -999 4 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130213" "SVR" NA NA "Barriere" "faible" 1 9 6 2013 NA NA "SE" 3 2 NA "MM" "PC" -20.97674 164.55661 "HR" "AP" "Complexe de recif barriere externe" "lagon enclave" "Fond lagonaire" "Recif intermediaire" "SA1" -999 4 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO13022b" "SVR" NA NA "Barriere" "pas" 1 7 6 2013 NA NA "SE" 3 2 NA "MD" "DC" -21.13094 164.73399 "HR" "AP" "Complexe de recif barriere imbrique" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA3" -999 5 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130300" "SVR" NA NA "Barriere" "fort" 1 8 6 2013 NA NA "SE" 2 1 NA "MD" "NL" -21.05564 164.65196 "RC" "AP" "Complexe de recif barriere cotier" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA1" -999 2 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130301" "SVR" NA NA "Recif intermediaire" "fort" 1 8 6 2013 NA NA "SE" 2 1 NA "MD" "NL" -21.05165 164.65134 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA5" -999 4 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130302" "SVR" NA NA "Recif intermediaire" "fort" 1 8 6 2013 NA NA "SE" 2 1 NA "MD" "NL" -21.05133 164.65179 "RC" "AP" "Complexe de recif barriere cotier" "platier recifal" "Corail vivant" "Recif barriere interne" "LC5" -999 1.6 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130304" "SVR" NA NA "Recif intermediaire" "fort" 1 9 6 2013 NA NA "SE" 3 2 NA "MD" "PC" -20.98656 164.62675 "HR" "AP" "Complexe de massif corallien de lagon" "front recifal" "Corail vivant" "Recif intermediaire" "LC4" -999 3 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130305" "SVR" NA NA "Recif intermediaire" "fort" 1 9 6 2013 NA NA "SE" 3 2 NA "MD" "PC" -20.99123 164.62384 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Corail vivant" "Recif intermediaire" "LC4" -999 2 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130306" "SVR" NA NA "Recif intermediaire" "fort" 1 9 6 2013 NA NA "SE" 3 2 NA "MD" "PC" -20.99482 164.62286 "HR" "AP" "Ile lagonaire" "lagon profond" "Corail vivant" "Fond lagonaire" "LC5" -999 6 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130307" "SVR" NA NA "Recif intermediaire" "fort" 1 9 6 2013 NA NA "SE" 3 2 NA "MD" "PC" -20.99526 164.63136 "HR" "AP" "Ile lagonaire" "lagon profond" "Detritique" "Fond lagonaire" NA -999 8 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO130311" "SVR" NA NA "Frangeant" "pas" 1 10 6 2013 NA NA "SE" 3 1 NA "MD" "PC" -20.93274 164.50845 "HR" "AP" "Recif frangeant protege de lagons" "platier recifal" "Corail vivant" "Frangeant cotier" "LC1" -999 4.5 -999 -999 -999 -999 "Cyrielle" +"AMP" "KO13059b" "SVR" NA NA "Barriere" "faible" 1 8 6 2013 NA NA "SE" 2 1 NA "MD" "NL" -21.06567 164.66766 "RC" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA3" -999 2 -999 -999 -999 -999 "Cyrielle" +"AMP" "LA070014" "SVR" "Laregnere" "LA" NA NA 1 19 6 2007 NA NA NA -999 -999 NA "MD" "PC" -22.32753 166.31062 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Detritique" "Frangeant ilot" "D6" -999 4.6 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070015" "SVR" "Laregnere" "LA" NA NA 1 19 6 2007 NA NA NA -999 -999 NA "MD" "PC" -22.3268 166.31217 "RE" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Frangeant ilot" "D6" -999 4.3 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070016" "SVR" "Laregnere" "LA" NA NA 1 19 6 2007 NA NA NA -999 -999 NA "MD" "PC" -22.32603 166.31383 "RE" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Frangeant ilot" "D6" -999 4.7 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070017" "SVR" "Laregnere" "LA" NA NA 1 19 6 2007 NA NA NA -999 -999 NA "MD" "PC" -22.32563 166.3156 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "SA5" -999 4 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070018" "SVR" "Laregnere" "LA" NA NA 1 19 6 2007 NA NA NA -999 -999 NA "MD" "PC" -22.32557 166.32158 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Herbier" "Frangeant ilot" "SG3" -999 1.7 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070020" "SVR" "Laregnere" "LA" NA NA 1 19 6 2007 NA NA NA -999 -999 NA "MD" "PC" -22.32617 166.32555 "RE" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Corail vivant" "Frangeant ilot" "LC3" -999 2.2 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070033" "SVR" "Laregnere" "LA" NA NA 1 20 6 2007 NA NA NA -999 -999 NA "MD" "PC" -22.32452 166.31657 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Herbier" "Frangeant ilot" "SG1" -999 5 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070034" "SVR" "Laregnere" "LA" NA NA 1 20 6 2007 NA NA NA -999 -999 NA "MD" "PC" -22.32613 166.32725 "RE" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Corail vivant" "Frangeant ilot" "LC3" -999 3 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070035" "SVR" "Laregnere" "LA" NA NA 1 20 6 2007 NA NA NA -999 -999 NA "MD" "PC" -22.32553 166.3312 "RE" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Corail vivant" "Frangeant ilot" "LC5" -999 2.7 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070037" "SVR" "Laregnere" "LA" NA NA 1 20 6 2007 NA NA NA -999 -999 NA "MD" "PC" -22.32558 166.33282 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Detritique" "Frangeant ilot" NA -999 4.1 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070038" "SVR" "Laregnere" "LA" NA NA 1 20 6 2007 NA NA NA -999 -999 NA "MD" "PC" -22.3265 166.33462 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Detritique" "Frangeant ilot" NA -999 6 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070060" "SVR" "Laregnere" "LA" NA NA 1 22 6 2007 NA NA NA -999 -999 NA "MM" "PQ" -22.32777 166.33598 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Corail vivant" "Frangeant ilot" "LC3" -999 5.8 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070061" "SVR" "Laregnere" "LA" NA NA 1 22 6 2007 NA NA NA -999 -999 NA "MM" "PQ" -22.32915 166.33725 "RE" "AP" "Ile lagonaire" "lagon profond" "Corail vivant" "Fond lagonaire" "LC1" -999 6 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070062" "SVR" "Laregnere" "LA" NA NA 1 22 6 2007 NA NA NA -999 -999 NA "MM" "PQ" -22.33083 166.3373 "RE" "AP" "Ile lagonaire" "lagon profond" "Detritique" "Fond lagonaire" "D3" -999 7.8 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070095" "SVR" "Laregnere" "LA" NA NA 1 27 6 2007 NA NA NA -999 -999 NA "MD" "LM" -22.33159 166.31222 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Fond lagonaire" "Frangeant ilot" NA -999 7 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070097" "SVR" "Laregnere" "LA" NA NA 1 27 6 2007 NA NA NA -999 -999 NA "MD" "LM" -22.33147 166.31627 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Frangeant ilot" "D2" -999 7.2 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070098" "SVR" "Laregnere" "LA" NA NA 1 27 6 2007 NA NA NA -999 -999 NA "MD" "LM" -22.33082 166.32389 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Fond lagonaire" "Frangeant ilot" "SA3" -999 8.4 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070099" "SVR" "Laregnere" "LA" NA NA 1 27 6 2007 NA NA NA -999 -999 NA "MD" "LM" -22.33063 166.32526 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Corail vivant" "Frangeant ilot" "D6" -999 8.2 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070100" "SVR" "Laregnere" "LA" NA NA 1 27 6 2007 NA NA NA -999 -999 NA "MD" "LM" -22.33078 166.32748 "RE" "AP" "Ile lagonaire" "lagon profond" "Detritique" "Frangeant ilot" "SA5" -999 7.7 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070101" "SVR" "Laregnere" "LA" NA NA 1 27 6 2007 NA NA NA -999 -999 NA "BM" "LM" -22.33082 166.32918 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Corail vivant" "Frangeant ilot" "LC5" -999 6.7 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070102" "SVR" "Laregnere" "LA" NA NA 1 27 6 2007 NA NA NA -999 -999 NA "MM" "LM" -22.33121 166.33079 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Fond lagonaire" "Frangeant ilot" "SA4" -999 7.4 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070103" "SVR" "Laregnere" "LA" NA NA 1 27 6 2007 NA NA NA -999 -999 NA "MM" "LM" -22.33168 166.33245 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Fond lagonaire" "Frangeant ilot" "LC5" -999 7 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070104" "SVR" "Laregnere" "LA" NA NA 1 27 6 2007 NA NA NA -999 -999 NA "MM" "LM" -22.3317 166.33409 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Fond lagonaire" "Frangeant ilot" "SA4" -999 5.4 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070106" "SVR" "Laregnere" "LA" NA NA 1 28 6 2007 NA NA NA -999 -999 NA "MD" "LM" -22.3243 166.33174 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "SA1" -999 4.1 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070107" "SVR" "Laregnere" "LA" NA NA 1 28 6 2007 NA NA NA -999 -999 NA "MD" "LM" -22.32436 166.33046 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "SA1" -999 3.1 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070108" "SVR" "Laregnere" "LA" NA NA 1 28 6 2007 NA NA NA -999 -999 NA "MD" "LM" -22.32424 166.32901 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Algueraie" "Frangeant ilot" "MA2" -999 3.5 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070110" "SVR" "Laregnere" "LA" NA NA 1 28 6 2007 NA NA NA -999 -999 NA "MD" "LM" -22.32405 166.32594 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Herbier" "Frangeant ilot" "SG1" -999 3.9 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070111" "SVR" "Laregnere" "LA" NA NA 1 28 6 2007 NA NA NA -999 -999 NA "MD" "LM" -22.3238 166.32427 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Algueraie" "Frangeant ilot" "MA3" -999 3.4 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070112" "SVR" "Laregnere" "LA" NA NA 1 28 6 2007 NA NA NA -999 -999 NA "MD" "LM" -22.32395 166.32279 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Algueraie" "Frangeant ilot" "SG3" -999 3.2 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070114" "SVR" "Laregnere" "LA" NA NA 1 28 6 2007 NA NA NA -999 -999 NA "MM" "LM" -22.32483 166.31983 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "SA3" -999 1.8 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070115" "SVR" "Laregnere" "LA" NA NA 1 28 6 2007 NA NA NA -999 -999 NA "MM" "LM" -22.32558 166.31909 "RE" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Frangeant ilot" "SA5" -999 1.9 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070116" "SVR" "Laregnere" "LA" NA NA 1 28 6 2007 NA NA NA -999 -999 NA "MM" "LM" -22.32637 166.31816 "RE" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Fond lagonaire" "Frangeant ilot" "SA5" -999 1.7 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070117" "SVR" "Laregnere" "LA" NA NA 1 28 6 2007 NA NA NA -999 -999 NA "MM" "LM" -22.32586 166.31661 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "SA1" -999 2 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070118" "SVR" "Laregnere" "LA" NA NA 1 28 6 2007 NA NA NA -999 -999 NA "MM" "LM" -22.32509 166.31807 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Herbier" "Frangeant ilot" "SG1" -999 3.9 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070119" "SVR" "Laregnere" "LA" NA NA 1 28 6 2007 NA NA NA -999 -999 NA "MM" "LM" -22.32365 166.31853 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Herbier" "Frangeant ilot" "SG2" -999 3.3 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070120" "SVR" "Laregnere" "LA" NA NA 1 28 6 2007 NA NA NA -999 -999 NA "MM" "LM" -22.32209 166.31921 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Algueraie" "Frangeant ilot" "MA3" -999 3 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070121" "SVR" "Laregnere" "LA" NA NA 1 2 7 2007 NA NA "0" 0 -999 NA "PM" "LD" -22.32593 166.3369 "RE" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA2" -999 13.4 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070122" "SVR" "Laregnere" "LA" NA NA 1 2 7 2007 NA NA "0" 0 -999 NA "PM" "LD" -22.32739 166.33776 "RE" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA2" -999 12.8 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070123" "SVR" "Laregnere" "LA" NA NA 1 2 7 2007 NA NA "0" 0 -999 NA "MD" "LD" -22.32918 166.3387 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA1" -999 12.4 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070124" "SVR" "Laregnere" "LA" NA NA 1 2 7 2007 NA NA "0" 0 -999 NA "MD" "LD" -22.33101 166.33913 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA1" -999 10.9 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070125" "SVR" "Laregnere" "LA" NA NA 1 2 7 2007 NA NA "0" 0 -999 NA "MD" "LD" -22.33268 166.33915 "RE" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA3" -999 12.3 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070126" "SVR" "Laregnere" "LA" NA NA 1 2 7 2007 NA NA "0" 0 -999 NA "MD" "LD" -22.33437 166.33602 "RE" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA3" -999 13.3 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070209" "SVR" "Laregnere" "LA" NA NA 1 5 7 2007 NA NA NA 2 -999 NA "MD" "LD" -22.32756 166.30578 "RE" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA3" -999 10.2 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070215" "SVR" "Laregnere" "LA" NA NA 1 5 7 2007 NA NA NA 2 -999 NA "MD" "LD" -22.32312 166.32414 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Algueraie" "Frangeant ilot" "MA2" -999 3.6 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070216" "SVR" "Laregnere" "LA" NA NA 1 5 7 2007 NA NA NA 2 -999 NA "MD" "LD" -22.31966 166.32348 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Algueraie" "Frangeant ilot" "MA1" -999 9.8 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070233" "SVR" "Laregnere" "LA" NA NA 1 6 7 2007 NA NA NA -999 -999 NA "MD" "LD" -22.33275 166.31002 "RE" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA4" -999 11 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070234" "SVR" "Laregnere" "LA" NA NA 1 30 7 2007 NA NA NA -999 -999 NA "MD" "PL" -22.33444 166.33373 "RE" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA2" -999 13.3 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070235" "SVR" "Laregnere" "LA" NA NA 1 30 7 2007 NA NA NA -999 -999 NA "MD" "PL" -22.33415 166.33118 "RE" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA3" -999 12.1 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070236" "SVR" "Laregnere" "LA" NA NA 1 30 7 2007 NA NA NA -999 -999 NA "MD" "PL" -22.33353 166.32871 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "MA4" -999 10.9 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070237" "SVR" "Laregnere" "LA" NA NA 1 30 7 2007 NA NA NA -999 -999 NA "MD" "PL" -22.33295 166.32369 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA1" -999 10.4 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070238" "SVR" "Laregnere" "LA" NA NA 1 30 7 2007 NA NA NA -999 -999 NA "MD" "PL" -22.33339 166.32091 "RE" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA3" -999 10.1 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070239" "SVR" "Laregnere" "LA" NA NA 1 30 7 2007 NA NA NA -999 -999 NA "MD" "PL" -22.33313 166.31879 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "MA4" -999 10.2 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070240" "SVR" "Laregnere" "LA" NA NA 1 30 7 2007 NA NA NA -999 -999 NA "MD" "PL" -22.33321 166.31588 "RE" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA3" -999 10.4 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070241" "SVR" "Laregnere" "LA" NA NA 1 30 7 2007 NA NA NA -999 -999 NA "MD" "PL" -22.33163 166.31411 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Fond lagonaire" "Frangeant ilot" "SA5" -999 10.6 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070242" "SVR" "Laregnere" "LA" NA NA 1 30 7 2007 NA NA NA -999 -999 NA "MD" "PL" -22.33317 166.31277 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA1" -999 7.1 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070243" "SVR" "Laregnere" "LA" NA NA 1 30 7 2007 NA NA NA -999 -999 NA "MD" "PL" -22.33118 166.31022 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Algueraie" "Frangeant ilot" "MA1" -999 8 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070244" "SVR" "Laregnere" "LA" NA NA 1 30 7 2007 NA NA NA -999 -999 NA "MD" "PL" -22.32963 166.30918 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Algueraie" "Frangeant ilot" "MA3" -999 7.7 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070245" "SVR" "Laregnere" "LA" NA NA 1 30 7 2007 NA NA NA -999 -999 NA "MD" "PL" -22.32843 166.30957 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "SA1" -999 7.2 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070257" "SVR" "Laregnere" "LA" NA NA 1 29 10 2007 NA NA NA -999 -999 NA "MD" "LD" -22.3241 166.31422 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Herbier" "Frangeant ilot" "SG1" -999 6.4 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070258" "SVR" "Laregnere" "LA" NA NA 1 8 11 2007 NA NA NA -999 -999 NA "MD" "DC" -22.32439 166.33328 "RE" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA4" -999 10.4 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070259" "SVR" "Laregnere" "LA" NA NA 1 8 11 2007 NA NA NA -999 -999 NA "MD" "DC" -22.33157 166.33516 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Frangeant ilot" NA -999 6.2 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070265" "SVR" "Laregnere" "LA" NA NA 1 8 11 2007 NA NA NA -999 -999 NA "MD" "DC" -22.32277 166.31329 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Frangeant ilot" NA -999 8.1 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070279" "SVR" "Laregnere" "LA" NA NA 1 25 1 2008 NA NA NA -999 -999 NA "MM" "DQ" -22.33289 166.32611 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA1" -999 11.4 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070280" "SVR" "Laregnere" "LA" NA NA 1 25 1 2008 NA NA NA -999 -999 NA "MM" "DQ" -22.33103 166.32005 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Frangeant ilot" "D2" -999 7.5 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070282" "SVR" "Laregnere" "LA" NA NA 1 25 1 2008 NA NA NA -999 -999 NA "PM" "DQ" -22.33021 166.30731 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA1" -999 12.5 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070283" "SVR" "Laregnere" "LA" NA NA 1 25 1 2008 NA NA NA -999 -999 NA "PM" "DQ" -22.33191 166.30568 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA1" -999 11.6 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070297" "SVR" "Laregnere" "LA" NA NA 1 25 1 2008 NA NA NA -999 -999 NA "MD" "DQ" -22.33018 166.306 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "MA4" -999 11.8 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070298" "SVR" "Laregnere" "LA" NA NA 1 25 1 2008 NA NA NA -999 -999 NA "MD" "DQ" -22.329 166.30763 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA1" -999 11.5 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070299" "SVR" "Laregnere" "LA" NA NA 1 25 1 2008 NA NA NA -999 -999 NA "MD" "DQ" -22.32881 166.30597 "RE" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA4" -999 11.1 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070304" "SVR" "Laregnere" "LA" NA NA 1 21 3 2008 NA NA NA -999 -999 NA "MD" "PL" -22.32294 166.32069 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "SA1" -999 3.4 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070305" "SVR" "Laregnere" "LA" NA NA 1 21 3 2008 NA NA NA -999 -999 NA "MD" "PL" -22.32241 166.32713 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Algueraie" "Frangeant ilot" "MA4" -999 5.1 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070306" "SVR" "Laregnere" "LA" NA NA 1 21 3 2008 NA NA NA -999 -999 NA "MD" "PL" -22.32264 166.32254 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Algueraie" "Frangeant ilot" "MA3" -999 4 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070307" "SVR" "Laregnere" "LA" NA NA 1 21 3 2008 NA NA NA -999 -999 NA "MD" "PL" -22.32275 166.32744 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Algueraie" "Frangeant ilot" "MA4" -999 4.8 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070308" "SVR" "Laregnere" "LA" NA NA 1 21 3 2008 NA NA NA -999 -999 NA "MD" "PL" -22.32267 166.32912 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Algueraie" "Frangeant ilot" "MA1" -999 4.2 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070309" "SVR" "Laregnere" "LA" NA NA 1 21 3 2008 NA NA NA -999 -999 NA "MD" "PL" -22.32321 166.33046 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Algueraie" "Frangeant ilot" "MA1" -999 4.5 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070310" "SVR" "Laregnere" "LA" NA NA 1 21 3 2008 NA NA NA -999 -999 NA "MD" "PL" -22.32103 166.32747 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Herbier" "Frangeant ilot" "SG3" -999 5.7 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070311" "SVR" "Laregnere" "LA" NA NA 1 21 3 2008 NA NA NA -999 -999 NA "MD" "PL" -22.32099 166.32549 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Herbier" "Frangeant ilot" "SG3" -999 6.8 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070312" "SVR" "Laregnere" "LA" NA NA 1 21 3 2008 NA NA NA -999 -999 NA "MD" "PL" -22.32103 166.32336 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "D4" -999 3 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070313" "SVR" "Laregnere" "LA" NA NA 1 21 3 2008 NA NA NA -999 -999 NA "MD" "PL" -22.32114 166.3212 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Algueraie" "Frangeant ilot" "MA3" -999 2.9 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070314" "SVR" "Laregnere" "LA" NA NA 1 21 3 2008 NA NA NA -999 -999 NA "MD" "PL" -22.31966 166.32016 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Herbier" "Frangeant ilot" "SG2" -999 6.9 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070315" "SVR" "Laregnere" "LA" NA NA 1 21 3 2008 NA NA NA -999 -999 NA "MD" "PL" -22.32611 166.32977 "RE" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Corail vivant" "Frangeant ilot" "LC2" -999 2.4 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA070316" "SVR" "Laregnere" "LA" NA NA 1 21 3 2008 NA NA NA -999 -999 NA "MD" "PL" -22.32543 166.33167 "RE" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Fond lagonaire" "Frangeant ilot" "LC5" -999 2.5 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA07139B" "SVR" "Laregnere" "LA" NA NA 1 2 7 2007 NA NA "0" 0 -999 NA "MD" "LD" -22.33127 166.30779 "RE" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA3" -999 10.4 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "LA080015" "SVR" "Laregnere" "LA" NA NA 1 1 7 2008 NA NA NA 2 -999 NA "MD" "DC" -22.32683 166.31209 "RE" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Fond lagonaire" "Frangeant ilot" "SA3" 6 4.2 -999 -999 -999 -999 "Drelon" +"AMP" "LA080018" "SVR" "Laregnere" "LA" NA NA 1 1 7 2008 NA NA NA 4 -999 NA "MM" "DC" -22.32557 166.32174 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Herbier" "Frangeant ilot" "SG2" 6 1.7 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "LA080020" "SVR" "Laregnere" "LA" NA NA 1 1 7 2008 NA NA NA 4 -999 NA "MM" "DC" -22.32603 166.32561 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "SA3" 5 2.2 -999 -999 -999 -999 "Drelon" +"AMP" "LA080035" "SVR" "Laregnere" "LA" NA NA 1 30 6 2008 NA NA NA -999 -999 NA "MD" "DC" -22.32536 166.33121 "RE" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Fond lagonaire" "Frangeant ilot" "SA3" 6 2.3 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "LA080037" "SVR" "Laregnere" "LA" NA NA 1 30 6 2008 NA NA NA -999 -999 NA "MD" "DC" -22.32556 166.33276 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Detritique" "Frangeant ilot" "D6" 6 4 -999 -999 -999 -999 "Drelon" +"AMP" "LA080038" "SVR" "Laregnere" "LA" NA NA 1 30 6 2008 NA NA NA -999 -999 NA "MD" "DC" -22.32645 166.3345 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Detritique" "Frangeant ilot" "D2" 6 5.8 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "LA080060" "SVR" "Laregnere" "LA" NA NA 1 30 6 2008 NA NA NA -999 -999 NA "MD" "DC" -22.32782 166.33606 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Detritique" "Frangeant ilot" "D6" 6 5.8 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "LA080061" "SVR" "Laregnere" "LA" NA NA 1 30 6 2008 NA NA NA -999 -999 NA "MD" "DC" -22.32918 166.33727 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA3" 6 6.6 -999 -999 -999 -999 "Drelon" +"AMP" "LA080062" "SVR" "Laregnere" "LA" NA NA 1 30 6 2008 NA NA NA -999 -999 NA "MD" "DC" -22.3308 166.33742 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "LC4" 6 7.9 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "LA080063" "SVR" "Laregnere" "LA" NA NA 1 30 6 2008 NA NA NA -999 -999 NA "BM" "DC" -22.33156 166.3358 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Frangeant ilot" "D1" 7 6.3 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "LA080065" "SVR" "Laregnere" "LA" NA NA 1 30 6 2008 NA NA NA -999 -999 NA "BM" "DC" -22.33175 166.33413 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Fond lagonaire" "Frangeant ilot" "SA1" 5 5.7 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "LA080067" "SVR" "Laregnere" "LA" NA NA 1 30 6 2008 NA NA NA -999 -999 NA "MM" "DC" -22.33116 166.3307 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Fond lagonaire" "Frangeant ilot" "D7" 7 7.4 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "LA080093" "SVR" "Laregnere" "LA" NA NA 1 1 7 2008 NA NA NA 3 -999 NA "MM" "DC" -22.32298 166.31503 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Herbier" "Frangeant ilot" "SG3" 6 7.7 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "LA080101" "SVR" "Laregnere" "LA" NA NA 1 30 6 2008 NA NA NA -999 -999 NA "MM" "DC" -22.33088 166.3291 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Fond lagonaire" "Frangeant ilot" "SA1" 5 7.3 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "LA080103" "SVR" "Laregnere" "LA" NA NA 1 30 6 2008 NA NA NA -999 -999 NA "MM" "DC" -22.33173 166.33252 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Fond lagonaire" "Frangeant ilot" "SA1" 3 7.5 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "LA080106" "SVR" "Laregnere" "LA" NA NA 1 30 6 2008 NA NA NA -999 -999 NA "MD" "DC" -22.32426 166.33174 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Algueraie" "Frangeant ilot" "MA4" 6 3.8 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "LA080107" "SVR" "Laregnere" "LA" NA NA 1 1 7 2008 NA NA NA 4 -999 NA "MM" "DC" -22.32432 166.33045 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "SA1" 9 3.3 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "LA080108" "SVR" "Laregnere" "LA" NA NA 1 1 7 2008 NA NA NA 4 -999 NA "MM" "DC" -22.32409 166.32897 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Algueraie" "Frangeant ilot" "MA3" 8 3.6 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "LA080110" "SVR" "Laregnere" "LA" NA NA 1 1 7 2008 NA NA NA 4 -999 NA "MM" "DC" -22.324 166.32589 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Herbier" "Frangeant ilot" "SG1" 7 4.1 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "LA080113" "SVR" "Laregnere" "LA" NA NA 1 2 7 2008 NA NA NA 2 -999 NA "MM" "DC" -22.32398 166.32106 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Herbier" "Frangeant ilot" "SG3" 8 2.5 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "LA080119" "SVR" "Laregnere" "LA" NA NA 1 1 7 2008 NA NA NA 3 -999 NA "MM" "DC" -22.32367 166.31855 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Herbier" "Frangeant ilot" "SG1" 6 3.1 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "LA080139" "SVR" "Laregnere" "LA" NA NA 1 2 7 2008 NA NA NA 2 -999 NA "MM" "DC" -22.33153 166.30763 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA1" 5 10.7 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "LA080210" "SVR" "Laregnere" "LA" NA NA 1 2 7 2008 NA NA NA 2 -999 NA "MM" "DC" -22.32995 166.30749 "RE" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA4" 5 11.4 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "LA080244" "SVR" "Laregnere" "LA" NA NA 1 2 7 2008 NA NA NA 2 -999 NA "MM" "DC" -22.32959 166.30917 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Fond lagonaire" "Frangeant ilot" "SA1" 6 7.9 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "LA080245" "SVR" "Laregnere" "LA" NA NA 1 2 7 2008 NA NA NA 2 -999 NA "BM" "DC" -22.3284 166.30958 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" NA 7 7.2 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "LA080258" "SVR" "Laregnere" "LA" NA NA 1 30 6 2008 NA NA NA -999 -999 NA "MD" "DC" -22.32429 166.33332 "RE" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA4" 5 9 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "LA080280" "SVR" "Laregnere" "LA" NA NA 1 30 6 2008 NA NA NA -999 -999 NA "MD" "DC" -22.33101 166.32003 "RE" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Frangeant ilot" "D5" 3 7.3 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "LA080283" "SVR" "Laregnere" "LA" NA NA 1 2 7 2008 NA NA NA 2 -999 NA "MM" "DC" -22.33192 166.30566 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "MA3" 6 10.5 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "LA080304" "SVR" "Laregnere" "LA" NA NA 1 30 6 2008 NA NA NA -999 -999 NA "MD" "DC" -22.32278 166.32077 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "SA1" 3 3 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "LA080308" "SVR" "Laregnere" "LA" NA NA 1 30 6 2008 NA NA NA -999 -999 NA "MD" "DC" -22.32264 166.32911 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Algueraie" "Frangeant ilot" "MA1" 5 3.3 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "LA080315" "SVR" "Laregnere" "LA" NA NA 1 1 7 2008 NA NA NA 4 -999 NA "MM" "DC" -22.32607 166.32975 "RE" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Frangeant ilot" "D3" 9 2.4 -999 -999 -999 -999 "Drelon" +"AMP" "LA08033B" "SVR" "Laregnere" "LA" NA NA 1 1 7 2008 NA NA NA 3 -999 NA "MD" "DC" -22.32449 166.31654 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Herbier" "Frangeant ilot" "SG2" 7 4.1 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "LA08072B" "SVR" "Laregnere" "LA" NA NA 1 1 7 2008 NA NA NA 1 -999 NA "MD" "DC" -22.33078 166.3219 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Frangeant ilot" "D3" 9 8.2 -999 -999 -999 -999 "Drelon" +"AMP" "LA08074B" "SVR" "Laregnere" "LA" NA NA 1 1 7 2008 NA NA NA 2 -999 NA "MD" "DC" -22.33134 166.31795 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Frangeant ilot" "D5" 8 7 -999 -999 -999 -999 "Drelon" +"AMP" "LA08075B" "SVR" "Laregnere" "LA" NA NA 1 1 7 2008 NA NA NA 2 -999 NA "MD" "DC" -22.33148 166.31626 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Frangeant ilot" "D2" 7 7.3 -999 -999 -999 -999 "Drelon" +"AMP" "LA08077B" "SVR" "Laregnere" "LA" NA NA 1 1 7 2008 NA NA NA 2 -999 NA "MD" "DC" -22.33147 166.31214 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Fond lagonaire" "Frangeant ilot" "SA3" 7 6 -999 -999 -999 -999 "Drelon" +"AMP" "LA08092B" "SVR" "Laregnere" "LA" NA NA 1 1 7 2008 NA NA NA 2 -999 NA "MD" "DC" -22.32437 166.31579 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Herbier" "Frangeant ilot" "SG3" 8 4 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "LA08096B" "SVR" "Laregnere" "LA" NA NA 1 1 7 2008 NA NA NA 2 -999 NA "MD" "DC" -22.33163 166.31401 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Frangeant ilot" "D7" 7 7.1 -999 -999 -999 -999 "Drelon" +"AMP" "LA08098B" "SVR" "Laregnere" "LA" NA NA 1 1 7 2008 NA NA NA 1 -999 NA "MD" "DC" -22.33077 166.32376 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Fond lagonaire" "Frangeant ilot" "SA3" 7 8.5 -999 -999 -999 -999 "Drelon" +"AMP" "LA08099B" "SVR" "Laregnere" "LA" NA NA 1 1 7 2008 NA NA NA 1 -999 NA "MD" "DC" -22.3308 166.32538 "RE" "AP" "Ile lagonaire" "lagon profond" "Detritique" "Frangeant ilot" "D5" 7 2.3 -999 -999 -999 -999 "Drelon" +"AMP" "LA08101B" "SVR" "Laregnere" "LA" NA NA 1 4 7 2008 NA NA NA 3 -999 NA "MM" "PC" -22.3308 166.32944 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Corail vivant" "Frangeant ilot" "LC1" 8 4 -999 -999 -999 -999 "Drelon" +"AMP" "LA08114B" "SVR" "Laregnere" "LA" NA NA 1 1 7 2008 NA NA NA 3 -999 NA "MM" "DC" -22.32478 166.31987 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "SA1" 3 2 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "LA08115B" "SVR" "Laregnere" "LA" NA NA 1 1 7 2008 NA NA NA 3 -999 NA "MD" "DC" -22.32548 166.31914 "RE" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Herbier" "Frangeant ilot" "SG1" 6 2.3 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "LA08117T" "SVR" "Laregnere" "LA" NA NA 1 1 7 2008 NA NA NA 3 -999 NA "BM" "DC" -22.32585 166.31669 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "SA1" 6 1.8 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "LA08118B" "SVR" "Laregnere" "LA" NA NA 1 1 7 2008 NA NA NA 3 -999 NA "MD" "DC" -22.32506 166.31811 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Herbier" "Frangeant ilot" "SG1" 5 4.3 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "LA08138B" "SVR" "Laregnere" "LA" NA NA 1 2 7 2008 NA NA NA 2 -999 NA "MM" "DC" -22.33105 166.31035 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Fond lagonaire" "Frangeant ilot" "SA1" 7 7.2 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "LA08257B" "SVR" "Laregnere" "LA" NA NA 1 1 7 2008 NA NA NA 2 -999 NA "MD" "DC" -22.32402 166.31416 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Herbier" "Frangeant ilot" "SG3" 7 4.9 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "LA090001" "SVR" "Laregnere" "LA" NA NA 1 25 6 2009 NA NA NA 3 -999 NA "MD" "PC" -22.32935 166.33738 "RE" "AP" "Ile lagonaire" "lagon profond" "Detritique" "Fond lagonaire" "D7" 9 7.6 -999 -999 -999 -999 "Drelon" +"AMP" "LA090002" "SVR" "Laregnere" "LA" NA NA 1 15 7 2009 NA NA NA -999 -999 NA "MD" "DQ" -22.33081 166.33729 "RE" "AP" "Ile lagonaire" "lagon profond" "Detritique" "Fond lagonaire" "D2" 7 7.7 -999 -999 -999 -999 "Drelon" +"AMP" "LA090003" "SVR" "Laregnere" "LA" NA NA 1 15 7 2009 NA NA NA -999 -999 NA "MD" "DQ" -22.33163 166.33579 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Frangeant ilot" "D2" 6 6.3 -999 -999 -999 -999 "Drelon" +"AMP" "LA090004" "SVR" "Laregnere" "LA" NA NA 1 25 6 2009 NA NA NA 2 -999 NA "MD" "PC" -22.33169 166.33268 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Fond lagonaire" "Frangeant ilot" "SA3" 10 7.6 -999 -999 -999 -999 "Drelon" +"AMP" "LA090006" "SVR" "Laregnere" "LA" NA NA 1 25 6 2009 NA NA NA 2 -999 NA "MD" "PC" -22.33138 166.33079 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Frangeant ilot" "D1" 9 8.5 -999 -999 -999 -999 "Drelon" +"AMP" "LA090008" "SVR" "Laregnere" "LA" NA NA 1 25 6 2009 NA NA NA 2 -999 NA "MD" "PC" -22.33081 166.32771 "RE" "AP" "Ile lagonaire" "lagon profond" "Detritique" "Frangeant ilot" "D2" 6 8.6 -999 -999 -999 -999 "Drelon" +"AMP" "LA090009" "SVR" "Laregnere" "LA" NA NA 1 25 6 2009 NA NA NA 2 -999 NA "PM" "PC" -22.33098 166.32533 "RE" "AP" "Ile lagonaire" "lagon profond" "Detritique" "Frangeant ilot" "D6" 8 8.9 -999 -999 -999 -999 "Drelon" +"AMP" "LA090010" "SVR" "Laregnere" "LA" NA NA 1 25 6 2009 NA NA NA 2 -999 NA "PM" "PC" -22.33093 166.32397 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Frangeant ilot" NA 8 8.9 -999 -999 -999 -999 "Drelon" +"AMP" "LA090011" "SVR" "Laregnere" "LA" NA NA 1 25 6 2009 NA NA NA 2 -999 NA "MM" "PC" -22.33089 166.3219 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Frangeant ilot" "D1" 8 8.8 -999 -999 -999 -999 "Drelon" +"AMP" "LA090012" "SVR" "Laregnere" "LA" NA NA 1 25 6 2009 NA NA NA 2 -999 NA "MM" "PC" -22.33105 166.32002 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Frangeant ilot" "D2" 7 8.1 -999 -999 -999 -999 "Drelon" +"AMP" "LA090013" "SVR" "Laregnere" "LA" NA NA 1 25 6 2009 NA NA NA 2 -999 NA "MM" "PC" -22.33142 166.31782 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Frangeant ilot" "D5" 8 8.2 -999 -999 -999 -999 "Drelon" +"AMP" "LA090014" "SVR" "Laregnere" "LA" NA NA 1 25 6 2009 NA NA NA 2 -999 NA "MM" "PC" -22.33153 166.31612 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Frangeant ilot" "D1" 7 7.9 -999 -999 -999 -999 "Drelon" +"AMP" "LA090015" "SVR" "Laregnere" "LA" NA NA 1 25 6 2009 NA NA NA 2 -999 NA "MM" "PC" -22.33168 166.31412 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Frangeant ilot" "D7" 10 7.7 -999 -999 -999 -999 "Drelon" +"AMP" "LA090016" "SVR" "Laregnere" "LA" NA NA 1 25 6 2009 NA NA NA 2 -999 NA "MM" "PC" -22.33159 166.31199 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Fond lagonaire" "Frangeant ilot" "SA3" 8 6.8 -999 -999 -999 -999 "Drelon" +"AMP" "LA090021" "SVR" "Laregnere" "LA" NA NA 1 25 6 2009 NA NA NA 3 -999 NA "MD" "PC" -22.32892 166.3076 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA1" 5 11.5 -999 -999 -999 -999 "William Roman" +"AMP" "LA090022" "SVR" "Laregnere" "LA" NA NA 1 25 6 2009 NA NA NA 3 -999 NA "MD" "PC" -22.32766 166.30576 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA1" 5 10 -999 -999 -999 -999 "William Roman" +"AMP" "LA090023" "SVR" "Laregnere" "LA" NA NA 1 24 6 2009 NA NA NA 5 -999 NA "MD" "PC" -22.32844 166.30967 "RE" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Fond lagonaire" "Frangeant ilot" "SA3" 6 7.5 -999 -999 -999 -999 "Drelon" +"AMP" "LA090025" "SVR" "Laregnere" "LA" NA NA 1 24 6 2009 NA NA NA 5 -999 NA "MD" "PC" -22.32688 166.31206 "RE" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Frangeant ilot" "D6" 7 4.6 -999 -999 -999 -999 "Drelon" +"AMP" "LA090032" "SVR" "Laregnere" "LA" NA NA 1 23 6 2009 NA NA NA 4 -999 NA "MD" "PC" -22.32432 166.31576 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Herbier" "Frangeant ilot" NA 7 5 -999 -999 -999 -999 "William Roman" +"AMP" "LA090040" "SVR" "Laregnere" "LA" NA NA 1 24 6 2009 NA NA NA 5 -999 NA "MD" "PC" -22.3256 166.32171 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Detritique" "Frangeant ilot" "D6" 7 2.4 -999 -999 -999 -999 "Drelon" +"AMP" "LA090042" "SVR" "Laregnere" "LA" NA NA 1 24 6 2009 NA NA NA 5 -999 NA "MD" "PC" -22.32285 166.32067 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "SA1" 6 3.2 -999 -999 -999 -999 "William Roman" +"AMP" "LA090046" "SVR" "Laregnere" "LA" NA NA 1 24 6 2009 NA NA NA 5 -999 NA "MD" "PC" -22.32244 166.32254 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Herbier" "Frangeant ilot" "SG1" 8 3.5 -999 -999 -999 -999 "Drelon" +"AMP" "LA090048" "SVR" "Laregnere" "LA" NA NA 1 23 6 2009 NA NA NA 5 -999 NA "MD" "PC" -22.32591 166.32354 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "SA3" 9 2.6 -999 -999 -999 -999 "Drelon" +"AMP" "LA090049" "SVR" "Laregnere" "LA" NA NA 1 23 6 2009 NA NA NA 5 -999 NA "MD" "PC" -22.32597 166.32572 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "SA3" 10 2.5 -999 -999 -999 -999 "Drelon" +"AMP" "LA090056" "SVR" "Laregnere" "LA" NA NA 1 24 6 2009 NA NA NA 4 -999 NA "MM" "PC" -22.32269 166.3272 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Herbier" "Frangeant ilot" "SG3" 8 4.9 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "LA090059" "SVR" "Laregnere" "LA" NA NA 1 23 6 2009 NA NA NA 5 -999 NA "MD" "PC" -22.32616 166.32733 "RE" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Frangeant ilot" "D6" 7 2.6 -999 -999 -999 -999 "Drelon" +"AMP" "LA090060" "SVR" "Laregnere" "LA" NA NA 1 23 6 2009 NA NA NA 5 -999 NA "MD" "PC" -22.32568 166.32916 "RE" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Fond lagonaire" "Frangeant ilot" "SA3" 6 3.2 -999 -999 -999 -999 "Drelon" +"AMP" "LA090062" "SVR" "Laregnere" "LA" NA NA 1 24 6 2009 NA NA NA 4 -999 NA "MM" "PC" -22.32257 166.32914 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Algueraie" "Frangeant ilot" "MA1" 6 4.2 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "LA090063" "SVR" "Laregnere" "LA" NA NA 1 24 6 2009 NA NA NA 4 -999 NA "MM" "PC" -22.32318 166.33046 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Algueraie" "Frangeant ilot" "MA1" 6 4.5 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "LA090065" "SVR" "Laregnere" "LA" NA NA 1 23 6 2009 NA NA NA 5 -999 NA "MD" "PC" -22.32532 166.3312 "RE" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Fond lagonaire" "Frangeant ilot" "SA3" 7 2.2 -999 -999 -999 -999 "Drelon" +"AMP" "LA090067" "SVR" "Laregnere" "LA" NA NA 1 15 7 2009 NA NA NA -999 -999 NA "MD" "DQ" -22.32417 166.33338 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA1" 7 10.7 -999 -999 -999 -999 "William Roman" +"AMP" "LA090068" "SVR" "Laregnere" "LA" NA NA 1 24 6 2009 NA NA NA 4 -999 NA "MM" "PC" -22.32567 166.33283 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Detritique" "Frangeant ilot" "D6" 7 5.4 -999 -999 -999 -999 "Drelon" +"AMP" "LA090069" "SVR" "Laregnere" "LA" NA NA 1 15 7 2009 NA NA NA -999 -999 NA "MD" "DQ" -22.32642 166.33445 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "SA5" 8 6 -999 -999 -999 -999 "Drelon" +"AMP" "LA090070" "SVR" "Laregnere" "LA" NA NA 1 25 6 2009 NA NA NA 3 -999 NA "MD" "PC" -22.32785 166.33613 "RE" "AP" "Ile lagonaire" "lagon profond" "Detritique" "Frangeant ilot" "D6" 7 7 -999 -999 -999 -999 "Drelon" +"AMP" "LA100001" "SVR" "Laregnere" "LA" NA NA 1 27 4 2010 NA NA NA 2 -999 NA "MD" "LM" -22.3253036 166.3176088 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Herbier" "Frangeant ilot" "SG1" 8 4.1 -999 -999 -999 -999 "Drelon" +"AMP" "LA100002" "SVR" "Laregnere" "LA" NA NA 1 27 4 2010 NA NA NA 2 -999 NA "MD" "LM" -22.3255764 166.3154887 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "SA5" 7.5 4.8 -999 -999 -999 -999 "Drelon" +"AMP" "LA100003" "SVR" "Laregnere" "LA" NA NA 1 27 4 2010 NA NA NA 2 -999 NA "MD" "LM" -22.3261312 166.3135609 "RE" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Frangeant ilot" "D7" 7 5 -999 -999 -999 -999 "Drelon" +"AMP" "LA100009" "SVR" "Laregnere" "LA" NA NA 1 26 2 2010 NA NA NA 5 -999 NA "MD" "LM" -22.3258369 166.3237439 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "SA3" 5.5 4.3 -999 -999 -999 -999 "Drelon" +"AMP" "LA100012" "SVR" "Laregnere" "LA" NA NA 1 26 2 2010 NA NA NA 5 -999 NA "MD" "LM" -22.3261274 166.3273664 "RE" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Frangeant ilot" NA 7 3 -999 -999 -999 -999 "Drelon" +"AMP" "LA100016" "SVR" "Laregnere" "LA" NA NA 1 26 2 2010 NA NA NA 4 -999 NA "MD" "LM" -22.3252913 166.3311979 "RE" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Fond lagonaire" "Frangeant ilot" "SA3" 7 3.6 -999 -999 -999 -999 "Drelon" +"AMP" "LA100018" "SVR" "Laregnere" "LA" NA NA 1 26 2 2010 NA NA NA 4 -999 NA "MD" "LM" -22.3255917 166.3329139 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Detritique" "Frangeant ilot" "D6" 8 5.5 -999 -999 -999 -999 "Drelon" +"AMP" "LA100028" "SVR" "Laregnere" "LA" NA NA 1 27 4 2010 NA NA NA 2 -999 NA "MD" "LM" -22.3268364 166.3121624 "RE" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Frangeant ilot" "D6" 7 4.6 -999 -999 -999 -999 "Drelon" +"AMP" "LA100029" "SVR" "Laregnere" "LA" NA NA 1 27 4 2010 NA NA NA 2 -999 NA "MD" "LM" -22.3283876 166.3097062 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Detritique" "Frangeant ilot" "D7" 7 7.7 -999 -999 -999 -999 "Drelon" +"AMP" "LA100030" "SVR" "Laregnere" "LA" NA NA 1 27 4 2010 NA NA NA 2 -999 NA "MD" "LM" -22.3299578 166.3093883 "RE" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Frangeant ilot" "D5" 6.5 7.9 -999 -999 -999 -999 "Drelon" +"AMP" "LA100032" "SVR" "Laregnere" "LA" NA NA 1 27 4 2010 NA NA NA 2 -999 NA "MD" "LM" -22.331401 166.3121459 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Frangeant ilot" "D7" 7 6.8 -999 -999 -999 -999 "Drelon" +"AMP" "LA100033" "SVR" "Laregnere" "LA" NA NA 1 23 3 2010 NA NA NA 4 -999 NA "MM" "PQ" -22.3316867 166.3140928 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Frangeant ilot" "D1" 8 8.5 -999 -999 -999 -999 "Drelon" +"AMP" "LA100036" "SVR" "Laregnere" "LA" NA NA 1 23 3 2010 NA NA NA 4 -999 NA "MM" "PQ" -22.3311045 166.3200013 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Frangeant ilot" "D1" 6 9.1 -999 -999 -999 -999 "Drelon" +"AMP" "LA100037" "SVR" "Laregnere" "LA" NA NA 1 2 3 2010 NA NA "0" 0 -999 NA "MM" "LD" -22.3314821 166.3179073 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Frangeant ilot" "D1" 7 9.4 -999 -999 -999 -999 "Drelon" +"AMP" "LA100038" "SVR" "Laregnere" "LA" NA NA 1 27 4 2010 NA NA NA 2 -999 NA "MD" "LM" -22.3308635 166.3218983 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Frangeant ilot" "D2" 8 9.5 -999 -999 -999 -999 "Drelon" +"AMP" "LA100039" "SVR" "Laregnere" "LA" NA NA 1 1 3 2010 NA NA NA 3 -999 NA "MD" "LD" -22.330944 166.3240196 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Fond lagonaire" "Frangeant ilot" "SA5" 8 10.5 -999 -999 -999 -999 "Drelon" +"AMP" "LA100040" "SVR" "Laregnere" "LA" NA NA 1 1 3 2010 NA NA NA 3 -999 NA "MD" "LD" -22.3309624 166.3253834 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Frangeant ilot" "SA1" 7 10.6 -999 -999 -999 -999 "Drelon" +"AMP" "LA100041" "SVR" "Laregnere" "LA" NA NA 1 1 3 2010 NA NA NA 3 -999 NA "MD" "LD" -22.3308213 166.3277496 "RE" "AP" "Ile lagonaire" "lagon profond" "Detritique" "Frangeant ilot" "D2" 7 9.5 -999 -999 -999 -999 "Drelon" +"AMP" "LA100046" "SVR" "Laregnere" "LA" NA NA 1 1 3 2010 NA NA NA 3 -999 NA "MM" "LD" -22.3294768 166.3374011 "RE" "AP" "Ile lagonaire" "lagon profond" "Detritique" "Fond lagonaire" NA 7 8 -999 -999 -999 -999 "Drelon" +"AMP" "LA100047" "SVR" "Laregnere" "LA" NA NA 1 23 3 2010 NA NA NA 3 -999 NA "MM" "PQ" -22.3280139 166.3363889 "RE" "AP" "Ile lagonaire" "lagon profond" "Detritique" "Frangeant ilot" NA 6.5 7.3 -999 -999 -999 -999 "Drelon" +"AMP" "LA100053" "SVR" "Laregnere" "LA" NA NA 1 1 3 2010 NA NA NA 3 -999 NA "MM" "LD" -22.3200321 166.3300809 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA5" 8 14.2 -999 -999 -999 -999 "Drelon" +"AMP" "LA100054" "SVR" "Laregnere" "LA" NA NA 1 23 3 2010 NA NA NA 3 -999 NA "MM" "PQ" -22.3265071 166.3344801 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Detritique" "Frangeant ilot" NA 7.5 5.8 -999 -999 -999 -999 "Drelon" +"AMP" "LA100055" "SVR" "Laregnere" "LA" NA NA 1 23 3 2010 NA NA NA 3 -999 NA "MM" "PQ" -22.3308428 166.336916 "RE" "AP" "Ile lagonaire" "lagon profond" "Detritique" "Fond lagonaire" "D2" 7 6.1 -999 -999 -999 -999 "Drelon" +"AMP" "LA100056" "SVR" "Laregnere" "LA" NA NA 1 23 3 2010 NA NA NA 3 -999 NA "MM" "PQ" -22.3314973 166.3358562 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Frangeant ilot" "D1" 8 6.8 -999 -999 -999 -999 "Drelon" +"AMP" "LI140001" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "Easo-Xepenehe sup15m" 1 26 9 2014 "11:23" NA "E" 3 1 NA "MD" "PC" -20.78718 167.13803 "HR" "AP" "" "" "Corail vivant" "Frangeant oceanique" "LC2" -999 22.5 -999 507.04 -999 -999 "Delphine Mallet" +"AMP" "LI140002" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "Easo-Xepenehe sup15m" 1 26 9 2014 "12:35" NA "E" 1 1 NA "MD" "PC" -20.7877 167.14055 "HR" "AP" "" "" "Corail vivant" "Frangeant oceanique" "LC2" -999 21.6 -999 740.46 -999 -999 "Delphine Mallet" +"AMP" "LI140003" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "Easo-Xepenehe sup15m" 1 26 9 2014 "13:17" NA "E" 1 1 NA "MD" "PC" -20.78843 167.1431 "HR" "AP" "" "" "Corail vivant" "Frangeant oceanique" "LC1" -999 21 -999 1000.61 -999 -999 "Delphine Mallet" +"AMP" "LI140004" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "Easo-Xepenehe sup15m" 1 26 9 2014 "14:01" NA "S" 1 1 NA "MD" "PC" -20.78921 167.1454 "HR" "AP" "" "" "Corail vivant" "Frangeant oceanique" "LC1" -999 28 -999 1236.92 -999 -999 "Delphine Mallet" +"AMP" "LI140006" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "200-400m" 1 26 9 2014 "10:52" NA "E" 3 1 NA "MD" "PC" -20.78725 167.13632 "HR" "AP" "" "" "Corail vivant" "Frangeant oceanique" "LC1" -999 23 -999 337.36 -999 -999 "Delphine Mallet" +"AMP" "LI140007" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "Easo-Xepenehe sup15m" 1 26 9 2014 "12:00" NA "E" 1 1 NA "MD" "PC" -20.78776 167.13881 "HR" "AP" "" "" "Corail vivant" "Frangeant oceanique" "LC1" -999 24 -999 560.82 -999 -999 "Delphine Mallet" +"AMP" "LI140008" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "Easo-Xepenehe sup15m" 1 27 9 2014 "12:20" NA "W" 2 1 NA "MD" "PC" -20.78869 167.14133 "HR" "AP" "" "" "Corail vivant" "Frangeant oceanique" "LC1" -999 24 -999 817.02 -999 -999 "Delphine Mallet" +"AMP" "LI140009" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "200-400m" 1 26 9 2014 "09:16" NA "E" 2 1 NA "PM" "PC" -20.78636 167.13229 "HR" "AP" "" "" "Detritique" "Frangeant oceanique" NA -999 24 -999 307.81 -999 -999 "Delphine Mallet" +"AMP" "LI140010" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "200-400m" 1 26 9 2014 "10:04" NA "E" 2 1 NA "PM" "PC" -20.7871 167.13472 "HR" "AP" "" "" "Corail vivant" "Frangeant oceanique" "LC4" -999 21 -999 232.54 -999 -999 "Delphine Mallet" +"AMP" "LI140011" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "200-400m" 1 26 9 2014 "10:08" NA "E" 2 1 NA "PM" "PC" -20.78839 167.13602 "HR" "AP" "" "" "Corail vivant" "Frangeant oceanique" "LC4" -999 27 -999 263.52 -999 -999 "Delphine Mallet" +"AMP" "LI140012" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "Easo-Xepenehe sup15m" 1 26 9 2014 "10:48" NA "E" 3 1 NA "MD" "PC" -20.78943 167.13742 "HR" "AP" "" "" "Corail vivant" "Frangeant oceanique" "LC4" -999 33.9 -999 413.53 -999 -999 "Delphine Mallet" +"AMP" "LI140013" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "Easo-Xepenehe sup15m" 1 26 9 2014 "08:55" NA "0" 0 1 NA "PM" "PC" -20.78624 167.13039 "HR" "AP" "" "" "Corail vivant" "Frangeant oceanique" "LC4" -999 23 -999 433.85 -999 -999 "Delphine Mallet" +"AMP" "LI140014" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "200-400m" 1 26 9 2014 "09:29" NA "E" 2 1 NA "PM" "PC" -20.78645 167.13298 "HR" "AP" "" "" "Detritique" "Frangeant oceanique" "D1" -999 25 -999 274.06 -999 -999 "Delphine Mallet" +"AMP" "LI140015" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "0-200m" 1 26 9 2014 "09:39" NA "E" 2 1 NA "PM" "PC" -20.78833 167.13452 "HR" "AP" "" "" "Detritique" "Frangeant oceanique" "D3" -999 28.1 -999 120.18 -999 -999 "Delphine Mallet" +"AMP" "LI140016" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "0-200m" 1 26 9 2014 "08:32" NA "0" 0 1 NA "PM" "PC" -20.78743 167.13242 "HR" "AP" "" "" "Detritique" "Frangeant oceanique" "D2" -999 34.4 -999 193.79 -999 -999 "Delphine Mallet" +"AMP" "LI140018" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "Easo-Xepenehe sup15m" 1 26 9 2014 "13:13" NA "E" 1 1 NA "MD" "PC" -20.79023 167.14174 "HR" "AP" "" "" "Corail vivant" "Frangeant oceanique" "LC2" -999 32 -999 874.93 -999 -999 "Delphine Mallet" +"AMP" "LI140019" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "Easo-Xepenehe sup15m" 1 26 9 2014 "13:48" NA "S" 1 1 NA "MD" "PC" -20.7912 167.14287 "HR" "AP" "" "" "Corail vivant" "Frangeant oceanique" "LC1" -999 40 -999 1004.07 -999 -999 "Delphine Mallet" +"AMP" "LI140021" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "200-400m" 1 26 9 2014 "08:22" NA "0" 0 1 NA "PM" "PC" -20.78758 167.13043 "HR" "AP" "" "" "Detritique" "Frangeant oceanique" NA -999 34 -999 356.46 -999 -999 "Delphine Mallet" +"AMP" "LI140022" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "Easo-Xepenehe sup15m" 1 26 9 2014 "08:39" NA "0" 0 1 NA "PM" "PC" -20.78534 167.13252 "HR" "AP" "" "" "Corail vivant" "Frangeant oceanique" "LC1" -999 16 -999 398.89 -999 -999 "Delphine Mallet" +"AMP" "LI140023" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "Easo-Xepenehe sup15m" 1 26 9 2014 "11:19" NA "E" 3 1 NA "MD" "PC" -20.7864 167.13745 "HR" "AP" "" "" "Corail vivant" "Frangeant oceanique" "LC1" -999 19.2 -999 488.95 -999 -999 "Delphine Mallet" +"AMP" "LI140024" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "Easo-Xepenehe sup15m" 1 26 9 2014 "12:26" NA "E" 1 1 NA "MD" "PC" -20.78714 167.13983 "HR" "AP" "" "" "Corail vivant" "Frangeant oceanique" "LC1" -999 20.6 -999 680.7 -999 -999 "Delphine Mallet" +"AMP" "LI140025" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "Easo-Xepenehe sup15m" 1 26 9 2014 "07:54" NA "0" 0 1 NA "MM" "PC" -20.78749 167.12906 "HR" "AP" "" "" "Detritique" "Frangeant oceanique" "D6" -999 25.3 -999 486.1 -999 -999 "Delphine Mallet" +"AMP" "LI140026" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "Easo-Xepenehe sup15m" 1 26 9 2014 "13:34" NA "S" 1 1 NA "MD" "PC" -20.78842 167.14479 "HR" "AP" "" "" "Corail vivant" "Frangeant oceanique" "LC1" -999 23 -999 1172.47 -999 -999 "Delphine Mallet" +"AMP" "LI140027" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "Easo-Xepenehe sup15m" 1 26 9 2014 "14:13" NA "S" 1 1 NA "MD" "PC" -20.79035 167.14528 "HR" "AP" "" "" "Corail vivant" "Frangeant oceanique" "LC4" -999 28 -999 1237.43 -999 -999 "Delphine Mallet" +"AMP" "LI140028" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "Easo-Xepenehe sup15m" 1 26 9 2014 "14:21" NA "SE" 1 1 NA "MD" "PC" -20.79141 167.14682 "HR" "AP" "" "" "Corail vivant" "Frangeant oceanique" "LC4" -999 30 -999 1416.71 -999 -999 "Delphine Mallet" +"AMP" "LI140029" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "Easo-Xepenehe sup15m" 1 26 9 2014 "12:46" NA "E" 1 1 NA "MD" "PC" -20.78898 167.14189 "HR" "AP" "" "" "Corail vivant" "Frangeant oceanique" "LC2" -999 24 -999 870.96 -999 -999 "Delphine Mallet" +"AMP" "LI140031" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "Easo-Xepenehe sup15m" 1 26 9 2014 "11:52" NA "E" 3 1 NA "MD" "PC" -20.78937 167.13928 "HR" "AP" "" "" "Corail vivant" "Frangeant oceanique" "LC4" -999 28 -999 605.41 -999 -999 "Delphine Mallet" +"AMP" "LI140032" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "Easo-Xepenehe sup15m" 1 26 9 2014 "11:27" NA "E" 3 1 NA "MD" "PC" -20.78834 167.13753 "HR" "AP" "" "" "Corail vivant" "Frangeant oceanique" "LC4" -999 28 -999 422.65 -999 -999 "Delphine Mallet" +"AMP" "LI140033" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "Easo-Xepenehe sup15m" 1 26 9 2014 "13:23" NA "E" 1 1 NA "MD" "PC" -20.7908 167.14082 "HR" "AP" "" "" "Corail vivant" "Frangeant oceanique" "LC4" -999 36.1 -999 792.9 -999 -999 "Delphine Mallet" +"AMP" "LI140035" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "200-400m" 1 26 9 2014 "10:45" NA "E" 3 1 NA "MD" "PC" -20.78988 167.13643 "HR" "AP" "" "" "Corail vivant" "Frangeant oceanique" "LC4" -999 34.5 -999 323.37 -999 -999 "Delphine Mallet" +"AMP" "LI140036" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "0-200m" 1 26 9 2014 "09:55" NA "E" 2 1 NA "PM" "PC" -20.78949 167.13393 "HR" "AP" "" "" "Detritique" "Frangeant oceanique" "D1" -999 36.5 -999 86.66 -999 -999 "Delphine Mallet" +"AMP" "LI140038" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "0-200m" 1 26 9 2014 "10:19" NA "E" 2 1 NA "MD" "PC" -20.78989 167.13441 "HR" "AP" "" "" "Detritique" "Frangeant oceanique" "D2" -999 36.5 -999 152.78 -999 -999 "Delphine Mallet" +"AMP" "LI140039" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "Easo-Xepenehe sup15m" 1 26 9 2014 "14:25" NA "SE" 1 1 NA "MD" "PC" -20.78882 167.14708 "HR" "AP" "" "" "Corail vivant" "Frangeant oceanique" "LC1" -999 19.8 -999 1408.2 -999 -999 "Delphine Mallet" +"AMP" "LI140041" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "Easo-Xepenehe sup15m" 1 27 9 2014 "08:22" NA "0" 0 1 NA "MM" "PC" -20.79044 167.12657 "HR" "AP" "" "" "Corail vivant" "Frangeant oceanique" "LC4" -999 23 -999 740.46 -999 -999 "Delphine Mallet" +"AMP" "LI140042" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "Easo-Xepenehe sup15m" 1 27 9 2014 "08:28" NA "0" 0 1 NA "MM" "PC" -20.79181 167.12708 "HR" "AP" "" "" "Corail vivant" "Frangeant oceanique" "LC4" -999 30 -999 740.38 -999 -999 "Delphine Mallet" +"AMP" "LI140043" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "Easo-Xepenehe sup15m" 1 27 9 2014 "08:38" NA "0" 0 1 NA "MM" "PC" -20.7926 167.12755 "HR" "AP" "" "" "Detritique" "Frangeant oceanique" "D5" -999 35 -999 745.36 -999 -999 "Delphine Mallet" +"AMP" "LI140046" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "Easo-Xepenehe sup15m" 1 27 9 2014 "09:15" NA "0" 0 1 NA "PM" "PC" -20.79221 167.12621 "HR" "AP" "" "" "Corail vivant" "Frangeant oceanique" "LC6" -999 31 -999 846.2 -999 -999 "Delphine Mallet" +"AMP" "LI140047" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "2nd mouillage" 1 27 9 2014 "09:09" NA "0" 0 1 NA "PM" "PC" -20.79376 167.12683 "HR" "AP" "" "" "Corail vivant" "Frangeant oceanique" "LC1" -999 41 -999 881.51 -999 -999 "Delphine Mallet" +"AMP" "LI140048" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "2nd mouillage" 1 27 9 2014 "10:10" NA "SW" 2 1 NA "PM" "PC" -20.79258 167.12494 "HR" "AP" "" "" "Corail vivant" "Frangeant oceanique" "LC4" -999 30 -999 981.26 -999 -999 "Delphine Mallet" +"AMP" "LI140049" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "2nd mouillage" 1 27 9 2014 "10:32" NA "SW" 2 1 NA "PM" "PC" -20.79358 167.12552 "HR" "AP" "" "" "Corail vivant" "Frangeant oceanique" "LC4" -999 35 -999 984.49 -999 -999 "Delphine Mallet" +"AMP" "LI140050" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "2nd mouillage" 1 27 9 2014 "10:35" NA "SW" 2 1 NA "PM" "PC" -20.79469 167.12578 "HR" "AP" "" "" "Corail vivant" "Frangeant oceanique" "LC1" -999 37 -999 1030.31 -999 -999 "Delphine Mallet" +"AMP" "LI140051" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "Easo-Xepenehe sup15m" 1 27 9 2014 "11:45" NA "W" 2 1 NA "MD" "PC" -20.79166 167.12395 "HR" "AP" "" "" "Corail vivant" "Frangeant oceanique" "LC2" -999 24 -999 1044.01 -999 -999 "Delphine Mallet" +"AMP" "LI140062" "SVR" "Jinek" NA "Frangeant oceanique" "Jinek sup15m" 1 1 10 2014 "09:37" NA "S" 3 1 NA "MM" "PC" -20.79197 167.12091 "HR" "AP" "" "" "Corail vivant" "Frangeant oceanique" "LC2" -999 26 -999 1353.09 -999 -999 "Delphine Mallet" +"AMP" "LI140063" "SVR" "Jinek" NA "Frangeant oceanique" "Jinek sup15m" 1 1 10 2014 "09:57" NA "S" 3 1 NA "MM" "PC" -20.79313 167.12076 "HR" "AP" "" "" "Corail vivant" "Frangeant oceanique" NA -999 32 -999 1410.79 -999 -999 "Delphine Mallet" +"AMP" "LI140064" "SVR" "Jinek" NA "Frangeant oceanique" "Jinek sup15m" 1 1 10 2014 "10:24" NA "S" 3 1 NA "MM" "PC" -20.79428 167.12064 "HR" "AP" "" "" "Detritique" "Frangeant oceanique" NA -999 40 -999 1467.98 -999 -999 "Delphine Mallet" +"AMP" "LI140067" "SVR" "Jinek" NA "Frangeant oceanique" "Jinek Nord inf15m" 1 30 9 2014 "10:19" NA "S" 4 1 NA "MM" "NL" -20.79181 167.11877 "HR" "AP" "" "" "Corail vivant" "Frangeant oceanique" "LC1" -999 14 -999 1568.44 -999 -999 "Delphine Mallet" +"AMP" "LI140068" "SVR" "Jinek" NA "Frangeant oceanique" "Jinek sup15m" 1 1 10 2014 "10:03" NA "S" 3 1 NA "MM" "PC" -20.79413 167.11897 "HR" "AP" "" "" "Corail vivant" "Frangeant oceanique" "LC2" -999 40 -999 1619.19 -999 -999 "Delphine Mallet" +"AMP" "LI140069" "SVR" "Jinek" NA "Frangeant oceanique" "Jinek sup15m" 1 1 10 2014 "10:31" NA "S" 3 1 NA "MM" "PC" -20.79419 167.1187 "HR" "AP" "" "" "Corail vivant" "Frangeant oceanique" "LC4" -999 40 -999 1653.16 -999 -999 "Delphine Mallet" +"AMP" "LI140072" "SVR" "Jinek" NA "Frangeant oceanique" "Jinek sup15m" 1 1 10 2014 "10:55" NA "S" 3 1 NA "MM" "PC" -20.79381 167.11816 "HR" "AP" "" "" "Corail vivant" "Frangeant oceanique" "LC2" -999 40 -999 1689.42 -999 -999 "Delphine Mallet" +"AMP" "LI140073" "SVR" "Jinek" NA "Frangeant oceanique" "Jinek sup15m" 1 1 10 2014 "10:50" NA "S" 3 1 NA "MM" "PC" -20.79442 167.11656 "HR" "AP" "" "" "Corail vivant" "Frangeant oceanique" "LC1" -999 41 -999 1873.01 -999 -999 "Delphine Mallet" +"AMP" "LI140077" "SVR" "Jinek" NA "Frangeant oceanique" "Jinek Nord inf15m" 1 30 9 2014 "10:33" NA "S" 4 1 NA "MM" "NL" -20.79122 167.11797 "HR" "AP" "" "" "Corail vivant" "Frangeant oceanique" "LC2" -999 12.7 -999 1641.87 -999 -999 "Delphine Mallet" +"AMP" "LI140081" "SVR" "Pointe Easo" NA "Frangeant oceanique" "Easo-Xepenehe inf15m" 1 27 9 2014 "12:17" NA "W" 1 1 NA "MD" "PC" -20.79005 167.12459 "HR" "AP" "Recif frangeant expose a l\92ocean" "front recifal" "Corail vivant" "Frangeant oceanique" "LC1" -999 6 -999 933.4 -999 -999 "Delphine Mallet" +"AMP" "LI140082" "SVR" "Pointe Easo" NA "Frangeant oceanique" "Easo-Xepenehe inf15m" 1 27 9 2014 "08:06" NA "0" 0 1 NA "MM" "PC" -20.78911 167.12576 "HR" "AP" "Recif frangeant expose a l\92ocean" "front recifal" "Corail vivant" "Frangeant oceanique" "LC5" -999 12 -999 806.49 -999 -999 "Delphine Mallet" +"AMP" "LI140083" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "Easo-Xepenehe inf15m" 1 26 9 2014 "12:37" NA NA 1 1 NA "MD" "PC" -20.78758 167.1261 "HR" "AP" "Recif frangeant expose a l\92ocean" "platier recifal" "Corail vivant" "Frangeant oceanique" "LC4" -999 4 -999 788.45 -999 -999 "Delphine Mallet" +"AMP" "LI140084" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "Easo-Xepenehe inf15m" 1 26 9 2014 "12:42" NA NA 1 1 NA "MD" "PC" -20.78679 167.12675 "HR" "AP" "Recif frangeant expose a l\92ocean" "front recifal" "Corail vivant" "Frangeant oceanique" NA -999 11 -999 737.64 -999 -999 "Delphine Mallet" +"AMP" "LI140085" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "Easo-Xepenehe sup15m" 1 26 9 2014 "07:47" NA "0" 0 1 NA "MM" "PC" -20.78651 167.12842 "HR" "AP" "" "" "Detritique" "Frangeant oceanique" "SA5" -999 18 -999 591.31 -999 -999 "Delphine Mallet" +"AMP" "LI140086" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "Easo-Xepenehe inf15m" 1 26 9 2014 "08:06" NA "0" 0 1 NA "MM" "PC" -20.78493 167.1268 "HR" "AP" "Recif frangeant expose a l\92ocean" "platier recifal" "Fond lagonaire" "Frangeant oceanique" "SA5" -999 5 -999 826.09 -999 -999 "Delphine Mallet" +"AMP" "LI140087" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "Easo-Xepenehe inf15m" 1 26 9 2014 "08:25" NA "0" 0 1 NA "PM" "PC" -20.78392 167.13016 "HR" "AP" "Recif frangeant expose a l\92ocean" "front recifal" "Corail vivant" "Frangeant oceanique" "LC3" -999 12 -999 647.2 -999 -999 "Delphine Mallet" +"AMP" "LI140088" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "Easo-Xepenehe inf15m" 1 26 9 2014 "08:11" NA "0" 0 1 NA "MM" "PC" -20.7826 167.12759 "HR" "AP" "Recif frangeant expose a l\92ocean" "platier recifal" "Detritique" "Frangeant oceanique" "D6" -999 2 -999 929.3 -999 -999 "Delphine Mallet" +"AMP" "LI140089" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "Easo-Xepenehe inf15m" 1 26 9 2014 "08:40" NA NA 1 1 NA "PM" "PC" -20.78216 167.13094 "HR" "AP" "Recif frangeant expose a l\92ocean" "platier recifal" "Corail vivant" "Frangeant oceanique" "SA5" -999 6 -999 785.29 -999 -999 "Delphine Mallet" +"AMP" "LI140090" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "Easo-Xepenehe inf15m" 1 26 9 2014 "08:52" NA NA 1 1 NA "PM" "PC" -20.78296 167.13184 "HR" "AP" "Recif frangeant expose a l\92ocean" "front recifal" "Corail vivant" "Frangeant oceanique" "LC1" -999 9 -999 677.89 -999 -999 "Delphine Mallet" +"AMP" "LI140091" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "Easo-Xepenehe inf15m" 1 26 9 2014 "09:11" NA NA 1 1 NA "PM" "PC" -20.78324 167.13304 "HR" "AP" "Recif frangeant expose a l\92ocean" "front recifal" "Corail vivant" "Frangeant oceanique" "LC2" -999 12 -999 624.94 -999 -999 "Delphine Mallet" +"AMP" "LI140092" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "Easo-Xepenehe inf15m" 1 26 9 2014 "08:58" NA NA 1 1 NA "PM" "PC" -20.78149 167.1337 "HR" "AP" "Recif frangeant expose a l\92ocean" "platier recifal" "Detritique" "Frangeant oceanique" "D3" -999 4 -999 817.23 -999 -999 "Delphine Mallet" +"AMP" "LI140093" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "Easo-Xepenehe inf15m" 1 26 9 2014 "09:20" NA NA 1 1 NA "PM" "PC" -20.78286 167.13582 "HR" "AP" "Recif frangeant expose a l\92ocean" "front recifal" "Corail vivant" "Frangeant oceanique" NA -999 9 -999 710.84 -999 -999 "Delphine Mallet" +"AMP" "LI140094" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "Easo-Xepenehe inf15m" 1 26 9 2014 "09:42" NA NA 1 1 NA "PM" "PC" -20.78484 167.13745 "HR" "AP" "" "" "Corail vivant" "Frangeant oceanique" NA -999 10 -999 600.91 -999 -999 "Delphine Mallet" +"AMP" "LI140096" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "Easo-Xepenehe sup15m" 1 26 9 2014 "09:35" NA NA 1 1 NA "PM" "PC" -20.7855 167.13661 "HR" "AP" "" "" "Corail vivant" "Frangeant oceanique" "LC2" -999 15 -999 487.41 -999 -999 "Delphine Mallet" +"AMP" "LI140097" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "Easo-Xepenehe inf15m" 1 26 9 2014 "10:00" NA NA 1 1 NA "PM" "PC" -20.78108 167.14001 "HR" "AP" "Recif frangeant expose a l\92ocean" "platier recifal" "Fond lagonaire" "Frangeant oceanique" "SA3" -999 2 -999 1101.27 -999 -999 "Delphine Mallet" +"AMP" "LI140098" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "Easo-Xepenehe inf15m" 1 26 9 2014 "10:12" NA NA 1 1 NA "PM" "PC" -20.78385 167.13933 "HR" "AP" "" "" "Corail vivant" "Frangeant oceanique" "LC1" -999 13 -999 822.17 -999 -999 "Delphine Mallet" +"AMP" "LI140099" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "Easo-Xepenehe sup15m" 1 26 9 2014 "10:29" NA NA 1 1 NA "MD" "PC" -20.78521 167.13982 "HR" "AP" "" "" "Corail vivant" "Frangeant oceanique" "LC1" -999 17 -999 766.9 -999 -999 "Delphine Mallet" +"AMP" "LI140100" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "Easo-Xepenehe inf15m" 1 26 9 2014 "09:54" NA NA 1 1 NA "PM" "PC" -20.78214 167.13806 "HR" "AP" "Recif frangeant expose a l\92ocean" "platier recifal" "Corail vivant" "Frangeant oceanique" "LC2" -999 9 -999 885.5 -999 -999 "Delphine Mallet" +"AMP" "LI140102" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "Easo-Xepenehe inf15m" 1 26 9 2014 "10:22" NA NA 1 1 NA "MD" "PC" -20.78403 167.14343 "HR" "AP" "Recif frangeant expose a l\92ocean" "front recifal" "Detritique" "Frangeant oceanique" NA -999 8 -999 1158.59 -999 -999 "Delphine Mallet" +"AMP" "LI140103" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "Easo-Xepenehe inf15m" 1 26 9 2014 "10:50" NA NA 1 1 NA "MD" "PC" -20.78671 167.14397 "HR" "AP" "" "" "Corail vivant" "Frangeant oceanique" "LC1" -999 6 -999 1108.9 -999 -999 "Delphine Mallet" +"AMP" "LI140104" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "Easo-Xepenehe sup15m" 1 26 9 2014 "11:11" NA NA 1 1 NA "MD" "PC" -20.78739 167.14363 "HR" "AP" "" "" "Corail vivant" "Frangeant oceanique" "LC2" -999 15 -999 1064.13 -999 -999 "Delphine Mallet" +"AMP" "LI140105" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "Easo-Xepenehe inf15m" 1 26 9 2014 "10:42" NA NA 1 1 NA "MD" "PC" -20.78355 167.14699 "HR" "AP" "Recif frangeant expose a l\92ocean" "platier recifal" "Fond lagonaire" "Frangeant oceanique" "SA4" -999 2 -999 1523.11 -999 -999 "Delphine Mallet" +"AMP" "LI140106" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "Easo-Xepenehe sup15m" 1 26 9 2014 "11:35" NA NA 1 1 NA "MD" "PC" -20.7888 167.14882 "HR" "AP" "" "" "Corail vivant" "Frangeant oceanique" "LC1" -999 18 -999 1590.9 -999 -999 "Delphine Mallet" +"AMP" "LI140107" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "Easo-Xepenehe inf15m" 1 26 9 2014 "11:24" NA NA 1 1 NA "MD" "PC" -20.78719 167.15091 "HR" "AP" "Recif frangeant expose a l\92ocean" "platier recifal" "Fond lagonaire" "Frangeant oceanique" "SA3" -999 4 -999 1824.76 -999 -999 "Delphine Mallet" +"AMP" "LI140108" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "Easo-Xepenehe sup15m" 1 26 9 2014 "12:01" NA NA 1 1 NA "MD" "PC" -20.7927 167.15396 "HR" "AP" "" "" "Corail vivant" "Frangeant oceanique" "LC2" -999 17 -999 2173.52 -999 -999 "Delphine Mallet" +"AMP" "LI140109" "SVR" "Pointe Easo" NA "Frangeant oceanique" "Easo-Xepenehe sup15m" 1 27 9 2014 "08:39" NA "0" 0 1 NA "MM" "PC" -20.7912 167.12292 "HR" "AP" "" "" "Detritique" "Frangeant oceanique" "D2" -999 21 -999 1134.45 -999 -999 "Delphine Mallet" +"AMP" "LI140110" "SVR" "Jinek" NA "Frangeant oceanique" "Jinek baignade" 1 27 9 2014 "09:24" NA "0" 0 1 NA "PM" "PC" -20.78898 167.12117 "HR" "AP" "Recif frangeant expose a l\92ocean" "front recifal" "Corail vivant" "Frangeant oceanique" "LC2" -999 7 -999 1289.92 -999 -999 "Delphine Mallet" +"AMP" "LI140111" "SVR" "Jinek" NA "Frangeant oceanique" "Jinek baignade" 1 27 9 2014 "09:52" NA "0" 0 1 NA "PM" "PC" -20.78758 167.12009 "HR" "AP" "Recif frangeant expose a l\92ocean" "front recifal" "Fond lagonaire" "Frangeant oceanique" "SA4" -999 8 -999 1405.49 -999 -999 "Delphine Mallet" +"AMP" "LI140113" "SVR" "Jinek" NA "Frangeant oceanique" "Jinek baignade" 1 27 9 2014 "10:53" NA "W" 1 1 NA "PM" "PC" -20.78812 167.12167 "HR" "AP" "Recif frangeant expose a l\92ocean" "platier recifal" "Corail vivant" "Frangeant oceanique" "LC5" -999 4 -999 1239.16 -999 -999 "Delphine Mallet" +"AMP" "LI140114" "SVR" "Jinek" NA "Frangeant oceanique" "Jinek baignade" 1 27 9 2014 "10:34" NA "W" 1 1 NA "PM" "PC" -20.78689 167.12103 "HR" "AP" "Recif frangeant expose a l\92ocean" "platier recifal" "Fond lagonaire" "Frangeant oceanique" "SA5" -999 3 -999 1320.11 -999 -999 "Delphine Mallet" +"AMP" "LI140115" "SVR" "Jinek" NA "Frangeant oceanique" "Jinek baignade" 1 27 9 2014 "10:16" NA "W" 1 1 NA "PM" "PC" -20.78587 167.12 "HR" "AP" "Recif frangeant expose a l\92ocean" "front recifal" "Detritique" "Frangeant oceanique" "D3" -999 4 -999 1449.57 -999 -999 "Delphine Mallet" +"AMP" "LI140120" "SVR" "Recif Jinek" NA "Frangeant oceanique" "Jinek Nord inf15m" 1 27 9 2014 "11:32" NA "W" 1 1 NA "MD" "PC" -20.78852 167.11516 "HR" "AP" "" "" "Detritique" "Frangeant oceanique" "D6" -999 7 -999 1914.13 -999 -999 "Delphine Mallet" +"AMP" "LI140121" "SVR" "Recif Jinek" NA "Frangeant oceanique" "Jinek sup15m" 1 27 9 2014 "11:37" NA "W" 1 1 NA "MD" "PC" -20.78858 167.11385 "HR" "AP" "" "" "Corail vivant" "Frangeant oceanique" "LC4" -999 17 -999 2042.82 -999 -999 "Delphine Mallet" +"AMP" "LI140122" "SVR" "Recif Jinek" NA "Frangeant oceanique" "Jinek Nord inf15m" 1 27 9 2014 "11:54" NA "W" 1 1 NA "MD" "PC" -20.78906 167.11472 "HR" "AP" "" "" "Corail vivant" "Frangeant oceanique" "LC2" -999 12 -999 1956.41 -999 -999 "Delphine Mallet" +"AMP" "LI140129" "SVR" "Jinek" NA "Frangeant oceanique" "Jinek Nord inf15m" 1 29 9 2014 "09:08" NA "S" 4 2 NA "MM" "NL" -20.78424 167.11732 "HR" "AP" "Recif frangeant expose a l\92ocean" "front recifal" "Detritique" "Frangeant oceanique" "D2" -999 10 -999 1757.67 -999 -999 "Delphine Mallet" +"AMP" "LI140130" "SVR" "Jinek" NA "Frangeant oceanique" "Jinek Nord inf15m" 1 29 9 2014 "09:11" NA "S" 4 2 NA "MM" "NL" -20.78201 167.11766 "HR" "AP" "Recif frangeant expose a l\92ocean" "front recifal" "Detritique" "Frangeant oceanique" "D1" -999 6 -999 1817.65 -999 -999 "Delphine Mallet" +"AMP" "LI140131" "SVR" "Jinek" NA "Frangeant oceanique" "Jinek sup15m" 1 29 9 2014 "12:14" NA "S" 4 2 NA "MD" "NL" -20.78321 167.11383 "HR" "AP" "" "" "Fond lagonaire" "Frangeant oceanique" "SA3" -999 24 -999 2141.79 -999 -999 "Delphine Mallet" +"AMP" "LI140133" "SVR" "Jinek" NA "Frangeant oceanique" "Jinek Nord inf15m" 1 29 9 2014 "09:38" NA "S" 4 2 NA "MM" "NL" -20.78001 167.11674 "HR" "AP" "Recif frangeant expose a l\92ocean" "front recifal" "Detritique" "Frangeant oceanique" "D2" -999 6 -999 2002.61 -999 -999 "Delphine Mallet" +"AMP" "LI140134" "SVR" "Jinek" NA "Frangeant oceanique" "Jinek Nord inf15m" 1 29 9 2014 "09:32" NA "S" 4 2 NA "MM" "NL" -20.78136 167.116 "HR" "AP" "Recif frangeant expose a l\92ocean" "front recifal" "Fond lagonaire" "Frangeant oceanique" "SA3" -999 13 -999 2000.79 -999 -999 "Delphine Mallet" +"AMP" "LI140136" "SVR" "Jinek" NA "Frangeant oceanique" "Jinek sup15m" 1 29 9 2014 "11:52" NA "S" 4 2 NA "PM" "NL" -20.77839 167.11069 "HR" "AP" "" "" "Fond lagonaire" "Frangeant oceanique" "SA5" -999 28 -999 2639.2 -999 -999 "Delphine Mallet" +"AMP" "LI140137" "SVR" "Jinek" NA "Frangeant oceanique" "Jinek Nord inf15m" 1 29 9 2014 "09:54" NA "S" 4 2 NA "MM" "NL" -20.77735 167.11552 "HR" "AP" "Recif frangeant expose a l\92ocean" "front recifal" "Detritique" "Frangeant oceanique" "D1" -999 6 -999 2263.21 -999 -999 "Delphine Mallet" +"AMP" "LI140138" "SVR" "Jinek" NA "Frangeant oceanique" "Jinek Nord inf15m" 1 29 9 2014 "10:07" NA "S" 4 2 NA "MM" "NL" -20.77744 167.11429 "HR" "AP" "Recif frangeant expose a l\92ocean" "front recifal" "Detritique" "Frangeant oceanique" "D2" -999 12 -999 2364.51 -999 -999 "Delphine Mallet" +"AMP" "LI140139" "SVR" "Jinek" NA "Frangeant oceanique" "Jinek sup15m" 1 29 9 2014 "11:44" NA "S" 4 2 NA "PM" "NL" -20.77733 167.11299 "HR" "AP" "Recif frangeant expose a l\92ocean" "front recifal" "Fond lagonaire" "Frangeant oceanique" "SA4" -999 18 -999 2488.74 -999 -999 "Delphine Mallet" +"AMP" "LI140141" "SVR" "Jinek" NA "Frangeant oceanique" "Jinek Nord inf15m" 1 29 9 2014 "10:30" NA "S" 4 2 NA "PM" "NL" -20.7749 167.11234 "HR" "AP" "Recif frangeant expose a l\92ocean" "front recifal" "Detritique" "Frangeant oceanique" NA -999 9 -999 2690.36 -999 -999 "Delphine Mallet" +"AMP" "LI140142" "SVR" "Jinek" NA "Frangeant oceanique" "Jinek sup15m" 1 29 9 2014 "11:29" NA "S" 4 2 NA "PM" "NL" -20.77543 167.11052 "HR" "AP" "Recif frangeant expose a l\92ocean" "front recifal" "Fond lagonaire" "Frangeant oceanique" "SA1" -999 17 -999 2821.24 -999 -999 "Delphine Mallet" +"AMP" "LI140143" "SVR" "Jinek" NA "Frangeant oceanique" "Jinek Nord inf15m" 1 29 9 2014 "10:40" NA "S" 4 2 NA "PM" "NL" -20.77065 167.10829 "HR" "AP" "Recif frangeant expose a l\92ocean" "front recifal" "Detritique" "Frangeant oceanique" "D6" -999 9 -999 3309.15 -999 -999 "Delphine Mallet" +"AMP" "LI140144" "SVR" "Jinek" NA "Frangeant oceanique" "Jinek Nord inf15m" 1 29 9 2014 "10:54" NA "S" 4 2 NA "PM" "NL" -20.77055 167.10596 "HR" "AP" "Recif frangeant expose a l\92ocean" "front recifal" "Corail vivant" "Frangeant oceanique" "LC6" -999 14 -999 3505.09 -999 -999 "Delphine Mallet" +"AMP" "LI140147" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "Easo-Xepenehe inf15m" 1 26 9 2014 "11:05" NA NA 1 1 NA "MD" "PC" -20.78524 167.14957 "HR" "AP" "Recif frangeant expose a l\92ocean" "platier recifal" "Fond lagonaire" "Frangeant oceanique" NA -999 2 -999 1720.97 -999 -999 "Delphine Mallet" +"AMP" "LI140148" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "Easo-Xepenehe inf15m" 1 26 9 2014 "11:42" NA NA 1 1 NA "MD" "PC" -20.79391 167.15575 "HR" "AP" "" "" "Corail vivant" "Frangeant oceanique" "LC4" -999 9 -999 2382.89 -999 -999 "Delphine Mallet" +"AMP" "LI140149" "SVR" "Jinek" NA "Frangeant oceanique" "Jinek baignade" 1 27 9 2014 "09:14" NA "0" 0 1 NA "PM" "PC" -20.78938 167.12134 "HR" "AP" "Recif frangeant expose a l\92ocean" "front recifal" "Corail vivant" "Frangeant oceanique" "LC5" -999 10 -999 1269.56 -999 -999 "Delphine Mallet" +"AMP" "LI140150" "SVR" "Jinek" NA "Frangeant oceanique" "Jinek baignade" 1 27 9 2014 "11:02" NA "W" 1 1 NA "PM" "PC" -20.78753 167.1214 "HR" "AP" "Recif frangeant expose a l\92ocean" "platier recifal" "Detritique" "Frangeant oceanique" NA -999 2 -999 1267.96 -999 -999 "Delphine Mallet" +"AMP" "LI140151" "SVR" "Jinek" NA "Frangeant oceanique" "Jinek baignade" 1 27 9 2014 "10:29" NA "W" 1 1 NA "PM" "PC" -20.78657 167.12054 "HR" "AP" "Recif frangeant expose a l\92ocean" "front recifal" "Corail vivant" "Frangeant oceanique" "LC6" -999 3 -999 1368.21 -999 -999 "Delphine Mallet" +"AMP" "LI140152" "SVR" "Jinek" NA "Frangeant oceanique" "Jinek baignade" 1 27 9 2014 "10:10" NA "W" 1 1 NA "PM" "PC" -20.78574 167.1183 "HR" "AP" "Recif frangeant expose a l\92ocean" "front recifal" "Corail vivant" "Frangeant oceanique" NA -999 4 -999 1619.48 -999 -999 "Delphine Mallet" +"AMP" "LI140153" "SVR" "Jinek" NA "Frangeant oceanique" "Jinek baignade" 1 27 9 2014 "09:31" NA "0" 0 1 NA "PM" "PC" -20.7885 167.12068 "HR" "AP" "Recif frangeant expose a l\92ocean" "front recifal" "Fond lagonaire" "Frangeant oceanique" "SA3" -999 9 -999 NA -999 -999 "Delphine Mallet" +"AMP" "LI140154" "SVR" "Jinek" NA "Frangeant oceanique" "Jinek baignade" 1 27 9 2014 "09:57" NA "W" 1 1 NA "PM" "PC" -20.78648 167.11949 "HR" "AP" "Recif frangeant expose a l\92ocean" "front recifal" "Fond lagonaire" "Frangeant oceanique" "SA5" -999 8 -999 1486.4 -999 -999 "Delphine Mallet" +"AMP" "LI140300" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "0-200m" 1 29 9 2014 "09:12" NA "S" 4 2 NA "MM" "NL" -20.78827 167.13274 "HR" "AP" "" "" "Detritique" "Frangeant oceanique" "D1" -999 38 -999 99.1 -999 -999 "Delphine Mallet" +"AMP" "LI140301" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "0-200m" 1 29 9 2014 "09:22" NA "S" 4 2 NA "MM" "NL" -20.78809 167.13324 "HR" "AP" "" "" "Detritique" "Frangeant oceanique" "D1" -999 40 -999 91.84 -999 -999 "Delphine Mallet" +"AMP" "LI140302" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "0-200m" 1 29 9 2014 "09:36" NA "S" 4 2 NA "MM" "NL" -20.78859 167.13345 "HR" "AP" "" "" "Detritique" "Frangeant oceanique" "D1" -999 36.5 -999 33.99 -999 -999 "Delphine Mallet" +"AMP" "LI140303" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "0-200m" 1 29 9 2014 "09:59" NA "S" 4 2 NA "MM" "NL" -20.78974 167.13394 "HR" "AP" "" "" "Detritique" "Frangeant oceanique" "D1" -999 40 -999 105.87 -999 -999 "Delphine Mallet" +"AMP" "LI140304" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "0-200m" 1 29 9 2014 "10:17" NA "S" 4 2 NA "PM" "NL" -20.7891 167.13509 "HR" "AP" "" "" "Detritique" "Frangeant oceanique" "D1" -999 35 -999 164.43 -999 -999 "Delphine Mallet" +"AMP" "LI140305" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "200-400m" 1 29 9 2014 "10:44" NA "S" 4 2 NA "PM" "NL" -20.78751 167.13135 "HR" "AP" "" "" "Corail vivant" "Frangeant oceanique" "LC2" -999 38 -999 271.3 -999 -999 "Delphine Mallet" +"AMP" "LI140306" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "200-400m" 1 29 9 2014 "11:44" NA "S" 4 2 NA "PM" "NL" -20.78899 167.13647 "HR" "AP" "" "" "Corail vivant" "Frangeant oceanique" "LC2" -999 33 -999 312.47 -999 -999 "Delphine Mallet" +"AMP" "LI140307" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "Easo-Xepenehe sup15m" 1 29 9 2014 "11:49" NA "S" 4 2 NA "PM" "NL" -20.78861 167.13846 "HR" "AP" "" "" "Corail vivant" "Frangeant oceanique" "LC1" -999 28 -999 516.42 -999 -999 "Delphine Mallet" +"AMP" "LI140308" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "Easo-Xepenehe sup15m" 1 29 9 2014 "12:17" NA "S" 4 2 NA "MD" "NL" -20.78992 167.14676 "HR" "AP" "" "" "Corail vivant" "Frangeant oceanique" "LC1" -999 23 -999 1381.95 -999 -999 "Delphine Mallet" +"AMP" "LI140309" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "Easo-Xepenehe sup15m" 1 29 9 2014 "12:21" NA "S" 4 2 NA "MD" "NL" -20.78905 167.14395 "HR" "AP" "" "" "Corail vivant" "Frangeant oceanique" "LC1" -999 25 -999 1086.16 -999 -999 "Delphine Mallet" +"AMP" "LI140400" "SVR" "Baie Xepenehe" NA "Frangeant oceanique" "0-200m" 1 30 9 2014 "09:39" NA "S" 4 1 NA "MM" "NL" -20.78893 167.1338 "HR" "AP" "" "" "Detritique" "Frangeant oceanique" "D1" -999 36.2 -999 33.99 -999 -999 "Delphine Mallet" +"AMP" "LI140401" "SVR" "Jinek" NA "Frangeant oceanique" "Jinek baignade" 1 27 9 2014 "11:10" NA "W" 1 1 NA "MD" "PC" -20.78854 167.12163 "HR" "AP" "Recif frangeant expose a l\92ocean" "platier recifal" "Corail vivant" "Frangeant oceanique" "LC1" -999 4 -999 1236.92 -999 -999 "Delphine Mallet" +"AMP" "LI140402" "SVR" "Chepenehe" NA "Frangeant oceanique" "0-200m" 1 1 10 2014 "09:05" NA "S" 3 1 NA "MM" "PC" -20.78953 167.13373 "HR" "AP" "" "" "Detritique" "Frangeant oceanique" "D1" -999 40 -999 78.26 -999 -999 "Delphine Mallet" +"AMP" "LI140403" "SVR" "Chepenehe" NA "Frangeant oceanique" "0-200m" 1 1 10 2014 "09:10" NA "S" 3 1 NA "MM" "PC" -20.78887 167.13356 "HR" "AP" "" "" "Detritique" "Frangeant oceanique" "D1" -999 39 -999 NA -999 -999 "Delphine Mallet" +"AMP" "LI14062B" "SVR" "Pointe Easo" NA "Frangeant oceanique" "Jinek baignade" 1 27 9 2014 "09:07" NA "0" 0 1 NA "PM" "PC" -20.79014 167.12169 "HR" "AP" "Recif frangeant expose a l\92ocean" "front recifal" "Detritique" "Frangeant oceanique" "D6" -999 13 -999 1242.88 -999 -999 "Delphine Mallet" +"AMP" "MA140021" "SVR" "Matthew" NA NA NA 3 2 7 2014 "09:37" NA "SW" 3 2 NA NA "LM" -22.33968 171.35768 "HR" "AP" "" "" "Fond lagonaire" "Frangeant oceanique" "SA3" 5 20 -999 -999 -999 -999 "William Roman" +"AMP" "MA140022" "SVR" "Matthew" NA NA NA 3 2 7 2014 "10:10" NA "SW" 3 2 NA NA "LM" -22.34169 171.35995 "HR" "AP" "" "" "Detritique" "Frangeant oceanique" NA 8 12 -999 -999 -999 -999 "William Roman" +"AMP" "ME130004" "SVR" NA NA "Platier" NA 1 25 7 2013 "14:15" "nuageux" "SW" 1 1 NA "MD" "LD" -22.38028 167.05687 "RI" "AP" "Complexe de massif corallien de mers interieures" "platier recifal" "Corail vivant" "Frangeant ilot" "LC1" -999 4 -999 -999 -999 -999 NA +"AMP" "ME130005" "SVR" NA NA "Pente externe" NA 1 25 7 2013 "13:44" "nuageux" "SW" 1 1 NA "MD" "LD" -22.38473 167.05815 "RI" "AP" "" "" "Corail vivant" "Fond lagonaire" "LC1" -999 4 -999 -999 -999 -999 NA +"AMP" "ME130014" "SVR" NA NA "Pente externe" NA 1 25 7 2013 "14:46" "nuageux" "SW" 1 1 NA "MD" "LD" -22.3759 167.06107 "RI" "AP" "Complexe de massif corallien de mers interieures" "front recifal" "Corail vivant" "Frangeant ilot" "LC1" -999 5 -999 -999 -999 -999 NA +"AMP" "ME130016" "SVR" NA NA "Pente externe" NA 1 26 7 2013 "15:56" "nuageux" "SE" 4 2 NA NA "LD" -22.37182 167.06969 "RI" "AP" "" "" "Fond lagonaire" "Recif barriere externe" "SA3" -999 7 -999 -999 -999 -999 NA +"AMP" "ME130018" "SVR" NA NA "Platier" NA 1 25 7 2013 "15:11" "nuageux" "SW" 2 1 NA "BM" "LD" -22.37229 167.06416 "RI" "AP" "" "" "Corail vivant" "Frangeant ilot" "LC1" -999 4 -999 -999 -999 -999 NA +"AMP" "ME130022" "SVR" NA NA "Platier" NA 1 25 7 2013 "15:36" "nuageux" "SW" 3 1 NA "BM" "LD" -22.37485 167.06833 "RI" "AP" "" "" "Corail vivant" "Frangeant ilot" "LC4" -999 5 -999 -999 -999 -999 NA +"AMP" "ME130034" "SVR" NA NA "Platier" NA 1 25 7 2013 "15:47" "nuageux" "SW" 2 1 NA "MM" "LD" -22.40449 167.07477 "RI" "AP" "Complexe de massif corallien de mers interieures" "platier recifal" "Corail vivant" "Recif barriere interne" "LC5" -999 5 -999 -999 -999 -999 NA +"AMP" "ME130035" "SVR" NA NA "Platier" NA 1 25 7 2013 "14:55" "nuageux" "SW" 2 1 NA "BM" "LD" -22.39892 167.07529 "RI" "AP" "Complexe de massif corallien de mers interieures" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA2" -999 3 -999 -999 -999 -999 NA +"AMP" "ME130036" "SVR" NA NA "Platier" NA 1 25 7 2013 "15:09" "nuageux" "SW" 2 1 NA "BM" "LD" -22.39178 167.07689 "RI" "AP" "Complexe de massif corallien de mers interieures" "platier recifal" "Corail vivant" "Recif barriere interne" "LC1" -999 8 -999 -999 -999 -999 NA +"AMP" "ME130041" "SVR" NA NA "Fond lagonaire" NA 1 25 7 2013 "13:55" "nuageux" "SW" 2 2 NA "MD" "LD" -22.38923 167.073 "RI" "AP" "Complexe de massif corallien de mers interieures" "lagon enclave" "Fond lagonaire" "Fond lagonaire" "SA1" -999 7 -999 -999 -999 -999 NA +"AMP" "ME130042" "SVR" NA NA "Fond lagonaire" NA 1 25 7 2013 "14:17" "nuageux" "SW" 2 2 NA "MD" "LD" -22.38904 167.0755 "RI" "AP" "Complexe de massif corallien de mers interieures" "lagon enclave" "Fond lagonaire" "Fond lagonaire" "SA1" -999 4 -999 -999 -999 -999 NA +"AMP" "ME130046" "SVR" NA NA "Platier" NA 1 26 7 2013 "15:24" "nuageux" "SE" 4 2 NA NA "LD" -22.36336 167.07005 "RI" "AP" "Complexe de massif corallien de mers interieures" "platier recifal" "Corail vivant" "Recif intermediaire" "LC4" -999 6 -999 -999 -999 -999 NA +"AMP" "ME130047" "SVR" NA NA "Pente externe" NA 1 26 7 2013 "08:12" "nuageux" "SE" 4 2 NA NA "LD" -22.372 167.06973 "RI" "AP" "" "" "Corail vivant" "Recif barriere externe" "LC1" -999 5 -999 -999 -999 -999 NA +"AMP" "ME130049" "SVR" NA NA "Plateau recifal" NA 1 26 7 2013 "09:32" "nuageux" "SE" 4 2 NA NA "LD" -22.36177 167.07487 "RI" "AP" "Complexe de massif corallien de mers interieures" "terrasse peu profonde" "Corail vivant" "Recif intermediaire" "LC5" -999 3 -999 -999 -999 -999 NA +"AMP" "ME130050" "SVR" NA NA "Fond lagonaire" NA 1 26 7 2013 "09:28" "nuageux" "SE" 4 2 NA NA "LD" -22.3625 167.07674 "RI" "AP" "Complexe de massif corallien de mers interieures" "lagon enclave" "Fond lagonaire" "Fond lagonaire" "SA1" -999 6 -999 -999 -999 -999 NA +"AMP" "ME130051" "SVR" NA NA "Fond lagonaire" NA 1 26 7 2013 "09:09" "nuageux" "SE" 4 2 NA NA "LD" -22.36531 167.07819 "RI" "AP" "Complexe de massif corallien de mers interieures" "lagon enclave" "Fond lagonaire" "Fond lagonaire" "SA3" -999 7 -999 -999 -999 -999 NA +"AMP" "ME130053" "SVR" NA NA "Platier" NA 1 26 7 2013 "08:35" "nuageux" "SE" 4 2 NA NA "LD" -22.37104 167.07249 "RI" "AP" "Complexe de massif corallien de mers interieures" "platier recifal" "Fond lagonaire" "Recif intermediaire" "SA3" -999 2 -999 -999 -999 -999 NA +"AMP" "ME130054" "SVR" NA NA "Plateau recifal" NA 1 26 7 2013 "08:31" "nuageux" "SE" 4 2 NA NA "LD" -22.36837 167.07242 "RI" "AP" "Complexe de massif corallien de mers interieures" "terrasse peu profonde" "Corail vivant" "Recif intermediaire" "LC5" -999 4 -999 -999 -999 -999 NA +"AMP" "ME130056" "SVR" NA NA "Pente externe" NA 1 26 7 2013 "15:03" "nuageux" "SE" 4 2 NA NA "LD" -22.35904 167.07094 "RI" "AP" "Complexe de massif corallien de mers interieures" "front recifal" "Fond lagonaire" "Recif barriere externe" "SA3" -999 4 -999 -999 -999 -999 NA +"AMP" "ME130063" "SVR" NA NA "Pente externe" NA 1 26 7 2013 "14:26" "nuageux" "SE" 4 2 NA NA "LD" -22.34672 167.07433 "RI" "AP" "Complexe de massif corallien de mers interieures" "front recifal" "Corail vivant" "Recif barriere externe" "LC2" -999 7 -999 -999 -999 -999 NA +"AMP" "ME130065" "SVR" NA NA "Plateau recifal" NA 1 26 7 2013 "10:42" "nuageux" "SE" 4 2 NA NA "LD" -22.35399 167.08752 "RI" "AP" "Complexe de massif corallien de mers interieures" "terrasse peu profonde" "Corail vivant" "Recif barriere interne" "LC5" -999 5 -999 -999 -999 -999 NA +"AMP" "ME130066" "SVR" NA NA "Plateau recifal" NA 1 26 7 2013 "10:35" "nuageux" "SE" 4 2 NA NA "LD" -22.356 167.0845 "RI" "AP" "Complexe de massif corallien de mers interieures" "terrasse peu profonde" "Corail vivant" "Recif intermediaire" "LC4" -999 7 -999 -999 -999 -999 NA +"AMP" "ME130068" "SVR" NA NA "Platier" NA 1 26 7 2013 "14:33" "nuageux" "SE" 4 2 NA "MD" "LD" -22.39095 167.08452 "RI" "AP" "" "" "Fond lagonaire" "Recif barriere externe" "SA3" -999 6 -999 -999 -999 -999 NA +"AMP" "ME130069" "SVR" NA NA "Pente externe" NA 1 26 7 2013 "14:09" "nuageux" "SE" 4 2 NA "MD" "LD" -22.38105 167.08495 "RI" "AP" "Complexe de massif corallien de mers interieures" "front recifal" "Fond lagonaire" "Recif barriere externe" NA -999 6 -999 -999 -999 -999 NA +"AMP" "ME130070" "SVR" NA NA "Pente externe" NA 1 26 7 2013 "14:05" "nuageux" "SE" 4 2 NA "MD" "LD" -22.37749 167.08594 "RI" "AP" "Complexe de massif corallien de mers interieures" "front recifal" "Fond lagonaire" "Recif barriere externe" "SA2" -999 6 -999 -999 -999 -999 NA +"AMP" "ME130071" "SVR" NA NA "Platier" NA 1 26 7 2013 "08:17" "nuageux" "SE" 3 2 NA "MM" "LD" -22.3755 167.09068 "RI" "AP" "Complexe de massif corallien de mers interieures" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA3" -999 9 -999 -999 -999 -999 NA +"AMP" "ME130073" "SVR" NA NA "Platier" NA 1 26 7 2013 "08:48" "nuageux" "SE" 3 2 NA "MM" "LD" -22.38373 167.08673 "RI" "AP" "Complexe de massif corallien de mers interieures" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA5" -999 4 -999 -999 -999 -999 NA +"AMP" "ME130074" "SVR" NA NA "Platier" NA 1 26 7 2013 "08:54" "nuageux" "SE" 3 2 NA "MM" "LD" -22.3886 167.08644 "RI" "AP" "Complexe de massif corallien de mers interieures" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA3" -999 5 -999 -999 -999 -999 NA +"AMP" "ME130075" "SVR" NA NA "Platier" NA 1 26 7 2013 "09:17" "nuageux" "SE" 3 2 NA "MM" "LD" -22.39177 167.08896 "RI" "AP" "Complexe de massif corallien de mers interieures" "platier recifal" "Corail vivant" "Recif barriere interne" "LC2" -999 2 -999 -999 -999 -999 NA +"AMP" "ME130076" "SVR" NA NA "Plateau recifal" NA 1 26 7 2013 "09:31" "nuageux" "SE" 3 2 NA "MM" "LD" -22.39338 167.09206 "RI" "AP" "Complexe de massif corallien de mers interieures" "terrasse peu profonde" "Algueraie" "Recif intermediaire" "MA3" -999 3 -999 -999 -999 -999 NA +"AMP" "ME130077" "SVR" NA NA "Plateau recifal" NA 1 26 7 2013 "09:41" "nuageux" "SE" 3 2 NA "PM" "LD" -22.391 167.09801 "RI" "AP" "Complexe de massif corallien de mers interieures" "terrasse peu profonde" "Fond lagonaire" "Recif intermediaire" "SA1" -999 3 -999 -999 -999 -999 NA +"AMP" "ME130078" "SVR" NA NA "Plateau recifal" NA 1 26 7 2013 "09:46" "nuageux" "SE" 3 2 NA "PM" "LD" -22.38804 167.09749 "RI" "AP" "Complexe de massif corallien de mers interieures" "terrasse peu profonde" "Fond lagonaire" "Recif intermediaire" "SA1" -999 4 -999 -999 -999 -999 NA +"AMP" "ME130079" "SVR" NA NA "Fond lagonaire" NA 1 26 7 2013 "10:12" "nuageux" "SE" 3 2 NA "PM" "LD" -22.3902 167.1039 "RI" "AP" "Complexe de massif corallien de mers interieures" "lagon enclave" "Fond lagonaire" "Fond lagonaire" "SA1" -999 6 -999 -999 -999 -999 NA +"AMP" "ME130080" "SVR" NA NA "Plateau recifal" NA 1 26 7 2013 "10:19" "nuageux" "SE" 3 2 NA "PM" "LD" -22.38798 167.10966 "RI" "AP" "Complexe de massif corallien de mers interieures" "terrasse peu profonde" "Fond lagonaire" "Recif intermediaire" "SA1" -999 4 -999 -999 -999 -999 NA +"AMP" "ME130081" "SVR" NA NA "Plateau recifal" NA 1 26 7 2013 "10:37" "nuageux" "SE" 3 2 NA "MD" "LD" -22.38217 167.10916 "RI" "AP" "Complexe de massif corallien de mers interieures" "terrasse peu profonde" "Fond lagonaire" "Recif intermediaire" "SA3" -999 3 -999 -999 -999 -999 NA +"AMP" "ME130082" "SVR" NA NA "Plateau recifal" NA 1 26 7 2013 "10:42" "nuageux" "SE" 3 2 NA "MD" "LD" -22.38277 167.1041 "RI" "AP" "Complexe de massif corallien de mers interieures" "terrasse peu profonde" "Fond lagonaire" "Recif intermediaire" "SA3" -999 2 -999 -999 -999 -999 NA +"AMP" "ME130083" "SVR" NA NA "Plateau recifal" NA 1 26 7 2013 "11:03" "nuageux" "SE" 3 2 NA "MD" "LD" -22.37988 167.11266 "RI" "AP" "Complexe de massif corallien de mers interieures" "terrasse peu profonde" "Fond lagonaire" "Recif intermediaire" "SA2" -999 3 -999 -999 -999 -999 NA +"AMP" "ME130084" "SVR" NA NA "Fond lagonaire" NA 1 26 7 2013 "11:10" "nuageux" "SE" 3 2 NA "MD" "LD" -22.37777 167.10715 "RI" "AP" "Complexe de massif corallien de mers interieures" "lagon enclave" "Fond lagonaire" "Recif intermediaire" "SA1" -999 3 -999 -999 -999 -999 NA +"AMP" "ME130085" "SVR" NA NA "Plateau recifal" NA 1 26 7 2013 "11:27" "pluie" "SE" 4 2 NA "MD" "LD" -22.37894 167.10198 "RI" "AP" "Complexe de massif corallien de mers interieures" "terrasse peu profonde" "Fond lagonaire" "Recif intermediaire" "SA3" -999 3 -999 -999 -999 -999 NA +"AMP" "ME130086" "SVR" NA NA "Plateau recifal" NA 1 26 7 2013 "11:39" "pluie" "SE" 4 2 NA "MD" "LD" -22.37652 167.10132 "RI" "AP" "Complexe de massif corallien de mers interieures" "terrasse peu profonde" "Fond lagonaire" "Recif intermediaire" "SA4" -999 3 -999 -999 -999 -999 NA +"AMP" "ME130087" "SVR" NA NA "Plateau recifal" NA 1 26 7 2013 "11:58" "nuageux" "SE" 4 2 NA "MD" "LD" -22.37282 167.09793 "RI" "AP" "Complexe de massif corallien de mers interieures" "terrasse peu profonde" "Fond lagonaire" "Recif intermediaire" "SA2" -999 4 -999 -999 -999 -999 NA +"AMP" "ME130088" "SVR" NA NA "Fond lagonaire" NA 1 26 7 2013 "12:08" "nuageux" "SE" 4 2 NA "MD" "LD" -22.36917 167.09512 "RI" "AP" "Complexe de massif corallien de mers interieures" "lagon enclave" "Detritique" "Fond lagonaire" NA -999 3 -999 -999 -999 -999 NA +"AMP" "ME130089" "SVR" NA NA "Fond lagonaire" NA 1 26 7 2013 "15:48" "nuageux" "SE" 4 2 NA "BM" "LD" -22.37961 167.09772 "RI" "AP" "Complexe de massif corallien de mers interieures" "lagon enclave" "Fond lagonaire" "Recif intermediaire" "SA4" -999 3 -999 -999 -999 -999 NA +"AMP" "ME130090" "SVR" NA NA "Plateau recifal" NA 1 26 7 2013 "16:15" "nuageux" "SE" 4 2 NA "BM" "LD" -22.38207 167.09637 "RI" "AP" "Complexe de massif corallien de mers interieures" "terrasse peu profonde" "Fond lagonaire" "Recif intermediaire" "SA3" -999 3 -999 -999 -999 -999 NA +"AMP" "ME130093" "SVR" NA NA "Fond lagonaire" NA 1 26 7 2013 "15:29" "nuageux" "SE" 4 2 NA "MD" "LD" -22.38527 167.09261 "RI" "AP" "Complexe de massif corallien de mers interieures" "lagon enclave" "Fond lagonaire" "Fond lagonaire" "SA3" -999 7 -999 -999 -999 -999 NA +"AMP" "ME130094" "SVR" NA NA "Fond lagonaire" NA 1 26 7 2013 "15:12" "nuageux" "SE" 4 2 NA "MD" "LD" -22.389 167.09328 "RI" "AP" "Complexe de massif corallien de mers interieures" "lagon enclave" "Fond lagonaire" "Fond lagonaire" "SA3" -999 7 -999 -999 -999 -999 NA +"AMP" "ME130095" "SVR" NA NA "Pente externe" NA 1 27 7 2013 "08:54" "nuageux" "SE" 4 2 NA NA "LD" -22.36456 167.11485 "RI" "AP" "Complexe de massif corallien de mers interieures" "front recifal" "Corail vivant" "Recif barriere externe" "LC4" -999 3 -999 -999 -999 -999 NA +"AMP" "ME130096" "SVR" NA NA "Pente externe" NA 1 27 7 2013 "08:48" "nuageux" "SE" 4 2 NA NA "LD" -22.36332 167.11192 "RI" "AP" "Complexe de massif corallien de mers interieures" "front recifal" "Corail vivant" "Recif barriere externe" "LC2" -999 9 -999 -999 -999 -999 NA +"AMP" "ME130098" "SVR" NA NA "Plateau recifal" NA 1 27 7 2013 "09:25" "nuageux" "SE" 4 2 NA NA "LD" -22.36868 167.12065 "RI" "AP" "Complexe de massif corallien de mers interieures" "terrasse peu profonde" "Detritique" "Recif barriere interne" "D6" -999 5 -999 -999 -999 -999 NA +"AMP" "ME130099" "SVR" NA NA "Plateau recifal" NA 1 27 7 2013 "10:12" "nuageux" "SE" 4 2 NA NA "LD" -22.37206 167.13835 "RI" "AP" "Complexe de massif corallien de mers interieures" "terrasse peu profonde" "Corail vivant" "Recif barriere interne" "SA5" -999 7 -999 -999 -999 -999 NA +"AMP" "ME1300F1" "SVR" NA NA "Frangeant" NA 1 25 7 2013 "10:50" "Ensoleill?" "0" 0 1 NA "MD" "LD" -22.36352 166.96564 "HR" "AP" "Recif frangeant de mers interieures" "front recifal" "Corail vivant" "Frangeant cotier" "LC2" -999 6 -999 -999 -999 -999 NA +"AMP" "ME1300F2" "SVR" NA NA "Frangeant" NA 1 25 7 2013 "10:55" "Ensoleill?" "0" 0 1 NA "MD" "LD" -22.36471 166.96347 "HR" "AP" "" "" "Corail vivant" "Frangeant cotier" "LC4" -999 5 -999 -999 -999 -999 NA +"AMP" "ME1300F3" "SVR" NA NA "Frangeant" NA 1 25 7 2013 "11:16" "nuageux" "SW" 1 1 NA "MD" "LD" -22.36953 166.95682 "HR" "AP" "" "" "Corail vivant" "Frangeant cotier" "LC4" -999 7 -999 -999 -999 -999 NA +"AMP" "ME1300F4" "SVR" NA NA "Frangeant" NA 1 25 7 2013 "11:22" "nuageux" "SW" 1 1 NA "MD" "LD" -22.37143 166.95312 "HR" "AP" "" "" "Corail vivant" "Frangeant cotier" "LC4" -999 6 -999 -999 -999 -999 NA +"AMP" "ME1300F5" "SVR" NA NA "Platier" NA 1 25 7 2013 "11:47" "nuageux" "SW" 1 1 NA "MD" "LD" -22.38316 166.96074 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Corail vivant" "Recif intermediaire" "LC2" -999 7 -999 -999 -999 -999 NA +"AMP" "ME130100" "SVR" NA NA "Fond lagonaire" NA 1 27 7 2013 "09:50" "nuageux" "SE" 4 2 NA NA "LD" -22.37153 167.13068 "RI" "AP" "Complexe de massif corallien de mers interieures" "lagon enclave" "Detritique" "Fond lagonaire" NA -999 11 -999 -999 -999 -999 NA +"AMP" "ME130101" "SVR" NA NA "Pente externe" NA 1 27 7 2013 "10:43" "nuageux" "SE" 4 2 NA NA "LD" -22.37393 167.15215 "RI" "AP" "Complexe de massif corallien de mers interieures" "front recifal" "Corail vivant" "Recif barriere externe" "LC4" -999 7 -999 -999 -999 -999 NA +"AMP" "ME130105" "SVR" NA NA "Pente externe" NA 1 27 7 2013 "14:03" "Ensoleill?" "SE" 3 2 NA NA "LD" -22.4022 167.16855 "RI" "AP" "Complexe de massif corallien de mers interieures" "front recifal" "Detritique" "Recif barriere externe" "D7" -999 6 -999 -999 -999 -999 NA +"AMP" "ME130106" "SVR" NA NA "Plateau recifal" NA 1 27 7 2013 "13:38" "Ensoleill?" "SE" 3 1 NA NA "LD" -22.39652 167.16293 "RI" "AP" "Complexe de massif corallien de mers interieures" "terrasse peu profonde" "Corail vivant" "Recif barriere interne" "LC6" -999 9 -999 -999 -999 -999 NA +"AMP" "ME130107" "SVR" NA NA "Platier" NA 1 27 7 2013 "13:42" "Ensoleill?" "SE" 3 1 NA NA "LD" -22.39808 167.16096 "RI" "AP" "Complexe de massif corallien de mers interieures" "platier recifal" "Corail vivant" "Recif barriere interne" "LC4" -999 10 -999 -999 -999 -999 NA +"AMP" "ME130108" "SVR" NA NA "Plateau recifal" NA 1 27 7 2013 "13:13" "Ensoleill?" "SE" 3 1 NA NA "LD" -22.39401 167.16586 "RI" "AP" "Complexe de massif corallien de mers interieures" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA1" -999 4 -999 -999 -999 -999 NA +"AMP" "ME130109" "SVR" NA NA "Plateau recifal" NA 1 27 7 2013 "13:18" "Ensoleill?" "SE" 3 1 NA NA "LD" -22.39538 167.17076 "RI" "AP" "Complexe de massif corallien de mers interieures" "terrasse peu profonde" "Detritique" "Recif barriere interne" NA -999 3 -999 -999 -999 -999 NA +"AMP" "ME130110" "SVR" NA NA "Platier" NA 1 27 7 2013 "14:46" "nuageux" "SE" 3 2 NA NA "LD" -22.3841 167.166 "RI" "AP" "Complexe de massif corallien de mers interieures" "platier recifal" "Detritique" "Recif barriere interne" NA -999 6 -999 -999 -999 -999 NA +"AMP" "ME130111" "SVR" NA NA "Platier" NA 1 27 7 2013 "14:53" "nuageux" "SE" 3 2 NA NA "LD" -22.38572 167.16302 "RI" "AP" "Complexe de massif corallien de mers interieures" "platier recifal" "Corail vivant" "Recif barriere interne" "LC6" -999 4 -999 -999 -999 -999 NA +"AMP" "ME130112" "SVR" NA NA "Fond lagonaire" NA 1 27 7 2013 "15:16" "Ensoleill?" "SE" 3 2 NA NA "LD" -22.38179 167.15042 "RI" "AP" "Complexe de massif corallien de mers interieures" "lagon enclave" "Detritique" "Fond lagonaire" "D6" -999 9 -999 -999 -999 -999 NA +"AMP" "ME130113" "SVR" NA NA "Fond lagonaire" NA 1 27 7 2013 "15:19" "nuageux" "SE" 3 2 NA NA "LD" -22.38137 167.14703 "RI" "AP" "Complexe de massif corallien de mers interieures" "lagon enclave" "Fond lagonaire" "Fond lagonaire" "SA1" -999 11 -999 -999 -999 -999 NA +"AMP" "ME130114" "SVR" NA NA "Fond lagonaire" NA 1 27 7 2013 "15:42" "pluie" "SE" 2 2 NA NA "LD" -22.37793 167.14459 "RI" "AP" "Complexe de massif corallien de mers interieures" "lagon enclave" "Fond lagonaire" "Fond lagonaire" "SA3" -999 8 -999 -999 -999 -999 NA +"AMP" "ME130115" "SVR" NA NA "Plateau recifal" NA 1 27 7 2013 "15:47" "pluie" "SE" 2 2 NA NA "LD" -22.37317 167.1436 "RI" "AP" "Complexe de massif corallien de mers interieures" "terrasse peu profonde" "Corail vivant" "Recif barriere interne" "LC2" -999 1.5 -999 -999 -999 -999 NA +"AMP" "ME130116" "SVR" NA NA "Plateau recifal" NA 1 27 7 2013 "08:48" "nuageux, pluie" "SE" 3 1 NA NA "LD" -22.36776 167.10464 "RI" "AP" "Complexe de massif corallien de mers interieures" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA4" -999 3 -999 -999 -999 -999 NA +"AMP" "ME130117" "SVR" NA NA "Plateau recifal" NA 1 27 7 2013 "08:57" "nuageux, pluie" "SE" 3 1 NA NA "LD" -22.36798 167.1115 "RI" "AP" "Complexe de massif corallien de mers interieures" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "LC6" -999 3 -999 -999 -999 -999 NA +"AMP" "ME130118" "SVR" NA NA "Platier" NA 1 27 7 2013 "09:21" "nuageux, pluie" "SE" 3 1 NA NA "LD" -22.37256 167.11108 "RI" "AP" "Complexe de massif corallien de mers interieures" "platier recifal" "Corail vivant" "Recif intermediaire" "LC5" -999 12 -999 -999 -999 -999 NA +"AMP" "ME130119" "SVR" NA NA "Platier" NA 1 27 7 2013 "09:33" "nuageux, pluie" "SE" 3 1 NA NA "LD" -22.37583 167.11427 "RI" "AP" "Complexe de massif corallien de mers interieures" "platier recifal" "Fond lagonaire" "Recif intermediaire" "SA3" -999 15 -999 -999 -999 -999 NA +"AMP" "ME130120" "SVR" NA NA "Platier" NA 1 27 7 2013 "09:56" "nuageux, pluie" "SE" 3 1 NA NA "LD" -22.38006 167.11778 "RI" "AP" "Complexe de massif corallien de mers interieures" "platier recifal" "Corail vivant" "Recif intermediaire" "LC1" -999 12 -999 -999 -999 -999 NA +"AMP" "ME130121" "SVR" NA NA "Plateau recifal" NA 1 27 7 2013 "10:09" "nuageux, pluie" "SE" 3 1 NA NA "LD" -22.37999 167.12097 "RI" "AP" "Complexe de massif corallien de mers interieures" "terrasse peu profonde" "Corail vivant" "Recif intermediaire" "LC2" -999 15 -999 -999 -999 -999 NA +"AMP" "ME130122" "SVR" NA NA "Platier" NA 1 27 7 2013 "10:40" "nuageux, pluie" "SE" 3 1 NA NA "LD" -22.38187 167.13101 "RI" "AP" "Complexe de massif corallien de mers interieures" "platier recifal" "Fond lagonaire" "Recif intermediaire" "SA3" -999 15 -999 -999 -999 -999 NA +"AMP" "ME130123" "SVR" NA NA "Platier" NA 1 27 7 2013 "10:48" "nuageux, pluie" "SE" 3 1 NA NA "LD" -22.38461 167.13496 "RI" "AP" "Complexe de massif corallien de mers interieures" "platier recifal" "Fond lagonaire" "Recif intermediaire" "SA3" -999 11 -999 -999 -999 -999 NA +"AMP" "ME130124" "SVR" NA NA "Platier" NA 1 27 7 2013 "13:36" "soleil" "SE" 3 1 NA NA "LD" -22.38289 167.14171 "RI" "AP" "Complexe de massif corallien de mers interieures" "platier recifal" "Fond lagonaire" "Recif intermediaire" "SA3" -999 10 -999 -999 -999 -999 NA +"AMP" "ME130125" "SVR" NA NA "Platier" NA 1 27 7 2013 "13:31" "soleil" "SE" 3 1 NA NA "LD" -22.38729 167.13875 "RI" "AP" "Complexe de massif corallien de mers interieures" "platier recifal" "Corail vivant" "Recif intermediaire" "LC5" -999 11 -999 -999 -999 -999 NA +"AMP" "ME130126" "SVR" NA NA "Platier" NA 1 27 7 2013 "13:11" "soleil" "SE" 3 1 NA NA "LD" -22.39208 167.1312 "RI" "AP" "Complexe de massif corallien de mers interieures" "platier recifal" "Corail vivant" "Recif intermediaire" "LC6" -999 6 -999 -999 -999 -999 NA +"AMP" "ME130127" "SVR" NA NA "Platier" NA 1 27 7 2013 "13:06" "nuageux, pluie" "SE" 3 1 NA NA "LD" -22.39324 167.1268 "RI" "AP" "Complexe de massif corallien de mers interieures" "platier recifal" "Fond lagonaire" "Recif intermediaire" "SA3" -999 3 -999 -999 -999 -999 NA +"AMP" "ME130128" "SVR" NA NA "Plateau recifal" NA 1 27 7 2013 "12:48" "soleil" "SE" 3 1 NA NA "LD" -22.39247 167.12199 "RI" "AP" "Complexe de massif corallien de mers interieures" "terrasse peu profonde" "Corail vivant" "Recif intermediaire" "LC5" -999 3 -999 -999 -999 -999 NA +"AMP" "ME130129" "SVR" NA NA "Platier" NA 1 27 7 2013 "12:42" "soleil" "SE" 3 1 NA NA "LD" -22.38299 167.11758 "RI" "AP" "Complexe de massif corallien de mers interieures" "platier recifal" "Fond lagonaire" "Recif intermediaire" "SA5" -999 3 -999 -999 -999 -999 NA +"AMP" "ME130130" "SVR" NA NA "Platier" NA 1 27 7 2013 "12:23" "soleil" "SE" 3 1 NA NA "LD" -22.38984 167.11414 "RI" "AP" "Complexe de massif corallien de mers interieures" "platier recifal" "Fond lagonaire" "Recif intermediaire" "SA3" -999 2 -999 -999 -999 -999 NA +"AMP" "ME130131" "SVR" NA NA "Fond lagonaire" NA 1 27 7 2013 "12:19" "nuageux" "SE" 3 1 NA NA "LD" -22.38804 167.11295 "RI" "AP" "Complexe de massif corallien de mers interieures" "lagon enclave" "Fond lagonaire" "Fond lagonaire" "SA3" -999 6 -999 -999 -999 -999 NA +"AMP" "ME130132" "SVR" NA NA "Plateau recifal" NA 1 27 7 2013 "12:02" "soleil" "SE" 3 1 NA NA "LD" -22.38827 167.11816 "RI" "AP" "Complexe de massif corallien de mers interieures" "terrasse peu profonde" "Fond lagonaire" "Recif intermediaire" "SA1" -999 9 -999 -999 -999 -999 NA +"AMP" "ME130133" "SVR" NA NA "Plateau recifal" NA 1 27 7 2013 "11:55" "soleil" "SE" 3 1 NA NA "LD" -22.3873 167.1223 "RI" "AP" "Complexe de massif corallien de mers interieures" "terrasse peu profonde" "Fond lagonaire" "Recif intermediaire" "SA3" -999 3 -999 -999 -999 -999 NA +"AMP" "ME130134" "SVR" NA NA "Plateau recifal" NA 1 27 7 2013 "11:18" "soleil" "SE" 3 1 NA NA "LD" -22.38446 167.11964 "RI" "AP" "Complexe de massif corallien de mers interieures" "terrasse peu profonde" "Fond lagonaire" "Recif intermediaire" "SA3" -999 3 -999 -999 -999 -999 NA +"AMP" "ME130135" "SVR" NA NA "Fond lagonaire" NA 1 27 7 2013 "11:12" "soleil" "SE" 3 1 NA NA "LD" -22.38325 167.1237 "RI" "AP" "Complexe de massif corallien de mers interieures" "lagon enclave" "Fond lagonaire" "Recif intermediaire" "SA1" -999 13 -999 -999 -999 -999 NA +"AMP" "ME130136" "SVR" NA NA "Plateau recifal" NA 1 28 7 2013 "08:28" "Nuageux" "SE" 4 1 NA NA "LD" -22.39285 167.14627 "RI" "AP" "Complexe de massif corallien de mers interieures" "terrasse peu profonde" "Fond lagonaire" "Recif intermediaire" "SA3" -999 2.5 -999 -999 -999 -999 NA +"AMP" "ME130137" "SVR" NA NA "Platier" NA 1 27 7 2013 "15:42" "pluie" "SE" 3 1 NA NA "LD" -22.39051 167.14627 "RI" "AP" "Complexe de massif corallien de mers interieures" "platier recifal" "Detritique" "Recif intermediaire" "SA5" -999 8 -999 -999 -999 -999 NA +"AMP" "ME130138" "SVR" NA NA "Plateau recifal" NA 1 27 7 2013 "16:02" "pluie" "SE" 3 1 NA NA "LD" -22.38732 167.14501 "RI" "AP" "Complexe de massif corallien de mers interieures" "terrasse peu profonde" "Corail vivant" "Recif intermediaire" "LC2" -999 6 -999 -999 -999 -999 NA +"AMP" "ME130139" "SVR" NA NA "Fond lagonaire" NA 1 28 7 2013 "08:35" "Nuageux" "SE" 4 1 NA NA "LD" -22.39136 167.158 "RI" "AP" "Complexe de massif corallien de mers interieures" "lagon enclave" "Fond lagonaire" "Fond lagonaire" "SA1" -999 2 -999 -999 -999 -999 NA +"AMP" "ME130144" "SVR" NA NA "Plateau recifal" NA 1 28 7 2013 "10:05" "pluie" "SE" 4 1 NA NA "LD" -22.39833 167.12167 "RI" "AP" "Complexe de massif corallien de mers interieures" "terrasse peu profonde" "Fond lagonaire" "Recif intermediaire" "SA5" -999 4 -999 -999 -999 -999 NA +"AMP" "ME130146" "SVR" NA NA "Platier" NA 1 28 7 2013 "10:56" "pluie" "SE" 4 1 NA NA "LD" -22.39482 167.11491 "RI" "AP" "Complexe de massif corallien de mers interieures" "platier recifal" "Fond lagonaire" "Recif intermediaire" "SA1" -999 2 -999 -999 -999 -999 NA +"AMP" "ME130147" "SVR" NA NA "Plateau recifal" NA 1 28 7 2013 "11:13" "pluie" "SE" 4 1 NA NA "LD" -22.39172 167.11244 "RI" "AP" "Complexe de massif corallien de mers interieures" "terrasse peu profonde" "Fond lagonaire" "Recif intermediaire" "SA3" -999 3 -999 -999 -999 -999 NA +"AMP" "ME130148" "SVR" NA NA "Platier" NA 1 28 7 2013 "11:19" "pluie" "SE" 5 1 NA NA "LD" -22.39156 167.10958 "RI" "AP" "Complexe de massif corallien de mers interieures" "platier recifal" "Fond lagonaire" "Recif intermediaire" "SA2" -999 6 -999 -999 -999 -999 NA +"AMP" "ME130149" "SVR" NA NA "Plateau recifal" NA 1 28 7 2013 "11:38" "pluie" "SE" 5 1 NA NA "LD" -22.39362 167.1066 "RI" "AP" "Complexe de massif corallien de mers interieures" "terrasse peu profonde" "Corail vivant" "Recif intermediaire" "LC5" -999 6 -999 -999 -999 -999 NA +"AMP" "ME130150" "SVR" NA NA "Fond lagonaire" NA 1 28 7 2013 "11:44" "pluie" "SE" 5 1 NA NA "LD" -22.39129 167.10684 "RI" "AP" "Complexe de massif corallien de mers interieures" "lagon enclave" "Fond lagonaire" "Fond lagonaire" "SA3" -999 10 -999 -999 -999 -999 NA +"AMP" "ME130151" "SVR" NA NA "Plateau recifal" NA 1 28 7 2013 "12:09" "pluie" "SE" 5 1 NA NA "LD" -22.39486 167.10068 "RI" "AP" "Complexe de massif corallien de mers interieures" "terrasse peu profonde" "Fond lagonaire" "Recif intermediaire" "SA1" -999 4 -999 -999 -999 -999 NA +"AMP" "ME130152" "SVR" NA NA "Plateau recifal" NA 1 28 7 2013 "12:15" "pluie" "SE" 5 1 NA NA "LD" -22.39679 167.09732 "RI" "AP" "Complexe de massif corallien de mers interieures" "terrasse peu profonde" "Fond lagonaire" "Recif intermediaire" "SA1" -999 7 -999 -999 -999 -999 NA +"AMP" "ME130153" "SVR" NA NA "Plateau recifal" NA 1 28 7 2013 "12:17" "pluie" "SE" 5 1 NA NA "LD" -22.39413 167.09628 "RI" "AP" "Complexe de massif corallien de mers interieures" "terrasse peu profonde" "Fond lagonaire" "Recif intermediaire" "SA3" -999 3 -999 -999 -999 -999 NA +"AMP" "ME130154" "SVR" NA NA "Fond lagonaire" NA 1 28 7 2013 "12:53" "pluie" "SE" 5 1 NA NA "LD" -22.3981 167.09505 "RI" "AP" "Complexe de massif corallien de mers interieures" "lagon enclave" "Fond lagonaire" "Fond lagonaire" "SA3" -999 7 -999 -999 -999 -999 NA +"AMP" "ME130155" "SVR" NA NA "Fond lagonaire" NA 1 28 7 2013 "12:58" "pluie" "SE" 5 1 NA NA "LD" -22.39931 167.0891 "RI" "AP" "Complexe de massif corallien de mers interieures" "lagon enclave" "Fond lagonaire" "Fond lagonaire" "SA1" -999 3 -999 -999 -999 -999 NA +"AMP" "ME130160" "SVR" NA NA "Pente externe" NA 1 29 7 2013 "09:43" "nuageux" "SE" 4 1 NA NA "DQ" -22.41767 167.07632 "RI" "AP" "Complexe de massif corallien de mers interieures" "front recifal" "Corail vivant" "Recif barriere externe" "LC2" -999 8 -999 -999 -999 -999 NA +"AMP" "ME130163" "SVR" NA NA "Plateau recifal" NA 1 28 7 2013 "08:28" "nuageux" "SE" 4 1 NA NA "LD" -22.40619 167.13626 "RI" "AP" "Complexe de massif corallien de mers interieures" "terrasse peu profonde" "Detritique" "Recif barriere interne" NA -999 2 -999 -999 -999 -999 NA +"AMP" "ME130164" "SVR" NA NA "Platier" NA 1 28 7 2013 "08:51" "nuageux" "SE" 4 1 NA NA "LD" -22.4112 167.12863 "RI" "AP" "Complexe de massif corallien de mers interieures" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA3" -999 2 -999 -999 -999 -999 NA +"AMP" "ME130165" "SVR" NA NA "Plateau recifal" NA 1 28 7 2013 "08:56" "nuageux" "SE" 4 1 NA NA "LD" -22.41299 167.12257 "RI" "AP" "Complexe de massif corallien de mers interieures" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA2" -999 15 -999 -999 -999 -999 NA +"AMP" "ME130166" "SVR" NA NA "Plateau recifal" NA 1 28 7 2013 "09:20" "nuageux" "SE" 4 1 NA NA "LD" -22.41763 167.11488 "RI" "AP" "Complexe de massif corallien de mers interieures" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA3" -999 7 -999 -999 -999 -999 NA +"AMP" "ME130170" "SVR" NA NA "Platier" NA 1 28 7 2013 "10:37" "pluie" "SE" 5 1 NA NA "LD" -22.42082 167.09592 "RI" "AP" "Complexe de massif corallien de mers interieures" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA3" -999 6 -999 -999 -999 -999 NA +"AMP" "ME130171" "SVR" NA NA "Platier" NA 1 28 7 2013 "10:44" "pluie" "SE" 5 2 NA NA "LD" -22.42344 167.09663 "RI" "AP" "Complexe de massif corallien de mers interieures" "platier recifal" "Corail vivant" "Recif barriere interne" NA -999 8 -999 -999 -999 -999 NA +"AMP" "ME130173" "SVR" NA NA "Platier" NA 1 28 7 2013 "11:14" "pluie" "SE" 5 2 NA NA "LD" -22.42366 167.105 "RI" "AP" "Complexe de massif corallien de mers interieures" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA3" -999 8 -999 -999 -999 -999 NA +"AMP" "ME130179" "SVR" NA NA "Plateau recifal" NA 1 29 7 2013 "14:37" "nuageux" "SE" 4 1 NA NA "DQ" -22.44329 167.09444 "RI" "AP" "Complexe de massif corallien de mers interieures" "terrasse peu profonde" "Detritique" "Frangeant ilot" "SA5" -999 2 -999 -999 -999 -999 NA +"AMP" "ME130190" "SVR" NA NA "Plateau recifal" NA 1 29 7 2013 "14:17" "nuageux" "SE" 4 1 NA NA "DQ" -22.44271 167.09459 "RI" "AP" "Complexe de massif corallien de mers interieures" "terrasse peu profonde" "Corail vivant" "Frangeant ilot" "LC5" -999 2.5 -999 -999 -999 -999 NA +"AMP" "ME130194" "SVR" NA NA "Platier" NA 1 29 7 2013 "15:02" "nuageux" "SE" 4 1 NA NA "DQ" -22.44463 167.0916 "RI" "AP" "Complexe de massif corallien de mers interieures" "platier recifal" "Fond lagonaire" "Frangeant ilot" "SA3" -999 5 -999 -999 -999 -999 NA +"AMP" "ME130204" "SVR" NA NA "Platier" NA 1 29 7 2013 "09:27" "nuageux" "ESE" 4 2 NA NA "DQ" -22.45331 167.1254 "RI" "AP" "Complexe de massif corallien de mers interieures" "platier recifal" "Detritique" "Recif intermediaire" NA -999 6 -999 -999 -999 -999 NA +"AMP" "ME130205" "SVR" NA NA "Platier" NA 1 29 7 2013 "09:49" "nuageux" "ESE" 4 2 NA NA "DQ" -22.45439 167.12529 "RI" "AP" "Complexe de massif corallien de mers interieures" "platier recifal" "Detritique" "Recif intermediaire" NA -999 3 -999 -999 -999 -999 NA +"AMP" "ME130206" "SVR" NA NA "Plateau recifal" NA 1 29 7 2013 "10:46" "nuageux" "ESE" 4 2 NA NA "DQ" -22.45305 167.13649 "RI" "AP" "Complexe de massif corallien de mers interieures" "terrasse peu profonde" "Fond lagonaire" "Recif intermediaire" "SA2" -999 4 -999 -999 -999 -999 NA +"AMP" "ME130207" "SVR" NA NA "Plateau recifal" NA 1 29 7 2013 "10:35" "nuageux" "ESE" 4 2 NA NA "DQ" -22.45203 167.13383 "RI" "AP" "Complexe de massif corallien de mers interieures" "terrasse peu profonde" "Fond lagonaire" "Recif intermediaire" "SA3" -999 6 -999 -999 -999 -999 NA +"AMP" "ME130208" "SVR" NA NA "Plateau recifal" NA 1 29 7 2013 "13:10" "nuageux" "ESE" 4 2 NA NA "DQ" -22.46432 167.13071 "RI" "AP" "Complexe de massif corallien de mers interieures" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA3" -999 3 -999 -999 -999 -999 NA +"AMP" "ME130209" "SVR" NA NA "Plateau recifal" NA 1 29 7 2013 "13:02" "nuageux" "ESE" 4 2 NA NA "DQ" -22.46601 167.13174 "RI" "AP" "Complexe de massif corallien de mers interieures" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA3" -999 3 -999 -999 -999 -999 NA +"AMP" "ME130210" "SVR" NA NA "Platier" NA 1 29 7 2013 "12:50" "nuageux" "ESE" 6 3 NA NA "DQ" -22.47032 167.13104 "RI" "AP" "Complexe de massif corallien de mers interieures" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA3" -999 3 -999 -999 -999 -999 NA +"AMP" "ME130211" "SVR" NA NA "Platier" NA 1 29 7 2013 "12:43" "nuageux" "ESE" 6 3 NA NA "DQ" -22.47336 167.13376 "RI" "AP" "Complexe de massif corallien de mers interieures" "platier recifal" "Algueraie" "Recif barriere interne" "MA3" -999 6 -999 -999 -999 -999 NA +"AMP" "ME130212" "SVR" NA NA "Platier" NA 1 29 7 2013 "12:24" "nuageux" "ESE" 4 2 NA NA "DQ" -22.47122 167.13795 "RI" "AP" "Complexe de massif corallien de mers interieures" "platier recifal" "Detritique" "Recif barriere interne" "LC6" -999 6 -999 -999 -999 -999 NA +"AMP" "ME130213" "SVR" NA NA "Platier" NA 1 29 7 2013 "12:19" "nuageux" "ESE" 4 2 NA NA "DQ" -22.47064 167.13531 "RI" "AP" "Complexe de massif corallien de mers interieures" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA3" -999 3 -999 -999 -999 -999 NA +"AMP" "ME130214" "SVR" NA NA "Platier" NA 1 29 7 2013 "11:53" "nuageux" "ESE" 4 2 NA NA "DQ" -22.46766 167.13696 "RI" "AP" "Complexe de massif corallien de mers interieures" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA1" -999 3 -999 -999 -999 -999 NA +"AMP" "ME130215" "SVR" NA NA "Platier" NA 1 29 7 2013 "11:45" "nuageux" "ESE" 4 2 NA NA "DQ" -22.46561 167.13365 "RI" "AP" "Complexe de massif corallien de mers interieures" "platier recifal" "Detritique" "Recif barriere interne" NA -999 6 -999 -999 -999 -999 NA +"AMP" "ME130217" "SVR" NA NA "Plateau recifal" NA 1 29 7 2013 "11:19" "nuageux" "ESE" 4 2 NA NA "DQ" -22.46495 167.13541 "RI" "AP" "Complexe de massif corallien de mers interieures" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA1" -999 2 -999 -999 -999 -999 NA +"AMP" "ME130218" "SVR" NA NA "Platier" NA 1 29 7 2013 "11:08" "nuageux" "ESE" 4 2 NA NA "DQ" -22.46005 167.13689 "RI" "AP" "Complexe de massif corallien de mers interieures" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA5" -999 6 -999 -999 -999 -999 NA +"AMP" "ME130220" "SVR" NA NA "Platier" NA 1 29 7 2013 "14:50" "nuageux" "ESE" 4 2 NA NA "DQ" -22.46519 167.13989 "RI" "AP" "Complexe de massif corallien de mers interieures" "platier recifal" "Corail vivant" "Recif barriere interne" "LC6" -999 6 -999 -999 -999 -999 NA +"AMP" "ME130222" "SVR" NA NA "Platier" NA 1 29 7 2013 "15:42" "nuageux" "ESE" 4 2 NA NA "DQ" -22.46177 167.14603 "RI" "AP" "Complexe de massif corallien de mers interieures" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA1" -999 6 -999 -999 -999 -999 NA +"AMP" "ME130223" "SVR" NA NA "Platier" NA 1 29 7 2013 "15:13" "nuageux" "ESE" 4 2 NA NA "DQ" -22.46439 167.14363 "RI" "AP" "Complexe de massif corallien de mers interieures" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA1" -999 6 -999 -999 -999 -999 NA +"AMP" "ME130224" "SVR" NA NA "Pente externe" NA 1 29 7 2013 "15:03" "nuageux" "ESE" 4 2 NA NA "DQ" -22.46681 167.14308 "RI" "AP" "Complexe de massif corallien de mers interieures" "front recifal" "Detritique" "Recif barriere interne" "D1" -999 4 -999 -999 -999 -999 NA +"AMP" "ME130225" "SVR" NA NA "Pente externe" NA 1 29 7 2013 "15:24" "nuageux" "ESE" 4 2 NA NA "DQ" -22.46441 167.14833 "RI" "AP" "Complexe de massif corallien de mers interieures" "front recifal" "Corail vivant" "Recif barriere interne" "LC6" -999 8 -999 -999 -999 -999 NA +"AMP" "ME130241" "SVR" NA NA "Platier" NA 1 31 7 2013 "12:52" "" NA -999 -999 NA NA "DC" -22.45191 167.16011 "RI" "AP" "Complexe de massif corallien de mers interieures" "terrasse peu profonde" "Corail vivant" "Recif barriere interne" "LC5" -999 5 -999 -999 -999 -999 NA +"AMP" "ME130246" "SVR" NA NA "Platier" NA 1 31 7 2013 "13:26" "" NA -999 -999 NA NA "DC" -22.45262 167.17244 "RI" "AP" "Complexe de massif corallien de mers interieures" "platier recifal" "Corail vivant" "Recif barriere interne" NA -999 3 -999 -999 -999 -999 NA +"AMP" "ME130248" "SVR" NA NA "Pente externe" NA 1 31 7 2013 "13:36" "Ensoleill?" "ESE" 3 2 NA NA "DC" -22.44761 167.17497 "RI" "AP" "Complexe de massif corallien de mers interieures" "front recifal" "Detritique" "Recif barriere interne" "SA5" -999 3 -999 -999 -999 -999 NA +"AMP" "ME130250" "SVR" NA NA "Platier" NA 1 31 7 2013 "10:29" "" NA -999 -999 NA NA "DC" -22.44482 167.17845 "RI" "AP" "Complexe de massif corallien de mers interieures" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA1" -999 2 -999 -999 -999 -999 NA +"AMP" "ME130251" "SVR" NA NA "Plateau recifal" NA 1 31 7 2013 "10:24" "Ensoleill?" "ESE" 1 2 NA NA "DC" -22.44308 167.17719 "RI" "AP" "Complexe de massif corallien de mers interieures" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "MA4" -999 3 -999 -999 -999 -999 NA +"AMP" "ME130252" "SVR" NA NA "Platier" NA 1 31 7 2013 "10:02" "Ensoleill?" "ESE" 1 2 NA NA "DC" -22.44131 167.17407 "RI" "AP" "Complexe de massif corallien de mers interieures" "platier recifal" "Corail vivant" "Recif barriere interne" "LC4" -999 3 -999 -999 -999 -999 NA +"AMP" "ME130258" "SVR" NA NA "Fond lagonaire" NA 1 31 7 2013 "11:22" "" NA -999 -999 NA NA "DC" -22.44118 167.19368 "RI" "AP" "Complexe de massif corallien de mers interieures" "lagon enclave" "Fond lagonaire" "Fond lagonaire" "SA1" -999 11 -999 -999 -999 -999 NA +"AMP" "ME130259" "SVR" NA NA "Plateau recifal" NA 1 31 7 2013 "11:18" "Ensoleill?" "ESE" 3 2 NA NA "DC" -22.43769 167.19316 "RI" "AP" "Complexe de massif corallien de mers interieures" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA2" -999 2 -999 -999 -999 -999 NA +"AMP" "ME130260" "SVR" NA NA "Plateau recifal" NA 1 31 7 2013 "11:40" "" NA -999 -999 NA NA "DC" -22.44019 167.19957 "RI" "AP" "Complexe de massif corallien de mers interieures" "lagon enclave" "Fond lagonaire" "Recif barriere interne" "SA3" -999 4 -999 -999 -999 -999 NA +"AMP" "ME130262" "SVR" NA NA "Plateau recifal" NA 1 31 7 2013 "11:44" "Ensoleill?" "ESE" 3 2 NA NA "DC" -22.4417 167.20145 "RI" "AP" "Complexe de massif corallien de mers interieures" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA3" -999 4 -999 -999 -999 -999 NA +"AMP" "ME130265" "SVR" NA NA "Plateau recifal" NA 1 31 7 2013 "08:34" "Ensoleill?" "ESE" 1 2 NA NA "DC" -22.41876 167.18098 "RI" "AP" "Complexe de massif corallien de mers interieures" "terrasse profonde" "Corail vivant" "Recif barriere interne" "LC5" -999 5 -999 -999 -999 -999 NA +"AMP" "ME130266" "SVR" NA NA "Plateau recifal" NA 1 31 7 2013 "08:29" "" NA -999 -999 NA NA "DC" -22.41774 167.18265 "RI" "AP" "Complexe de massif corallien de mers interieures" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA5" -999 2 -999 -999 -999 -999 NA +"AMP" "ME130267" "SVR" NA NA "Pente externe" NA 1 31 7 2013 "07:53" "Ensoleill?" "ESE" 1 2 NA NA "DC" -22.42717 167.18425 "RI" "AP" "Complexe de massif corallien de mers interieures" "front recifal" "Corail vivant" "Recif barriere externe" "LC2" -999 6 -999 -999 -999 -999 NA +"AMP" "ME130268" "SVR" NA NA "Pente externe" NA 1 31 7 2013 "08:05" "Ensoleill?" "ESE" 1 2 NA NA "DC" -22.4282 167.18343 "RI" "AP" "Complexe de massif corallien de mers interieures" "terrasse profonde" "Corail vivant" "Recif barriere interne" "LC2" -999 16 -999 -999 -999 -999 NA +"AMP" "ME130269" "SVR" NA NA "Platier" NA 1 31 7 2013 "09:34" "Ensoleill?" "ESE" 1 2 NA NA "DC" -22.43587 167.17522 "RI" "AP" "" "" "Corail vivant" "Recif barriere interne" "LC4" -999 19 -999 -999 -999 -999 NA +"AMP" "ME130271" "SVR" NA NA "Plateau recifal" NA 1 31 7 2013 "09:01" "" NA -999 -999 NA NA "DC" -22.42981 167.17155 "RI" "AP" "Complexe de massif corallien de mers interieures" "terrasse profonde" "Fond lagonaire" "Recif barriere interne" "SA4" -999 17 -999 -999 -999 -999 NA +"AMP" "ME130273" "SVR" NA NA "Pente externe" NA 1 31 7 2013 "12:18" "Ensoleill?" "ESE" 3 2 NA NA "DC" -22.44942 167.18182 "RI" "AP" "Complexe de massif corallien de mers interieures" "front recifal" "Corail vivant" "Recif barriere externe" "LC4" -999 9 -999 -999 -999 -999 NA +"AMP" "ME130274" "SVR" NA NA "Pente externe" NA 1 31 7 2013 "12:25" "" NA -999 -999 NA NA "DC" -22.45376 167.17636 "RI" "AP" "Complexe de massif corallien de mers interieures" "terrasse profonde" "Corail vivant" "Recif barriere externe" "LC2" -999 15 -999 -999 -999 -999 NA +"AMP" "ME130300" "SVR" NA NA "Platier" NA 1 27 7 2013 "11:32" "soleil" "SE" 3 1 NA NA "LD" -22.38264 167.12099 "RI" "AP" "Complexe de massif corallien de mers interieures" "platier recifal" "Fond lagonaire" "Recif intermediaire" "SA5" -999 2 -999 -999 -999 -999 NA +"AMP" "ME130301" "SVR" NA NA "Plateau recifal" NA 1 27 7 2013 "11:37" "soleil" "SE" 3 1 NA NA "LD" -22.38545 167.12061 "RI" "AP" "Complexe de massif corallien de mers interieures" "terrasse peu profonde" "Fond lagonaire" "Recif intermediaire" "SA3" -999 4 -999 -999 -999 -999 NA +"AMP" "ME130400" "SVR" NA NA "Plateau recifal" NA 1 28 7 2013 "10:24" "pluie" "SE" 4 1 NA NA "LD" -22.39551 167.12108 "RI" "AP" "Complexe de massif corallien de mers interieures" "terrasse peu profonde" "Corail vivant" "Recif intermediaire" "LC6" -999 5 -999 -999 -999 -999 NA +"AMP" "ME130401" "SVR" NA NA "Fond lagonaire" NA 1 29 7 2013 "16:09" "nuageux" "ESE" 4 2 NA NA "DQ" -22.46002 167.14229 "RI" "AP" "Complexe de massif corallien de mers interieures" "lagon enclave" "Fond lagonaire" "Fond lagonaire" "SA2" -999 15 -999 -999 -999 -999 NA +"AMP" "ME130402" "SVR" NA NA "Fond lagonaire" NA 1 27 7 2013 "10:17" "nuageux, pluie" "SE" 3 1 NA NA "LD" -22.38029 167.11797 "RI" "AP" "Complexe de massif corallien de mers interieures" "lagon enclave" "Corail vivant" "Recif intermediaire" "LC3" -999 12 -999 -999 -999 -999 NA +"AMP" "ME130403" "SVR" NA NA "Pente externe" NA 1 27 7 2013 "14:09" "Ensoleill?" "SE" 3 2 NA NA "LD" -22.40244 167.16623 "RI" "AP" "Complexe de massif corallien de mers interieures" "front recifal" "Corail vivant" "Recif barriere externe" "LC1" -999 8 -999 -999 -999 -999 NA +"AMP" "ME13102PM" "SVR" NA NA "Pente externe" NA 1 27 7 2013 "10:49" "nuageux" "SE" 4 2 NA NA "LD" -22.37444 167.15649 "RI" "AP" "Complexe de massif corallien de mers interieures" "front recifal" "Corail vivant" "Recif barriere externe" "LC4" -999 8 -999 -999 -999 -999 NA +"AMP" "ME13168PM" "SVR" NA NA "Plateau recifal" NA 1 28 7 2013 "10:11" "pluie" "SE" 5 1 NA NA "LD" -22.41858 167.09807 "RI" "AP" "Complexe de massif corallien de mers interieures" "terrasse peu profonde" "Corail vivant" "Recif intermediaire" "LC6" -999 7 -999 -999 -999 -999 NA +"AMP" "ME13247PM" "SVR" NA NA "Platier" NA 1 31 7 2013 "13:45" "" NA -999 -999 NA NA "DC" -22.45082 167.1763 "RI" "AP" "Complexe de massif corallien de mers interieures" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA4" -999 3 -999 -999 -999 -999 NA +"AMP" "ME1347PM" "SVR" NA NA "Pente externe" NA 1 26 7 2013 "16:17" "nuageux" "SE" 4 2 NA NA "LD" -22.37066 167.07544 "RI" "AP" "Complexe de massif corallien de mers interieures" "front recifal" "Fond lagonaire" "Recif barriere externe" "SA3" -999 7 -999 -999 -999 -999 NA +"AMP" "ME1359PM" "SVR" NA NA "Pente externe" NA 1 26 7 2013 "13:51" "nuageux" "SE" 4 2 NA NA "LD" -22.34918 167.08727 "RI" "AP" "Complexe de massif corallien de mers interieures" "front recifal" "Corail vivant" "Recif barriere externe" "LC4" -999 5 -999 -999 -999 -999 NA +"AMP" "MK080424" "SVR" "Mbe Kouen" "MK" NA NA 1 9 7 2008 NA NA NA 6 -999 NA "MM" "PC" -22.25972 166.2274 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" -999 10 -999 -999 -999 -999 "Drelon" +"AMP" "MK080425" "SVR" "Mbe Kouen" "MK" NA NA 1 9 7 2008 NA NA NA 6 -999 NA "MM" "PC" -22.2567 166.22752 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Detritique" "Recif intermediaire" "D5" -999 4.7 -999 -999 -999 -999 "Drelon" +"AMP" "MK080426" "SVR" "Mbe Kouen" "MK" NA NA 1 9 7 2008 NA NA NA 3 -999 NA "MM" "PC" -22.25465 166.22733 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Detritique" "Recif intermediaire" "D7" -999 3.6 -999 -999 -999 -999 NA +"AMP" "MK080427" "SVR" "Mbe Kouen" "MK" NA NA 1 9 7 2008 NA NA NA 3 -999 NA "MM" "PC" -22.25306 166.22519 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Detritique" "Recif intermediaire" NA -999 5 -999 -999 -999 -999 "Drelon" +"AMP" "MK080428" "SVR" "Mbe Kouen" "MK" NA NA 1 9 7 2008 NA NA NA 4 -999 NA "MD" "PC" -22.25147 166.22371 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Detritique" "Recif intermediaire" "D5" -999 6 -999 -999 -999 -999 "Drelon" +"AMP" "MK080430" "SVR" "Mbe Kouen" "MK" NA NA 1 9 7 2008 NA NA NA 1 -999 NA "MD" "NL" -22.25141 166.22717 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Recif intermediaire" "D2" -999 3 -999 -999 -999 -999 "Drelon" +"AMP" "MK080431" "SVR" "Mbe Kouen" "MK" NA NA 1 9 7 2008 NA NA NA 1 -999 NA "MD" "NL" -22.25122 166.22941 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Fond lagonaire" "Recif intermediaire" "SA3" -999 3.8 -999 -999 -999 -999 "Drelon" +"AMP" "MK080432" "SVR" "Mbe Kouen" "MK" NA NA 1 9 7 2008 NA NA NA 1 -999 NA "MD" "NL" -22.25178 166.23109 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Recif intermediaire" "D1" -999 5.5 -999 -999 -999 -999 "Drelon" +"AMP" "MK080433" "SVR" "Mbe Kouen" "MK" NA NA 1 9 7 2008 NA NA NA 1 -999 NA "MD" "NL" -22.25322 166.23239 "HR" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Recif intermediaire" "D5" -999 6.7 -999 -999 -999 -999 "Drelon" +"AMP" "MK080434" "SVR" "Mbe Kouen" "MK" NA NA 1 9 7 2008 NA NA NA 1 -999 NA "MD" "NL" -22.25624 166.23372 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Recif intermediaire" "D5" -999 5.7 -999 -999 -999 -999 "Drelon" +"AMP" "MK080435" "SVR" "Mbe Kouen" "MK" NA NA 1 9 7 2008 NA NA NA 1 -999 NA "MD" "NL" -22.25827 166.23452 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Recif intermediaire" "D1" -999 6.6 -999 -999 -999 -999 "Drelon" +"AMP" "MK080436" "SVR" "Mbe Kouen" "MK" NA NA 1 9 7 2008 NA NA NA 1 -999 NA "MD" "NL" -22.26122 166.235 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Recif intermediaire" NA -999 4 -999 -999 -999 -999 "Drelon" +"AMP" "MK080439" "SVR" "Mbe Kouen" "MK" NA NA 1 9 7 2008 NA NA NA 1 -999 NA "MD" "NL" -22.27038 166.23523 "HR" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Recif intermediaire" "D5" -999 6.2 -999 -999 -999 -999 "Drelon" +"AMP" "MK080440" "SVR" "Mbe Kouen" "MK" NA NA 1 9 7 2008 NA NA NA 1 -999 NA "MD" "NL" -22.27307 166.23523 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Fond lagonaire" "D5" -999 6.5 -999 -999 -999 -999 "Drelon" +"AMP" "MK080441" "SVR" "Mbe Kouen" "MK" NA NA 1 9 7 2008 NA NA NA 4 -999 NA "MM" "PC" -22.27285 166.23369 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Fond lagonaire" "D1" -999 3.5 -999 -999 -999 -999 "Drelon" +"AMP" "MK080443" "SVR" "Mbe Kouen" "MK" NA NA 1 9 7 2008 NA NA NA 5 -999 NA "MD" "PC" -22.26778 166.22276 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Fond lagonaire" "D5" -999 5 -999 -999 -999 -999 "Drelon" +"AMP" "MK080445" "SVR" "Mbe Kouen" "MK" NA NA 1 1 8 2008 NA NA NA 5 -999 NA "MD" "PC" -22.26721 166.2189 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Fond lagonaire" "D5" -999 5.5 -999 -999 -999 -999 "Drelon" +"AMP" "MK080446" "SVR" "Mbe Kouen" "MK" NA NA 1 1 8 2008 NA NA NA 5 -999 NA "MD" "PC" -22.26738 166.21565 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif intermediaire" "SA3" -999 7 -999 -999 -999 -999 "Drelon" +"AMP" "MK080447" "SVR" "Mbe Kouen" "MK" NA NA 1 1 8 2008 NA NA NA 5 -999 NA "MD" "PC" -22.26608 166.21411 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Algueraie" "Recif intermediaire" "MA4" -999 6.4 -999 -999 -999 -999 "Drelon" +"AMP" "MK080448" "SVR" "Mbe Kouen" "MK" NA NA 1 1 8 2008 NA NA NA 5 -999 NA "MD" "PC" -22.26412 166.21567 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Recif intermediaire" "SA1" -999 6 -999 -999 -999 -999 "Drelon" +"AMP" "MK080453" "SVR" "Mbe Kouen" "MK" NA NA 1 1 8 2008 NA NA NA 6 -999 NA "MM" "PC" -22.26088 166.23066 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Detritique" "Recif intermediaire" "D7" -999 4 -999 -999 -999 -999 "Drelon" +"AMP" "MK080454" "SVR" "Mbe Kouen" "MK" NA NA 1 1 8 2008 NA NA NA 4 -999 NA "MM" "PC" -22.26291 166.23077 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Detritique" "Recif intermediaire" "D5" -999 4.7 -999 -999 -999 -999 "Drelon" +"AMP" "MK080455" "SVR" "Mbe Kouen" "MK" NA NA 1 1 8 2008 NA NA NA 4 -999 NA "MM" "PC" -22.26558 166.23113 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Detritique" "Recif intermediaire" "D3" -999 4.9 -999 -999 -999 -999 "Drelon" +"AMP" "MK080456" "SVR" "Mbe Kouen" "MK" NA NA 1 1 8 2008 NA NA NA 1 -999 NA "MD" "NL" -22.23921 166.22503 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Detritique" "Frangeant ilot" "D6" -999 6.5 -999 -999 -999 -999 "Drelon" +"AMP" "MK080457" "SVR" "Mbe Kouen" "MK" NA NA 1 1 8 2008 NA NA NA 1 -999 NA "MD" "NL" -22.23928 166.22752 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Frangeant ilot" "D5" -999 4.6 -999 -999 -999 -999 "Drelon" +"AMP" "MK080458" "SVR" "Mbe Kouen" "MK" NA NA 1 1 8 2008 NA NA NA 1 -999 NA "MD" "NL" -22.241 166.23075 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Frangeant ilot" "D6" -999 3.6 -999 -999 -999 -999 "Drelon" +"AMP" "MK080459" "SVR" "Mbe Kouen" "MK" NA NA 1 1 8 2008 NA NA NA 1 -999 NA "MD" "NL" -22.24154 166.23264 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Frangeant ilot" NA -999 5 -999 -999 -999 -999 "Drelon" +"AMP" "MK080460" "SVR" "Mbe Kouen" "MK" NA NA 1 1 8 2008 NA NA NA 1 -999 NA "MD" "NL" -22.24212 166.23482 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Corail vivant" "Frangeant ilot" "LC3" -999 5.5 -999 -999 -999 -999 "Drelon" +"AMP" "MK080461" "SVR" "Mbe Kouen" "MK" NA NA 1 1 8 2008 NA NA NA 1 -999 NA "MM" "NL" -22.2448 166.23521 "HR" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Frangeant ilot" "D1" -999 5.7 -999 -999 -999 -999 "Drelon" +"AMP" "MK080462" "SVR" "Mbe Kouen" "MK" NA NA 1 1 8 2008 NA NA NA 1 -999 NA "MM" "NL" -22.24713 166.23314 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Frangeant ilot" "D1" -999 5 -999 -999 -999 -999 "Drelon" +"AMP" "MK080463" "SVR" "Mbe Kouen" "MK" NA NA 1 1 8 2008 NA NA NA 1 -999 NA "MM" "NL" -22.24788 166.22864 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Frangeant ilot" "D2" -999 6 -999 -999 -999 -999 "Drelon" +"AMP" "MK080464" "SVR" "Mbe Kouen" "MK" NA NA 1 1 8 2008 NA NA NA 1 -999 NA "MM" "NL" -22.24743 166.22575 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Frangeant ilot" "D4" -999 3.7 -999 -999 -999 -999 "Drelon" +"AMP" "MK080465" "SVR" "Mbe Kouen" "MK" NA NA 1 1 8 2008 NA NA NA 1 -999 NA "MM" "NL" -22.24529 166.22357 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Frangeant ilot" "D6" -999 5.4 -999 -999 -999 -999 "Drelon" +"AMP" "MK080466" "SVR" "Mbe Kouen" "MK" NA NA 1 1 8 2008 NA NA NA 1 -999 NA "MM" "NL" -22.24292 166.2218 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Frangeant ilot" "D1" -999 4.1 -999 -999 -999 -999 "Drelon" +"AMP" "MK080467" "SVR" "Mbe Kouen" "MK" NA NA 1 1 8 2008 NA NA NA 1 -999 NA "MM" "NL" -22.24035 166.22283 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Detritique" "Frangeant ilot" "D2" -999 5.5 -999 -999 -999 -999 "Drelon" +"AMP" "MK090207" "SVR" "Mbe Kouen" "MK" NA NA 1 3 7 2009 NA NA "NO" 3 -999 NA "MD" "LM" -22.2549163 166.227266 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Detritique" "Recif intermediaire" "D7" -999 2.5 -999 -999 -999 -999 "Drelon" +"AMP" "MK090208" "SVR" "Mbe Kouen" "MK" NA NA 1 3 7 2009 NA NA "NO" 3 -999 NA "MD" "LM" -22.2532333 166.225283 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Detritique" "Recif intermediaire" NA -999 4.9 -999 -999 -999 -999 "Drelon" +"AMP" "MK090210" "SVR" "Mbe Kouen" "MK" NA NA 1 2 7 2009 NA NA NA -999 -999 NA "MM" "LM" -22.2496053 166.2250743 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Algueraie" "Fond lagonaire" "MA3" -999 9.1 -999 -999 -999 -999 "Drelon" +"AMP" "MK090211" "SVR" "Mbe Kouen" "MK" NA NA 1 2 7 2009 NA NA NA -999 -999 NA "MM" "LM" -22.2515359 166.2273297 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Recif intermediaire" "D5" -999 2.7 -999 -999 -999 -999 "Drelon" +"AMP" "MK090212" "SVR" "Mbe Kouen" "MK" NA NA 1 2 7 2009 NA NA NA -999 -999 NA "MM" "LM" -22.2513136 166.2293066 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Recif intermediaire" "D2" -999 4.3 -999 -999 -999 -999 "Drelon" +"AMP" "MK090213" "SVR" "Mbe Kouen" "MK" NA NA 1 2 7 2009 NA NA NA -999 -999 NA "MM" "LM" -22.2518408 166.2310249 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Recif intermediaire" "D1" -999 5.4 -999 -999 -999 -999 "Drelon" +"AMP" "MK090214" "SVR" "Mbe Kouen" "MK" NA NA 1 2 7 2009 NA NA NA -999 -999 NA "MM" "LM" -22.2529996 166.2320971 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Recif intermediaire" "D5" -999 6 -999 -999 -999 -999 "Drelon" +"AMP" "MK090215" "SVR" "Mbe Kouen" "MK" NA NA 1 2 7 2009 NA NA NA -999 -999 NA "MM" "LM" -22.2560798 166.2336207 "HR" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Recif intermediaire" "D5" -999 6 -999 -999 -999 -999 "Drelon" +"AMP" "MK090216" "SVR" "Mbe Kouen" "MK" NA NA 1 2 7 2009 NA NA NA -999 -999 NA "MM" "LM" -22.2582377 166.2344147 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Recif intermediaire" "D1" -999 6.3 -999 -999 -999 -999 "Drelon" +"AMP" "MK090217" "SVR" "Mbe Kouen" "MK" NA NA 1 2 7 2009 NA NA NA -999 -999 NA "MM" "LM" -22.2615331 166.234927 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Recif intermediaire" "D1" -999 4.5 -999 -999 -999 -999 "Drelon" +"AMP" "MK090218" "SVR" "Mbe Kouen" "MK" NA NA 1 2 7 2009 NA NA NA -999 -999 NA "MM" "LM" -22.2640186 166.2354327 "HR" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Recif intermediaire" "D1" -999 4.2 -999 -999 -999 -999 "Drelon" +"AMP" "MK090219" "SVR" "Mbe Kouen" "MK" NA NA 1 2 7 2009 NA NA NA -999 -999 NA "BM" "LM" -22.2667114 166.2351086 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Detritique" "Recif intermediaire" "D5" -999 5.6 -999 -999 -999 -999 "Drelon" +"AMP" "MK090220" "SVR" "Mbe Kouen" "MK" NA NA 1 2 7 2009 NA NA NA -999 -999 NA "MD" "LM" -22.2705272 166.2352515 "HR" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Recif intermediaire" "D7" -999 5.9 -999 -999 -999 -999 "Drelon" +"AMP" "MK090221" "SVR" "Mbe Kouen" "MK" NA NA 1 2 7 2009 NA NA NA -999 -999 NA "MD" "LM" -22.2731591 166.2349647 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Fond lagonaire" "D5" -999 5.8 -999 -999 -999 -999 "Drelon" +"AMP" "MK090222" "SVR" "Mbe Kouen" "MK" NA NA 1 2 7 2009 NA NA NA -999 -999 NA "MD" "LM" -22.2731093 166.2338269 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Fond lagonaire" "D2" -999 4.7 -999 -999 -999 -999 "Drelon" +"AMP" "MK090224" "SVR" "Mbe Kouen" "MK" NA NA 1 15 7 2009 NA NA NA -999 -999 NA "MM" "DQ" -22.2674169 166.2194728 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Fond lagonaire" "D7" -999 6.6 -999 -999 -999 -999 "Drelon" +"AMP" "MK090225" "SVR" "Mbe Kouen" "MK" NA NA 1 3 7 2009 NA NA "NO" 3 -999 NA "MM" "LM" -22.267133 166.2176231 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Detritique" "Recif intermediaire" "D2" -999 3.8 -999 -999 -999 -999 "Drelon" +"AMP" "MK090226" "SVR" "Mbe Kouen" "MK" NA NA 1 3 7 2009 NA NA "NO" 3 -999 NA "MM" "LM" -22.2672939 166.215712 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Detritique" "Recif intermediaire" NA -999 6.4 -999 -999 -999 -999 "Drelon" +"AMP" "MK090227" "SVR" "Mbe Kouen" "MK" NA NA 1 3 7 2009 NA NA "NO" 3 -999 NA "MM" "LM" -22.2664129 166.2149119 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Detritique" "Recif intermediaire" "D5" -999 2.3 -999 -999 -999 -999 "Drelon" +"AMP" "MK090228" "SVR" "Mbe Kouen" "MK" NA NA 1 15 7 2009 NA NA NA -999 -999 NA "MM" "DQ" -22.2654044 166.2170516 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Fond lagonaire" "Recif intermediaire" "SA3" -999 2.2 -999 -999 -999 -999 "Drelon" +"AMP" "MK090229" "SVR" "Mbe Kouen" "MK" NA NA 1 3 7 2009 NA NA "NO" 3 -999 NA "MM" "LM" -22.2652228 166.21949 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Fond lagonaire" "Frangeant ilot" "SA4" -999 2.9 -999 -999 -999 -999 "Drelon" +"AMP" "MK090230" "SVR" "Mbe Kouen" "MK" NA NA 1 3 7 2009 NA NA "NO" 3 -999 NA "MM" "LM" -22.263861 166.2215294 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Fond lagonaire" "Frangeant ilot" "SA5" -999 2.8 -999 -999 -999 -999 "Drelon" +"AMP" "MK090231" "SVR" "Mbe Kouen" "MK" NA NA 1 3 7 2009 NA NA "NO" 3 -999 NA "MM" "LM" -22.2618282 166.2237861 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Frangeant ilot" "D7" -999 3.3 -999 -999 -999 -999 "Drelon" +"AMP" "MK090234" "SVR" "Mbe Kouen" "MK" NA NA 1 3 7 2009 NA NA "NO" 3 -999 NA "MD" "LM" -22.2629046 166.2310459 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Detritique" "Recif intermediaire" "D7" -999 3.5 -999 -999 -999 -999 "Drelon" +"AMP" "MK090236" "SVR" "Mbe Kouen" "MK" NA NA 1 2 7 2009 NA NA NA -999 -999 NA "MM" "LM" -22.2398215 166.2252745 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Frangeant ilot" "D2" -999 2.5 -999 -999 -999 -999 "Drelon" +"AMP" "MK090237" "SVR" "Mbe Kouen" "MK" NA NA 1 2 7 2009 NA NA NA -999 -999 NA "MM" "LM" -22.2395124 166.2274854 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Frangeant ilot" "D1" -999 3.6 -999 -999 -999 -999 "Drelon" +"AMP" "MK090238" "SVR" "Mbe Kouen" "MK" NA NA 1 2 7 2009 NA NA NA -999 -999 NA "MM" "LM" -22.2409923 166.2306198 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Frangeant ilot" "D6" -999 3.9 -999 -999 -999 -999 "Drelon" +"AMP" "MK090239" "SVR" "Mbe Kouen" "MK" NA NA 1 2 7 2009 NA NA NA -999 -999 NA "MM" "LM" -22.2416635 166.2324748 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Frangeant ilot" "D5" -999 5.1 -999 -999 -999 -999 "Drelon" +"AMP" "MK090240" "SVR" "Mbe Kouen" "MK" NA NA 1 2 7 2009 NA NA NA -999 -999 NA "MM" "LM" -22.242255 166.234519 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Frangeant ilot" "D3" -999 4.3 -999 -999 -999 -999 "Drelon" +"AMP" "MK090241" "SVR" "Mbe Kouen" "MK" NA NA 1 2 7 2009 NA NA NA -999 -999 NA "MM" "LM" -22.2446173 166.2352243 "HR" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Frangeant ilot" "D6" -999 6.5 -999 -999 -999 -999 "Drelon" +"AMP" "MK090242" "SVR" "Mbe Kouen" "MK" NA NA 1 2 7 2009 NA NA NA -999 -999 NA "MM" "LM" -22.2472066 166.2334833 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "SA5" -999 8 -999 -999 -999 -999 "Drelon" +"AMP" "MK090243" "SVR" "Mbe Kouen" "MK" NA NA 1 2 7 2009 NA NA NA -999 -999 NA "MM" "LM" -22.247793 166.2287293 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Frangeant ilot" "D7" -999 5.4 -999 -999 -999 -999 "Drelon" +"AMP" "MK090244" "SVR" "Mbe Kouen" "MK" NA NA 1 2 7 2009 NA NA NA -999 -999 NA "MM" "LM" -22.2474108 166.2257355 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Frangeant ilot" "D5" -999 3.5 -999 -999 -999 -999 "Drelon" +"AMP" "MK090245" "SVR" "Mbe Kouen" "MK" NA NA 1 3 7 2009 NA NA "NO" 3 -999 NA "MD" "LM" -22.2454709 166.2236647 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Frangeant ilot" "D7" -999 5.8 -999 -999 -999 -999 "Drelon" +"AMP" "MK090248" "SVR" "Mbe Kouen" "MK" NA NA 1 2 7 2009 NA NA NA -999 -999 NA "MM" "LM" -22.2417997 166.2300768 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Corail vivant" "Frangeant ilot" "LC2" -999 1.5 -999 -999 -999 -999 "Drelon" +"AMP" "MK090249" "SVR" "Mbe Kouen" "MK" NA NA 1 2 7 2009 NA NA NA -999 -999 NA "MM" "LM" -22.2428813 166.2303346 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Fond lagonaire" "Frangeant ilot" "SA5" -999 1.3 -999 -999 -999 -999 "Drelon" +"AMP" "MK090250" "SVR" "Mbe Kouen" "MK" NA NA 1 3 7 2009 NA NA "NO" 4 -999 NA "MM" "LM" -22.265316 166.2254603 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Frangeant ilot" "D5" -999 5 -999 -999 -999 -999 "Drelon" +"AMP" "MK090251" "SVR" "Mbe Kouen" "MK" NA NA 1 15 7 2009 NA NA NA -999 -999 NA "MM" "DQ" -22.2635165 166.2253527 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Frangeant ilot" "D3" -999 3.5 -999 -999 -999 -999 "Drelon" +"AMP" "MK090252" "SVR" "Mbe Kouen" "MK" NA NA 1 15 7 2009 NA NA NA -999 -999 NA "MM" "DQ" -22.2613878 166.2253403 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Algueraie" "Frangeant ilot" "MA3" -999 2.1 -999 -999 -999 -999 "Drelon" +"AMP" "MK100200" "SVR" "Mbe Kouen" "MK" NA NA 1 16 4 2010 NA NA NA 5 -999 NA "MM" "PC" -22.26789 166.22289 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Fond lagonaire" "D5" -999 7.5 -999 -999 -999 -999 "Drelon" +"AMP" "MK100202" "SVR" "Mbe Kouen" "MK" NA NA 1 9 3 2010 NA NA NA 5 -999 NA "MM" "DC" -22.26162 166.22395 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Frangeant ilot" "SA5" -999 3.1 -999 -999 -999 -999 "Drelon" +"AMP" "MK100203" "SVR" "Mbe Kouen" "MK" NA NA 1 9 3 2010 NA NA NA 5 -999 NA "MM" "DC" -22.26382 166.2216 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Fond lagonaire" "Frangeant ilot" "SA5" -999 3.5 -999 -999 -999 -999 "Drelon" +"AMP" "MK100204" "SVR" "Mbe Kouen" "MK" NA NA 1 9 3 2010 NA NA NA 5 -999 NA "MM" "DC" -22.26513 166.21959 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Fond lagonaire" "Frangeant ilot" "SA3" -999 3.8 -999 -999 -999 -999 "Drelon" +"AMP" "MK100205" "SVR" "Mbe Kouen" "MK" NA NA 1 16 4 2010 NA NA NA 3 -999 NA "MM" "PC" -22.26649 166.21488 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Detritique" "Recif intermediaire" "D2" -999 4.3 -999 -999 -999 -999 "Drelon" +"AMP" "MK100206" "SVR" "Mbe Kouen" "MK" NA NA 1 16 4 2010 NA NA NA 3 -999 NA "MM" "PC" -22.26724 166.2157 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Detritique" "Recif intermediaire" "D6" -999 5.2 -999 -999 -999 -999 "Drelon" +"AMP" "MK100207" "SVR" "Mbe Kouen" "MK" NA NA 1 16 4 2010 NA NA NA 5 -999 NA "MM" "PC" -22.26703 166.21791 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Detritique" "Recif intermediaire" "D1" -999 4.5 -999 -999 -999 -999 "Drelon" +"AMP" "MK100208" "SVR" "Mbe Kouen" "MK" NA NA 1 16 4 2010 NA NA NA 5 -999 NA "MM" "PC" -22.26739 166.21943 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA3" -999 7.3 -999 -999 -999 -999 "Drelon" +"AMP" "MK100209" "SVR" "Mbe Kouen" "MK" NA NA 1 16 4 2010 NA NA NA 4 -999 NA "MD" "PC" -22.2652 166.22544 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Frangeant ilot" "D7" -999 4 -999 -999 -999 -999 "Drelon" +"AMP" "MK100210" "SVR" "Mbe Kouen" "MK" NA NA 1 16 4 2010 NA NA NA 4 -999 NA "MD" "PC" -22.26341 166.22533 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Frangeant ilot" "D2" -999 3.2 -999 -999 -999 -999 "Drelon" +"AMP" "MK100213" "SVR" "Mbe Kouen" "MK" NA NA 1 9 3 2010 NA NA NA 5 -999 NA "MM" "DC" -22.26531 166.21708 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Fond lagonaire" "Recif intermediaire" "SA3" -999 2.4 -999 -999 -999 -999 "Drelon" +"AMP" "MK100214" "SVR" "Mbe Kouen" "MK" NA NA 1 9 3 2010 NA NA NA 4 -999 NA "MD" "DC" -22.26592 166.23122 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Detritique" "Recif intermediaire" "D7" -999 5.2 -999 -999 -999 -999 "Drelon" +"AMP" "MK100215" "SVR" "Mbe Kouen" "MK" NA NA 1 9 3 2010 NA NA NA 5 -999 NA "MM" "DC" -22.26098 166.23054 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Detritique" "Recif intermediaire" "D7" -999 3.6 -999 -999 -999 -999 "Drelon" +"AMP" "MK100216" "SVR" "Mbe Kouen" "MK" NA NA 1 9 3 2010 NA NA NA 5 -999 NA "MM" "DC" -22.25131 166.22368 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Detritique" "Recif intermediaire" "D7" -999 6.9 -999 -999 -999 -999 "Drelon" +"AMP" "MK100219" "SVR" "Mbe Kouen" "MK" NA NA 1 9 3 2010 NA NA NA 5 -999 NA "MD" "DC" -22.26272 166.23105 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Detritique" "Recif intermediaire" "D7" -999 4 -999 -999 -999 -999 "Drelon" +"AMP" "MK100220" "SVR" "Mbe Kouen" "MK" NA NA 1 9 3 2010 NA NA NA 4 -999 NA "MD" "DC" -22.27269 166.23357 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Fond lagonaire" "D6" -999 4 -999 -999 -999 -999 NA +"AMP" "MK100221" "SVR" "Mbe Kouen" "MK" NA NA 1 24 3 2010 NA NA NA 3 -999 NA "MM" "LM" -22.27064 166.2354 "HR" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Recif intermediaire" "D7" -999 5.3 -999 -999 -999 -999 "Drelon" +"AMP" "MK100222" "SVR" "Mbe Kouen" "MK" NA NA 1 24 3 2010 NA NA NA 3 -999 NA "MM" "LM" -22.26662 166.23508 "HR" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Recif intermediaire" "D5" -999 5.5 -999 -999 -999 -999 "Drelon" +"AMP" "MK100223" "SVR" "Mbe Kouen" "MK" NA NA 1 24 3 2010 NA NA NA 3 -999 NA "MM" "LM" -22.26404 166.23576 "HR" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Recif intermediaire" "D7" -999 5 -999 -999 -999 -999 "Drelon" +"AMP" "MK100224" "SVR" "Mbe Kouen" "MK" NA NA 1 24 3 2010 NA NA NA 3 -999 NA "MM" "LM" -22.26175 166.23543 "HR" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Recif intermediaire" "D1" -999 6.6 -999 -999 -999 -999 "Drelon" +"AMP" "MK100225" "SVR" "Mbe Kouen" "MK" NA NA 1 24 3 2010 NA NA NA 3 -999 NA "MM" "LM" -22.25839 166.23467 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Recif intermediaire" "D2" -999 7.7 -999 -999 -999 -999 "Drelon" +"AMP" "MK100226" "SVR" "Mbe Kouen" "MK" NA NA 1 24 3 2010 NA NA NA 3 -999 NA "MM" "LM" -22.25596 166.23368 "HR" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Recif intermediaire" "D7" -999 7.4 -999 -999 -999 -999 "Drelon" +"AMP" "MK100227" "SVR" "Mbe Kouen" "MK" NA NA 1 24 3 2010 NA NA NA 3 -999 NA "MM" "LM" -22.25301 166.23225 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Recif intermediaire" "D5" -999 6.5 -999 -999 -999 -999 "Drelon" +"AMP" "MK100229" "SVR" "Mbe Kouen" "MK" NA NA 1 9 3 2010 NA NA NA 5 -999 NA "MM" "DC" -22.25164 166.22756 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Recif intermediaire" "D3" -999 3.1 -999 -999 -999 -999 "Drelon" +"AMP" "MK100230" "SVR" "Mbe Kouen" "MK" NA NA 1 9 3 2010 NA NA NA 5 -999 NA "MM" "DC" -22.25318 166.2247 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Detritique" "Recif intermediaire" NA -999 5.5 -999 -999 -999 -999 "Drelon" +"AMP" "MK100231" "SVR" "Mbe Kouen" "MK" NA NA 1 9 3 2010 NA NA NA 5 -999 NA "MM" "DC" -22.25457 166.22714 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Detritique" "Recif intermediaire" "D7" -999 4.4 -999 -999 -999 -999 "Drelon" +"AMP" "MK100234" "SVR" "Mbe Kouen" "MK" NA NA 1 9 3 2010 NA NA NA 4 -999 NA "MD" "DC" -22.27041 166.23301 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA4" -999 3.3 -999 -999 -999 -999 "Drelon" +"AMP" "MK100237" "SVR" "Mbe Kouen" "MK" NA NA 1 24 3 2010 NA NA NA 3 -999 NA "MM" "LM" -22.2474 166.22576 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Frangeant ilot" "D2" -999 4 -999 -999 -999 -999 "Drelon" +"AMP" "MK100238" "SVR" "Mbe Kouen" "MK" NA NA 1 24 3 2010 NA NA NA 3 -999 NA "MM" "LM" -22.24781 166.22874 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Frangeant ilot" "D2" -999 6 -999 -999 -999 -999 "Drelon" +"AMP" "MK100239" "SVR" "Mbe Kouen" "MK" NA NA 1 24 3 2010 NA NA NA 4 -999 NA "MM" "LM" -22.24714 166.23352 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Frangeant ilot" "LC3" -999 7.2 -999 -999 -999 -999 "Drelon" +"AMP" "MK100240" "SVR" "Mbe Kouen" "MK" NA NA 1 24 3 2010 NA NA NA 4 -999 NA "MM" "LM" -22.24455 166.23523 "HR" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Frangeant ilot" "LC3" -999 6.4 -999 -999 -999 -999 "Drelon" +"AMP" "MK100241" "SVR" "Mbe Kouen" "MK" NA NA 1 24 3 2010 NA NA NA 4 -999 NA "MM" "LM" -22.24224 166.23461 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Frangeant ilot" "D2" -999 4.5 -999 -999 -999 -999 "Drelon" +"AMP" "MK100242" "SVR" "Mbe Kouen" "MK" NA NA 1 24 3 2010 NA NA NA 4 -999 NA "MM" "LM" -22.24161 166.23256 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Frangeant ilot" "D2" -999 5.8 -999 -999 -999 -999 "Drelon" +"AMP" "MK100243" "SVR" "Mbe Kouen" "MK" NA NA 1 24 3 2010 NA NA NA 4 -999 NA "MM" "LM" -22.24096 166.23061 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Frangeant ilot" "D5" -999 4.6 -999 -999 -999 -999 "Drelon" +"AMP" "MK100244" "SVR" "Mbe Kouen" "MK" NA NA 1 25 3 2010 NA NA NA 5 -999 NA "MM" "LM" -22.23942 166.22758 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Frangeant ilot" "D1" -999 4.6 -999 -999 -999 -999 "Drelon" +"AMP" "MK100245" "SVR" "Mbe Kouen" "MK" NA NA 1 24 3 2010 NA NA NA 4 -999 NA "MM" "LM" -22.23989 166.22532 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Frangeant ilot" "D1" -999 3 -999 -999 -999 -999 "Drelon" +"AMP" "MK100246" "SVR" "Mbe Kouen" "MK" NA NA 1 24 3 2010 NA NA NA 4 -999 NA "MM" "LM" -22.24551 166.22382 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Frangeant ilot" "D2" -999 6.1 -999 -999 -999 -999 "Drelon" +"AMP" "MK100247" "SVR" "Mbe Kouen" "MK" NA NA 1 25 3 2010 NA NA NA 5 -999 NA "MM" "LM" -22.24275 166.22177 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Frangeant ilot" "D2" -999 4.7 -999 -999 -999 -999 "Drelon" +"AMP" "MK100248" "SVR" "Mbe Kouen" "MK" NA NA 1 24 3 2010 NA NA NA 4 -999 NA "MM" "LM" -22.24034 166.2231 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Frangeant ilot" "D1" -999 5.7 -999 -999 -999 -999 "Drelon" +"AMP" "MK100249" "SVR" "Mbe Kouen" "MK" NA NA 1 24 3 2010 NA NA NA 4 -999 NA "MM" "LM" -22.24752 166.23104 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Frangeant ilot" "D5" -999 6.2 -999 -999 -999 -999 "Drelon" +"AMP" "MK100252" "SVR" "Mbe Kouen" "MK" NA NA 1 24 3 2010 NA NA NA 4 -999 NA "MM" "LM" -22.23996 166.22933 "HR" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Frangeant ilot" "D6" -999 6 -999 -999 -999 -999 "Drelon" +"AMP" "OU090001" "SVR" NA NA NA NA 1 7 10 2009 NA NA NA -999 -999 NA "MD" "LD" -21.8636 165.7321 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Corail vivant" "Recif barriere interne" "LC5" 9 2.8 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090002" "SVR" NA NA NA NA 1 8 10 2009 NA NA NA -999 -999 NA "MD" "LD" -21.8576 165.7381 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Fond lagonaire" "D7" 9 9.7 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090004" "SVR" NA NA NA NA 1 8 10 2009 NA NA NA -999 -999 NA "MD" "LD" -21.8604 165.742 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA3" 8 9.7 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090005" "SVR" NA NA NA NA 1 9 10 2009 NA NA NA -999 -999 NA "MD" "LD" -21.85527 165.75164 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Algueraie" "Fond lagonaire" "MA3" 5 14.9 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090006" "SVR" NA NA NA NA 1 9 10 2009 NA NA NA -999 -999 NA "MD" "LD" -21.8541 165.7561 "RE" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA1" 5 13.1 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090007" "SVR" NA NA NA NA 1 9 10 2009 NA NA NA -999 -999 NA "MD" "LD" -21.8525 165.7604 "RE" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG3" 5 10.9 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090011" "SVR" NA NA NA NA 1 12 10 2009 NA NA NA -999 -999 NA "MM" "DQ" -21.84865 165.7761 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA1" -999 4 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090012" "SVR" NA NA NA NA 1 16 10 2009 NA NA NA -999 -999 NA "MM" "DC" -21.84753 165.77857 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA1" -999 4.2 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090014" "SVR" NA NA NA NA 1 5 10 2009 NA NA NA -999 -999 NA "MD" "LD" -21.8661 165.7363 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA3" 7 4.5 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090015" "SVR" NA NA NA NA 1 5 10 2009 NA NA NA -999 -999 NA "MD" "LD" -21.8656 165.7404 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Herbier" "Fond lagonaire" "SG2" 9 4 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090017" "SVR" NA NA NA NA 1 8 10 2009 NA NA NA -999 -999 NA "MD" "LD" -21.8605 165.74974 "RE" "AP" "" "" "Fond lagonaire" "Fond lagonaire" "SA1" -999 9.2 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090018" "SVR" NA NA NA NA 1 5 10 2009 NA NA NA -999 -999 NA "MD" "LD" -21.8583 165.7545 "RE" "AP" "Ile lagonaire" "lagon profond" "Detritique" "Fond lagonaire" "D2" 5 19 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090019" "SVR" NA NA NA NA 1 9 10 2009 NA NA NA -999 -999 NA "MD" "LD" -21.858 165.7594 "RE" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA2" 5 12.6 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU09001B" "SVR" NA NA NA NA 1 7 10 2009 NA NA NA -999 -999 NA "MD" "LD" -21.8622 165.7319 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Recif barriere interne" NA 6 2.4 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090020" "SVR" NA NA NA NA 1 9 10 2009 NA NA NA -999 -999 NA "MD" "LD" -21.85641 165.76408 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SG4" -999 10.4 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090021" "SVR" NA NA NA NA 1 12 10 2009 NA NA NA -999 -999 NA "MM" "DQ" -21.85445 165.76906 "RE" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" NA -999 7 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090022" "SVR" NA NA NA NA 1 12 10 2009 NA NA NA -999 -999 NA "MM" "DQ" -21.85304 165.77333 "RE" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG3" -999 6 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090023" "SVR" NA NA NA NA 1 16 10 2009 NA NA NA -999 -999 NA "MM" "DC" -21.8517 165.7781 "RE" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG1" 7 4.8 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090024" "SVR" NA NA NA NA 1 16 10 2009 NA NA NA -999 -999 NA "MM" "DC" -21.85 165.7827 "RE" "AP" "Recif frangeant protege de lagons" "platier recifal" "Corail vivant" "Frangeant cotier" "LC4" 5 2.6 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090025" "SVR" NA NA NA NA 1 7 10 2009 NA NA NA -999 -999 NA "MD" "LD" -21.8804 165.7526 "RE" "AP" "Complexe de recif barriere externe" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA5" 10 4.9 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090026" "SVR" NA NA NA NA 1 8 10 2009 NA NA NA -999 -999 NA "MM" "LD" -21.87 165.739 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA3" 10 4.9 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090027" "SVR" NA NA NA NA 1 7 10 2009 NA NA NA -999 -999 NA "MM" "LD" -21.8684 165.7435 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" 12 6.1 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090028" "SVR" NA NA NA NA 1 7 10 2009 NA NA NA -999 -999 NA "MM" "LD" -21.8687 165.7463 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" 12 8 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090029" "SVR" NA NA NA NA 1 7 10 2009 NA NA NA -999 -999 NA "MM" "LD" -21.86515 165.753 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" -999 9 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090030" "SVR" NA NA NA NA 1 9 10 2009 NA NA NA -999 -999 NA "MD" "LD" -21.8634 165.7576 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA1" 6 15.6 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090032" "SVR" NA NA NA NA 1 14 10 2009 NA NA NA -999 -999 NA "MM" "DC" -21.85984 165.76756 "RE" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG3" -999 10 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090033" "SVR" NA NA NA NA 1 16 10 2009 NA NA NA -999 -999 NA "MM" "DC" -21.85999 165.79113 "RE" "AP" "Recif frangeant protege de lagons" "platier recifal" "Herbier" "Frangeant cotier" "SG2" -999 7.2 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090034" "SVR" NA NA NA NA 1 16 10 2009 NA NA NA -999 -999 NA "MM" "DC" -21.8548 165.782 "RE" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG2" 7 5.3 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090035" "SVR" NA NA NA NA 1 7 10 2009 NA NA NA -999 -999 NA "MM" "LD" -21.8727 165.7469 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Fond lagonaire" "D2" 15 4 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090036" "SVR" NA NA NA NA 1 7 10 2009 NA NA NA -999 -999 NA "MM" "LD" -21.86869 165.74959 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" -999 8.4 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090037" "SVR" NA NA NA NA 1 7 10 2009 NA NA NA -999 -999 NA "MM" "LD" -21.87112 165.75408 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" -999 7 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090039" "SVR" NA NA NA NA 1 9 10 2009 NA NA NA -999 -999 NA "MD" "LD" -21.8659 165.7652 "RE" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA2" 5 10.8 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU09003B" "SVR" NA NA NA NA 1 9 10 2009 NA NA NA -999 -999 NA "MD" "LD" -21.8576 165.744 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Algueraie" "Recif barriere interne" "MA2" 8 14.6 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090040" "SVR" NA NA NA NA 1 16 10 2009 NA NA NA -999 -999 NA "MM" "DC" -21.8612 165.77875 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Herbier" "Frangeant ilot" "SG2" -999 6.6 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090041" "SVR" NA NA NA NA 1 16 10 2009 NA NA NA -999 -999 NA "MM" "DC" -21.85925 165.78347 "RE" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG3" -999 6 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090042" "SVR" NA NA NA NA 1 7 10 2009 NA NA NA -999 -999 NA "MD" "LD" -21.8769 165.7528 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA3" 11 6.8 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090046" "SVR" NA NA NA NA 1 14 10 2009 NA NA NA -999 -999 NA "MM" "DC" -21.8682 165.7695 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Corail vivant" "Frangeant ilot" "LC4" 7 4.5 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090047" "SVR" NA NA NA NA 1 12 10 2009 NA NA NA -999 -999 NA "MD" "DQ" -21.862 165.7866 "RE" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG1" 5 8 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090048" "SVR" NA NA NA NA 1 7 10 2009 NA NA NA -999 -999 NA "MD" "LD" -21.87798 165.75768 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" -999 7.4 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090051" "SVR" NA NA NA NA 1 15 10 2009 NA NA NA -999 -999 NA "MM" "DC" -21.86668 165.78416 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "SA1" -999 1.5 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090052" "SVR" NA NA NA NA 1 15 10 2009 NA NA NA -999 -999 NA "MM" "DC" -21.8652 165.7878 "RE" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG2" 5 6.2 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090053" "SVR" NA NA NA NA 1 16 10 2009 NA NA NA -999 -999 NA "MD" "DC" -21.8634 165.7918 "RE" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG1" 8 5.7 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090054" "SVR" NA NA NA NA 1 7 10 2009 NA NA NA -999 -999 NA "MD" "LD" -21.88312 165.76055 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA1" -999 6.1 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090058" "SVR" NA NA NA NA 1 15 10 2009 NA NA NA -999 -999 NA "MM" "DC" -21.8719 165.7846 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Algueraie" "Frangeant ilot" NA 8 2 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090059" "SVR" NA NA NA NA 1 15 10 2009 NA NA NA -999 -999 NA "MM" "DC" -21.8687 165.7905 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Algueraie" "Frangeant ilot" "MA2" 6 6.3 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU09005B" "SVR" NA NA NA NA 1 9 10 2009 NA NA NA -999 -999 NA "MD" "LD" -21.856 165.7481 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Algueraie" "Fond lagonaire" "MA1" 7 13.9 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090060" "SVR" NA NA NA NA 1 16 10 2009 NA NA NA -999 -999 NA "MD" "DC" -21.8669 165.7949 "RE" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG1" 7 6.3 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090061" "SVR" NA NA NA NA 1 7 10 2009 NA NA NA -999 -999 NA "MD" "LD" -21.887 165.7616 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA5" 11 5.2 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090065" "SVR" NA NA NA NA 1 14 10 2009 NA NA NA -999 -999 NA "MM" "DC" -21.8771 165.7842 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Frangeant ilot" "D5" 5 5 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090066" "SVR" NA NA NA NA 1 16 10 2009 NA NA NA -999 -999 NA "MD" "DC" -21.8706 165.7986 "RE" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG2" 7 6.4 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090067" "SVR" NA NA NA NA 1 16 10 2009 NA NA NA -999 -999 NA "MD" "DC" -21.8685 165.8028 "RE" "AP" "" "" "Algueraie" "Fond lagonaire" "MA3" 6 7.1 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090068" "SVR" NA NA NA NA 1 16 10 2009 NA NA NA -999 -999 NA "MD" "DC" -21.8669 165.8065 "RE" "AP" "Ile lagonaire" "lagon profond" "Corail vivant" "Frangeant cotier" "LC2" 5 3.4 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090075" "SVR" NA NA NA NA 1 14 10 2009 NA NA NA -999 -999 NA "MM" "DC" -21.8783 165.7915 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Algueraie" "Frangeant ilot" "MA2" 8 8 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090076" "SVR" NA NA NA NA 1 14 10 2009 NA NA NA -999 -999 NA "MM" "DC" -21.877 165.7953 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Frangeant ilot" "D5" 8 5 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090100" "SVR" NA NA NA NA 1 8 10 2009 NA NA NA -999 -999 NA "MM" "LD" -21.90436 165.77385 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "MA4" -999 5.7 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090102" "SVR" NA NA NA NA 1 6 10 2009 NA NA NA -999 -999 NA "MM" "LD" -21.8888 165.7948 "HR" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA1" 6 4 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090106" "SVR" NA NA NA NA 1 8 10 2009 NA NA NA -999 -999 NA "MM" "LD" -21.9169 165.7718 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "MA4" 10 4.1 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090108" "SVR" NA NA NA NA 1 8 10 2009 NA NA NA -999 -999 NA "MM" "LD" -21.9108 165.7854 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA3" 9 10.8 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090110" "SVR" NA NA NA NA 1 14 10 2009 NA NA NA -999 -999 NA "MD" "DC" -21.8901 165.8035 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG3" 6 7 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090111" "SVR" NA NA NA NA 1 14 10 2009 NA NA NA -999 -999 NA "MD" "DC" -21.8897 165.8101 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG3" 5 6 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090114" "SVR" NA NA NA NA 1 6 10 2009 NA NA NA -999 -999 NA "MD" "LD" -21.92025 165.78211 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA1" -999 7 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090115" "SVR" NA NA NA NA 1 8 10 2009 NA NA NA -999 -999 NA "MM" "LD" -21.92018 165.78956 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "MA3" -999 3.5 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090116" "SVR" NA NA NA NA 1 8 10 2009 NA NA NA -999 -999 NA "MM" "LD" -21.9167 165.793 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA3" 15 8.5 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090123" "SVR" NA NA NA NA 1 9 10 2009 NA NA NA -999 -999 NA "MM" "LD" -21.925 165.804 "HR" "AP" "Complexe de recif barriere externe" "platier recifal" "Detritique" "Recif barriere interne" "D5" 12 2.7 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090124" "SVR" NA NA NA NA 1 9 10 2009 NA NA NA -999 -999 NA "MM" "LD" -21.91717 165.81251 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Algueraie" "Recif barriere interne" "MA3" -999 3.3 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090129" "SVR" NA NA NA NA 1 9 10 2009 NA NA NA -999 -999 NA "MM" "LD" -21.9261 165.8249 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "MA3" 14 3.5 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090130" "SVR" NA NA NA NA 1 9 10 2009 NA NA NA -999 -999 NA "MM" "LD" -21.9203 165.82985 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Algueraie" "Recif barriere interne" "MA3" -999 7.1 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU0901BB" "SVR" NA NA NA NA 1 7 10 2009 NA NA NA -999 -999 NA "MD" "LD" -21.8608 165.735 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Fond lagonaire" "D7" 9 3.1 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU09025B" "SVR" NA NA NA NA 1 7 10 2009 NA NA NA -999 -999 NA "MD" "LD" -21.8803 165.753 "RE" "AP" "Complexe de recif barriere externe" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA4" 10 4.9 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU09026B" "SVR" NA NA NA NA 1 8 10 2009 NA NA NA -999 -999 NA "MM" "LD" -21.8718 165.7382 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA3" 9 5.2 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU09035B" "SVR" NA NA NA NA 1 7 10 2009 NA NA NA -999 -999 NA "MD" "LD" -21.8729 165.75 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Fond lagonaire" "SA5" 10 7.1 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090L11" "SVR" NA NA NA NA 1 8 10 2009 NA NA NA -999 -999 NA "MD" "LD" -21.85792 165.73427 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Recif barriere interne" NA 9 2.6 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090L12" "SVR" NA NA NA NA 1 8 10 2009 NA NA NA -999 -999 NA "PM" "LD" -21.87308 165.73536 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Recif barriere interne" "D5" 10 3 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090L13" "SVR" NA NA NA NA 1 7 10 2009 NA NA NA -999 -999 NA "MD" "LD" -21.87561 165.74072 "RE" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Recif barriere interne" "D6" 10 2.6 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090L14" "SVR" NA NA NA NA 1 7 10 2009 NA NA NA -999 -999 NA "MD" "LD" -21.87759 165.74796 "RE" "AP" "Complexe de recif barriere externe" "platier recifal" "Detritique" "Recif barriere interne" "D5" 9 3 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090L15" "SVR" NA NA NA NA 1 7 10 2009 NA NA NA -999 -999 NA "MD" "LD" -21.88033 165.75296 "RE" "AP" "Complexe de recif barriere externe" "platier recifal" "Detritique" "Recif barriere interne" "D7" 15 3 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090L16" "SVR" NA NA NA NA 1 7 10 2009 NA NA NA -999 -999 NA "MD" "LD" -21.88666 165.76004 "RE" "AP" "Complexe de recif barriere externe" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA4" 14 3.1 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090L21" "SVR" NA NA NA NA 1 15 10 2009 NA NA NA -999 -999 NA "MM" "DC" -21.86578 165.7693 "RE" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Corail vivant" "Frangeant ilot" "LC4" 5 3.7 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090L22" "SVR" NA NA NA NA 1 15 10 2009 NA NA NA -999 -999 NA "MM" "DC" -21.85952 165.77126 "RE" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Corail vivant" "Frangeant ilot" "LC3" 5 4.9 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090L23" "SVR" NA NA NA NA 1 14 10 2009 NA NA NA -999 -999 NA "MM" "DC" -21.87245 165.77192 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Frangeant ilot" "D6" 6 4 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090L24" "SVR" NA NA NA NA 1 14 10 2009 NA NA NA -999 -999 NA "MM" "DC" -21.87543 165.77895 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Frangeant ilot" NA 7 3.5 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090L25" "SVR" NA NA NA NA 1 14 10 2009 NA NA NA -999 -999 NA "MM" "DC" -21.87776 165.78798 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Frangeant ilot" "D6" 6 4 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090L26" "SVR" NA NA NA NA 1 15 10 2009 NA NA NA -999 -999 NA "MM" "DC" -21.87293 165.79482 "RE" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Fond lagonaire" "Frangeant ilot" NA 6 3.1 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090L32" "SVR" NA NA NA NA 1 12 10 2009 NA NA NA -999 -999 NA "MM" "DQ" -21.84598 165.78079 "RE" "AP" "Recif frangeant protege de lagons" "platier recifal" "Detritique" "Frangeant cotier" "D3" 4 4 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090L33" "SVR" NA NA NA NA 1 16 10 2009 NA NA NA -999 -999 NA "BM" "DC" -21.86069 165.79028 "RE" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Frangeant cotier" "MA4" 7 1.6 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090L35" "SVR" NA NA NA NA 1 16 10 2009 NA NA NA -999 -999 NA "MD" "DC" -21.86545 165.80024 "RE" "AP" "Ile lagonaire" "lagon profond" "Detritique" "Frangeant cotier" "D6" 7 2.7 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090L36" "SVR" NA NA NA NA 1 16 10 2009 NA NA NA -999 -999 NA "MD" "DC" -21.86165 165.79485 "RE" "AP" "Ile lagonaire" "lagon profond" "Corail vivant" "Frangeant cotier" NA 6 2.5 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090L41" "SVR" NA NA NA NA 1 16 10 2009 NA NA NA -999 -999 NA "PM" "DC" -21.8671 165.77921 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "SA1" 10 1.6 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090L42" "SVR" NA NA NA NA 1 16 10 2009 NA NA NA -999 -999 NA "MD" "DC" -21.86696 165.78035 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "SA1" 14 2 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090L43" "SVR" NA NA NA NA 1 16 10 2009 NA NA NA -999 -999 NA "MD" "DC" -21.86435 165.78288 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "SA1" 13 2.2 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090L44" "SVR" NA NA NA NA 1 15 10 2009 NA NA NA -999 -999 NA "MM" "DC" -21.87129 165.79201 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" NA 5 1.4 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090L45" "SVR" NA NA NA NA 1 15 10 2009 NA NA NA -999 -999 NA "MM" "DC" -21.86356 165.77521 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "SA3" 8 2.1 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090L46" "SVR" NA NA NA NA 1 16 10 2009 NA NA NA -999 -999 NA "MD" "DC" -21.86432 165.77806 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "SA1" 12 3 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090L51" "SVR" NA NA NA NA 1 6 10 2009 NA NA NA -999 -999 NA "MD" "LD" -21.90697 165.7684 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" NA 10 3 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090L52" "SVR" NA NA NA NA 1 6 10 2009 NA NA NA -999 -999 NA "MD" "LD" -21.92674 165.79121 "HR" "AP" "Complexe de recif barriere externe" "platier recifal" "Corail vivant" "Recif barriere interne" "LC4" 11 2 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090L53" "SVR" NA NA NA NA 1 5 10 2009 NA NA NA -999 -999 NA "MM" "LD" -21.84156 165.7192 "HR" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA1" 10 4 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090L54" "SVR" NA NA NA NA 1 5 10 2009 NA NA NA -999 -999 NA "MD" "LD" -21.84556 165.72466 "HR" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Detritique" "Recif barriere interne" "D5" 9 2 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090L61" "SVR" NA NA NA NA 1 16 10 2009 NA NA NA -999 -999 NA "MD" "DC" -21.8933 165.83803 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA1" 5 7 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090L71" "SVR" NA NA NA NA 1 16 10 2009 NA NA NA -999 -999 NA "MD" "DC" -21.87046 165.81256 "HR" "AP" "Ile lagonaire" "lagon profond" "Detritique" "Frangeant cotier" "D3" 4 4.5 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090L72" "SVR" NA NA NA NA 1 16 10 2009 NA NA NA -999 -999 NA "MD" "DC" -21.87547 165.82583 "HR" "AP" "Ile lagonaire" "lagon profond" "Corail vivant" "Frangeant cotier" "LC5" 6 2.3 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090L81" "SVR" NA NA NA NA 1 16 10 2009 NA NA NA -999 -999 NA "MD" "DC" -21.89455 165.82739 "HR" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA1" 6 5.6 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU090L82" "SVR" NA NA NA NA 1 6 10 2009 NA NA NA -999 -999 NA "MD" "LD" -21.90528 165.83952 "HR" "AP" "Recif frangeant protege de lagons" "platier recifal" "Detritique" "Frangeant ilot" NA 6 4 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU09103B" "SVR" NA NA NA NA 1 14 10 2009 NA NA NA -999 -999 NA "BM" "DC" -21.8795 165.8082 "HR" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA1" 5 10 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU09106B" "SVR" NA NA NA NA 1 6 10 2009 NA NA NA -999 -999 NA "MD" "LD" -21.9129 165.7707 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA3" 10 4 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU09106C" "SVR" NA NA NA NA 1 9 10 2009 NA NA NA -999 -999 NA "MM" "LD" -21.9199 165.7707 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Corail vivant" "Recif barriere interne" "LC3" 15 2.5 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU09107B" "SVR" NA NA NA NA 1 6 10 2009 NA NA NA -999 -999 NA "MD" "LD" -21.91196 165.77531 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Algueraie" "Recif barriere interne" "MA4" -999 5 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU09107C" "SVR" NA NA NA NA 1 9 10 2009 NA NA NA -999 -999 NA "MM" "LD" -21.9151 165.7803 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Algueraie" "Recif barriere interne" "MA3" 14 4.5 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU09110B" "SVR" NA NA NA NA 1 14 10 2009 NA NA NA -999 -999 NA "MD" "DC" -21.8866 165.808 "HR" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA1" 5 8 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU09110C" "SVR" NA NA NA NA 1 13 10 2009 NA NA NA -999 -999 NA "MM" "DC" -21.886 165.8138 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG1" 5 8 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU09111B" "SVR" NA NA NA NA 1 14 10 2009 NA NA NA -999 -999 NA "MD" "DC" -21.8874 165.8142 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG2" 5 6 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU09114B" "SVR" NA NA NA NA 1 6 10 2009 NA NA NA -999 -999 NA "MD" "LD" -21.9186 165.7769 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA1" 9 6 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU09123B" "SVR" NA NA NA NA 1 9 10 2009 NA NA NA -999 -999 NA "MM" "LD" -21.926 165.7977 "HR" "AP" "Complexe de recif barriere externe" "platier recifal" "Corail vivant" "Recif barriere interne" "LC3" 15 2.8 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU09124B" "SVR" NA NA NA NA 1 9 10 2009 NA NA NA -999 -999 NA "MM" "LD" -21.92088 165.79846 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "MA3" -999 3.3 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU09129B" "SVR" NA NA NA NA 1 9 10 2009 NA NA NA -999 -999 NA "MM" "LD" -21.9233 165.8124 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Corail vivant" "Recif barriere interne" "LC1" 14 2.1 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU09130B" "SVR" NA NA NA NA 1 9 10 2009 NA NA NA -999 -999 NA "MM" "LD" -21.9181 165.8207 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Algueraie" "Recif barriere interne" "MA2" 15 4.4 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU09L12R" "SVR" NA NA NA NA 1 8 10 2009 NA NA NA -999 -999 NA "PM" "LD" -21.87308 165.73507 "RE" "AP" "Complexe de recif barriere externe" "platier recifal" "Detritique" "Recif barriere interne" "D6" 12 3 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU09L14R" "SVR" NA NA NA NA 1 7 10 2009 NA NA NA -999 -999 NA "MD" "LD" -21.87774 165.74765 "RE" "AP" "Complexe de recif barriere externe" "platier recifal" "Corail vivant" "Recif barriere interne" NA 14 3 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU09L15R" "SVR" NA NA NA NA 1 7 10 2009 NA NA NA -999 -999 NA "MD" "LD" -21.88044 165.75256 "RE" "AP" "Complexe de recif barriere externe" "platier recifal" "Detritique" "Recif barriere interne" "D5" 14 2.8 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU09L16R" "SVR" NA NA NA NA 1 7 10 2009 NA NA NA -999 -999 NA "MD" "LD" -21.88691 165.75995 "RE" "AP" "Complexe de recif barriere externe" "platier recifal" "Detritique" "Recif barriere interne" "D7" 12 2.6 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU09L22R" "SVR" NA NA NA NA 1 15 10 2009 NA NA NA -999 -999 NA "MM" "DC" -21.85958 165.771 "RE" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Corail vivant" "Frangeant ilot" NA 5 3.4 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU09L23R" "SVR" NA NA NA NA 1 14 10 2009 NA NA NA -999 -999 NA "MM" "DC" -21.87258 165.77228 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Corail vivant" "Frangeant ilot" NA 8 3 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU09L24R" "SVR" NA NA NA NA 1 14 10 2009 NA NA NA -999 -999 NA "MM" "DC" -21.87532 165.77923 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Corail vivant" "Frangeant ilot" "D6" 6 3 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU09L25R" "SVR" NA NA NA NA 1 14 10 2009 NA NA NA -999 -999 NA "MM" "DC" -21.87756 165.78798 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Corail vivant" "Frangeant ilot" "LC3" 6 3 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU09L26R" "SVR" NA NA NA NA 1 15 10 2009 NA NA NA -999 -999 NA "MM" "DC" -21.873 165.7946 "RE" "AP" "" "" "Detritique" "Frangeant ilot" NA 6 2.55 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU09L32R" "SVR" NA NA NA NA 1 12 10 2009 NA NA NA -999 -999 NA "MM" "DQ" -21.84602 165.78104 "RE" "AP" "Recif frangeant protege de lagons" "platier recifal" "Detritique" "Frangeant cotier" "D3" 5 2 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU09L35R" "SVR" NA NA NA NA 1 16 10 2009 NA NA NA -999 -999 NA "MD" "DC" -21.86535 165.80022 "RE" "AP" "Ile lagonaire" "lagon profond" "Corail vivant" "Frangeant cotier" "LC2" 6 2.3 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU09L36R" "SVR" NA NA NA NA 1 16 10 2009 NA NA NA -999 -999 NA "MD" "DC" -21.86156 165.79489 "RE" "AP" "Ile lagonaire" "lagon profond" "Corail vivant" "Frangeant cotier" "LC2" 6 1.7 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU09L42B" "SVR" NA NA NA NA 1 16 10 2009 NA NA NA -999 -999 NA "MD" "DC" -21.86658 165.78067 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "SA1" 15 1.7 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU09L51R" "SVR" NA NA NA NA 1 6 10 2009 NA NA NA -999 -999 NA "MD" "LD" -21.90687 165.76763 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Recif barriere interne" "D6" 13 3 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU09L52R" "SVR" NA NA NA NA 1 6 10 2009 NA NA NA -999 -999 NA "MD" "LD" -21.92679 165.79082 "HR" "AP" "Complexe de recif barriere externe" "platier recifal" "Detritique" "Recif barriere interne" "D7" 12 2 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU09L53R" "SVR" NA NA NA NA 1 5 10 2009 NA NA NA -999 -999 NA "MM" "LD" -21.84426 165.71894 "HR" "AP" "Complexe de recif barriere cotier" "terrasse peu profonde" "Detritique" "Recif barriere interne" "D7" 7 2 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU09L54R" "SVR" NA NA NA NA 1 5 10 2009 NA NA NA -999 -999 NA "MD" "LD" -21.84662 165.72398 "HR" "AP" "Complexe de recif barriere cotier" "platier recifal" "Detritique" "Recif barriere interne" "D3" 9 2 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU09L63R" "SVR" NA NA NA NA 1 9 10 2009 NA NA NA -999 -999 NA "MD" "LD" -21.83821 165.75869 "HR" "AP" "Recif frangeant protege de lagons" "platier recifal" "Detritique" "Frangeant cotier" "D6" 4 2.4 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "OU09L71R" "SVR" NA NA NA NA 1 16 10 2009 NA NA NA -999 -999 NA "MD" "DC" -21.87044 165.81285 "HR" "AP" "Ile lagonaire" "lagon profond" "Detritique" "Frangeant cotier" "D6" 7 2.4 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "PA170001" "SVR" "Petit Astrolabe" NA "Recif barriere" NA 1 24 10 2017 "-999" NA "SE" 1 1 -999 "" "" -19.88751 165.82997 "HR" NA "Banc de recif barriere" "platier recifal" "Detritique" "Recif barriere interne" NA 20 4 -999 -999 -999 -999 "William ROMAN" +"AMP" "PA170002" "SVR" "Petit Astrolabe" NA "Recif barriere" NA 1 24 10 2017 "-999" NA "SE" 1 1 -999 "" "" -19.88601 165.82973 "HR" NA "Banc lagonaire" "terrasse profonde" "Detritique" "Recif barriere interne" NA 10 13 -999 -999 -999 -999 "William ROMAN" +"AMP" "PA170003" "SVR" "Petit Astrolabe" NA "Recif barriere" NA 1 24 10 2017 "-999" NA "SE" 1 1 -999 "" "" -19.89347 165.82173 "HR" NA "Banc de recif barriere" "platier recifal" "Detritique" "Recif barriere interne" NA 15 8 -999 -999 -999 -999 "William ROMAN" +"AMP" "PA170004" "SVR" "Petit Astrolabe" NA "Recif barriere" NA 1 24 10 2017 "-999" NA "SE" 1 1 -999 "" "" -19.8937 165.82069 "HR" NA "Banc de recif barriere" "platier recifal" "Detritique" "Recif barriere interne" NA 15 14 -999 -999 -999 -999 "William ROMAN" +"AMP" "PA170005" "SVR" "Petit Astrolabe" NA "Recif barriere" NA 1 24 10 2017 "-999" NA "SE" 1 1 -999 "" "" -19.89865 165.8181 "HR" NA "" "" "Detritique" "Recif barriere externe" NA 25 8 -999 -999 -999 -999 "William ROMAN" +"AMP" "PA170006" "SVR" "Petit Astrolabe" NA "Recif barriere" NA 1 24 10 2017 "-999" NA "SE" 1 1 -999 "" "" -19.89894 165.82004 "HR" NA "Banc de recif barriere" "front recifal" "Detritique" "Recif barriere externe" NA 25 10 -999 -999 -999 -999 "William ROMAN" +"AMP" "PA170007" "SVR" "Petit Astrolabe" NA "Recif barriere" NA 1 24 10 2017 "-999" NA "SE" 1 1 -999 "" "" -19.89048 165.83542 "HR" NA "Banc de recif barriere" "front recifal" "Detritique" "Recif barriere externe" NA 25 10 -999 -999 -999 -999 "William ROMAN" +"AMP" "PA170008" "SVR" "Petit Astrolabe" NA "Recif barriere" NA 1 24 10 2017 "-999" NA "SE" 1 1 -999 "" "" -19.88876 165.8378 "HR" NA "Banc de recif barriere" "front recifal" "Detritique" "Recif barriere externe" NA 25 8 -999 -999 -999 -999 "William ROMAN" +"AMP" "PA170009" "SVR" "Petit Astrolabe" NA "Recif barriere" NA 1 24 10 2017 "-999" NA "SE" 1 1 -999 "" "" -19.88209 165.84204 "HR" NA "Banc de recif barriere" "front recifal" "Detritique" "Recif barriere externe" NA 25 10 -999 -999 -999 -999 "William ROMAN" +"AMP" "PA170010" "SVR" "Petit Astrolabe" NA "Recif barriere" NA 1 24 10 2017 "-999" NA "SE" 1 1 -999 "" "" -19.87955 165.84262 "HR" NA "" "" "Detritique" "Recif barriere externe" NA 25 9 -999 -999 -999 -999 "William ROMAN" +"AMP" "PA170011" "SVR" "Petit Astrolabe" NA "Recif barriere" NA 1 24 10 2017 "-999" NA "SE" 1 1 -999 "" "" -19.87085 165.84216 "HR" NA "Banc de recif barriere" "front recifal" "Detritique" "Recif barriere externe" NA 25 10 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "PA170012" "SVR" "Petit Astrolabe" NA "Recif barriere" NA 1 24 10 2017 "-999" NA "SE" 1 1 -999 "" "" -19.86734 165.84329 "HR" NA "Banc de recif barriere" "front recifal" "Corail vivant" "Recif barriere externe" NA 25 10 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "PA170013" "SVR" "Petit Astrolabe" NA "Recif barriere" NA 1 24 10 2017 "-999" NA "SE" 1 1 -999 "" "" -19.85999 165.84601 "HR" NA "Banc de recif barriere" "front recifal" "Detritique" "Recif barriere externe" NA 25 8 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "PA170014" "SVR" "Petit Astrolabe" NA "Recif barriere" NA 1 24 10 2017 "-999" NA "SE" 1 1 -999 "" "" -19.8574 165.8475 "HR" NA "Banc de recif barriere" "front recifal" "Detritique" "Recif barriere externe" NA 25 10 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "PA170015" "SVR" "Petit Astrolabe" NA "Recif barriere" NA 1 24 10 2017 "-999" NA "SE" 1 1 -999 "" "" -19.85218 165.84993 "HR" NA "Banc de recif barriere" "front recifal" "Detritique" "Recif barriere externe" NA 20 9 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "PA170016" "SVR" "Petit Astrolabe" NA "Recif barriere" NA 1 24 10 2017 "-999" NA "SE" 1 1 -999 "" "" -19.84983 165.85133 "HR" NA "Banc de recif barriere" "front recifal" "Detritique" "Recif barriere externe" NA 20 10 -999 -999 -999 -999 "William ROMAN" +"AMP" "PA170017" "SVR" "Petit Astrolabe" NA "Recif barriere" NA 1 24 10 2017 "-999" NA "SE" 1 1 -999 "" "" -19.8473 165.85287 "HR" NA "Banc de recif barriere" "front recifal" "Detritique" "Recif barriere externe" NA 20 9 -999 -999 -999 -999 "William ROMAN" +"AMP" "PA170018" "SVR" "Petit Astrolabe" NA "Recif barriere" NA 1 24 10 2017 "-999" NA "SE" 1 1 -999 "" "" -19.84512 165.85345 "HR" NA "Banc de recif barriere" "front recifal" "Detritique" "Recif barriere externe" NA 20 10 -999 -999 -999 -999 "William ROMAN" +"AMP" "PA170019" "SVR" "Petit Astrolabe" NA "Recif barriere" NA 1 24 10 2017 "-999" NA "SE" 1 1 -999 "" "" -19.8423 165.8528 "HR" NA "Banc de recif barriere" "front recifal" "Detritique" "Recif barriere externe" NA 25 9 -999 -999 -999 -999 "William ROMAN" +"AMP" "PA170020" "SVR" "Petit Astrolabe" NA "Recif barriere" NA 1 24 10 2017 "-999" NA "SE" 1 1 -999 "" "" -19.84059 165.85187 "HR" NA "Banc de recif barriere" "front recifal" "Detritique" "Recif barriere externe" NA 20 10 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "PA170021" "SVR" "Petit Astrolabe" NA "Recif barriere" NA 1 24 10 2017 "-999" NA "SE" 1 1 -999 "" "" -19.83794 165.84706 "HR" NA "Banc de recif barriere" "front recifal" "Detritique" "Recif barriere externe" NA 20 9 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "PA170022" "SVR" "Petit Astrolabe" NA "Recif barriere" NA 1 24 10 2017 "-999" NA "SE" 1 1 -999 "" "" -19.8382 165.8441 "HR" NA "Banc de recif barriere" "front recifal" "Corail vivant" "Recif barriere externe" NA 20 9 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "PA170023" "SVR" "Petit Astrolabe" NA "Recif barriere" NA 1 24 10 2017 "-999" NA "SE" 1 1 -999 "" "" -19.84281 165.84349 "HR" NA "Banc lagonaire" "terrasse profonde" "Detritique" "Recif barriere interne" NA 15 7 -999 -999 -999 -999 "William ROMAN" +"AMP" "PA170024" "SVR" "Petit Astrolabe" NA "Recif barriere" NA 1 24 10 2017 "-999" NA "SE" 1 1 -999 "" "" -19.84345 165.8441 "HR" NA "Banc lagonaire" "terrasse profonde" "Detritique" "Recif barriere interne" NA 10 7 -999 -999 -999 -999 "William ROMAN" +"AMP" "PA170025" "SVR" "Petit Astrolabe" NA "Recif barriere" NA 1 24 10 2017 "-999" NA "SE" 1 1 -999 "" "" -19.85391 165.84311 "HR" NA "Banc lagonaire" "terrasse profonde" "Fond lagonaire" "Recif barriere interne" NA 15 10 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "PA170026" "SVR" "Petit Astrolabe" NA "Recif barriere" NA 1 24 10 2017 "-999" NA "SE" 1 1 -999 "" "" -19.85608 165.84222 "HR" NA "Banc de recif barriere" "platier recifal" "Detritique" "Recif barriere interne" NA 15 9 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "PA170027" "SVR" "Petit Astrolabe" NA "Recif barriere" NA 1 24 10 2017 "-999" NA "SE" 1 1 -999 "" "" -19.86515 165.83931 "HR" NA "Banc de recif barriere" "platier recifal" "Detritique" "Recif barriere interne" NA 20 9 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "PA170028" "SVR" "Petit Astrolabe" NA "Recif barriere" NA 1 24 10 2017 "-999" NA "SE" 1 1 -999 "" "" -19.86729 165.83829 "HR" NA "Banc de recif barriere" "platier recifal" "Detritique" "Recif barriere interne" NA 15 9 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "PA170029" "SVR" "Petit Astrolabe" NA "Recif barriere" NA 1 24 10 2017 "-999" NA "SE" 1 1 -999 "" "" -19.87084 165.83734 "HR" NA "Banc de recif barriere" "platier recifal" "Detritique" "Recif barriere interne" NA 15 9 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "PA170030" "SVR" "Petit Astrolabe" NA "Recif barriere" NA 1 24 10 2017 "-999" NA "SE" 1 1 -999 "" "" -19.87251 165.83711 "HR" NA "Banc de recif barriere" "platier recifal" "Fond lagonaire" "Recif barriere interne" NA 15 9 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "PA170031" "SVR" "Petit Astrolabe" NA "Recif barriere" NA 1 24 10 2017 "-999" NA "SE" 1 1 -999 "" "" -19.87629 165.83662 "HR" NA "Banc de recif barriere" "platier recifal" "Detritique" "Recif barriere interne" NA 15 10 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "PA170032" "SVR" "Petit Astrolabe" NA "Recif barriere" NA 1 24 10 2017 "-999" NA "SE" 1 1 -999 "" "" -19.87842 165.83598 "HR" NA "Banc de recif barriere" "platier recifal" "Detritique" "Recif barriere interne" NA 15 9 -999 -999 -999 -999 "William ROMAN" +"AMP" "PA170033" "SVR" "Grand Astrolabe" NA "Recif barriere" NA 1 25 10 2017 "-999" NA "SE" 4 3 -999 "" "" -19.86798 165.56624 "HR" NA "Banc lagonaire" "terrasse lagonaire peu profonde" "Fond lagonaire" "Recif barriere interne" NA 12 11 -999 -999 -999 -999 "William ROMAN" +"AMP" "PA170034" "SVR" "Grand Astrolabe" NA "Recif barriere" NA 1 25 10 2017 "-999" NA "SE" 4 3 -999 "" "" -19.86951 165.5611 "HR" NA "Banc de recif barriere" "platier recifal" "Fond lagonaire" "Recif barriere interne" NA 12 10 -999 -999 -999 -999 "William ROMAN" +"AMP" "PA170035" "SVR" "Grand Astrolabe" NA "Recif barriere" NA 1 25 10 2017 "-999" NA "SE" 4 3 -999 "" "" -19.87766 165.54092 "HR" NA "Banc de recif barriere" "platier recifal" "Detritique" "Recif barriere interne" NA 15 10 -999 -999 -999 -999 "William ROMAN" +"AMP" "PA170036" "SVR" "Grand Astrolabe" NA "Recif barriere" NA 1 25 10 2017 "-999" NA "SE" 4 3 -999 "" "" -19.87711 165.53545 "HR" NA "Banc de recif barriere" "platier recifal" "Fond lagonaire" "Recif barriere interne" NA 15 10 -999 -999 -999 -999 "William ROMAN" +"AMP" "PA170037" "SVR" "Grand Astrolabe" NA "Recif barriere" NA 1 25 10 2017 "-999" NA "SE" 4 3 -999 "" "" -19.87715 165.52028 "HR" NA "Banc de recif barriere" "platier recifal" "Detritique" "Recif barriere interne" NA 15 8 -999 -999 -999 -999 "William ROMAN" +"AMP" "PA170038" "SVR" "Grand Astrolabe" NA "Recif barriere" NA 1 25 10 2017 "-999" NA "SE" 4 3 -999 "" "" -19.88206 165.51717 "HR" NA "" "" "Detritique" "Recif barriere externe" NA 20 8 -999 -999 -999 -999 "William ROMAN" +"AMP" "PA170039" "SVR" "Grand Astrolabe" NA "Recif barriere" NA 1 25 10 2017 "-999" NA "SE" 4 3 -999 "" "" -19.88213 165.52187 "HR" NA "Banc de recif barriere" "front recifal" "Detritique" "Recif barriere externe" NA 15 4 -999 -999 -999 -999 "William ROMAN" +"AMP" "PA170040" "SVR" "Grand Astrolabe" NA "Recif barriere" NA 1 25 10 2017 "-999" NA "SE" 4 3 -999 "" "" -19.88391 165.52676 "HR" NA "" "" "Detritique" "Recif barriere externe" NA 20 7 -999 -999 -999 -999 "William ROMAN" +"AMP" "PA170041" "SVR" "Grand Astrolabe" NA "Recif barriere" NA 1 25 10 2017 "-999" NA "SE" 4 3 -999 "" "" -19.88273 165.52951 "HR" NA "Banc de recif barriere" "front recifal" "Detritique" "Recif barriere externe" NA 20 11 -999 -999 -999 -999 "William ROMAN" +"AMP" "PA170042" "SVR" "Grand Astrolabe" NA "Recif barriere" NA 1 25 10 2017 "-999" NA "SE" 4 3 -999 "" "" -19.87892 165.54849 "HR" NA "Banc de recif barriere" "front recifal" "Corail vivant" "Recif barriere externe" NA 20 8 -999 -999 -999 -999 "William ROMAN" +"AMP" "PA170043" "SVR" "Grand Astrolabe" NA "Recif barriere" NA 1 25 10 2017 "-999" NA "SE" 4 3 -999 "" "" -19.87741 165.55174 "HR" NA "Banc de recif barriere" "front recifal" "Corail vivant" "Recif barriere externe" NA 15 5 -999 -999 -999 -999 "William ROMAN" +"AMP" "PA170044" "SVR" "Grand Astrolabe" NA "Recif barriere" NA 1 25 10 2017 "-999" NA "SE" 4 3 -999 "" "" -19.81197 165.60086 "HR" NA "Banc lagonaire" "terrasse lagonaire peu profonde" "Fond lagonaire" "Recif barriere interne" NA 15 8 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "PA170045" "SVR" "Grand Astrolabe" NA "Recif barriere" NA 1 25 10 2017 "-999" NA "SE" 4 3 -999 "" "" -19.80709 165.60333 "HR" NA "Banc lagonaire" "terrasse lagonaire peu profonde" "Fond lagonaire" "Recif barriere interne" NA 15 8 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "PA170046" "SVR" "Grand Astrolabe" NA "Recif barriere" NA 1 25 10 2017 "-999" NA "SE" 4 3 -999 "" "" -19.79282 165.60866 "HR" NA "Banc de recif barriere" "platier recifal" "Detritique" "Recif barriere interne" NA 15 8 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "PA170047" "SVR" "Grand Astrolabe" NA "Recif barriere" NA 1 25 10 2017 "-999" NA "SE" 4 3 -999 "" "" -19.78874 165.6064 "HR" NA "Banc de recif barriere" "platier recifal" "Detritique" "Recif barriere interne" NA 15 9 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "PA170048" "SVR" "Grand Astrolabe" NA "Recif barriere" NA 1 25 10 2017 "-999" NA "SE" 4 3 -999 "" "" -19.7855 165.60542 "HR" NA "Banc de recif barriere" "platier recifal" "Detritique" "Recif barriere interne" NA 12 11 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "PA170049" "SVR" "Grand Astrolabe" NA "Recif barriere" NA 1 25 10 2017 "-999" NA "SE" 4 3 -999 "" "" -19.78441 165.60532 "HR" NA "Banc de recif barriere" "platier recifal" "Detritique" "Recif barriere interne" NA 15 8 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "PA170050" "SVR" "Grand Astrolabe" NA "Recif barriere" NA 1 25 10 2017 "-999" NA "SE" 4 3 -999 "" "" -19.78427 165.61037 "HR" NA "Banc de recif barriere" "front recifal" "Detritique" "Recif barriere externe" NA 20 8 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "PA170051" "SVR" "Grand Astrolabe" NA "Recif barriere" NA 1 25 10 2017 "-999" NA "SE" 4 3 -999 "" "" -19.78623 165.61089 "HR" NA "Banc de recif barriere" "front recifal" "Detritique" "Recif barriere externe" NA 20 10 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "PA170052" "SVR" "Grand Astrolabe" NA "Recif barriere" NA 1 25 10 2017 "-999" NA "SE" 4 3 -999 "" "" -19.80139 165.61696 "HR" NA "Banc de recif barriere" "front recifal" "Detritique" "Recif barriere externe" NA 20 8 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "PA170053" "SVR" "Grand Astrolabe" NA "Recif barriere" NA 1 25 10 2017 "-999" NA "SE" 4 3 -999 "" "" -19.80479 165.61414 "HR" NA "" "" "Corail vivant" "Recif barriere externe" NA 20 9 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "PA170054" "SVR" "Grand Astrolabe" NA "Recif barriere" NA 1 25 10 2017 "-999" NA "SE" 4 3 -999 "" "" -19.81265 165.60548 "HR" NA "" "" "Detritique" "Recif barriere externe" NA 20 8 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "PA170055" "SVR" "Grand Astrolabe" NA "Recif barriere" NA 1 25 10 2017 "-999" NA "SE" 4 3 -999 "" "" -19.81589 165.60387 "HR" NA "" "" "Detritique" "Recif barriere externe" NA 20 8 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "PA170056" "SVR" "Grand Astrolabe" NA "Recif barriere" NA 1 25 10 2017 "-999" NA "SE" 4 3 -999 "" "" -19.71637 165.60023 "HR" NA "Banc de recif barriere" "front recifal" "Corail vivant" "Recif barriere externe" NA 20 9 -999 -999 -999 -999 "William ROMAN" +"AMP" "PA170057" "SVR" "Grand Astrolabe" NA "Recif barriere" NA 1 25 10 2017 "-999" NA "SE" 4 3 -999 "" "" -19.71972 165.5999 "HR" NA "Banc de recif barriere" "front recifal" "Detritique" "Recif barriere externe" NA 20 10 -999 -999 -999 -999 "William ROMAN" +"AMP" "PA170058" "SVR" "Grand Astrolabe" NA "Recif barriere" NA 1 25 10 2017 "-999" NA "SE" 4 3 -999 "" "" -19.70377 165.5999 "HR" NA "Banc de recif barriere" "front recifal" "Detritique" "Recif barriere externe" NA 20 11 -999 -999 -999 -999 "William ROMAN" +"AMP" "PA170059" "SVR" "Grand Astrolabe" NA "Recif barriere" NA 1 25 10 2017 "-999" NA "SE" 4 3 -999 "" "" -19.70456 165.59705 "HR" NA "Banc de recif barriere" "platier recifal" "Detritique" "Recif barriere interne" NA 15 5 -999 -999 -999 -999 "William ROMAN" +"AMP" "PA170060" "SVR" "Grand Astrolabe" NA "Recif barriere" NA 1 25 10 2017 "-999" NA "SE" 4 3 -999 "" "" -19.70548 165.59251 "HR" NA "Banc de recif barriere" "platier recifal" "Corail vivant" "Recif barriere interne" NA 15 7 -999 -999 -999 -999 "William ROMAN" +"AMP" "PA170061" "SVR" "Grand Astrolabe" NA "Recif barriere" NA 1 25 10 2017 "-999" NA "SE" 4 3 -999 "" "" -19.70786 165.59178 "HR" NA "Banc de recif barriere" "platier recifal" "Detritique" "Recif barriere interne" NA 10 7 -999 -999 -999 -999 "William ROMAN" +"AMP" "PA170062" "SVR" "Grand Astrolabe" NA "Recif barriere" NA 1 25 10 2017 "-999" NA "SE" 4 3 -999 "" "" -19.70833 165.59409 "HR" NA "Banc de recif barriere" "platier recifal" "Detritique" "Recif barriere interne" NA 10 6 -999 -999 -999 -999 "William ROMAN" +"AMP" "PA170063" "SVR" "Grand Astrolabe" NA "Recif barriere" NA 1 25 10 2017 "-999" NA "SE" 4 3 -999 "" "" -19.71869 165.59323 "HR" NA "Banc lagonaire" "terrasse lagonaire peu profonde" "Detritique" "Recif barriere interne" NA 12 11 -999 -999 -999 -999 "William ROMAN" +"AMP" "PA170064" "SVR" "Grand Astrolabe" NA "Recif barriere" NA 1 25 10 2017 "-999" NA "SE" 4 3 -999 "" "" -19.72004 165.59401 "HR" NA "Banc lagonaire" "terrasse lagonaire peu profonde" "Fond lagonaire" "Recif barriere interne" NA 15 8 -999 -999 -999 -999 "William ROMAN" +"AMP" "PA170065" "SVR" "Grand Astrolabe" NA "Recif barriere" NA 1 25 10 2017 "-999" NA "SE" 4 3 -999 "" "" -19.72276 165.595 "HR" NA "Banc de recif barriere" "platier recifal" "Detritique" "Recif barriere interne" NA 12 8 -999 -999 -999 -999 "William ROMAN" +"AMP" "PA170066" "SVR" "Grand Astrolabe" NA "Recif barriere" NA 1 25 10 2017 "-999" NA "SE" 4 3 -999 "" "" -19.72448 165.59448 "HR" NA "Banc de recif barriere" "platier recifal" "Detritique" "Recif barriere interne" NA 12 8 -999 -999 -999 -999 "William ROMAN" +"AMP" "PA170067" "SVR" "Petrie" NA "Recif barriere" NA 1 26 10 2017 "-999" NA "SE" 4 3 -999 "" "" -18.5679 164.43765 "HR" NA "Banc lagonaire" "terrasse lagonaire peu profonde" "Fond lagonaire" "Recif barriere interne" NA 15 9 -999 -999 -999 -999 "William ROMAN" +"AMP" "PA170068" "SVR" "Petrie" NA "Recif barriere" NA 1 26 10 2017 "-999" NA "SE" 4 3 -999 "" "" -18.57205 164.43831 "HR" NA "Banc de recif barriere" "platier recifal" "Detritique" "Recif barriere interne" NA 15 10 -999 -999 -999 -999 "William ROMAN" +"AMP" "PA170069" "SVR" "Petrie" NA "Recif barriere" NA 1 26 10 2017 "-999" NA "SE" 4 3 -999 "" "" -18.59092 164.44244 "HR" NA "Banc de recif barriere" "platier recifal" "Detritique" "Recif barriere interne" NA 13 5 -999 -999 -999 -999 "William ROMAN" +"AMP" "PA170070" "SVR" "Petrie" NA "Recif barriere" NA 1 26 10 2017 "-999" NA "SE" 4 3 -999 "" "" -18.59393 164.44151 "HR" NA "Banc lagonaire" "terrasse lagonaire peu profonde" "Detritique" "Recif barriere interne" NA 15 7 -999 -999 -999 -999 "William ROMAN" +"AMP" "PA170071" "SVR" "Petrie" NA "Recif barriere" NA 1 26 10 2017 "-999" NA "SE" 4 3 -999 "" "" -18.59827 164.43857 "HR" NA "Banc de recif barriere" "platier recifal" "Fond lagonaire" "Recif barriere interne" NA 15 6 -999 -999 -999 -999 "William ROMAN" +"AMP" "PA170072" "SVR" "Petrie" NA "Recif barriere" NA 1 26 10 2017 "-999" NA "SE" 4 3 -999 "" "" -18.60133 164.43521 "HR" NA "Banc de recif barriere" "platier recifal" "Detritique" "Recif barriere interne" NA 12 6 -999 -999 -999 -999 "William ROMAN" +"AMP" "PA170073" "SVR" "Petrie" NA "Recif barriere" NA 1 26 10 2017 "-999" NA "SE" 4 3 -999 "" "" -18.60032 164.44501 "HR" NA "Banc de recif barriere" "front recifal" "Detritique" "Recif barriere externe" NA 20 10 -999 -999 -999 -999 "William ROMAN" +"AMP" "PA170074" "SVR" "Petrie" NA "Recif barriere" NA 1 26 10 2017 "-999" NA "SE" 4 3 -999 "" "" -18.59708 164.4463 "HR" NA "Banc de recif barriere" "front recifal" "Detritique" "Recif barriere externe" NA 18 10 -999 -999 -999 -999 "William ROMAN" +"AMP" "PA170075" "SVR" "Petrie" NA "Recif barriere" NA 1 26 10 2017 "-999" NA "SE" 4 3 -999 "" "" -18.58357 164.44724 "HR" NA "Banc de recif barriere" "front recifal" "Detritique" "Recif barriere externe" NA 20 11 -999 -999 -999 -999 "William ROMAN" +"AMP" "PA170076" "SVR" "Petrie" NA "Recif barriere" NA 1 26 10 2017 "-999" NA "SE" 4 3 -999 "" "" -18.58064 164.44795 "HR" NA "" "" "Detritique" "Recif barriere externe" NA 20 10 -999 -999 -999 -999 "William ROMAN" +"AMP" "PA170077" "SVR" "Petrie" NA "Recif barriere" NA 1 26 10 2017 "-999" NA "SE" 4 3 -999 "" "" -18.568 164.44409 "HR" NA "Banc de recif barriere" "front recifal" "Detritique" "Recif barriere externe" NA 18 10 -999 -999 -999 -999 "William ROMAN" +"AMP" "PA170078" "SVR" "Petrie" NA "Recif barriere" NA 1 26 10 2017 "-999" NA "SE" 4 3 -999 "" "" -18.56576 164.44371 "HR" NA "Banc de recif barriere" "front recifal" "Detritique" "Recif barriere externe" NA 18 11 -999 -999 -999 -999 "William ROMAN" +"AMP" "PA170079" "SVR" "Petrie" NA "Recif barriere" NA 1 26 10 2017 "-999" NA "SE" 4 3 -999 "" "" -18.51098 164.43515 "HR" NA "" "" "Detritique" "Recif barriere externe" NA 20 9 -999 -999 -999 -999 "William ROMAN" +"AMP" "PA170080" "SVR" "Petrie" NA "Recif barriere" NA 1 26 10 2017 "-999" NA "SE" 4 3 -999 "" "" -18.50859 164.43065 "HR" NA "Banc de recif barriere" "front recifal" "Corail vivant" "Recif barriere externe" NA 20 8 -999 -999 -999 -999 "William ROMAN" +"AMP" "PA170081" "SVR" "Petrie" NA "Recif barriere" NA 1 26 10 2017 "-999" NA "SE" 4 3 -999 "" "" -18.49306 164.41653 "HR" NA "Banc de recif barriere" "front recifal" "Corail vivant" "Recif barriere externe" NA 20 10 -999 -999 -999 -999 "William ROMAN" +"AMP" "PA170082" "SVR" "Petrie" NA "Recif barriere" NA 1 26 10 2017 "-999" NA "SE" 4 3 -999 "" "" -18.48571 164.4164 "HR" NA "Banc de recif barriere" "front recifal" "Detritique" "Recif barriere externe" NA 17 10 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "PA170083" "SVR" "Petrie" NA "Recif barriere" NA 1 26 10 2017 "-999" NA "SE" 4 3 -999 "" "" -18.48172 164.40729 "HR" NA "" "" "Corail vivant" "Recif barriere externe" NA 17 11 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "PA170084" "SVR" "Petrie" NA "Recif barriere" NA 1 26 10 2017 "-999" NA "SE" 4 3 -999 "" "" -18.48449 164.40434 "HR" NA "" "" "Corail vivant" "Recif barriere externe" NA 19 9 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "PA170085" "SVR" "Petrie" NA "Recif barriere" NA 1 26 10 2017 "-999" NA "SE" 4 3 -999 "" "" -18.49954 164.41342 "HR" NA "Banc de recif barriere" "platier recifal" "Detritique" "Recif barriere interne" NA 12 10 -999 -999 -999 -999 "William ROMAN" +"AMP" "PA170086" "SVR" "Petrie" NA "Recif barriere" NA 1 26 10 2017 "-999" NA "SE" 4 3 -999 "" "" -18.50406 164.41704 "HR" NA "Banc de recif barriere" "platier recifal" "Detritique" "Recif barriere interne" NA 11 10 -999 -999 -999 -999 "William ROMAN" +"AMP" "PA170087" "SVR" "Petrie" NA "Recif barriere" NA 1 26 10 2017 "-999" NA "SE" 4 3 -999 "" "" -18.49164 164.40498 "HR" NA "Banc de recif barriere" "platier recifal" "Fond lagonaire" "Recif barriere interne" NA 13 7 -999 -999 -999 -999 "William ROMAN" +"AMP" "PA170088" "SVR" "Petrie" NA "Recif barriere" NA 1 26 10 2017 "-999" NA "SE" 4 3 -999 "" "" -18.49467 164.40176 "HR" NA "Banc de recif barriere" "platier recifal" "Fond lagonaire" "Recif barriere interne" NA 13 9 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "PA170090" "SVR" "Petrie" NA "Recif barriere" NA 1 26 10 2017 "-999" NA "SE" 4 3 -999 "" "" -18.50013 164.39438 "HR" NA "Banc de recif barriere" "platier recifal" "Detritique" "Recif barriere interne" NA 15 7 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "PA170091" "SVR" "Petrie" NA "Recif barriere" NA 1 26 10 2017 "-999" NA "SE" 4 3 -999 "" "" -18.54725 164.3533 "HR" NA "Banc de recif barriere" "platier recifal" "Corail vivant" "Recif barriere externe" NA 20 6 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "PA170092" "SVR" "Petrie" NA "Recif barriere" NA 1 26 10 2017 "-999" NA "SE" 4 3 -999 "" "" -18.55136 164.35681 "HR" NA "Banc de recif barriere" "front recifal" "Detritique" "Recif barriere externe" NA 13 10 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "PA170093" "SVR" "Petrie" NA "Recif barriere" NA 1 26 10 2017 "-999" NA "SE" 4 3 -999 "" "" -18.56106 164.36462 "HR" NA "Banc de recif barriere" "platier recifal ennoye" "Detritique" "Recif barriere interne" NA 15 10 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "PA170094" "SVR" "Petrie" NA "Recif barriere" NA 1 26 10 2017 "-999" NA "SE" 4 3 -999 "" "" -18.56414 164.36674 "HR" NA "Banc de recif barriere" "platier recifal ennoye" "Detritique" "Recif barriere interne" NA 15 10 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "PA170095" "SVR" "Petrie" NA "Recif barriere" NA 1 26 10 2017 "-999" NA "SE" 4 3 -999 "" "" -18.56987 164.37 "HR" NA "Banc de recif barriere" "platier recifal ennoye" "Detritique" "Recif barriere interne" NA 15 8 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "PA170096" "SVR" "Petrie" NA "Recif barriere" NA 1 26 10 2017 "-999" NA "SE" 4 3 -999 "" "" -18.57079 164.37091 "HR" NA "Banc de recif barriere" "platier recifal ennoye" "Detritique" "Recif barriere interne" NA 15 10 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "PA170097" "SVR" "Petrie" NA "Recif barriere" NA 1 26 10 2017 "-999" NA "SE" 4 3 -999 "" "" -18.57053 164.37303 "HR" NA "Banc de recif barriere" "platier recifal ennoye" "Fond lagonaire" "Recif barriere interne" NA 15 7 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "PA170098" "SVR" "Petrie" NA "Recif barriere" NA 1 26 10 2017 "-999" NA "SE" 4 3 -999 "" "" -18.56749 164.37119 "HR" NA "Banc de recif barriere" "platier recifal ennoye" "Detritique" "Recif barriere interne" NA 13 8 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "PA170099" "SVR" "Petrie" NA "Recif barriere" NA 1 26 10 2017 "-999" NA "SE" 4 3 -999 "" "" -18.55343 164.36192 "HR" NA "Banc lagonaire" "terrasse lagonaire peu profonde" "Detritique" "Recif barriere interne" NA 15 7 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "PA170100" "SVR" "Petrie" NA "Recif barriere" NA 1 26 10 2017 "-999" NA "SE" 4 3 -999 "" "" -18.55126 164.36049 "HR" NA "Banc lagonaire" "terrasse lagonaire peu profonde" "Detritique" "Recif barriere interne" NA 15 6 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "PA170101" "SVR" "Petrie" NA "Recif barriere" NA 1 26 10 2017 "-999" NA "SE" 4 3 -999 "" "" -18.54609 164.35981 "HR" NA "Banc de recif barriere" "platier recifal" "Detritique" "Recif barriere interne" NA 13 10 -999 -999 -999 -999 "Bastien PREUSS" +"AMP" "PE140003" "SVR" "Petrie" NA "Barriere" NA 1 5 7 2014 NA NA "SE" 4 2 NA NA "LM" -18.50231 164.39063 "HR" "AP" "Banc de recif barriere" "platier recifal" "Detritique" "Recif barriere interne" "D3" 10 9 -999 -999 -999 -999 "William Roman" +"AMP" "PE140004" "SVR" "Petrie" NA "Barriere" NA 1 5 7 2014 NA NA "SE" 4 2 NA NA "LM" -18.50045 164.39392 "HR" "AP" "Banc de recif barriere" "platier recifal" "Detritique" "Recif barriere interne" "D3" 10 8 -999 -999 -999 -999 "William Roman" +"AMP" "PE140005" "SVR" "Petrie" NA "Barriere" NA 1 5 7 2014 NA NA "SE" 4 2 NA NA "LM" -18.49681 164.40935 "HR" "AP" "Banc lagonaire" "terrasse lagonaire peu profonde" "Detritique" "Recif barriere interne" "D5" 10 9 -999 -999 -999 -999 "William Roman" +"AMP" "PE140006" "SVR" "Petrie" NA "Barriere" NA 1 5 7 2014 NA NA "SE" 4 2 NA NA "LM" -18.49947 164.41312 "HR" "AP" "Banc de recif barriere" "platier recifal" "Detritique" "Recif barriere interne" "D5" 10 13 -999 -999 -999 -999 "William Roman" +"AMP" "PE140007" "SVR" "Petrie" NA "Barriere" NA 1 5 7 2014 NA NA "SE" 5 3 NA NA "LM" -18.50275 164.41562 "HR" "AP" "Banc lagonaire" "terrasse lagonaire peu profonde" "Detritique" "Recif barriere interne" "D5" 10 13 -999 -999 -999 -999 "William Roman" +"AMP" "PE140008" "SVR" "Petrie" NA "Barriere" NA 1 5 7 2014 NA NA "SE" 5 3 NA NA "LM" -18.50997 164.4239 "HR" "AP" "Banc de recif barriere" "platier recifal" "Detritique" "Recif barriere interne" "D3" 10 15 -999 -999 -999 -999 "William Roman" +"AMP" "PE140009" "SVR" "Petrie" NA "Barriere" NA 1 5 7 2014 NA NA "SE" 5 3 NA NA "LM" -18.5109 164.42718 "HR" "AP" "Banc de recif barriere" "platier recifal" "Detritique" "Recif barriere interne" "D7" 10 7 -999 -999 -999 -999 "William Roman" +"AMP" "PE140010" "SVR" "Petrie" NA "Barriere" NA 1 5 7 2014 NA NA "SE" 5 4 NA NA "LM" -18.52556 164.44186 "HR" "AP" "Banc lagonaire" "terrasse lagonaire peu profonde" "Corail vivant" "Recif barriere interne" NA 10 4 -999 -999 -999 -999 "William Roman" +"AMP" "PE140011" "SVR" "Petrie" NA "Barriere" NA 1 5 7 2014 NA NA "SE" 5 4 NA NA "LM" -18.52359 164.44206 "HR" "AP" "Banc lagonaire" "terrasse lagonaire peu profonde" "Detritique" "Recif barriere interne" "D5" 10 7 -999 -999 -999 -999 "William Roman" +"AMP" "PE140012" "SVR" "Petrie" NA "Barriere" NA 1 5 7 2014 NA NA "SE" 5 4 NA NA "LM" -18.54352 164.43591 "HR" "AP" "Banc lagonaire" "terrasse lagonaire peu profonde" "Detritique" "Recif barriere interne" NA 10 8 -999 -999 -999 -999 "William Roman" +"AMP" "PE140013" "SVR" "Petrie" NA "Barriere" NA 1 5 7 2014 NA NA "SE" 5 4 NA NA "LM" -18.54554 164.43669 "HR" "AP" "Banc de recif barriere" "platier recifal" "Detritique" "Recif barriere interne" NA 10 4.5 -999 -999 -999 -999 "William Roman" +"AMP" "PE140015" "SVR" "Petrie" NA "Barriere" NA 1 5 7 2014 NA NA "SE" 5 4 NA NA "LM" -18.56354 164.43736 "HR" "AP" "Banc de recif barriere" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA3" 10 6 -999 -999 -999 -999 "William Roman" +"AMP" "PE140016" "SVR" "Petrie" NA "Barriere" NA 1 5 7 2014 NA NA "SE" 5 4 NA NA "LM" -18.56586 164.43738 "HR" "AP" "Banc lagonaire" "terrasse lagonaire peu profonde" "Corail vivant" "Recif barriere interne" "LC5" 10 9.4 -999 -999 -999 -999 "William Roman" +"AMP" "PE140017" "SVR" "Petrie" NA "Barriere" NA 1 5 7 2014 NA NA "SE" 5 4 NA NA "LM" -18.5843 164.44043 "HR" "AP" "Banc lagonaire" "terrasse lagonaire peu profonde" "Fond lagonaire" "Recif barriere interne" "SA3" 10 11 -999 -999 -999 -999 "William Roman" +"AMP" "PE140018" "SVR" "Petrie" NA "Barriere" NA 1 5 7 2014 NA NA "SE" 5 4 NA NA "LM" -18.58611 164.43996 "HR" "AP" "Banc lagonaire" "terrasse lagonaire peu profonde" "Fond lagonaire" "Recif barriere interne" "SA1" 10 7.5 -999 -999 -999 -999 "William Roman" +"AMP" "PE140021" "SVR" "Petrie" NA "Barriere" NA 1 6 7 2014 NA NA "SE" 3 2 NA NA "LM" -18.59922 164.43822 "HR" "AP" "Banc de recif barriere" "platier recifal" "Fond lagonaire" "Recif barriere interne" "SA1" 10 6 -999 -999 -999 -999 "William Roman" +"AMP" "PE140022" "SVR" "Petrie" NA "Barriere" NA 1 6 7 2014 NA NA "SE" 3 2 NA NA "LM" -18.59211 164.43077 "HR" "AP" "Banc lagonaire" "terrasse lagonaire peu profonde" "Detritique" "Recif barriere interne" "D1" 10 10 -999 -999 -999 -999 "William Roman" +"AMP" "PE140023" "SVR" "Petrie" NA "Barriere" NA 1 6 7 2014 NA NA "SE" 3 2 NA NA "LM" -18.5885 164.4034 "HR" "AP" "Banc de recif barriere" "platier recifal ennoye" "Detritique" "Recif barriere interne" "D7" 10 9 -999 -999 -999 -999 "William Roman" +"AMP" "PE140024" "SVR" "Petrie" NA "Barriere" NA 1 6 7 2014 NA NA "SE" 3 2 NA NA "LM" -18.58279 164.40079 "HR" "AP" "Banc lagonaire" "terrasse lagonaire peu profonde" "Detritique" "Recif barriere interne" "D7" 10 11 -999 -999 -999 -999 "William Roman" +"AMP" "PE140025" "SVR" "Petrie" NA "Barriere" NA 1 6 7 2014 NA NA "SE" 3 2 NA NA "LM" -18.57874 164.37967 "HR" "AP" "Banc lagonaire" "terrasse lagonaire peu profonde" "Detritique" "Recif barriere interne" NA 10 8 -999 -999 -999 -999 "William Roman" +"AMP" "PE140026" "SVR" "Petrie" NA "Barriere" NA 1 6 7 2014 NA NA "SE" 3 2 NA NA "LM" -18.57647 164.37762 "HR" "AP" "Banc lagonaire" "terrasse lagonaire peu profonde" "Detritique" "Recif barriere interne" NA 10 7 -999 -999 -999 -999 "William Roman" +"AMP" "PE140027" "SVR" "Petrie" NA "Barriere" NA 1 6 7 2014 NA NA "SE" 3 2 NA NA "LM" -18.57495 164.37288 "HR" "AP" "Banc de recif barriere" "platier recifal" "Corail vivant" "Recif barriere interne" "LC4" 10 5 -999 -999 -999 -999 "William Roman" +"AMP" "PE140028" "SVR" "Petrie" NA "Barriere" NA 1 6 7 2014 NA NA "SE" 3 2 NA NA "LM" -18.57348 164.37213 "HR" "AP" "Banc de recif barriere" "platier recifal" "Detritique" "Recif barriere interne" "D1" 10 9 -999 -999 -999 -999 "William Roman" +"AMP" "PE140029" "SVR" "Petrie" NA "Barriere" NA 1 6 7 2014 NA NA "SE" 3 2 NA NA "LM" -18.55287 164.36174 "HR" "AP" "Banc lagonaire" "terrasse lagonaire peu profonde" "Corail vivant" "Recif barriere interne" "LC2" 10 3.5 -999 -999 -999 -999 "William Roman" +"AMP" "PE140030" "SVR" "Petrie" NA "Barriere" NA 1 6 7 2014 NA NA "SE" 3 2 NA NA "LM" -18.54937 164.36021 "HR" "AP" "Banc lagonaire" "terrasse lagonaire peu profonde" "Corail vivant" "Recif barriere interne" "D7" 10 10 -999 -999 -999 -999 "William Roman" +"AMP" "PE140031" "SVR" "Petrie" NA "Barriere" NA 1 6 7 2014 NA NA "SE" 3 2 NA NA "LM" -18.55827 164.35867 "HR" "AP" "" "" "Corail vivant" "Recif barriere externe" "LC1" 10 8 -999 -999 -999 -999 "William Roman" +"AMP" "PE140032" "SVR" "Petrie" NA "Barriere" NA 1 6 7 2014 NA NA "SE" 3 2 NA NA "LM" -18.55197 164.35747 "HR" "AP" "Banc de recif barriere" "front recifal" "Detritique" "Recif barriere externe" "D5" 10 11 -999 -999 -999 -999 "William Roman" +"AMP" "PE140033" "SVR" "Petrie" NA "Barriere" NA 1 6 7 2014 NA NA "SE" 3 2 NA NA "LM" -18.49953 164.38959 "HR" "AP" "" "" "Corail vivant" "Recif barriere externe" NA 10 4 -999 -999 -999 -999 "William Roman" +"AMP" "PE140034" "SVR" "Petrie" NA "Barriere" NA 1 6 7 2014 NA NA "SE" 3 2 NA NA "LM" -18.49413 164.3961 "HR" "AP" "Banc de recif barriere" "front recifal" "Detritique" "Recif barriere externe" NA 10 5 -999 -999 -999 -999 "William Roman" +"AMP" "PE140035" "SVR" "Petrie" NA "Barriere" NA 1 6 7 2014 NA NA "SE" 3 2 NA NA "LM" -18.49254 164.39853 "HR" "AP" "Banc de recif barriere" "front recifal" "Corail vivant" "Recif barriere externe" "LC1" 10 8 -999 -999 -999 -999 "William Roman" +"AMP" "PE140037" "SVR" "Petrie" NA "Barriere" NA 1 6 7 2014 NA NA "SE" 3 2 NA NA "LM" -18.48572 164.4042 "HR" "AP" "Banc de recif barriere" "front recifal" "Detritique" "Recif barriere externe" "D7" 10 13 -999 -999 -999 -999 "William Roman" +"AMP" "PE140038" "SVR" "Petrie" NA "Barriere" NA 1 6 7 2014 NA NA "SE" 3 2 NA NA "LM" -18.4845 164.4052 "HR" "AP" "Banc de recif barriere" "front recifal" "Corail vivant" "Recif barriere externe" "D3" 10 17.5 -999 -999 -999 -999 "William Roman" +"AMP" "PE140039" "SVR" "Petrie" NA "Barriere" NA 1 6 7 2014 NA NA "SE" 3 2 NA NA "LM" -18.48178 164.40901 "HR" "AP" "Banc de recif barriere" "front recifal" "Detritique" "Recif barriere externe" "D5" 10 7.5 -999 -999 -999 -999 "William Roman" +"AMP" "PE140040" "SVR" "Petrie" NA "Barriere" NA 1 6 7 2014 NA NA "SE" 3 2 NA NA "LM" -18.48765 164.40188 "HR" "AP" "Banc de recif barriere" "front recifal" "Detritique" "Recif barriere externe" "D3" 10 11 -999 -999 -999 -999 "William Roman" +"AMP" "PO120001" "SVR" NA NA "Barriere" NA 1 20 11 2012 NA NA "SE" 1 2 NA "MM" "PQ" -20.52436 164.82872 "HR" "AP" "Complexe de recif barriere externe" "passe" "Corail vivant" "Passe" NA -999 6 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120003" "SVR" NA NA "Barriere" NA 1 20 11 2012 NA NA "SE" 1 2 NA "MM" "PQ" -20.4849 164.81033 "HR" "AP" "Complexe de recif barriere externe" "platier recifal" "Detritique" "Recif barriere interne" "D5" -999 1.6 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120004" "SVR" NA NA "Barriere" NA 1 20 11 2012 NA NA "SE" 1 2 NA "MM" "PQ" -20.49377 164.80057 "HR" "AP" "Complexe de recif barriere externe" "terrasse profonde a champ de constructions coralliennes" "Corail vivant" "Recif barriere interne" "LC2" -999 11 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120005" "SVR" NA NA "Barriere" NA 1 20 11 2012 NA NA "SE" 1 2 NA "MM" "PQ" -20.4617 164.77481 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse profonde" "Detritique" "Recif barriere interne" "D2" -999 13 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120006" "SVR" NA NA "Barriere" NA 1 20 11 2012 NA NA "SE" 1 2 NA "MM" "PQ" -20.45384 164.78024 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Recif barriere interne" NA -999 3 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120007" "SVR" NA NA "Barriere" NA 1 20 11 2012 NA NA "SE" 2 2 NA "MD" "PQ" -20.42789 164.75558 "HR" "AP" "Complexe de recif barriere externe" "front recifal" "Corail vivant" "Recif barriere externe" "LC1" -999 11 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120008" "SVR" NA NA "Barriere" NA 1 20 11 2012 NA NA "SE" 2 2 NA "MM" "PQ" -20.4377 164.755 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Recif barriere interne" "D6" -999 4 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120009" "SVR" NA NA "Barriere" NA 1 20 11 2012 NA NA "SE" 2 2 NA "MM" "PQ" -20.42991 164.74892 "RN" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Recif barriere interne" "D6" -999 17 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120010" "SVR" NA NA "Barriere" NA 1 20 11 2012 NA NA "SE" 2 2 NA "MD" "PQ" -20.41749 164.74113 "RN" "AP" "Complexe de recif barriere externe" "front recifal" "Corail vivant" "Recif barriere externe" "LC4" -999 8 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120012" "SVR" NA NA "Pente interne" NA 1 19 11 2012 NA NA NA 2 2 NA "MD" "PC" -20.4164 164.73318 "AGDR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde a champ de constructions coralliennes" "Detritique" "Recif barriere interne" "D2" -999 4 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120013" "SVR" NA NA "Barriere" NA 1 20 11 2012 NA NA "SE" 2 2 NA "MD" "PQ" -20.40907 164.73621 "AGDR" "AP" "Complexe de recif barriere externe" "front recifal" "Corail vivant" "Recif barriere externe" "LC2" -999 10 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120016" "SVR" NA NA "Barriere" NA 1 21 11 2012 NA NA "SE" 2 1 NA "MD" "LM" -20.39409 164.70917 "AGDR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde a champ de constructions coralliennes" "Detritique" "Recif barriere interne" "D2" -999 3 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120017" "SVR" NA NA "Barriere" NA 1 21 11 2012 NA NA "SE" 2 1 NA "MD" "LM" -20.39844 164.70645 "AGDR" "AP" "Complexe de recif barriere externe" "terrasse profonde a champ de constructions coralliennes" "Fond lagonaire" "Recif barriere interne" "SA3" -999 13 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120018" "SVR" NA NA "Barriere" NA 1 21 11 2012 NA NA "SE" 2 1 NA "MM" "LM" -20.38482 164.6762 "AGDR" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Recif barriere interne" "SA1" -999 4.5 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120020" "SVR" NA NA "Barriere" NA 1 21 11 2012 NA NA "SE" 2 1 NA "MM" "LM" -20.38672 164.6904 "RN" "AP" "Complexe de recif barriere externe" "terrasse profonde a champ de constructions coralliennes" "Fond lagonaire" "Recif barriere interne" "SA3" -999 10.5 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120021" "SVR" NA NA "Barriere" NA 1 21 11 2012 NA NA "SE" 2 1 NA "MM" "LM" -20.37849 164.69383 "RN" "AP" "Complexe de recif barriere externe" "platier recifal" "Detritique" "Recif barriere interne" NA -999 3 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120022" "SVR" NA NA "Barriere" NA 1 21 11 2012 NA NA "SE" 2 1 NA "MM" "LM" -20.38071 164.67871 "RN" "AP" "Complexe de recif barriere externe" "terrasse peu profonde a champ de constructions coralliennes" "Fond lagonaire" "Recif barriere interne" "SA2" -999 10.5 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120023" "SVR" NA NA "Barriere" NA 1 21 11 2012 NA NA "SE" 3 1 NA "MM" "LM" -20.36835 164.65927 "RN" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Recif barriere interne" "D1" -999 4 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120026" "SVR" NA NA "Barriere - Passe" NA 1 21 11 2012 NA NA "SE" 3 1 NA "MM" "LM" -20.35305 164.62927 "AGDR" "AP" "Complexe de recif barriere externe" "front recifal" "Corail vivant" "Passe" "LC4" -999 6 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120028" "SVR" NA NA "Barriere" NA 1 22 11 2012 NA NA "SE" 1 2 NA "MD" "LM" -20.34923 164.61337 "HR" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Recif barriere interne" "SA5" -999 5 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120029" "SVR" NA NA "Barriere" NA 1 22 11 2012 NA NA "SE" 1 2 NA "MM" "LM" -20.31884 164.61655 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde a champ de constructions coralliennes" "Fond lagonaire" "Recif barriere interne" "SA3" -999 3 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120030" "SVR" NA NA "Barriere" NA 1 22 11 2012 NA NA "SE" 1 2 NA "MM" "LM" -20.28587 164.5672 "HR" "AP" "Complexe de recif barriere externe" "terrasse profonde a champ de constructions coralliennes" "Fond lagonaire" "Recif barriere interne" "SA3" -999 4 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120031" "SVR" NA NA "Barriere" NA 1 22 11 2012 NA NA "SE" 1 2 NA "MM" "LM" -20.28348 164.57217 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Recif barriere interne" NA -999 3 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120036" "SVR" NA NA "Intermediaire" NA 1 19 11 2012 NA NA NA 4 2 NA "MD" "PC" -20.45181 164.70938 "HR" "AP" "Complexe de recif barriere imbrique" "terrasse peu profonde" "Fond lagonaire" "Recif intermediaire" "SA4" -999 9 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120037" "SVR" NA NA "Intermediaire" NA 1 20 11 2012 NA NA NA 4 2 NA "MM" "PQ" -20.44003 164.71054 "HR" "AP" "Complexe de recif barriere imbrique" "platier recifal" "Corail vivant" "Recif intermediaire" NA -999 4 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120038" "SVR" NA NA "Intermediaire" NA 1 19 11 2012 NA NA NA 3 2 NA "MD" "PC" -20.44399 164.69498 "HR" "AP" "Complexe de recif barriere imbrique" "terrasse peu profonde" "Corail vivant" "Recif intermediaire" "LC5" -999 4.5 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120041" "SVR" NA NA "Intermediaire" NA 1 19 11 2012 NA NA NA 3 2 NA "MD" "PC" -20.42964 164.67853 "RN" "AP" "Complexe de recif barriere imbrique" "terrasse peu profonde" "Fond lagonaire" "Recif intermediaire" "SA1" -999 2.5 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120042" "SVR" NA NA "Intermediaire" NA 1 22 11 2012 NA NA "SE" 1 1 NA "MD" "LM" -20.42318 164.66034 "AGDR" "AP" "Complexe de recif barriere imbrique" "terrasse peu profonde" "Algueraie" "Recif intermediaire" "MA3" -999 8 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120043" "SVR" NA NA "Intermediaire" NA 1 22 11 2012 NA NA "SE" 1 1 NA "MD" "LM" -20.41867 164.66069 "RN" "AP" "Complexe de recif barriere imbrique" "platier recifal" "Detritique" "Recif intermediaire" "D2" -999 3 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120044" "SVR" NA NA "Intermediaire" NA 1 22 11 2012 NA NA "SE" 1 1 NA "MD" "LM" -20.40881 164.66318 "RN" "AP" "Complexe de recif barriere imbrique" "front recifal ou terrasse" "Fond lagonaire" "Recif intermediaire" "SA1" -999 8.5 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120045" "SVR" NA NA "Intermediaire" NA 1 20 11 2012 NA NA NA 3 2 NA "MD" "PQ" -20.4123 164.67682 "RN" "AP" "Complexe de recif barriere imbrique" "front recifal ou terrasse" "Corail vivant" "Recif intermediaire" "LC1" -999 6 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120046" "SVR" NA NA "Intermediaire" NA 1 23 11 2012 NA NA "0" 0 2 NA "MM" "LM" -20.40423 164.65784 "AGDR" "AP" "Complexe de recif barriere imbrique" "front recifal ou terrasse" "Detritique" "Recif intermediaire" "D3" -999 7 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120048" "SVR" NA NA "Intermediaire" NA 1 22 11 2012 NA NA "SE" 1 1 NA "MD" "LM" -20.39586 164.64441 "HR" "AP" "Complexe de recif barriere imbrique" "front recifal ou terrasse" "Fond lagonaire" "Recif intermediaire" "SA5" -999 5 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120050" "SVR" NA NA "Intermediaire" NA 1 23 11 2012 NA NA "0" 0 2 NA "MM" "LM" -20.39254 164.62477 "HR" "AP" "Complexe de recif barriere imbrique" "front recifal ou terrasse" "Fond lagonaire" "Recif intermediaire" "SA3" -999 5 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120051" "SVR" NA NA "Intermediaire" NA 1 23 11 2012 NA NA "0" 0 2 NA "MM" "LM" -20.39865 164.62431 "HR" "AP" "Complexe de recif barriere imbrique" "terrasse peu profonde" "Detritique" "Recif intermediaire" "D4" -999 5 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120053" "SVR" NA NA "Intermediaire" NA 1 23 11 2012 NA NA "0" 0 1 NA "MM" "LM" -20.3855 164.61063 "HR" "AP" "Recif frangeant protege de lagons" "platier recifal" "Corail vivant" "Frangeant cotier" "D5" -999 4 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120054" "SVR" NA NA "Intermediaire" NA 1 23 11 2012 NA NA "0" 0 1 NA "MM" "LM" -20.3808 164.6087 "HR" "AP" "Recif frangeant protege de lagons" "platier recifal" "Fond lagonaire" "Frangeant cotier" "SA3" -999 1 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120055" "SVR" NA NA "Intermediaire" NA 1 23 11 2012 NA NA "0" 0 1 NA "MM" "LM" -20.37435 164.60365 "HR" "AP" "Recif frangeant protege de lagons" "platier recifal" "Corail vivant" "Frangeant cotier" "LC2" -999 5 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120056" "SVR" NA NA "Intermediaire" NA 1 22 11 2012 NA NA "SE" 1 2 NA "MM" "LM" -20.30716 164.55269 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse profonde" "Detritique" "Recif intermediaire" "D1" -999 6 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120066" "SVR" NA NA "Frangeant" NA 1 23 11 2012 NA NA "SE" 2 1 NA "MM" "LM" -20.35016 164.56873 "HR" "AP" "Recif frangeant protege de lagons" "platier recifal" "Corail vivant" "Frangeant cotier" "LC1" -999 4 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120069" "SVR" NA NA "Frangeant" NA 1 22 11 2012 NA NA "SE" 2 2 NA "MM" "LM" -20.43304 164.65582 "AGDR" "AP" "Recif frangeant protege de lagons" "platier recifal" "Fond lagonaire" "Frangeant cotier" "SA1" -999 3 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120071" "SVR" NA NA "Frangeant" NA 1 19 11 2012 NA NA NA 4 2 NA "MD" "PC" -20.44279 164.66853 "AGDR" "AP" "Recif frangeant protege de lagons" "platier recifal" "Algueraie" "Frangeant cotier" "SG2" -999 4 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120072" "SVR" NA NA "Frangeant" NA 1 19 11 2012 NA NA NA 4 2 NA "MD" "PC" -20.45893 164.68945 "HR" "AP" "Recif frangeant protege de lagons" "platier recifal" "Fond lagonaire" "Frangeant cotier" "SA1" -999 3 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120073" "SVR" NA NA "Frangeant" NA 1 23 11 2012 NA NA "0" 0 2 NA "MM" "LM" -20.46814 164.70778 "HR" "AP" "Recif frangeant protege de lagons" "platier recifal" "Detritique" "Frangeant cotier" "D1" -999 4 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120076" "SVR" NA NA "Barriere" NA 1 20 11 2012 NA NA "SE" 2 2 NA "MD" "PQ" -20.42743 164.74945 "RN" "AP" "Complexe de recif barriere externe" "passe" "Corail vivant" "Passe" NA -999 4 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120077" "SVR" NA NA "PE/Passe" NA 1 19 11 2012 NA NA NA 4 2 NA "MD" "PC" -20.43336 164.7397 "RN" "AP" "Ile lagonaire" "lagon profond" "Corail vivant" "Passe" "LC6" -999 5 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120078" "SVR" NA NA "Pente interne" NA 1 19 11 2012 NA NA NA 1 2 NA "MD" "PC" -20.41295 164.72749 "AGDR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde a champ de constructions coralliennes" "Detritique" "Recif barriere interne" "D2" -999 3.5 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120083" "SVR" NA NA "Barriere" NA 1 21 11 2012 NA NA "SE" 3 1 NA "MM" "LM" -20.37464 164.67235 "RN" "AP" "Complexe de recif barriere externe" "terrasse peu profonde a champ de constructions coralliennes" "Detritique" "Recif barriere interne" "D2" -999 6 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120087" "SVR" NA NA "Barriere" NA 1 21 11 2012 NA NA "SE" 3 1 NA "MM" "LM" -20.36297 164.6487 "AGDR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Recif barriere interne" NA -999 6 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120089" "SVR" NA NA "Intermediaire" NA 1 19 11 2012 NA NA NA 4 2 NA "MD" "PC" -20.4487 164.70413 "HR" "AP" "Complexe de recif barriere imbrique" "terrasse peu profonde" "Detritique" "Recif intermediaire" "D1" -999 3.7 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120090" "SVR" NA NA "Intermediaire" NA 1 20 11 2012 NA NA NA 4 2 NA "MM" "PQ" -20.43556 164.70073 "HR" "AP" "Complexe de recif barriere imbrique" "front recifal ou terrasse" "Detritique" "Recif intermediaire" "D2" -999 4 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120092" "SVR" NA NA "Intermediaire" NA 1 20 11 2012 NA NA NA 4 2 NA "MM" "PQ" -20.42588 164.69052 "RN" "AP" "Complexe de recif barriere imbrique" "platier recifal" "Corail vivant" "Recif intermediaire" "LC2" -999 1.5 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120094" "SVR" NA NA "Intermediaire" NA 1 20 11 2012 NA NA NA 3 2 NA "MD" "PQ" -20.42041 164.68246 "RN" "AP" "Complexe de recif barriere imbrique" "front recifal ou terrasse" "Fond lagonaire" "Recif intermediaire" "SA5" -999 3 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120096" "SVR" NA NA "Intermediaire" NA 1 20 11 2012 NA NA NA 3 2 NA "MD" "PQ" -20.40939 164.67245 "RN" "AP" "Complexe de recif barriere imbrique" "front recifal ou terrasse" "Corail vivant" "Recif intermediaire" "LC3" -999 6 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120097" "SVR" NA NA "Frangeant" NA 1 22 11 2012 NA NA "SE" 2 2 NA "MM" "LM" -20.42524 164.65117 "AGDR" "AP" "Ile lagonaire" "lagon profond" "Detritique" "Frangeant cotier" NA -999 4 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120103" "SVR" NA NA "Barriere" NA 1 20 11 2012 NA NA "SE" 2 2 NA "MM" "PQ" -20.4423 164.76659 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Detritique" "Recif barriere interne" "D5" -999 3 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120104" "SVR" NA NA "Barriere" NA 1 20 11 2012 NA NA "SE" 2 2 NA "MM" "PQ" -20.44609 164.76282 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA1" -999 14 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120105" "SVR" NA NA "PE/Passe" NA 1 19 11 2012 NA NA NA 5 2 NA "MD" "PC" -20.42331 164.74333 "RN" "AP" "Complexe de recif barriere externe" "front recifal" "Detritique" "Passe" NA -999 9 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120111" "SVR" NA NA "Barriere" NA 1 22 11 2012 NA NA "SE" 1 2 NA "MM" "LM" -20.26228 164.53899 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA3" -999 3 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120121" "SVR" NA NA "Intermediaire" NA 1 20 11 2012 NA NA NA 4 2 NA "MM" "PQ" -20.42315 164.6879 "RN" "AP" "Complexe de recif barriere imbrique" "platier recifal" "Corail vivant" "Recif intermediaire" "LC1" -999 2 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120134" "SVR" NA NA "Frangeant" NA 1 22 11 2012 NA NA "SE" 2 2 NA "MM" "LM" -20.36544 164.59308 "HR" "AP" "Recif frangeant protege de lagons" "platier recifal" "Corail vivant" "Frangeant cotier" NA -999 6 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120136" "SVR" NA NA "Frangeant" NA 1 22 11 2012 NA NA "SE" 2 2 NA "MM" "LM" -20.35538 164.577 "HR" "AP" "Recif frangeant protege de lagons" "platier recifal" "Fond lagonaire" "Frangeant cotier" "SA3" -999 3 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120138" "SVR" NA NA "Frangeant" NA 1 22 11 2012 NA NA "SE" 1 2 NA "MD" "LM" -20.30837 164.53427 "HR" "AP" "Recif frangeant protege de lagons" "platier recifal" "Corail vivant" "Frangeant cotier" "LC1" -999 2.5 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120200" "SVR" NA NA "Intermediaire" NA 1 20 11 2012 NA NA NA 4 2 NA "MM" "PQ" -20.43459 164.69289 "RN" "AP" "Complexe de recif barriere imbrique" "terrasse peu profonde" "Corail vivant" "Recif intermediaire" "LC4" -999 3 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120201" "SVR" NA NA "Intermediaire" NA 1 20 11 2012 NA NA NA 4 2 NA "MM" "PQ" -20.44409 164.71483 "HR" "AP" "Complexe de recif barriere imbrique" "front recifal ou terrasse" "Detritique" "Recif intermediaire" NA -999 3 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120202" "SVR" NA NA "Intermediaire" NA 1 20 11 2012 NA NA NA 4 2 NA "MM" "PQ" -20.44543 164.71741 "HR" "AP" "Complexe de recif barriere imbrique" "front recifal ou terrasse" "Detritique" "Recif intermediaire" "LC6" -999 9 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120203" "SVR" NA NA "Intermediaire" NA 1 20 11 2012 NA NA NA 4 2 NA "MM" "PQ" -20.44832 164.71776 "HR" "AP" "Complexe de recif barriere imbrique" "platier recifal" "Corail vivant" "Recif intermediaire" "LC2" -999 4.5 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120204" "SVR" NA NA "Intermediaire" NA 1 20 11 2012 NA NA NA 3 2 NA "MM" "PQ" -20.45077 164.71509 "HR" "AP" "Complexe de recif barriere imbrique" "terrasse peu profonde" "Corail vivant" "Recif intermediaire" "LC6" -999 1.5 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120205" "SVR" NA NA "Intermediaire" NA 1 20 11 2012 NA NA NA 3 2 NA "MM" "PQ" -20.45035 164.71461 "HR" "AP" "Complexe de recif barriere imbrique" "terrasse peu profonde" "Corail vivant" "Recif intermediaire" "LC4" -999 1 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120206" "SVR" NA NA "Intermediaire" NA 1 20 11 2012 NA NA NA 3 2 NA "MM" "PQ" -20.44765 164.69688 "HR" "AP" "Complexe de recif barriere imbrique" "terrasse peu profonde" "Corail vivant" "Recif intermediaire" "LC5" -999 3 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120208" "SVR" NA NA "Barriere" NA 1 21 11 2012 NA NA "SE" 3 1 NA "MM" "LM" -20.36352 164.64056 "AGDR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA1" -999 7 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120209" "SVR" NA NA "Barriere" NA 1 21 11 2012 NA NA "SE" 3 1 NA "MM" "LM" -20.36594 164.65842 "RN" "AP" "Complexe de recif barriere externe" "platier recifal" "Detritique" "Recif barriere interne" "D6" -999 4 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120210" "SVR" NA NA "Barriere" NA 1 21 11 2012 NA NA "SE" 3 1 NA "MM" "LM" -20.37247 164.6579 "AGDR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "SA1" -999 6 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120211" "SVR" NA NA "Barriere" NA 1 21 11 2012 NA NA "SE" 2 1 NA "MM" "LM" -20.37926 164.6741 "RN" "AP" "Complexe de recif barriere externe" "terrasse peu profonde a champ de constructions coralliennes" "Detritique" "Recif barriere interne" "D6" -999 9 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120212" "SVR" NA NA "Intermediaire" NA 1 21 11 2012 NA NA "SE" 2 2 NA "MD" "LM" -20.43449 164.69247 "RN" "AP" "Complexe de recif barriere imbrique" "terrasse peu profonde" "Corail vivant" "Recif intermediaire" "LC1" -999 2 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120213" "SVR" NA NA "Intermediaire" NA 1 21 11 2012 NA NA "SE" 2 2 NA "MD" "LM" -20.43241 164.68138 "RN" "AP" "Complexe de recif barriere imbrique" "terrasse peu profonde" "Corail vivant" "Recif intermediaire" "LC1" -999 2 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120233" "SVR" NA NA "Frangeant" NA 1 23 11 2012 NA NA "SE" 2 1 NA "MM" "LM" -20.35602 164.5746 "HR" "AP" "Recif frangeant protege de lagons" "platier recifal" "Corail vivant" "Frangeant cotier" "LC2" -999 2 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120288" "SVR" NA NA "Intermediaire" NA 1 20 11 2012 NA NA NA 3 2 NA "MM" "PQ" -20.45055 164.71356 "HR" "AP" "Complexe de recif barriere imbrique" "terrasse peu profonde" "Fond lagonaire" "Recif intermediaire" "SA5" -999 5 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120300" "SVR" NA NA "Barriere" NA 1 22 11 2012 NA NA "SE" 1 2 NA "MM" "LM" -20.26275 164.53345 "HR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde" "Fond lagonaire" "Recif barriere interne" "MA4" -999 5 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120301" "SVR" NA NA "Intermediaire" NA 1 22 11 2012 NA NA "SE" 1 2 NA "MM" "LM" -20.30024 164.55856 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse profonde" "Detritique" "Recif intermediaire" "D6" -999 10 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120302" "SVR" NA NA "Intermediaire" NA 1 22 11 2012 NA NA "SE" 1 2 NA "MM" "LM" -20.31381 164.56612 "HR" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Recif intermediaire" "SA3" -999 10 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120305" "SVR" NA NA "Barriere" NA 1 22 11 2012 NA NA "SE" 1 2 NA "MM" "LM" -20.30338 164.58786 "HR" "AP" "Complexe de recif barriere externe" "terrasse profonde a champ de constructions coralliennes" "Fond lagonaire" "Recif barriere interne" "SA5" -999 13 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120309" "SVR" NA NA "Intermediaire" NA 1 23 11 2012 NA NA "0" 0 2 NA "MM" "LM" -20.41214 164.63913 "HR" "AP" "Ile lagonaire" "lagon profond" "Detritique" "Fond lagonaire" "D2" -999 9 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO120311" "SVR" NA NA "Intermediaire" NA 1 23 11 2012 NA NA "0" 0 2 NA "MM" "LM" -20.40278 164.68542 "AGDR" "AP" "Ile lagonaire" "lagon profond" "Detritique" "Recif intermediaire" "D3" -999 10 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "PO12MA01" "SVR" NA NA "Pente interne" NA 1 19 11 2012 NA NA NA -999 -999 NA NA "PC" -20.40499 164.71716 "AGDR" "AP" "Complexe de recif barriere externe" "terrasse peu profonde a champ de constructions coralliennes" "Detritique" "Recif barriere interne" NA -999 4 -999 -999 -999 -999 "Fanny Witkovski" +"AMP" "RD070007" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 19 6 2007 NA NA NA -999 -999 NA "MM" "PC" -22.30793 166.29937 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG4" -999 14.8 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "RD070008" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 19 6 2007 NA NA NA -999 -999 NA "MM" "PC" -22.31102 166.30128 "HR" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA4" -999 15 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "RD070009" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 19 6 2007 NA NA NA -999 -999 NA "PM" "PC" -22.31397 166.30297 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG3" -999 15.4 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "RD070010" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 19 6 2007 NA NA NA -999 -999 NA "MD" "PC" -22.31693 166.3042 "HR" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA3" -999 14.8 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "RD070011" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 19 6 2007 NA NA NA -999 -999 NA "MD" "PC" -22.31975 166.30565 "HR" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA3" -999 13.2 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "RD070012" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 19 6 2007 NA NA NA -999 -999 NA "MD" "PC" -22.32247 166.30753 "RE" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG3" -999 10 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "RD070013" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 19 6 2007 NA NA NA -999 -999 NA "MD" "PC" -22.3254 166.30908 "RE" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "SG3" -999 8.8 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "RD070026" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 20 6 2007 NA NA NA -999 -999 NA "PM" "PC" -22.3056 166.30327 "HR" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "SG4" -999 15.6 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "RD070027" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 20 6 2007 NA NA NA -999 -999 NA "PM" "PC" -22.3085 166.3049 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG3" -999 15 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "RD070028" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 20 6 2007 NA NA NA -999 -999 NA "MD" "PC" -22.31183 166.30675 "HR" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "SG4" -999 14.9 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "RD070029" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 20 6 2007 NA NA NA -999 -999 NA "MD" "PC" -22.31458 166.30843 "HR" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA3" -999 13.7 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "RD070173" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 4 7 2007 NA NA "0" 0 -999 NA "MD" "LD" -22.31942 166.31685 "RE" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG2" -999 8.8 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "RD070174" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 4 7 2007 NA NA "0" 0 -999 NA "MD" "LD" -22.31696 166.31468 "HR" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA2" -999 10.6 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "RD070175" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 4 7 2007 NA NA "0" 0 -999 NA "MD" "LD" -22.31433 166.31256 "HR" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA3" -999 13.5 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "RD070176" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 4 7 2007 NA NA "0" 0 -999 NA "MD" "LD" -22.31161 166.31042 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG4" -999 13.6 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "RD070177" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 4 7 2007 NA NA "0" 0 -999 NA "MD" "LD" -22.30873 166.30849 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG3" -999 13.4 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "RD070204" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 5 7 2007 NA NA NA 2 -999 NA "MD" "LD" -22.31334 166.29803 "HR" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA4" -999 18.8 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "RD070206" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 5 7 2007 NA NA NA 2 -999 NA "MD" "LD" -22.31913 166.30104 "HR" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA3" -999 15.2 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "RD070208" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 5 7 2007 NA NA NA 2 -999 NA "MD" "LD" -22.32478 166.30454 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG3" -999 9.2 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "RD070219" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 6 7 2007 NA NA NA -999 -999 NA "MM" "LD" -22.30306 166.30433 "HR" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "SG4" -999 14.9 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "RD070220" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 6 7 2007 NA NA NA -999 -999 NA "MM" "LD" -22.30031 166.30235 "RE" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA4" -999 16.4 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "RD070228" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 6 7 2007 NA NA NA -999 -999 NA "MD" "LD" -22.30993 166.29569 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG3" -999 13.5 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "RD070229" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 6 7 2007 NA NA NA -999 -999 NA "MD" "LD" -22.31618 166.29922 "HR" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA3" -999 18.6 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "RD070230" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 6 7 2007 NA NA NA -999 -999 NA "MD" "LD" -22.32189 166.3025 "HR" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA1" -999 13.9 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "RD070247" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 30 7 2007 NA NA NA -999 -999 NA "MM" "PL" -22.3202 166.31149 "RE" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA4" -999 9.7 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "RD070248" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 30 7 2007 NA NA NA -999 -999 NA "MM" "PL" -22.317 166.30979 "HR" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA2" -999 11.2 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "RD080010" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 3 7 2008 NA NA NA 2 -999 NA "MD" "NL" -22.31689 166.30419 "HR" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA2" 7 14.8 -999 -999 -999 -999 "William Roman" +"AMP" "RD080011" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 3 7 2008 NA NA NA 2 -999 NA "MD" "NL" -22.31969 166.30576 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" NA 8 13.2 -999 -999 -999 -999 "William Roman" +"AMP" "RD080012" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 3 7 2008 NA NA NA 1 -999 NA "MD" "NL" -22.32247 166.30749 "RE" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA3" 6 10 -999 -999 -999 -999 "William Roman" +"AMP" "RD080026" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 24 6 2008 NA NA NA -999 -999 NA "MD" "LD" -22.30559 166.30316 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG4" 7 15.1 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "RD080028" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 24 6 2008 NA NA NA -999 -999 NA "MD" "LD" -22.31176 166.30676 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG4" 3 14.5 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "RD080029" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 24 6 2008 NA NA NA -999 -999 NA "MD" "LD" -22.3145 166.30827 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG3" 5 13.5 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "RD080030" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 24 6 2008 NA NA NA -999 -999 NA "MD" "LD" -22.31712 166.30983 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG3" 3 12 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "RD080031" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 24 6 2008 NA NA NA -999 -999 NA "MD" "LD" -22.32005 166.31148 "RE" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG4" 7 10.8 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "RD08007B" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 4 7 2008 NA NA NA 4 -999 NA "MD" "PC" -22.30804 166.29923 "HR" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA1" 6 14.8 -999 -999 -999 -999 "William Roman" +"AMP" "RD08008B" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 3 7 2008 NA NA NA 2 -999 NA "MD" "NL" -22.3109 166.30147 "HR" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA3" 9 15 -999 -999 -999 -999 "William Roman" +"AMP" "RD08009B" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 3 7 2008 NA NA NA 2 -999 NA "MD" "NL" -22.31391 166.30302 "HR" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA1" 7 15.4 -999 -999 -999 -999 "William Roman" +"AMP" "RD080173" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 24 6 2008 NA NA NA -999 -999 NA "MD" "LD" -22.31933 166.31692 "RE" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG2" 3 8.5 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "RD080174" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 24 6 2008 NA NA NA -999 -999 NA "MD" "LD" -22.31704 166.31469 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG2" 3 10.1 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "RD080175" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 24 6 2008 NA NA NA -999 -999 NA "MD" "LD" -22.31414 166.3126 "HR" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA1" 7 13.2 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "RD080176" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 24 6 2008 NA NA NA -999 -999 NA "MD" "LD" -22.31174 166.31038 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG3" 6 13.5 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "RD080177" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 24 6 2008 NA NA NA -999 -999 NA "MD" "LD" -22.30873 166.30853 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG4" 5 13 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "RD080204" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 3 7 2008 NA NA NA 2 -999 NA "MD" "NL" -22.31323 166.29803 "HR" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA4" 8 18 -999 -999 -999 -999 "William Roman" +"AMP" "RD080205" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 3 7 2008 NA NA NA 2 -999 NA "MD" "NL" -22.31624 166.29936 "HR" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA1" 6 17 -999 -999 -999 -999 "William Roman" +"AMP" "RD080206" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 3 7 2008 NA NA NA 3 -999 NA "MD" "NL" -22.31909 166.301 "HR" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA2" 7 14.7 -999 -999 -999 -999 "William Roman" +"AMP" "RD080207" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 3 7 2008 NA NA NA 3 -999 NA "MD" "NL" -22.32199 166.30265 "HR" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA2" 6 13.1 -999 -999 -999 -999 "William Roman" +"AMP" "RD080208" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 3 7 2008 NA NA NA 3 -999 NA "MD" "NL" -22.32484 166.30458 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG3" 8 9 -999 -999 -999 -999 "William Roman" +"AMP" "RD080219" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 24 6 2008 NA NA NA -999 -999 NA "MD" "LD" -22.30314 166.30427 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG3" 5 15 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "RD080228" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 27 6 2008 NA NA NA -999 -999 NA "MM" "DC" -22.30978 166.29561 "HR" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA1" 5 13.7 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "RD080275" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 3 7 2008 NA NA NA 3 -999 NA "MD" "NL" -22.32289 166.30036 "HR" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA3" 8 13.1 -999 -999 -999 -999 "William Roman" +"AMP" "RD080400" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 8 7 2008 NA NA NA 5 -999 NA "MM" "PC" -22.32111 166.29868 "HR" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" NA 9 15.4 -999 -999 -999 -999 "William Roman" +"AMP" "RD080401" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 8 7 2008 NA NA NA 5 -999 NA "MM" "PC" -22.31816 166.29702 "HR" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "SA2" 7 19.1 -999 -999 -999 -999 "William Roman" +"AMP" "RD080402" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 8 7 2008 NA NA NA 6 -999 NA "MM" "PC" -22.31549 166.2956 "HR" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA4" 5 19.6 -999 -999 -999 -999 "William Roman" +"AMP" "RD080403" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 8 7 2008 NA NA NA 6 -999 NA "MM" "PC" -22.31254 166.29406 "HR" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA1" 8 19.5 -999 -999 -999 -999 "William Roman" +"AMP" "RD080406" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 8 7 2008 NA NA NA 6 -999 NA "MD" "PC" -22.31986 166.29339 "HR" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA4" 5 19 -999 -999 -999 -999 "William Roman" +"AMP" "RD080407" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 8 7 2008 NA NA NA 6 -999 NA "MD" "PC" -22.3176 166.29289 "HR" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA3" 5 19.4 -999 -999 -999 -999 "William Roman" +"AMP" "RD090097" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 29 7 2009 NA NA "S" 3 -999 NA "MM" "LM" -22.32455 166.30448 "HR" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA1" 7 9.3 -999 -999 -999 -999 "Drelon" +"AMP" "RD090099" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 30 6 2009 NA NA "N" 3 -999 NA "MM" "LM" -22.32279 166.29558 "HR" "AP" "Ile lagonaire" "lagon profond" "Detritique" "Fond lagonaire" "D1" 7 16.4 -999 -999 -999 -999 "William Roman" +"AMP" "RD090100" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 1 7 2009 NA NA "SE" 2 -999 NA "MM" "LM" -22.32232 166.3074 "RE" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG2" 5 10.4 -999 -999 -999 -999 "William Roman" +"AMP" "RD090101" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 1 7 2009 NA NA "SE" 2 -999 NA "MM" "LM" -22.31995 166.31127 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA1" 7 10.8 -999 -999 -999 -999 "William Roman" +"AMP" "RD090103" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 30 6 2009 NA NA "N" 3 -999 NA "MM" "LM" -22.32294 166.30058 "HR" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" NA 7 13.6 -999 -999 -999 -999 "William Roman" +"AMP" "RD090104" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 30 6 2009 NA NA "N" 3 -999 NA "MM" "LM" -22.32201 166.30287 "HR" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA3" 7 15 -999 -999 -999 -999 "William Roman" +"AMP" "RD090105" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 30 6 2009 NA NA "N" 3 -999 NA "MM" "LM" -22.31956 166.30596 "HR" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA1" 6 15.2 -999 -999 -999 -999 "William Roman" +"AMP" "RD090106" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 1 7 2009 NA NA "SE" 2 -999 NA "MM" "LM" -22.31693 166.30983 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG2" 6 12 -999 -999 -999 -999 "William Roman" +"AMP" "RD090107" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 1 7 2009 NA NA "SE" 2 -999 NA "MM" "LM" -22.31697 166.31482 "HR" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA2" 6 10.3 -999 -999 -999 -999 "William Roman" +"AMP" "RD090108" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 1 7 2009 NA NA "SE" 2 -999 NA "MM" "LM" -22.31402 166.31273 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG4" 7 13 -999 -999 -999 -999 "William Roman" +"AMP" "RD090109" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 30 6 2009 NA NA "N" 3 -999 NA "MM" "LM" -22.32103 166.29871 "HR" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA1" 5 15.3 -999 -999 -999 -999 "William Roman" +"AMP" "RD090110" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 30 6 2009 NA NA "N" 3 -999 NA "MM" "LM" -22.31925 166.30095 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG4" 6 17.4 -999 -999 -999 -999 "William Roman" +"AMP" "RD090111" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 30 6 2009 NA NA "N" 3 -999 NA "MM" "LM" -22.31679 166.30415 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SA1" 7 17.3 -999 -999 -999 -999 "William Roman" +"AMP" "RD090112" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 1 7 2009 NA NA "SE" 2 -999 NA "MM" "LM" -22.31446 166.30832 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG4" 7 13.4 -999 -999 -999 -999 "William Roman" +"AMP" "RD090114" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 30 6 2009 NA NA "N" 3 -999 NA "MM" "LM" -22.32001 166.2934 "HR" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA1" 6 18.9 -999 -999 -999 -999 "William Roman" +"AMP" "RD090115" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 30 6 2009 NA NA "N" 3 -999 NA "MM" "LM" -22.31815 166.29695 "HR" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA4" 7 19.3 -999 -999 -999 -999 "William Roman" +"AMP" "RD090116" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 30 6 2009 NA NA "N" 3 -999 NA "MM" "LM" -22.3162 166.29944 "HR" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA1" 7 18.9 -999 -999 -999 -999 "William Roman" +"AMP" "RD090117" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 1 7 2009 NA NA "SE" 2 -999 NA "MM" "LM" -22.31396 166.30297 "HR" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA1" 7 15.6 -999 -999 -999 -999 "Drelon" +"AMP" "RD090118" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 1 7 2009 NA NA "SE" 2 -999 NA "MM" "LM" -22.31183 166.30667 "HR" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA4" 6 14.6 -999 -999 -999 -999 "William Roman" +"AMP" "RD090119" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 1 7 2009 NA NA "SE" 2 -999 NA "MM" "LM" -22.30876 166.30855 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG4" 7 13.2 -999 -999 -999 -999 "Drelon" +"AMP" "RD090120" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 30 6 2009 NA NA "N" 3 -999 NA "MM" "LM" -22.31763 166.29292 "HR" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA1" 6 18.9 -999 -999 -999 -999 "William Roman" +"AMP" "RD090121" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 30 6 2009 NA NA "N" 3 -999 NA "MM" "LM" -22.31538 166.29559 "HR" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA1" 6 19.8 -999 -999 -999 -999 "William Roman" +"AMP" "RD090122" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 30 6 2009 NA NA "N" 3 -999 NA "MM" "LM" -22.31318 166.29811 "HR" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA3" 6 20.3 -999 -999 -999 -999 "William Roman" +"AMP" "RD090123" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 1 7 2009 NA NA "SE" 2 -999 NA "MM" "LM" -22.31101 166.30134 "HR" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA3" 6 15.1 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "RD090124" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 1 7 2009 NA NA "SE" 2 -999 NA "MM" "LM" -22.30848 166.30512 "HR" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA3" 6 14.5 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "RD090125" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 1 7 2009 NA NA "SE" 2 -999 NA "MM" "LM" -22.30606 166.30659 "HR" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA2" 6 14.3 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "RD090126" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 30 6 2009 NA NA "N" 3 -999 NA "MM" "LM" -22.31482 166.29189 "HR" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA4" 7 19.4 -999 -999 -999 -999 "William Roman" +"AMP" "RD090127" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 30 6 2009 NA NA "N" 3 -999 NA "MM" "LM" -22.31244 166.29392 "HR" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA1" 5 21.5 -999 -999 -999 -999 "William Roman" +"AMP" "RD090128" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 26 6 2009 NA NA NA 2 -999 NA "MD" "PC" -22.30978 166.29556 "HR" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA1" 6 13 -999 -999 -999 -999 "William Roman" +"AMP" "RD090129" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 26 6 2009 NA NA NA 2 -999 NA "MD" "PC" -22.30791 166.29906 "HR" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA1" 4 13.7 -999 -999 -999 -999 "William Roman" +"AMP" "RD090130" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 26 6 2009 NA NA NA 2 -999 NA "MD" "PC" -22.30554 166.30322 "HR" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA1" 7 14.9 -999 -999 -999 -999 "William Roman" +"AMP" "RD090131" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 26 6 2009 NA NA NA 2 -999 NA "MD" "PC" -22.30307 166.30452 "HR" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA1" 5 14.1 -999 -999 -999 -999 "William Roman" +"AMP" "RD090193" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 30 6 2009 NA NA "N" 3 -999 NA "MM" "LM" -22.31234 166.2909 "HR" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA1" 5 19.4 -999 -999 -999 -999 "William Roman" +"AMP" "RD100067" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 3 3 2010 NA NA "0" 0 -999 NA "MM" "LD" -22.3229285 166.3006841 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG4" 8 14.3 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "RD100084" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 3 3 2010 NA NA "0" 0 -999 NA "MD" "LD" -22.3078476 166.2992149 "HR" "AP" "Ile lagonaire" "lagon profond" "Detritique" "Fond lagonaire" "D1" 7 15.3 -999 -999 -999 -999 NA +"AMP" "RD100085" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 3 3 2010 NA NA "0" 0 -999 NA "MM" "LD" -22.309738 166.295813 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG3" 6 13.8 -999 -999 -999 -999 "William Roman" +"AMP" "RD100086" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 3 3 2010 NA NA "0" 0 -999 NA "MM" "LD" -22.3210253 166.2987636 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG3" 9 15.9 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "RD100087" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 3 3 2010 NA NA "0" 0 -999 NA "MM" "LD" -22.318103 166.2970644 "HR" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA4" 5 19.7 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "RD100088" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 3 3 2010 NA NA "0" 0 -999 NA "MM" "LD" -22.3153791 166.2957215 "HR" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA2" 9 20.1 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "RD100089" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 3 3 2010 NA NA "0" 0 -999 NA "MM" "LD" -22.3124494 166.2940107 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG4" 8 20 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "RD100090" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 3 3 2010 NA NA "0" 0 -999 NA "MM" "LD" -22.3130425 166.2983685 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG4" 7 18 -999 -999 -999 -999 "William Roman" +"AMP" "RD100091" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 3 3 2010 NA NA "0" 0 -999 NA "MM" "LD" -22.3161721 166.2995852 "HR" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA1" 5 17.8 -999 -999 -999 -999 "William Roman" +"AMP" "RD100092" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 3 3 2010 NA NA "0" 0 -999 NA "MM" "LD" -22.3192755 166.3011259 "HR" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA2" 8 16.2 -999 -999 -999 -999 "William Roman" +"AMP" "RD100093" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 3 3 2010 NA NA "0" 0 -999 NA "PM" "LD" -22.3220567 166.3030828 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG3" 6 14.5 -999 -999 -999 -999 "William Roman" +"AMP" "RD100094" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 3 3 2010 NA NA "0" 0 -999 NA "MD" "LD" -22.3195839 166.306018 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG3" 6 14.4 -999 -999 -999 -999 "William Roman" +"AMP" "RD100095" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 3 3 2010 NA NA "0" 0 -999 NA "MD" "LD" -22.3167905 166.3042316 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG1" 8 16 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "RD100096" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 3 3 2010 NA NA "0" 0 -999 NA "MD" "LD" -22.310936 166.3014607 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG1" 9 16.2 -999 -999 -999 -999 "William Roman" +"AMP" "RD100097" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 3 3 2010 NA NA "0" 0 -999 NA "MD" "LD" -22.313915 166.3030453 "HR" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA2" 9 16.5 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "RD100098" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 3 3 2010 NA NA "0" 0 -999 NA "MD" "LD" -22.3083853 166.3054033 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG2" 7 15.5 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "RD100107" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 3 3 2010 NA NA "0" 0 -999 NA "MD" "LD" -22.3199278 166.3113922 "RE" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG4" 6.5 11.4 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "RD100108" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 3 3 2010 NA NA "0" 0 -999 NA "PM" "LD" -22.3222861 166.3075812 "RE" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG1" 7 11.3 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "RD100127" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 3 3 2010 NA NA "0" 0 -999 NA "MM" "LD" -22.3102921 166.2923598 "HR" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA3" 8 19.3 -999 -999 -999 -999 "William Roman" +"AMP" "RD100135" "SVR" "Radiales Signal laregnere" "RD" NA NA 1 3 3 2010 NA NA "0" 0 -999 NA "MD" "LD" -22.3192988 166.3170887 "RE" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG1" 5 9.1 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "RL070141" "SVR" "Recif Laregnere" "RL" NA NA 1 2 7 2007 NA NA "0" 0 -999 NA "MD" "LD" -22.32912 166.30352 "HR" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA4" -999 9.2 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "RL070142" "SVR" "Recif Laregnere" "RL" NA NA 1 2 7 2007 NA NA "0" 0 -999 NA "MD" "LD" -22.32814 166.30159 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Algueraie" "Recif intermediaire" "MA4" -999 5.3 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "RL070211" "SVR" "Recif Laregnere" "RL" NA NA 1 5 7 2007 NA NA NA 2 -999 NA "MD" "LD" -22.33223 166.30366 "HR" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA1" -999 11.7 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "RL070213" "SVR" "Recif Laregnere" "RL" NA NA 1 5 7 2007 NA NA NA 2 -999 NA "MD" "LD" -22.32958 166.3003 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Recif intermediaire" "SA5" -999 5.1 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "RL070231" "SVR" "Recif Laregnere" "RL" NA NA 1 6 7 2007 NA NA NA -999 -999 NA "MD" "LD" -22.3338 166.29889 "HR" "AP" "Complexe de massif corallien de lagon" "front recifal" "Fond lagonaire" "Recif intermediaire" "SA4" -999 9.2 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "RL070232" "SVR" "Recif Laregnere" "RL" NA NA 1 6 7 2007 NA NA NA -999 -999 NA "MD" "LD" -22.33374 166.29488 "HR" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Recif intermediaire" "D2" -999 13.5 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "RL070249" "SVR" "Recif Laregnere" "RL" NA NA 1 31 7 2007 NA NA NA -999 -999 NA "MD" "LD" -22.33098 166.30192 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Algueraie" "Recif intermediaire" "MA4" -999 7.8 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "RL070250" "SVR" "Recif Laregnere" "RL" NA NA 1 31 7 2007 NA NA NA -999 -999 NA "MD" "LD" -22.33238 166.30029 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Detritique" "Recif intermediaire" "D2" -999 5.5 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "RL070260" "SVR" "Recif Laregnere" "RL" NA NA 1 8 11 2007 NA NA NA -999 -999 NA "MD" "DC" -22.3337 166.30154 "HR" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA1" -999 11.5 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "RL070261" "SVR" "Recif Laregnere" "RL" NA NA 1 8 11 2007 NA NA NA -999 -999 NA "MD" "DC" -22.33509 166.29959 "HR" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA3" -999 12.8 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "RL070262" "SVR" "Recif Laregnere" "RL" NA NA 1 8 11 2007 NA NA NA -999 -999 NA "MD" "DC" -22.33547 166.29651 "HR" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA4" -999 14.1 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "RL070263" "SVR" "Recif Laregnere" "RL" NA NA 1 8 11 2007 NA NA NA -999 -999 NA "MD" "DC" -22.33486 166.29358 "HR" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA4" -999 18 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "RL070264" "SVR" "Recif Laregnere" "RL" NA NA 1 8 11 2007 NA NA NA -999 -999 NA "MD" "DC" -22.33128 166.2937 "HR" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Recif intermediaire" "D5" -999 14 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "RL070270" "SVR" "Recif Laregnere" "RL" NA NA 1 16 11 2007 NA NA NA -999 -999 NA "MM" "PC" -22.32796 166.29865 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Recif intermediaire" NA -999 4.8 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "RL070272" "SVR" "Recif Laregnere" "RL" NA NA 1 16 11 2007 NA NA NA -999 -999 NA "PM" "PC" -22.32433 166.29845 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Recif intermediaire" "SA1" -999 7.7 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "RL070286" "SVR" "Recif Laregnere" "RL" NA NA 1 25 1 2008 NA NA NA -999 -999 NA "MD" "DQ" -22.33009 166.29395 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Recif intermediaire" "SA4" -999 6.5 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "RL070287" "SVR" "Recif Laregnere" "RL" NA NA 1 25 1 2008 NA NA NA -999 -999 NA "MD" "DQ" -22.32698 166.29559 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG1" -999 13.7 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "RL070288" "SVR" "Recif Laregnere" "RL" NA NA 1 25 1 2008 NA NA NA -999 -999 NA "MD" "DQ" -22.32587 166.29521 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG2" -999 13.8 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "RL070289" "SVR" "Recif Laregnere" "RL" NA NA 1 25 1 2008 NA NA NA -999 -999 NA "MD" "DQ" -22.32454 166.2968 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG3" -999 11.9 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "RL070290" "SVR" "Recif Laregnere" "RL" NA NA 1 25 1 2008 NA NA NA -999 -999 NA "MD" "DQ" -22.32312 166.29955 "HR" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA1" -999 13.8 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "RL070291" "SVR" "Recif Laregnere" "RL" NA NA 1 25 1 2008 NA NA NA -999 -999 NA "MD" "DQ" -22.32634 166.29973 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Recif intermediaire" "MA4" -999 14.3 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "RL070292" "SVR" "Recif Laregnere" "RL" NA NA 1 25 1 2008 NA NA NA -999 -999 NA "MD" "DQ" -22.32756 166.29794 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Detritique" "Recif intermediaire" "SA4" -999 4.5 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "RL070294" "SVR" "Recif Laregnere" "RL" NA NA 1 25 1 2008 NA NA NA -999 -999 NA "MD" "DQ" -22.33158 166.30096 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Herbier" "Recif intermediaire" "SG2" -999 7 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "RL070295" "SVR" "Recif Laregnere" "RL" NA NA 1 25 1 2008 NA NA NA -999 -999 NA "MD" "DQ" -22.3304 166.30191 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Herbier" "Recif intermediaire" "SG3" -999 8 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "RL070296" "SVR" "Recif Laregnere" "RL" NA NA 1 25 1 2008 NA NA NA -999 -999 NA "MD" "DQ" -22.33015 166.3042 "HR" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA1" -999 11 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "RL070300" "SVR" "Recif Laregnere" "RL" NA NA 1 25 1 2008 NA NA NA -999 -999 NA "MD" "DQ" -22.32933 166.30362 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG3" -999 10 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "RL070301" "SVR" "Recif Laregnere" "RL" NA NA 1 25 1 2008 NA NA NA -999 -999 NA "MD" "DQ" -22.32885 166.3011 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Algueraie" "Recif intermediaire" "MA2" -999 6.3 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "RL07285B" "SVR" "Recif Laregnere" "RL" NA NA 1 25 1 2008 NA NA NA -999 -999 NA "MD" "DQ" -22.32858 166.2944 "HR" "AP" "Ile lagonaire" "lagon profond" "Detritique" "Fond lagonaire" "D7" -999 13 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "RL080142" "SVR" "Recif Laregnere" "RL" NA NA 1 2 7 2008 NA NA NA 2 -999 NA "MD" "DC" -22.32809 166.30165 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Herbier" "Recif intermediaire" "SG3" 8 7.3 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "RL080144" "SVR" "Recif Laregnere" "RL" NA NA 1 2 7 2008 NA NA NA 2 -999 NA "MD" "DC" -22.33377 166.29869 "HR" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Recif intermediaire" "D1" 7 7.8 -999 -999 -999 -999 "Drelon" +"AMP" "RL080145" "SVR" "Recif Laregnere" "RL" NA NA 1 2 7 2008 NA NA NA 2 -999 NA "MD" "DC" -22.33414 166.29657 "HR" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Recif intermediaire" NA 9 4.3 -999 -999 -999 -999 "Drelon" +"AMP" "RL080146" "SVR" "Recif Laregnere" "RL" NA NA 1 3 7 2008 NA NA NA 1 -999 NA "MD" "NL" -22.33331 166.29472 "HR" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Recif intermediaire" "D1" 9 13 -999 -999 -999 -999 "Drelon" +"AMP" "RL080150" "SVR" "Recif Laregnere" "RL" NA NA 1 2 7 2008 NA NA NA 2 -999 NA "MD" "DC" -22.32814 166.29855 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Herbier" "Recif intermediaire" "SG3" 10 4.8 -999 -999 -999 -999 "Drelon" +"AMP" "RL080211" "SVR" "Recif Laregnere" "RL" NA NA 1 2 7 2008 NA NA NA 2 -999 NA "MM" "DC" -22.33224 166.30354 "HR" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA1" 7 10.1 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "RL080213" "SVR" "Recif Laregnere" "RL" NA NA 1 2 7 2008 NA NA NA 2 -999 NA "MD" "DC" -22.32966 166.30029 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Recif intermediaire" "SA3" 8 5.6 -999 -999 -999 -999 "Drelon" +"AMP" "RL080232" "SVR" "Recif Laregnere" "RL" NA NA 1 3 7 2008 NA NA NA 1 -999 NA "MD" "NL" -22.33375 166.29488 "HR" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Recif intermediaire" "D1" 8 12.7 -999 -999 -999 -999 "Drelon" +"AMP" "RL080250" "SVR" "Recif Laregnere" "RL" NA NA 1 2 7 2008 NA NA NA 2 -999 NA "MD" "DC" -22.33245 166.30026 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Detritique" "Recif intermediaire" "D2" 9 5.3 -999 -999 -999 -999 "Drelon" +"AMP" "RL080264" "SVR" "Recif Laregnere" "RL" NA NA 1 3 7 2008 NA NA NA 1 -999 NA "MD" "NL" -22.33133 166.29374 "HR" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Recif intermediaire" "D7" 8 14.5 -999 -999 -999 -999 "Drelon" +"AMP" "RL080268" "SVR" "Recif Laregnere" "RL" NA NA 1 3 7 2008 NA NA NA 1 -999 NA "MD" "NL" -22.33067 166.29381 "HR" "AP" "Complexe de massif corallien de lagon" "front recifal" "Fond lagonaire" "Recif intermediaire" "SA3" 9 13.6 -999 -999 -999 -999 "Drelon" +"AMP" "RL080269" "SVR" "Recif Laregnere" "RL" NA NA 1 2 7 2008 NA NA NA 2 -999 NA "MD" "DC" -22.32691 166.29654 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG2" 7 9.7 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "RL080272" "SVR" "Recif Laregnere" "RL" NA NA 1 2 7 2008 NA NA NA 2 -999 NA "MD" "DC" -22.32424 166.29851 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Recif intermediaire" "SA1" 8 7.7 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "RL080273" "SVR" "Recif Laregnere" "RL" NA NA 1 2 7 2008 NA NA NA 2 -999 NA "MD" "DC" -22.32885 166.29418 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Recif intermediaire" "SG4" 9 14.2 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "RL080274" "SVR" "Recif Laregnere" "RL" NA NA 1 2 7 2008 NA NA NA 2 -999 NA "MD" "DC" -22.32569 166.30197 "HR" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA3" 10 7.9 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "RL080285" "SVR" "Recif Laregnere" "RL" NA NA 1 2 7 2008 NA NA NA 2 -999 NA "MD" "DC" -22.32867 166.29468 "HR" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA3" 10 11.8 -999 -999 -999 -999 "Drelon" +"AMP" "RL080286" "SVR" "Recif Laregnere" "RL" NA NA 1 3 7 2008 NA NA NA 1 -999 NA "MD" "NL" -22.33007 166.29401 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Recif intermediaire" "D6" 8 11 -999 -999 -999 -999 "Drelon" +"AMP" "RL080289" "SVR" "Recif Laregnere" "RL" NA NA 1 2 7 2008 NA NA NA 2 -999 NA "MD" "DC" -22.32444 166.29682 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG2" 8 11.7 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "RL080291" "SVR" "Recif Laregnere" "RL" NA NA 1 2 7 2008 NA NA NA 2 -999 NA "MD" "DC" -22.32636 166.29962 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Algueraie" "Recif intermediaire" "MA4" 7 5.3 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "RL080292" "SVR" "Recif Laregnere" "RL" NA NA 1 2 7 2008 NA NA NA 2 -999 NA "MD" "DC" -22.32764 166.29787 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Recif intermediaire" "SA3" 9 3.8 -999 -999 -999 -999 "Drelon" +"AMP" "RL080293" "SVR" "Recif Laregnere" "RL" NA NA 1 2 7 2008 NA NA NA 2 -999 NA "MD" "DC" -22.32905 166.29937 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Recif intermediaire" "SA1" 9 4.7 -999 -999 -999 -999 "Drelon" +"AMP" "RL080294" "SVR" "Recif Laregnere" "RL" NA NA 1 2 7 2008 NA NA NA 2 -999 NA "MD" "DC" -22.33162 166.3011 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Herbier" "Recif intermediaire" "SG2" 6 7.3 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "RL080296" "SVR" "Recif Laregnere" "RL" NA NA 1 2 7 2008 NA NA NA 2 -999 NA "MM" "DC" -22.33016 166.30427 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG3" 7 11.2 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "RL080301" "SVR" "Recif Laregnere" "RL" NA NA 1 2 7 2008 NA NA NA 2 -999 NA "MD" "DC" -22.32903 166.30108 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Algueraie" "Recif intermediaire" "MA2" 6 6.5 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "RL090072" "SVR" "Recif Laregnere" "RL" NA NA 1 29 7 2009 NA NA "S" 3 -999 NA "MM" "LM" -22.3291 166.2943 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Fond lagonaire" "Recif intermediaire" "SA1" 8 12.7 -999 -999 -999 -999 "Drelon" +"AMP" "RL090074" "SVR" "Recif Laregnere" "RL" NA NA 1 29 7 2009 NA NA "S" 3 -999 NA "MM" "LM" -22.33084 166.29373 "HR" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Recif intermediaire" "D5" 10 13.9 -999 -999 -999 -999 "Drelon" +"AMP" "RL090075" "SVR" "Recif Laregnere" "RL" NA NA 1 29 7 2009 NA NA "S" 3 -999 NA "MM" "LM" -22.33192 166.29388 "HR" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Recif intermediaire" "D5" 9 15.6 -999 -999 -999 -999 "Drelon" +"AMP" "RL090076" "SVR" "Recif Laregnere" "RL" NA NA 1 29 7 2009 NA NA "S" 3 -999 NA "MM" "LM" -22.33299 166.2943 "HR" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Recif intermediaire" "D1" 9 14.6 -999 -999 -999 -999 "Drelon" +"AMP" "RL090078" "SVR" "Recif Laregnere" "RL" NA NA 1 25 6 2009 NA NA NA 3 -999 NA "MD" "PC" -22.33418 166.29662 "HR" "AP" "Complexe de massif corallien de lagon" "front recifal" "Corail vivant" "Recif intermediaire" "LC3" 11 3.1 -999 -999 -999 -999 "Drelon" +"AMP" "RL090080" "SVR" "Recif Laregnere" "RL" NA NA 1 25 6 2009 NA NA NA 3 -999 NA "MD" "PC" -22.33262 166.30032 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Detritique" "Recif intermediaire" "D6" 9 5.5 -999 -999 -999 -999 "Drelon" +"AMP" "RL090089" "SVR" "Recif Laregnere" "RL" NA NA 1 29 7 2009 NA NA "S" 3 -999 NA "MM" "LM" -22.32937 166.29905 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Detritique" "Recif intermediaire" "D3" 8 4.3 -999 -999 -999 -999 "Drelon" +"AMP" "RL090091" "SVR" "Recif Laregnere" "RL" NA NA 1 29 7 2009 NA NA "S" 3 -999 NA "MM" "LM" -22.32761 166.2976 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Detritique" "Recif intermediaire" "SA5" 9 3.2 -999 -999 -999 -999 "Drelon" +"AMP" "RL090093" "SVR" "Recif Laregnere" "RL" NA NA 1 29 7 2009 NA NA "S" 3 -999 NA "MM" "LM" -22.328 166.29576 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Recif intermediaire" "D5" 7 4.4 -999 -999 -999 -999 "Drelon" +"AMP" "RL090095" "SVR" "Recif Laregnere" "RL" NA NA 1 29 7 2009 NA NA "S" 3 -999 NA "MM" "LM" -22.32618 166.29949 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Algueraie" "Recif intermediaire" "MA3" 8 5.8 -999 -999 -999 -999 "Drelon" +"AMP" "RL090098" "SVR" "Recif Laregnere" "RL" NA NA 1 29 7 2009 NA NA "S" 3 -999 NA "MM" "LM" -22.32427 166.29676 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG2" 7 12.2 -999 -999 -999 -999 "Drelon" +"AMP" "RL100064" "SVR" "Recif Laregnere" "RL" NA NA 1 2 3 2010 NA NA "0" 0 -999 NA "MM" "LD" -22.3315955 166.3013425 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Algueraie" "Recif intermediaire" "MA4" 6 8.6 -999 -999 -999 -999 "Drelon" +"AMP" "RL100065" "SVR" "Recif Laregnere" "RL" NA NA 1 2 3 2010 NA NA "0" 0 -999 NA "MM" "LD" -22.332547 166.3004609 "HR" "AP" "Ile lagonaire" "lagon profond" "Detritique" "Recif intermediaire" "D5" 8 7 -999 -999 -999 -999 "Drelon" +"AMP" "RL100066" "SVR" "Recif Laregnere" "RL" NA NA 1 2 3 2010 NA NA "0" 0 -999 NA "MD" "LD" -22.3342828 166.2968484 "HR" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Recif intermediaire" "D5" 7 7.8 -999 -999 -999 -999 "Drelon" +"AMP" "RL100074" "SVR" "Recif Laregnere" "RL" NA NA 1 2 3 2010 NA NA "0" 0 -999 NA "PM" "LD" -22.3295617 166.2991186 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Corail vivant" "Recif intermediaire" "LC1" 7 4.5 -999 -999 -999 -999 "Drelon" +"AMP" "RL100075" "SVR" "Recif Laregnere" "RL" NA NA 1 2 3 2010 NA NA "0" 0 -999 NA "PM" "LD" -22.3276111 166.2975576 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Detritique" "Recif intermediaire" "D2" 7 4.8 -999 -999 -999 -999 "Drelon" +"AMP" "RL100076" "SVR" "Recif Laregnere" "RL" NA NA 1 23 3 2010 NA NA NA 5 -999 NA "MM" "PQ" -22.3279463 166.2957783 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Recif intermediaire" "LC3" 6 7.6 -999 -999 -999 -999 "Drelon" +"AMP" "RL100078" "SVR" "Recif Laregnere" "RL" NA NA 1 2 3 2010 NA NA "0" 0 -999 NA "MD" "LD" -22.3309087 166.2937575 "HR" "AP" "Complexe de massif corallien de lagon" "front recifal" "Fond lagonaire" "Recif intermediaire" NA 8 15.4 -999 -999 -999 -999 "Drelon" +"AMP" "RL100079" "SVR" "Recif Laregnere" "RL" NA NA 1 2 3 2010 NA NA "0" 0 -999 NA "MD" "LD" -22.3320366 166.2938894 "HR" "AP" "Complexe de massif corallien de lagon" "front recifal" "Fond lagonaire" "Recif intermediaire" "SA1" 8 16.6 -999 -999 -999 -999 "Drelon" +"AMP" "RL100080" "SVR" "Recif Laregnere" "RL" NA NA 1 2 3 2010 NA NA "0" 0 -999 NA "MD" "LD" -22.333073 166.2943444 "HR" "AP" "Complexe de massif corallien de lagon" "front recifal" "Fond lagonaire" "Recif intermediaire" "SA3" 9 15.8 -999 -999 -999 -999 "Drelon" +"AMP" "RL10065B" "SVR" "Recif Laregnere" "RL" NA NA 1 2 3 2010 NA NA "0" 0 -999 NA "MD" "LD" -22.332609 166.3003223 "HR" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Detritique" "Recif intermediaire" "D7" 8 6.3 -999 -999 -999 -999 "Drelon" +"AMP" "RS070167" "SVR" "Recif Senez" "RS" NA NA 1 3 7 2007 NA NA "0" 0 -999 NA "MD" "LD" -22.29556 166.33023 "HR" "AP" "Ile lagonaire" "lagon profond" "Detritique" "Fond lagonaire" "D6" -999 9.7 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "RS070168" "SVR" "Recif Senez" "RS" NA NA 1 3 7 2007 NA NA "0" 0 -999 NA "MD" "LD" -22.29635 166.33105 "HR" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" NA -999 7.2 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "RS070169" "SVR" "Recif Senez" "RS" NA NA 1 3 7 2007 NA NA "0" 0 -999 NA "MD" "LD" -22.29629 166.33191 "HR" "AP" "Complexe de massif corallien de lagon" "front recifal" "Corail vivant" "Recif intermediaire" "LC1" -999 2.7 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "RS070170" "SVR" "Recif Senez" "RS" NA NA 1 3 7 2007 NA NA "0" 0 -999 NA "MD" "LD" -22.29608 166.33301 "HR" "AP" "Ile lagonaire" "lagon profond" "Corail vivant" "Fond lagonaire" "LC5" -999 6 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "RS070171" "SVR" "Recif Senez" "RS" NA NA 1 3 7 2007 NA NA "0" 0 -999 NA "MD" "LD" -22.29522 166.33315 "HR" "AP" "Ile lagonaire" "lagon profond" "Detritique" "Fond lagonaire" "D1" -999 4.9 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "RS070172" "SVR" "Recif Senez" "RS" NA NA 1 3 7 2007 NA NA "0" 0 -999 NA "MD" "LD" -22.29383 166.33268 "HR" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Recif intermediaire" NA -999 7.6 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "RS070187" "SVR" "Recif Senez" "RS" NA NA 1 4 7 2007 NA NA "0" 0 -999 NA "MD" "LD" -22.29511 166.33024 "HR" "AP" "Ile lagonaire" "lagon profond" "Detritique" "Fond lagonaire" "D1" -999 5.5 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "RS070188" "SVR" "Recif Senez" "RS" NA NA 1 4 7 2007 NA NA "0" 0 -999 NA "MD" "LD" -22.29454 166.33158 "HR" "AP" "Complexe de massif corallien de lagon" "front recifal" "Algueraie" "Recif intermediaire" "D4" -999 4.7 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "RS070189" "SVR" "Recif Senez" "RS" NA NA 1 4 7 2007 NA NA "0" 0 -999 NA "MD" "LD" -22.29565 166.33147 "HR" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Corail vivant" "Recif intermediaire" "LC2" -999 1.6 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "SI070002" "SVR" "Ilot Signal" "SI" NA NA 1 18 6 2007 NA NA NA -999 -999 NA "MD" "PC" -22.2944 166.29053 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Corail vivant" "Frangeant ilot" "D6" -999 4.8 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "SI070005" "SVR" "Ilot Signal" "SI" NA NA 1 18 6 2007 NA NA NA -999 -999 NA "MD" "PC" -22.293 166.29137 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Corail vivant" "Frangeant ilot" "LC2" -999 4.1 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "SI070024" "SVR" "Ilot Signal" "SI" NA NA 1 20 6 2007 NA NA NA -999 -999 NA "MM" "PC" -22.3013 166.28945 "RE" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Corail vivant" "Frangeant ilot" NA -999 7.1 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "SI070040" "SVR" "Ilot Signal" "SI" NA NA 1 21 6 2007 NA NA NA -999 -999 NA "MM" "PC" -22.29543 166.29675 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Detritique" "Frangeant ilot" "D6" -999 5.6 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "SI070042" "SVR" "Ilot Signal" "SI" NA NA 1 21 6 2007 NA NA NA -999 -999 NA "MM" "PC" -22.29688 166.29815 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Detritique" "Frangeant ilot" NA -999 6.9 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "SI070045" "SVR" "Ilot Signal" "SI" NA NA 1 21 6 2007 NA NA NA -999 -999 NA "MM" "PC" -22.30003 166.29947 "RE" "AP" "Ile lagonaire" "lagon profond" "Detritique" "Fond lagonaire" "D2" -999 6.4 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "SI070046" "SVR" "Ilot Signal" "SI" NA NA 1 21 6 2007 NA NA NA -999 -999 NA "MM" "PC" -22.30175 166.2992 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA5" -999 7.9 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "SI070049" "SVR" "Ilot Signal" "SI" NA NA 1 21 6 2007 NA NA NA -999 -999 NA "PM" "PC" -22.30462 166.29783 "HR" "AP" "Ile lagonaire" "lagon profond" "Detritique" "Fond lagonaire" "D3" -999 7 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "SI070059" "SVR" "Ilot Signal" "SI" NA NA 1 21 6 2007 NA NA NA -999 -999 NA "MD" "PC" -22.2955 166.28992 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Herbier" "Frangeant ilot" "SG1" -999 6.1 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "SI070078" "SVR" "Ilot Signal" "SI" NA NA 1 25 6 2007 NA NA NA -999 -999 NA "BM" "LM" -22.29322 166.29297 "RE" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Corail vivant" "Frangeant ilot" "LC1" -999 2.1 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "SI070079" "SVR" "Ilot Signal" "SI" NA NA 1 25 6 2007 NA NA NA -999 -999 NA "MM" "LM" -22.29356 166.2945 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Corail vivant" "Frangeant ilot" "LC2" -999 3.1 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "SI070080" "SVR" "Ilot Signal" "SI" NA NA 1 25 6 2007 NA NA NA -999 -999 NA "MM" "LM" -22.29463 166.29572 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Corail vivant" "Frangeant ilot" "LC2" -999 4 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "SI070081" "SVR" "Ilot Signal" "SI" NA NA 1 25 6 2007 NA NA NA -999 -999 NA "MM" "LM" -22.29768 166.28913 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Herbier" "Frangeant ilot" "SG2" -999 4.4 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "SI070082" "SVR" "Ilot Signal" "SI" NA NA 1 25 6 2007 NA NA NA -999 -999 NA "MM" "LM" -22.29808 166.28766 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA1" -999 15.1 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "SI070083" "SVR" "Ilot Signal" "SI" NA NA 1 25 6 2007 NA NA NA -999 -999 NA "MM" "LM" -22.29662 166.28791 "RE" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG3" -999 13.4 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "SI070085" "SVR" "Ilot Signal" "SI" NA NA 1 26 6 2007 NA NA NA -999 -999 NA "MD" "LM" -22.29501 166.28797 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SG4" -999 13 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "SI070151" "SVR" "Ilot Signal" "SI" NA NA 1 3 7 2007 NA NA "0" 0 -999 NA "PM" "LD" -22.30041 166.28919 "RE" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Frangeant ilot" "D5" -999 6.3 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "SI070152" "SVR" "Ilot Signal" "SI" NA NA 1 3 7 2007 NA NA "0" 0 -999 NA "PM" "LD" -22.30191 166.28962 "RE" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Frangeant ilot" "D5" -999 6.4 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "SI070153" "SVR" "Ilot Signal" "SI" NA NA 1 3 7 2007 NA NA "0" 0 -999 NA "MD" "LD" -22.30355 166.2901 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Frangeant ilot" "D1" -999 7.4 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "SI070154" "SVR" "Ilot Signal" "SI" NA NA 1 3 7 2007 NA NA "0" 0 -999 NA "MD" "LD" -22.30518 166.29079 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Corail vivant" "Frangeant ilot" "D6" -999 10.9 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "SI070155" "SVR" "Ilot Signal" "SI" NA NA 1 3 7 2007 NA NA "0" 0 -999 NA "MD" "LD" -22.30647 166.29235 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Frangeant ilot" "D2" -999 6.9 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "SI070156" "SVR" "Ilot Signal" "SI" NA NA 1 3 7 2007 NA NA "0" 0 -999 NA "MD" "LD" -22.3066 166.29422 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Frangeant ilot" "D6" -999 8.4 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "SI070157" "SVR" "Ilot Signal" "SI" NA NA 1 3 7 2007 NA NA "0" 0 -999 NA "MD" "LD" -22.3057 166.29596 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Corail vivant" "Frangeant ilot" "D3" -999 7.6 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "SI070159" "SVR" "Ilot Signal" "SI" NA NA 1 3 7 2007 NA NA "0" 0 -999 NA "MD" "LD" -22.3028 166.29876 "RE" "AP" "Ile lagonaire" "lagon profond" "Detritique" "Fond lagonaire" "D6" -999 6.5 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "SI070160" "SVR" "Ilot Signal" "SI" NA NA 1 3 7 2007 NA NA "0" 0 -999 NA "MD" "LD" -22.30082 166.29937 "RE" "AP" "Ile lagonaire" "lagon profond" "Corail vivant" "Fond lagonaire" "D5" -999 6.7 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "SI070161" "SVR" "Ilot Signal" "SI" NA NA 1 3 7 2007 NA NA "0" 0 -999 NA "MD" "LD" -22.2987 166.29952 "RE" "AP" "Ile lagonaire" "lagon profond" "Detritique" "Fond lagonaire" "D6" -999 6.8 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "SI070163" "SVR" "Ilot Signal" "SI" NA NA 1 3 7 2007 NA NA "0" 0 -999 NA "MD" "LD" -22.29473 166.29664 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Herbier" "Frangeant ilot" "SG2" -999 7.4 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "SI070164" "SVR" "Ilot Signal" "SI" NA NA 1 3 7 2007 NA NA "0" 0 -999 NA "MD" "LD" -22.29326 166.295 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Herbier" "Frangeant ilot" "SG3" -999 6.4 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "SI070165" "SVR" "Ilot Signal" "SI" NA NA 1 3 7 2007 NA NA "0" 0 -999 NA "MD" "LD" -22.29416 166.29578 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Herbier" "Frangeant ilot" "SG2" -999 6 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "SI070166" "SVR" "Ilot Signal" "SI" NA NA 1 3 7 2007 NA NA "0" 0 -999 NA "MD" "LD" -22.29266 166.29394 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Herbier" "Frangeant ilot" NA -999 4 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "SI070181" "SVR" "Ilot Signal" "SI" NA NA 1 4 7 2007 NA NA "0" 0 -999 NA "MD" "LD" -22.29763 166.30041 "RE" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG2" -999 11.6 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "SI070184" "SVR" "Ilot Signal" "SI" NA NA 1 4 7 2007 NA NA "0" 0 -999 NA "MD" "LD" -22.29307 166.28886 "RE" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG3" -999 12 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "SI070185" "SVR" "Ilot Signal" "SI" NA NA 1 4 7 2007 NA NA "0" 0 -999 NA "MD" "LD" -22.29212 166.29027 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Herbier" "Frangeant ilot" "SG2" -999 9.4 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "SI070186" "SVR" "Ilot Signal" "SI" NA NA 1 4 7 2007 NA NA "0" 0 -999 NA "MD" "LD" -22.29196 166.29184 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Algueraie" "Frangeant ilot" "MA3" -999 3.5 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "SI070190" "SVR" "Ilot Signal" "SI" NA NA 1 5 7 2007 NA NA NA 2 -999 NA "MM" "LD" -22.29631 166.29938 "RE" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "SG4" -999 15.3 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "SI070191" "SVR" "Ilot Signal" "SI" NA NA 1 5 7 2007 NA NA NA 2 -999 NA "MM" "LD" -22.29962 166.30093 "RE" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA1" -999 9.8 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "SI070193" "SVR" "Ilot Signal" "SI" NA NA 1 5 7 2007 NA NA NA 2 -999 NA "MM" "LD" -22.30298 166.30011 "RE" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA4" -999 16.3 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "SI070195" "SVR" "Ilot Signal" "SI" NA NA 1 5 7 2007 NA NA NA 2 -999 NA "PM" "LD" -22.30626 166.29806 "RE" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG4" -999 13.8 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "SI070197" "SVR" "Ilot Signal" "SI" NA NA 1 5 7 2007 NA NA NA 2 -999 NA "MD" "LD" -22.30799 166.29458 "RE" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG2" -999 15.9 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "SI070199" "SVR" "Ilot Signal" "SI" NA NA 1 5 7 2007 NA NA NA 2 -999 NA "MD" "LD" -22.30706 166.29078 "RE" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG4" -999 16.5 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "SI070201" "SVR" "Ilot Signal" "SI" NA NA 1 5 7 2007 NA NA NA 2 -999 NA "MD" "LD" -22.3039 166.2885 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA1" -999 19.2 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "SI070221" "SVR" "Ilot Signal" "SI" NA NA 1 6 7 2007 NA NA NA -999 -999 NA "MM" "LD" -22.29188 166.29656 "RE" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA4" -999 18.6 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "SI070222" "SVR" "Ilot Signal" "SI" NA NA 1 6 7 2007 NA NA NA -999 -999 NA "MM" "LD" -22.30171 166.30043 "RE" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA4" -999 15.5 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "SI070223" "SVR" "Ilot Signal" "SI" NA NA 1 6 7 2007 NA NA NA -999 -999 NA "MM" "LD" -22.30694 166.29662 "RE" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG3" -999 15.5 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "SI070224" "SVR" "Ilot Signal" "SI" NA NA 1 6 7 2007 NA NA NA -999 -999 NA "MM" "LD" -22.30504 166.29925 "RE" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG3" -999 15.6 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "SI070225" "SVR" "Ilot Signal" "SI" NA NA 1 6 7 2007 NA NA NA -999 -999 NA "PM" "LD" -22.30787 166.2924 "RE" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "SG4" -999 17.2 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "SI070226" "SVR" "Ilot Signal" "SI" NA NA 1 6 7 2007 NA NA NA -999 -999 NA "MD" "LD" -22.30577 166.28939 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA1" -999 19.8 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "SI070227" "SVR" "Ilot Signal" "SI" NA NA 1 6 7 2007 NA NA NA -999 -999 NA "MD" "LD" -22.3021 166.28794 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA4" -999 18.2 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "SI070276" "SVR" "Ilot Signal" "SI" NA NA 1 29 11 2007 NA NA NA -999 -999 NA "MM" "LD" -22.29645 166.2897 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Corail vivant" "Frangeant ilot" "LC5" -999 6.3 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "SI070277" "SVR" "Ilot Signal" "SI" NA NA 1 29 11 2007 NA NA NA -999 -999 NA "MM" "LD" -22.29911 166.28903 "RE" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Frangeant ilot" NA -999 5.5 -999 -999 -999 -999 "Kevin Leleu" +"AMP" "SI080001" "SVR" "Ilot Signal" "SI" NA NA 1 25 6 2008 NA NA NA -999 -999 NA "MM" "DQ" -22.29503 166.29043 "RE" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Fond lagonaire" "Frangeant ilot" "SA3" 5 4.2 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "SI080005" "SVR" "Ilot Signal" "SI" NA NA 1 25 6 2008 NA NA NA -999 -999 NA "MM" "DQ" -22.2929 166.29136 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "SA4" 8 4.1 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "SI080024" "SVR" "Ilot Signal" "SI" NA NA 1 25 6 2008 NA NA NA -999 -999 NA "MD" "DQ" -22.30118 166.28927 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "MA4" 7 9.1 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "SI08002B" "SVR" "Ilot Signal" "SI" NA NA 1 26 6 2008 NA NA NA -999 -999 NA "MM" "DQ" -22.29451 166.29042 "RE" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Fond lagonaire" "Frangeant ilot" "SA5" 8 4.8 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "SI080043" "SVR" "Ilot Signal" "SI" NA NA 1 27 6 2008 NA NA NA -999 -999 NA "MM" "DC" -22.29729 166.29832 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Detritique" "Frangeant ilot" NA 8 6.2 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "SI080045" "SVR" "Ilot Signal" "SI" NA NA 1 24 6 2008 NA NA NA -999 -999 NA "MM" "LD" -22.29998 166.29944 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" NA 5 6.3 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "SI080047" "SVR" "Ilot Signal" "SI" NA NA 1 24 6 2008 NA NA NA -999 -999 NA "PM" "LD" -22.30247 166.29881 "HR" "AP" "Ile lagonaire" "lagon profond" "Detritique" "Fond lagonaire" "D2" 9 7.5 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "SI080048" "SVR" "Ilot Signal" "SI" NA NA 1 24 6 2008 NA NA NA -999 -999 NA "MD" "LD" -22.30343 166.29864 "HR" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" NA 9 7.5 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "SI080052" "SVR" "Ilot Signal" "SI" NA NA 1 27 6 2008 NA NA NA -999 -999 NA "MM" "DC" -22.30632 166.29485 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Frangeant ilot" "D2" 7 7.4 -999 -999 -999 -999 "Drelon" +"AMP" "SI080053" "SVR" "Ilot Signal" "SI" NA NA 1 27 6 2008 NA NA NA -999 -999 NA "MD" "DC" -22.30663 166.29382 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Frangeant ilot" "D1" 8 8.5 -999 -999 -999 -999 "Drelon" +"AMP" "SI080054" "SVR" "Ilot Signal" "SI" NA NA 1 27 6 2008 NA NA NA -999 -999 NA "MD" "DC" -22.30626 166.29181 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Frangeant ilot" "D1" 8 7.5 -999 -999 -999 -999 "Drelon" +"AMP" "SI080059" "SVR" "Ilot Signal" "SI" NA NA 1 25 6 2008 NA NA NA -999 -999 NA "MM" "DQ" -22.29549 166.28978 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Herbier" "Frangeant ilot" "SG3" 3 7.2 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "SI080083" "SVR" "Ilot Signal" "SI" NA NA 1 25 6 2008 NA NA NA -999 -999 NA "MD" "DQ" -22.29658 166.28811 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA1" 5 13 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "SI080085" "SVR" "Ilot Signal" "SI" NA NA 1 25 6 2008 NA NA NA -999 -999 NA "MM" "DQ" -22.29489 166.2881 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA1" 3 13.7 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "SI080086" "SVR" "Ilot Signal" "SI" NA NA 1 25 6 2008 NA NA NA -999 -999 NA "MM" "DQ" -22.2935 166.28833 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA1" 6 13.2 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "SI080151" "SVR" "Ilot Signal" "SI" NA NA 1 25 6 2008 NA NA NA -999 -999 NA "MD" "DQ" -22.30052 166.2891 "RE" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Frangeant ilot" NA 8 9 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "SI080155" "SVR" "Ilot Signal" "SI" NA NA 1 27 6 2008 NA NA NA -999 -999 NA "MM" "DC" -22.30655 166.29241 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Frangeant ilot" "D2" 8 6.8 -999 -999 -999 -999 "Drelon" +"AMP" "SI080157" "SVR" "Ilot Signal" "SI" NA NA 1 27 6 2008 NA NA NA -999 -999 NA "MD" "DC" -22.30568 166.29612 "HR" "AP" "Ile lagonaire" "lagon profond" "Detritique" "Frangeant ilot" "D1" 9 7.4 -999 -999 -999 -999 "Drelon" +"AMP" "SI080160" "SVR" "Ilot Signal" "SI" NA NA 1 24 6 2008 NA NA NA -999 -999 NA "MM" "LD" -22.30079 166.29946 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA3" 7 7.5 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "SI080161" "SVR" "Ilot Signal" "SI" NA NA 1 24 6 2008 NA NA NA -999 -999 NA "MM" "LD" -22.2986 166.29947 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA4" 8 7 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "SI080162" "SVR" "Ilot Signal" "SI" NA NA 1 27 6 2008 NA NA NA -999 -999 NA "MD" "DC" -22.2967 166.29815 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "SA1" 8 7 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "SI080163" "SVR" "Ilot Signal" "SI" NA NA 1 27 6 2008 NA NA NA -999 -999 NA "MM" "DC" -22.29475 166.29663 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Herbier" "Frangeant ilot" NA 9 7.6 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "SI080166" "SVR" "Ilot Signal" "SI" NA NA 1 25 6 2008 NA NA NA -999 -999 NA "MM" "DQ" -22.29263 166.29329 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "MA3" 10 3 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "SI080180" "SVR" "Ilot Signal" "SI" NA NA 1 24 6 2008 NA NA NA -999 -999 NA "MM" "LD" -22.30045 166.30239 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG4" 5 16.8 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "SI080184" "SVR" "Ilot Signal" "SI" NA NA 1 25 6 2008 NA NA NA -999 -999 NA "MM" "DQ" -22.29304 166.28924 "RE" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG3" 5 12.4 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "SI080186" "SVR" "Ilot Signal" "SI" NA NA 1 25 6 2008 NA NA NA -999 -999 NA "MM" "DQ" -22.29194 166.29175 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Algueraie" "Frangeant ilot" "MA3" 7 3.9 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "SI080191" "SVR" "Ilot Signal" "SI" NA NA 1 24 6 2008 NA NA NA -999 -999 NA "MM" "LD" -22.29917 166.30086 "RE" "AP" "Ile lagonaire" "lagon profond" "Algueraie" "Fond lagonaire" "MA1" 7 9.8 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "SI080192" "SVR" "Ilot Signal" "SI" NA NA 1 24 6 2008 NA NA NA -999 -999 NA "PM" "LD" -22.30152 166.30047 "HR" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA1" 7 15.3 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "SI080193" "SVR" "Ilot Signal" "SI" NA NA 1 24 6 2008 NA NA NA -999 -999 NA "MD" "LD" -22.30309 166.30007 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SA1" 6 16.4 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "SI080194" "SVR" "Ilot Signal" "SI" NA NA 1 27 6 2008 NA NA NA -999 -999 NA "MD" "DC" -22.30478 166.29942 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG3" 8 15.5 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "SI080195" "SVR" "Ilot Signal" "SI" NA NA 1 27 6 2008 NA NA NA -999 -999 NA "MM" "DC" -22.30617 166.29818 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG3" 7 13.8 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "SI080197" "SVR" "Ilot Signal" "SI" NA NA 1 27 6 2008 NA NA NA -999 -999 NA "MM" "DC" -22.30799 166.29476 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG2" 7 15.6 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "SI080198" "SVR" "Ilot Signal" "SI" NA NA 1 27 6 2008 NA NA NA -999 -999 NA "MD" "DC" -22.30791 166.2925 "RE" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG3" 6 16.8 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "SI080199" "SVR" "Ilot Signal" "SI" NA NA 1 27 6 2008 NA NA NA -999 -999 NA "MD" "DC" -22.30711 166.29082 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA1" 6 15.6 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "SI080200" "SVR" "Ilot Signal" "SI" NA NA 1 27 6 2008 NA NA NA -999 -999 NA "MM" "DC" -22.30559 166.28927 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA1" 7 19.4 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "SI080201" "SVR" "Ilot Signal" "SI" NA NA 1 25 6 2008 NA NA NA -999 -999 NA "MD" "DQ" -22.30393 166.28842 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "MA3" 6 19.5 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "SI080223" "SVR" "Ilot Signal" "SI" NA NA 1 27 6 2008 NA NA NA -999 -999 NA "MM" "DC" -22.3069 166.29668 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG2" 7 14 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "SI08040B" "SVR" "Ilot Signal" "SI" NA NA 1 27 6 2008 NA NA NA -999 -999 NA "MM" "DC" -22.29551 166.29676 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Detritique" "Frangeant ilot" "D6" 9 5.4 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "SI08046B" "SVR" "Ilot Signal" "SI" NA NA 1 4 7 2008 NA NA NA 4 -999 NA "MD" "PC" -22.30159 166.29927 "HR" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA3" 8 7.8 -999 -999 -999 -999 "Drelon" +"AMP" "SI08048B" "SVR" "Ilot Signal" "SI" NA NA 1 27 6 2008 NA NA NA -999 -999 NA "MM" "DC" -22.30343 166.29876 "HR" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG2" 7 8.4 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "SI08056B" "SVR" "Ilot Signal" "SI" NA NA 1 25 6 2008 NA NA NA -999 -999 NA "MD" "DQ" -22.29939 166.28911 "RE" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Frangeant ilot" "D2" 6 5.5 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "SI08057B" "SVR" "Ilot Signal" "SI" NA NA 1 26 6 2008 NA NA NA -999 -999 NA "MM" "DQ" -22.29842 166.28917 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Herbier" "Frangeant ilot" NA -999 4.4 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "SI08058B" "SVR" "Ilot Signal" "SI" NA NA 1 27 6 2008 NA NA NA -999 -999 NA "MM" "DC" -22.29631 166.28966 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Herbier" "Frangeant ilot" NA 6 6.3 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "SI08082B" "SVR" "Ilot Signal" "SI" NA NA 1 27 6 2008 NA NA NA -999 -999 NA "MM" "DC" -22.29806 166.28759 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA1" 3 16 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "SI08083B" "SVR" "Ilot Signal" "SI" NA NA 1 27 6 2008 NA NA NA -999 -999 NA "MM" "DC" -22.29662 166.28776 "RE" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG4" 6 14.4 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "SI08087T" "SVR" "Ilot Signal" "SI" NA NA 1 27 6 2008 NA NA NA -999 -999 NA "MD" "DC" -22.29731 166.28908 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Herbier" "Frangeant ilot" "SG2" 7 5 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "SI08089B" "SVR" "Ilot Signal" "SI" NA NA 1 27 6 2008 NA NA NA -999 -999 NA "MD" "DC" -22.3009 166.2868 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA1" 6 19.2 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "SI090141" "SVR" "Ilot Signal" "SI" NA NA 1 26 6 2009 NA NA NA 2 -999 NA "MD" "PC" -22.3048 166.29749 "HR" "AP" "Ile lagonaire" "lagon profond" "Detritique" "Fond lagonaire" "D1" 7 6.1 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "SI090142" "SVR" "Ilot Signal" "SI" NA NA 1 26 6 2009 NA NA NA 2 -999 NA "MD" "PC" -22.30575 166.29603 "HR" "AP" "Ile lagonaire" "lagon profond" "Detritique" "Frangeant ilot" "D2" 8 7.8 -999 -999 -999 -999 "Drelon" +"AMP" "SI090143" "SVR" "Ilot Signal" "SI" NA NA 1 26 6 2009 NA NA NA 2 -999 NA "MD" "PC" -22.3063 166.29511 "HR" "AP" "Ile lagonaire" "lagon profond" "Detritique" "Frangeant ilot" "D5" 10 8.3 -999 -999 -999 -999 "Drelon" +"AMP" "SI090144" "SVR" "Ilot Signal" "SI" NA NA 1 26 6 2009 NA NA NA 2 -999 NA "MD" "PC" -22.30666 166.29365 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Frangeant ilot" "D2" 8 8.4 -999 -999 -999 -999 "Drelon" +"AMP" "SI090146" "SVR" "Ilot Signal" "SI" NA NA 1 26 6 2009 NA NA NA 2 -999 NA "MD" "PC" -22.30619 166.29155 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Frangeant ilot" "D1" 7 10.1 -999 -999 -999 -999 "Drelon" +"AMP" "SI090147" "SVR" "Ilot Signal" "SI" NA NA 1 16 7 2009 NA NA "SO" 3 -999 NA "MM" "DC" -22.30497 166.29061 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Frangeant ilot" "D2" 7 9.9 -999 -999 -999 -999 "Drelon" +"AMP" "SI090148" "SVR" "Ilot Signal" "SI" NA NA 1 16 7 2009 NA NA "SO" 3 -999 NA "MM" "DC" -22.30325 166.28979 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Frangeant ilot" "D2" 7 9.5 -999 -999 -999 -999 "Drelon" +"AMP" "SI090149" "SVR" "Ilot Signal" "SI" NA NA 1 16 7 2009 NA NA "SO" 3 -999 NA "MM" "DC" -22.30154 166.28935 "RE" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Frangeant ilot" "D7" 7 9.5 -999 -999 -999 -999 "Drelon" +"AMP" "SI090151" "SVR" "Ilot Signal" "SI" NA NA 1 16 7 2009 NA NA "SO" 3 -999 NA "MM" "DC" -22.30037 166.28921 "RE" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Frangeant ilot" "D2" 9 5.6 -999 -999 -999 -999 "Drelon" +"AMP" "SI090152" "SVR" "Ilot Signal" "SI" NA NA 1 16 7 2009 NA NA "SO" 3 -999 NA "MM" "DC" -22.29945 166.28905 "RE" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Frangeant ilot" "D5" 9 5.6 -999 -999 -999 -999 "Drelon" +"AMP" "SI090153" "SVR" "Ilot Signal" "SI" NA NA 1 16 7 2009 NA NA "SO" 3 -999 NA "MM" "DC" -22.29821 166.28897 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Herbier" "Frangeant ilot" "SG1" 8 5.4 -999 -999 -999 -999 "Drelon" +"AMP" "SI090155" "SVR" "Ilot Signal" "SI" NA NA 1 16 7 2009 NA NA "SO" 3 -999 NA "MM" "DC" -22.29639 166.28957 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "SA1" 7 5.1 -999 -999 -999 -999 "Drelon" +"AMP" "SI090156" "SVR" "Ilot Signal" "SI" NA NA 1 16 7 2009 NA NA "SO" 3 -999 NA "MM" "DC" -22.29547 166.28985 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Herbier" "Frangeant ilot" NA 7 5.5 -999 -999 -999 -999 "Drelon" +"AMP" "SI090158" "SVR" "Ilot Signal" "SI" NA NA 1 16 7 2009 NA NA "SO" 3 -999 NA "MM" "DC" -22.29437 166.29045 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "SA4" 7 4.6 -999 -999 -999 -999 "Drelon" +"AMP" "SI090160" "SVR" "Ilot Signal" "SI" NA NA 1 1 7 2009 NA NA "ENE" 2 -999 NA "MM" "LM" -22.29293 166.29141 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Detritique" "Frangeant ilot" "D2" 8 3.8 -999 -999 -999 -999 "Drelon" +"AMP" "SI090161" "SVR" "Ilot Signal" "SI" NA NA 1 1 7 2009 NA NA "ENE" 2 -999 NA "MM" "LM" -22.29292 166.29296 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Detritique" "Frangeant ilot" "D5" 8 3.1 -999 -999 -999 -999 "Drelon" +"AMP" "SI090162" "SVR" "Ilot Signal" "SI" NA NA 1 1 7 2009 NA NA "ENE" 2 -999 NA "MM" "LM" -22.29371 166.29483 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Detritique" "Frangeant ilot" "D5" 7 4.6 -999 -999 -999 -999 "Drelon" +"AMP" "SI090163" "SVR" "Ilot Signal" "SI" NA NA 1 1 7 2009 NA NA "ENE" 2 -999 NA "MM" "LM" -22.29479 166.29595 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "SA5" 7 5.4 -999 -999 -999 -999 "Drelon" +"AMP" "SI090164" "SVR" "Ilot Signal" "SI" NA NA 1 1 7 2009 NA NA "ENE" 2 -999 NA "MM" "LM" -22.29552 166.29687 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "SA5" 7 5.1 -999 -999 -999 -999 "Drelon" +"AMP" "SI090165" "SVR" "Ilot Signal" "SI" NA NA 1 1 7 2009 NA NA "ENE" 2 -999 NA "MM" "LM" -22.29612 166.29755 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "SA1" 6 6.5 -999 -999 -999 -999 "Drelon" +"AMP" "SI090166" "SVR" "Ilot Signal" "SI" NA NA 1 26 6 2009 NA NA NA 2 -999 NA "MD" "PC" -22.29739 166.29838 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" NA 6 6.5 -999 -999 -999 -999 "Drelon" +"AMP" "SI090167" "SVR" "Ilot Signal" "SI" NA NA 1 1 7 2009 NA NA "ENE" 2 -999 NA "MM" "LM" -22.29891 166.29949 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" NA 7 7 -999 -999 -999 -999 "Drelon" +"AMP" "SI090168" "SVR" "Ilot Signal" "SI" NA NA 1 26 6 2009 NA NA NA 2 -999 NA "MD" "PC" -22.30088 166.29947 "RE" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA1" 7 7.8 -999 -999 -999 -999 "Drelon" +"AMP" "SI090169" "SVR" "Ilot Signal" "SI" NA NA 1 26 6 2009 NA NA NA 2 -999 NA "MD" "PC" -22.30167 166.2993 "HR" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA1" 7 8.6 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "SI090171" "SVR" "Ilot Signal" "SI" NA NA 1 26 6 2009 NA NA NA 2 -999 NA "MD" "PC" -22.30349 166.29863 "HR" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" NA 8 7.4 -999 -999 -999 -999 "Drelon" +"AMP" "SI090172" "SVR" "Ilot Signal" "SI" NA NA 1 26 6 2009 NA NA NA 2 -999 NA "MD" "PC" -22.30799 166.29251 "RE" "AP" "Ile lagonaire" "lagon profond" "Herbier" "Fond lagonaire" "SG3" 7 16.6 -999 -999 -999 -999 "William Roman" +"AMP" "SI090189" "SVR" "Ilot Signal" "SI" NA NA 1 1 7 2009 NA NA "SE" 2 -999 NA "MM" "LM" -22.29506 166.29734 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Herbier" "Frangeant ilot" "SG3" 7 10.3 -999 -999 -999 -999 "Drelon" +"AMP" "SI100109" "SVR" "Ilot Signal" "SI" NA NA 1 26 4 2010 NA NA "0" 0 -999 NA "MD" "LM" -22.2973472 166.2983597 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Detritique" "Frangeant ilot" NA 7 6 -999 -999 -999 -999 "Drelon" +"AMP" "SI100111" "SVR" "Ilot Signal" "SI" NA NA 1 26 4 2010 NA NA "0" 0 -999 NA "MD" "LM" -22.3004985 166.3026673 "HR" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA1" 6 16.5 -999 -999 -999 -999 "Delphine Mallet" +"AMP" "SI100112" "SVR" "Ilot Signal" "SI" NA NA 1 26 4 2010 NA NA "0" 0 -999 NA "MD" "LM" -22.3009366 166.2993941 "RE" "AP" "Ile lagonaire" "lagon profond" "Detritique" "Fond lagonaire" NA 8 6.8 -999 -999 -999 -999 "Drelon" +"AMP" "SI100113" "SVR" "Ilot Signal" "SI" NA NA 1 16 4 2010 NA NA NA 5 -999 NA "MD" "PC" -22.3035541 166.2986077 "HR" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA1" 7 7.6 -999 -999 -999 -999 "Drelon" +"AMP" "SI100114" "SVR" "Ilot Signal" "SI" NA NA 1 16 4 2010 NA NA NA 5 -999 NA "MD" "PC" -22.3049599 166.2974192 "HR" "AP" "Ile lagonaire" "lagon profond" "Fond lagonaire" "Fond lagonaire" "SA1" 8 7.5 -999 -999 -999 -999 "Drelon" +"AMP" "SI100115" "SVR" "Ilot Signal" "SI" NA NA 1 16 4 2010 NA NA NA 5 -999 NA "MD" "PC" -22.3058315 166.2959802 "HR" "AP" "Ile lagonaire" "lagon profond" "Detritique" "Frangeant ilot" "D1" 6.5 8.2 -999 -999 -999 -999 "Drelon" +"AMP" "SI100116" "SVR" "Ilot Signal" "SI" NA NA 1 16 4 2010 NA NA NA 5 -999 NA "MD" "PC" -22.306739 166.2935265 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Frangeant ilot" "D2" 6 9.3 -999 -999 -999 -999 "Drelon" +"AMP" "SI100117" "SVR" "Ilot Signal" "SI" NA NA 1 26 4 2010 NA NA "0" 0 -999 NA "MD" "LM" -22.3063035 166.2917041 "RE" "AP" "Complexe de massif corallien de lagon" "front recifal" "Detritique" "Frangeant ilot" "D1" 6 10.2 -999 -999 -999 -999 "Drelon" +"AMP" "SI100129" "SVR" "Ilot Signal" "SI" NA NA 1 26 4 2010 NA NA "0" 0 -999 NA "MD" "LM" -22.2955173 166.2967791 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Detritique" "Frangeant ilot" "D2" 6.5 5.3 -999 -999 -999 -999 "Drelon" +"AMP" "SI100130" "SVR" "Ilot Signal" "SI" NA NA 1 26 4 2010 NA NA "0" 0 -999 NA "MD" "LM" -22.2947766 166.2960761 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Detritique" "Frangeant ilot" "D1" 7 5.4 -999 -999 -999 -999 "Drelon" +"AMP" "SI100131" "SVR" "Ilot Signal" "SI" NA NA 1 26 4 2010 NA NA "0" 0 -999 NA "MD" "LM" -22.2937402 166.2949608 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "SA3" 7 4.8 -999 -999 -999 -999 "Drelon" +"AMP" "SI100132" "SVR" "Ilot Signal" "SI" NA NA 1 16 4 2010 NA NA NA 5 -999 NA "MD" "PC" -22.2929916 166.2928995 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "SA4" 7.5 3.8 -999 -999 -999 -999 "Drelon" +"AMP" "SI100133" "SVR" "Ilot Signal" "SI" NA NA 1 26 4 2010 NA NA "0" 0 -999 NA "MD" "LM" -22.2930767 166.2914348 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Detritique" "Frangeant ilot" "D2" 6.5 3.7 -999 -999 -999 -999 "Drelon" +"AMP" "SI100136" "SVR" "Ilot Signal" "SI" NA NA 1 26 4 2010 NA NA "0" 0 -999 NA "MD" "LM" -22.3052715 166.2907546 "RE" "AP" "Ile lagonaire" "lagon profond" "Detritique" "Frangeant ilot" "D3" 6.5 10.5 -999 -999 -999 -999 "Drelon" +"AMP" "SI100138" "SVR" "Ilot Signal" "SI" NA NA 1 26 4 2010 NA NA "0" 0 -999 NA "MD" "LM" -22.3022725 166.2895628 "RE" "AP" "Ile lagonaire" "lagon profond" "Detritique" "Frangeant ilot" "D2" 6 8 -999 -999 -999 -999 "Drelon" +"AMP" "SI100151" "SVR" "Ilot Signal" "SI" NA NA 1 26 4 2010 NA NA "0" 0 -999 NA "MD" "LM" -22.2940228 166.2910229 "RE" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Frangeant ilot" "D6" 5 3.5 -999 -999 -999 -999 "Drelon" +"AMP" "SI100152" "SVR" "Ilot Signal" "SI" NA NA 1 26 4 2010 NA NA "0" 0 -999 NA "MD" "LM" -22.2951626 166.2903255 "RE" "AP" "Complexe de massif corallien de lagon" "terrasse peu profonde" "Fond lagonaire" "Frangeant ilot" "LC3" 7 5.4 -999 -999 -999 -999 "Drelon" +"AMP" "SI100153" "SVR" "Ilot Signal" "SI" NA NA 1 27 4 2010 NA NA NA 2 -999 NA "MD" "LM" -22.2960763 166.2901483 "RE" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Frangeant ilot" "D6" 7 3.5 -999 -999 -999 -999 "Drelon" +"AMP" "SI100154" "SVR" "Ilot Signal" "SI" NA NA 1 27 4 2010 NA NA NA 2 -999 NA "MD" "LM" -22.2968722 166.2895325 "RE" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Fond lagonaire" "Frangeant ilot" "D7" 6 4.6 -999 -999 -999 -999 "Drelon" +"AMP" "SI100155" "SVR" "Ilot Signal" "SI" NA NA 1 26 4 2010 NA NA "0" 0 -999 NA "MD" "LM" -22.2981441 166.2895349 "RE" "AP" "Complexe de massif corallien de lagon" "platier recifal" "Detritique" "Frangeant ilot" "D6" 7 4.1 -999 -999 -999 -999 "Drelon" +"AMP" "WA140001" "SVR" "Walpole" NA "Recif ilot" NA 1 1 7 2014 NA NA "SW" 3 3 NA NA "LM" -22.59854 168.95012 "HR" "AP" "Recif frangeant expose a l\92ocean" "front recifal" "Corail vivant" "Frangeant oceanique" "D6" 10 10 -999 -999 -999 -999 "William Roman" +"AMP" "WA140002" "SVR" "Walpole" NA "Recif ilot" NA 1 1 7 2014 NA NA "SW" 3 3 NA NA "LM" -22.60011 168.94862 "HR" "AP" "Recif frangeant expose a l\92ocean" "front recifal" "Corail vivant" "Frangeant oceanique" "LC1" 10 15 -999 -999 -999 -999 "William Roman" +"AMP" "WA140003" "SVR" "Walpole" NA "Recif ilot" NA 1 1 7 2014 NA NA "SW" 3 4 NA NA "LM" -22.60251 168.94389 "HR" "AP" "Recif frangeant expose a l\92ocean" "front recifal" "Detritique" "Frangeant oceanique" "D1" 10 23.3 -999 -999 -999 -999 "William Roman"