Skip to content

Commit

Permalink
version 1.1-1
Browse files Browse the repository at this point in the history
  • Loading branch information
Cl�ment Calenge authored and gaborcsardi committed Oct 4, 2004
1 parent 5527cc5 commit 0be817f
Show file tree
Hide file tree
Showing 33 changed files with 242 additions and 236 deletions.
2 changes: 1 addition & 1 deletion CONTENTS
Expand Up @@ -339,7 +339,7 @@ URL: ../../../library/habitat/html/speed.html
Entry: squirrel
Aliases: squirrel
Keywords: dataset
Description: Radio-Tracking of Squirrels
Description: Radio-Tracking Data of Squirrels
URL: ../../../library/habitat/html/squirrel.html

Entry: storemapattr
Expand Down
6 changes: 3 additions & 3 deletions DESCRIPTION
@@ -1,10 +1,10 @@
Package: adehabitat
Version: 1.1
Date: 2004/09/15
Version: 1.1-1
Date: 2004/10/04
Title: Analysis of habitat selection by animals
Author: Cl�ment Calenge, contributions from Mathieu Basille
Maintainer: Cl�ment Calenge <calenge@biomserv.univ-lyon1.fr>
Depends: R (>= 1.8.0), ade4
Description: A collection of tools for the analysis of habitat selection by animals
License: GPL version 2 or newer
Packaged: Thu Sep 23 15:04:00 2004; Clement Calenge
Packaged: Mon Oct 4 09:27:40 2004; Clement Calenge
2 changes: 1 addition & 1 deletion INDEX
Expand Up @@ -74,7 +74,7 @@ setmask Applies a Mask on Objects of Class 'asc' or
'kasc'
speed Computes the Speed Between Successive
Relocations of an Animal
squirrel Radio-Tracking of Squirrels
squirrel Radio-Tracking Data of Squirrels
storemapattr Store attributes of maps of class asc and kasc
subsetmap Storing a Part of a Map
vanoise Habitat Use by Three Species of Galliformes in
Expand Down
181 changes: 85 additions & 96 deletions R/adehabitat.r
Expand Up @@ -111,99 +111,85 @@ colasc<-function(x, ...)
##### import.asc allows to import Arcview ascii raster file


import.asc<-function(file, type=c("numeric", "factor"), lev=NULL,
levnb = 1, labnb = 3)
{
type<-match.arg(type)
if (substr(file, nchar(file)-3, nchar(file))!=".asc")
stop("not a valid .asc file")
if ((type!="numeric")&(type!="factor"))
stop("argument type should be \"factor\" or \"numeric\"")
if ((type=="numeric")&(!is.null(lev)))
stop("lev can be specified only when type is \"factor\" ")
if ((type=="factor")&(length(lev)==1))
if (!file.exists(lev))
stop("lev is not a valid file")


### File header reading
zz<-file(file, "r")
nc<-readLines(zz, 1)
nl<-readLines(zz, 1)
xll<-readLines(zz, 1)
yll<-readLines(zz, 1)
cs<-readLines(zz, 1)
nas<-readLines(zz, 1)

### Gets the information from the file header
cs<-strsplit(cs," ")
cs<-as.numeric(cs[[1]][length(cs[[1]])])
cornx<-TRUE
corny<-TRUE
xll<-strsplit(xll," ")
if ((xll[[1]][1]=="xllcenter")|(xll[[1]][1]=="XLLCENTER"))
cornx<-FALSE
xll<-as.numeric(xll[[1]][length(xll[[1]])])
yll<-strsplit(yll," ")
if ((yll[[1]][1]=="yllcenter")|(xll[[1]][1]=="YLLCENTER"))
corny<-FALSE
yll<-as.numeric(yll[[1]][length(yll[[1]])])
nas<-strsplit(nas," ")
nas<-as.numeric(nas[[1]][length(nas[[1]])])

### Temporary file
tmp<-readLines(zz)
close(zz)
file.create("toto230876.tmp")
zz<-file("toto230876.tmp", "w")
writeLines(tmp, zz)
close(zz)

### read the matrix and delete the tmp
output<-read.table("toto230876.tmp")
file.remove("toto230876.tmp")
output<-as.matrix(output)
output[output==nas]<-NA
output<-t(output)
output<-output[,ncol(output):1]

## calcul de la table des correspondances
if (type=="factor") {
if (is.null(lev))
lev<-levels(factor(output))
if (length(lev)>1) {
if (length(lev)!=length(levels(factor(output))))
stop("uncorrect length of lev")
}
if (length(lev)==1) {
toto<-read.table(lev, header=TRUE, sep=",")
toto<-data.frame(lev=toto[,levnb], hihi=rep(1,nrow(toto)),
lab=toto[,labnb])
toto<-toto[order(toto[,1]),]
if (nrow(toto)!=nlevels(factor(output)))
stop("lev is not a valid correspondence table exported from Arcview")
lev<-as.character(toto[,3])
}

## On remplace les valeurs dans output
attr(output, "levels")<-lev
import.asc<- function (file, type = c("numeric", "factor"), lev = NULL,
levnb = 1, labnb = 3)
{
type <- match.arg(type)
if (substr(file, nchar(file) - 3, nchar(file)) != ".asc")
stop("not a valid .asc file")
if ((type != "numeric") & (type != "factor"))
stop("argument type should be \"factor\" or \"numeric\"")
if ((type == "numeric") & (!is.null(lev)))
stop("lev can be specified only when type is \"factor\" ")
if ((type == "factor") & (length(lev) == 1))
if (!file.exists(lev))
stop("lev is not a valid file")
zz <- file(file, "r")
nc <- readLines(zz, 1)
nl <- readLines(zz, 1)
xll <- readLines(zz, 1)
yll <- readLines(zz, 1)
cs <- readLines(zz, 1)
nas <- readLines(zz, 1)
cs <- strsplit(cs, " ")
cs <- as.numeric(cs[[1]][length(cs[[1]])])
cornx <- TRUE
corny <- TRUE
xll <- strsplit(xll, " ")
if ((xll[[1]][1] == "xllcenter") | (xll[[1]][1] == "XLLCENTER"))
cornx <- FALSE
xll <- as.numeric(xll[[1]][length(xll[[1]])])
yll <- strsplit(yll, " ")
if ((yll[[1]][1] == "yllcenter") | (xll[[1]][1] == "YLLCENTER"))
corny <- FALSE
yll <- as.numeric(yll[[1]][length(yll[[1]])])
nas <- strsplit(nas, " ")
nas <- as.numeric(nas[[1]][length(nas[[1]])])
nc <- strsplit(nc, " ")
nc <- as.numeric(nc[[1]][length(nc[[1]])])
nl <- strsplit(nl, " ")
nl <- as.numeric(nl[[1]][length(nl[[1]])])
tmp <- readLines(zz)
close(zz)
file.create("toto230876.tmp")
zz <- file("toto230876.tmp", "w")
writeLines(tmp, zz)
close(zz)
output <-scan("toto230876.tmp", quiet=TRUE)
file.remove("toto230876.tmp")
output[output == nas] <- NA
output<-matrix(c(as.matrix(output)), ncol=nl)
output <- output[, ncol(output):1]
if (type == "factor") {
if (is.null(lev))
lev <- levels(factor(output))
if (length(lev) > 1) {
if (length(lev) != length(levels(factor(output))))
stop("uncorrect length of lev")
}

## setting of the attributes
attr(output,"xll")<-xll
if (cornx)
attr(output,"xll")<-xll+cs/2
attr(output,"yll")<-yll
if (corny)
attr(output,"yll")<-yll+cs/2
attr(output,"cellsize")<-cs

## Case where output is a factor
attr(output, "type")<-type

class(output)<-"asc"
return(output)
if (length(lev) == 1) {
toto <- read.table(lev, header = TRUE, sep = ",")
toto <- data.frame(lev = toto[, levnb],
hihi = rep(1, nrow(toto)),
lab = toto[, labnb])
toto <- toto[order(toto[, 1]), ]
if (nrow(toto) != nlevels(factor(output)))
stop("lev is not a valid correspondence table exported from Arcview")
lev <- as.character(toto[, 3])
}
attr(output, "levels") <- lev
}
attr(output, "xll") <- xll
if (cornx)
attr(output, "xll") <- xll + cs/2
attr(output, "yll") <- yll
if (corny)
attr(output, "yll") <- yll + cs/2
attr(output, "cellsize") <- cs
attr(output, "type") <- type
class(output) <- "asc"
return(output)
}



Expand Down Expand Up @@ -1884,7 +1870,7 @@ print.rand.kselect<-function(x, ...)
cat("Observed value:", x$global[1], "\n")
cat("P-value :", x$global[2], "\n")
cat("\n")
cat("Test for each individual\n(to be compared with bonferroni alpha level:",
cat("Test of the marginality of each individual\n(to be compared with bonferroni alpha level:",
x$alpha/nrow(x$marg),"):\n\n")
print(x$marg, ...)
cat("\nSign of the mean for each animal and each variable: \n")
Expand Down Expand Up @@ -2660,7 +2646,7 @@ print.khr<-function(x, ...)

cat("\nEach animal is a component of the list, and for each animal,\n")
cat("the following elements are available:\n")
cat("$UD The utilisation distribution (object of class \"asc\")\n")
cat("$UD The utilization distribution (object of class \"asc\")\n")
cat("$locs The relocations of the animal\n")
if (th=="LSCV") {
cat("$h A list with the following components:\n")
Expand Down Expand Up @@ -2807,7 +2793,8 @@ plot.hrsize<-function(x, ...)
{
if (!inherits(x, "hrsize"))
stop("should be of class hrsize")
par(mfrow=n2mfrow(ncol(x)))
opar<-par(mfrow=n2mfrow(ncol(x)))
on.exit(par(opar))
for (i in 1:ncol(x)) {
plot(as.numeric(row.names(x)),
x[,i],
Expand Down Expand Up @@ -2892,6 +2879,7 @@ getverticeshr<-function(x, lev=95)
ud[!is.na(ud)]<-1
contour[[i]]<-getcontour(ud)
}
names(contour)<-names(x)
return(contour)
}

Expand Down Expand Up @@ -3806,6 +3794,7 @@ speed<-function(x, id=levels(x$id), burst=levels(x$burst),
{
if (!inherits(x, "traj"))
stop("should be an object of class traj")
units<-match.arg(units)

## sélection des dates
x<-getburst(x, burst=burst, id=id, date=date)
Expand Down Expand Up @@ -4256,10 +4245,10 @@ enfa <- function (kasc, pts, scannf = TRUE, nf = 1)
co <- matrix(nrow = ncol(tab), ncol = nf+1)
co[,1] <- mar
co[,2:(nf+1)] <- (Rs12 %*% eigen(H)$vectors)[,1:nf]
f3 <- function(i) co[,i]/sqrt(crossprod(co[,i]))
f3 <- function(i) co[,i]/sqrt(crossprod(co[,i])/length(co[,i]))
c1 <- matrix(unlist(lapply(1:(nf+1), f3)), ncol(tab))
li <- data.frame(tab %*% c1[,1:(nf+1)])
f3 <- function(i) li[,i]/sqrt(crossprod(li[,i]))
f3 <- function(i) li[,i]/sqrt(crossprod(li[,i])/length(li[,i]))
l1 <- matrix(unlist(lapply(1:(nf+1), f3)), nrow(tab))
co <- data.frame(co)
c1 <- data.frame(c1)
Expand Down
4 changes: 3 additions & 1 deletion man/as.area.Rd
Expand Up @@ -7,7 +7,9 @@
An object of class \code{area} is a data frame with three variables.
The first variable is a factor defining the polygons.\cr
The second and third variables are the xy coordinates of the
polygon vertices in the order where they are found.
polygon vertices in the order where they are found. This kind
of objects are current in the package \code{ade4}, though this package
does not define \code{area} as a special class.
}
\usage{
as.area(x)
Expand Down
4 changes: 2 additions & 2 deletions man/compana.Rd
Expand Up @@ -76,9 +76,9 @@ compana(used, avail, test = c("randomisation", "parametric"),
\item{rank}{the rank of the habitat types. It is equal to the number
of \code{"+"} for each habitat type in row of \code{rm}.}
\item{rmv}{the matrix of statistics used to build \code{rm}.
if \code{(test == "parametric")}, the matrix contains the
if \code{(test = "parametric")}, the matrix contains the
values of \code{t}, in the t-test comparing the row and the column
habitat. if \code{(test == "randomisation")}, the matrix contains
habitat. if \code{(test = "randomisation")}, the matrix contains
the mean difference between the used and available log-ratios (see
Aebischer et al., 1993).}
\item{profile}{The profile of preferences: resource types are sorted
Expand Down
6 changes: 4 additions & 2 deletions man/domain.Rd
Expand Up @@ -16,7 +16,7 @@ domain(kasc, pts, type = c("value", "potential"), thresh = 0.95)
\item{type}{a character string. The \code{"value"} of the suitability
may be returned
or the \code{"potential"} area of distribution}
\item{thresh}{if \code{value == "potential"}, a threshold value should be
\item{thresh}{if \code{value = "potential"}, a threshold value should be
supplied for the suitability (by default 0.95)}
}
\details{
Expand Down Expand Up @@ -63,7 +63,9 @@ contour(hsm, add = TRUE)

## Potential distribution
hsm <- domain(kasc, pts, type = "potential")
image(hsm)
image(elevation, main = "Habitat suitability map")
image(hsm, add = TRUE, col = "orange")
points(pts, col = "red", pch = 16)

}
\keyword{spatial}
Expand Down
6 changes: 3 additions & 3 deletions man/enfa.Rd
Expand Up @@ -18,7 +18,7 @@ hist.enfa(x, scores = TRUE, type = c("h", "l"),
\item{pts}{a data frame with two columns, giving the coordinates of
the species locations}
\item{scannf}{logical. Whether the eigenvalues bar plot should be displayed}
\item{nf}{if \code{scannf == FALSE}, an integer indicating the number of kept
\item{nf}{if \code{scannf = FALSE}, an integer indicating the number of kept
specialization axes }
\item{x}{an object of class \code{enfa}}
\item{scores}{logical. If \code{TRUE}, the histograms display
Expand All @@ -28,10 +28,10 @@ hist.enfa(x, scores = TRUE, type = c("h", "l"),
\item{type}{what type of plot should be drawn. Possible types are:\cr
* \code{"h"} for histograms,\cr
* \code{"l"} for kernel density estimates (see \code{?density}).\cr
By default, \code{type == "h"} is used. If \code{type = "l"} is used,
By default, \code{type = "h"} is used. If \code{type = "l"} is used,
the position of the mean of each distribution is indicated by dotted
lines}
\item{adjust}{if \code{type == "l"}, a parameter used to control the
\item{adjust}{if \code{type = "l"}, a parameter used to control the
bandwidth of the density estimates (see \code{?density})}
\item{colZ}{color for the histograms of the available pixels}
\item{colS}{color for the histograms of the used pixels}
Expand Down
2 changes: 1 addition & 1 deletion man/getascattr.Rd
Expand Up @@ -21,7 +21,7 @@ getkascattr(xkfrom, xkto)
\item{type}{a character string giving the type of the map
(\code{"factor"} for maps of categorical
variables, and \code{"numeric"} otherwise)}
\item{lev}{if \code{type == "factor"},
\item{lev}{if \code{type = "factor"},
a character vector giving the levels of the mapped variable
(see \code{help(import.asc)})}
\item{xkfrom}{an object of class \code{kasc}}
Expand Down
6 changes: 4 additions & 2 deletions man/getcontour.Rd
Expand Up @@ -4,8 +4,7 @@
\description{
\code{getcontour} computes the contour polygon of a raster object
of class \code{asc}. When the object is made of several parts, the
function returns one polygon per part. \cr
Warning! holes are not taken into account by the function.
function returns one polygon per part.
}
\usage{
getcontour(x)
Expand All @@ -17,6 +16,9 @@ getcontour(x)
\value{
Returns an object of class \code{area}.
}
\section{Warning }{
Holes in the polygons are not taken into account by the function.
}
\author{ Clément Calenge \email{calenge@biomserv.univ-lyon1.fr} }
\seealso{ \code{\link{import.asc}} for additionnal information on
objects of class \code{asc}, \code{\link{as.area}} for
Expand Down
2 changes: 1 addition & 1 deletion man/hist.kasc.Rd
Expand Up @@ -13,7 +13,7 @@ hist.kasc(x, type = c("h", "l"), adjust = 1, col = "blue", \dots)
\item{type}{what type of plot should be drawn. Possible types are:\cr
* \code{"h"} for histograms,\cr
* \code{"l"} for kernel density estimates (see \code{?density}).\cr
By default, \code{type == "h"} is used. If \code{type == "l"} is used,
By default, \code{type = "h"} is used. If \code{type = "l"} is used,
the position of the mean of each distribution is indicated by dotted
lines}
\item{adjust}{if \code{type = "l"}, a parameter used to control the
Expand Down
4 changes: 2 additions & 2 deletions man/histniche.Rd
Expand Up @@ -19,10 +19,10 @@ histniche(kasc, pts, type = c("h", "l"), adjust = 1,
\item{type}{what type of plot should be drawn. Possible types are:\cr
* \code{"h"} for histograms,\cr
* \code{"l"} for kernel density estimates (see \code{?density}).\cr
By default, \code{type == "h"} is used. If \code{type == "l"} is used,
By default, \code{type = "h"} is used. If \code{type = "l"} is used,
the position of the mean of each distribution is indicated by dotted
lines}
\item{adjust}{if \code{type == "l"}, a parameter used to control the
\item{adjust}{if \code{type = "l"}, a parameter used to control the
bandwidth of the density estimate (see \code{?density})}
\item{colZ}{color for the histograms of the available pixels}
\item{colS}{color for the histograms of the used pixels}
Expand Down
1 change: 0 additions & 1 deletion man/image.sahrlocs.Rd
Expand Up @@ -68,7 +68,6 @@ image(sahr, ani = "Chou")
image(sahr, var = "Elevation")

## Load and displays the relocations of the animals
data(puechabon)
locs <- puechabon$locs[,c(1,4:5)]
image(sahr, var = "Elevation", dfidxy = locs, pch = 21)
}
Expand Down

0 comments on commit 0be817f

Please sign in to comment.