You can subscribe to this list here.
| 2002 |
Jan
|
Feb
|
Mar
|
Apr
|
May
|
Jun
|
Jul
|
Aug
|
Sep
|
Oct
(267) |
Nov
(344) |
Dec
(119) |
|---|---|---|---|---|---|---|---|---|---|---|---|---|
| 2003 |
Jan
(23) |
Feb
(15) |
Mar
(16) |
Apr
(388) |
May
|
Jun
(4) |
Jul
|
Aug
|
Sep
(4) |
Oct
|
Nov
|
Dec
|
|
From: <td...@us...> - 2003-02-12 18:56:26
|
Update of /cvsroot/genex/genex-server/site/webtools
In directory sc8-pr-cvs1:/tmp/cvs-serv4307
Removed Files:
Tag: Rel-1_0_1-branch
add_analysis.pl
Log Message:
Moved to analysis
--- add_analysis.pl DELETED ---
|
|
From: <td...@us...> - 2003-02-06 15:31:34
|
Update of /cvsroot/genex/genex-server/site/webtools/analysis
In directory sc8-pr-cvs1:/tmp/cvs-serv3196
Added Files:
Tag: Rel-1_0_1-branch
sourceLPE.ssc
Log Message:
Initial addition
--- NEW FILE: sourceLPE.ssc ---
# lowess-based LPE error estimation
permute <- function(a) {
# all possible permutaions for vector a
aa <- matrix(NA,length(a)-1,length(a))
for (i in 1:(length(a)-1))
aa[i,] <- a[c((i+1):length(a), 1:i)]
return(aa)
}
am.trans <- function(y) {
# transform mutiple replicated arrays into (A, M) format for all
# comparisons twice, e.g., (Y1+Y2, Y1-Y2) and (Y1+Y2, Y2-Y1)
# for a baseline error distribution
# y(ngene X n): matrix for replicated arrays under a sample condition
n <- ncol(y)
if(n < 2) { cat("There is no replicated arrays!"); q()}
A <- c(); M <- c()
cc <- permute(1:n)
for (i in 1:(n-1)) {
A <- c(A, c((y + y[,cc[i,]])/2))
M <- c(M, c(y - y[,cc[i,]]))
}
return(cbind(A,M))
}
baseOlig.error <- function(y, q=0.01) {
# evaluate LPE distribution of M at percentile intervals of A
# matrix y (log intensity) of replicated Oligo arrays after normalization
# q = quantile width
AM <- am.trans(y)
na.point <- (1:nrow(AM))[!is.na(AM[,1]) & !is.na(AM[,2])]
# cut off spots of A < 4 not to estimate errors from many tresholded genes
cutoff.point <- (1:nrow(AM))[AM[,1] >= 4]
point <- intersect(na.point, cutoff.point)
A <- AM[point,1]; M <- AM[point,2]
quantile.A <- quantile(A,probs=seq(0,1,q),na.rm=T)
quan.n <- length(quantile.A)
var.M <- rep(NA,length=quan.n)
for(i in 2:quan.n)
{
var.M[i] <- var(M[A>quantile.A[i-1] & A<=quantile.A[i]])
}
# Set the variance at interval (0, 1st) as the variance of the 1st percentile range
var.M[1] <- var.M[2]
# B-spline fit of variance
fit <- spline(quantile.A, var.M)
return(cbind(A = fit$x, var.M = fit$y))
}
baseCDNA.error <- function(y, q=0.01) {
# evaluate LPE distribution of M at percentile intervals of A
# matrix y (log ratio intensity) of replicated cDNA arrays after normalization
# q = quantile width
AM <- am.trans(y)
na.point <- (1:nrow(AM))[!is.na(AM[,1]) & !is.na(AM[,2])]
A <- AM[na.point,1]; M <- AM[na.point,2]
quantile.A <- quantile(A,probs=seq(0,1,q),na.rm=T)
quan.n <- length(quantile.A)-1
var.M <- rep(NA,length=quan.n)
for(i in 1:quan.n)
{
var.M[i] <- var(M[A>quantile.A[i] & A<=quantile.A[i+1]],na.method="available")
}
# B-spline fit of variance
fit <- spline(quantile.A[-1], var.M)
return(cbind(A = fit$x, var.M = fit$y))
}
# This function is not needed any more.
predict.error <- function(newdata, base.error) {
# predict error for new data using baseline error output
nq <- nrow(base.error)
nd <- length(newdata)
var.new <- rep(base.error[1,2], nd)
for(i in 2:nq)
{
var.new[newdata > base.error[i,1]] <- base.error[i,2]
}
var.new
}
lpe <- function(x, y, basevar.x, basevar.y, array.type="olig") {
# LPE significance evaluation with replicates
# x and y two array samples with n1 and n2 replicates
# basevar.x (basevar.y): n.quantile x 2 matrix of LPE baseline error of x (y)
# array.type: "olig" for Affymetrix oligo array and "cDNA" for cDNA array
n1 <- ncol(x); n2 <- ncol(y)
if (n1< 2 | n2 < 2) { stop("No replicated arrays!")}
ngenes <- nrow(x)
if(n1 > 2 | n2 > 2) {
median.x <- apply(x,1, median, na.rm=T)
median.y <- apply(y, 1, median, na.rm=T)
diff <- median.x - median.y
quan.n <- nrow(basevar.x)
# prediction by linear approximation to B-spline fit;
var.x <- approx(basevar.x[,1], basevar.x[,2], median.x)$y
na.point <- (1:ngenes)[is.na(var.x)]
if(array.type=="olig") {
# replace left-hand NA's by max var, right-hand by min
var.x <- approx(basevar.x[,1], basevar.x[,2], median.x)$y
var.x[is.na(var.x)] <- max(basevar.x[,2])
var.x[median.x >= basevar.x[quan.n,1] ] <- min(basevar.x[,2])
} else if(array.type=="cDNA") {
var.x[na.point][median.x[na.point] <= basevar.x[1,1]] <- basevar.x[1,2]
var.x[na.point][median.x[na.point] >= basevar.x[quan.n,1]] <- basevar.x[quan.n,2]
}
quan.n <- nrow(basevar.y)
var.y <- approx(basevar.y[,1], basevar.y[,2], median.y)$y
na.point <- (1:ngenes)[is.na(var.y)]
if(array.type=="olig") {
var.y[is.na(var.y)] <- max(basevar.y[,2])
var.y[median.y >= basevar.y[quan.n,1] ] <- min(basevar.y[,2])
} else if(array.type=="cDNA") {
var.y[na.point][median.y[na.point] <= basevar.y[1,1]] <- basevar.y[1,2]
var.y[na.point][median.y[na.point] >= basevar.y[quan.n,1]] <- basevar.y[quan.n,2]
}
if(is.na(sum(var.x)+sum(var.y))) { stop(var.x, var.y) }
std.diff <- sqrt(1.57*(var.x/n1 + var.y/n2) )
pnorm.diff <- pnorm(diff,mean=0,sd=std.diff)
p.out <- 2* apply(cbind(pnorm.diff, 1-pnorm.diff), 1, min)
return(cbind(x,median.1 = median.x,y, median.2=median.y,
median.diff=diff,diff.std=std.diff,pvalue=p.out))
}
else if (n1==2 & n2 ==2) {
median.x <- (x[,1] + x[,2])/2
median.y <- (y[,1] + y[,2])/2
diff <- median.x - median.y
quan.n <- nrow(basevar.x)
# prediction by linear approximation to B-spline fit;
var.x <- approx(basevar.x[,1], basevar.x[,2], median.x)$y
na.point <- (1:ngenes)[is.na(var.x)]
if(array.type=="olig") {
# replace left-hand NA's by max var, right-hand by min
var.x <- approx(basevar.x[,1], basevar.x[,2], median.x)$y
var.x[is.na(var.x)] <- max(basevar.x[,2])
var.x[median.x >= basevar.x[quan.n,1] ] <- min(basevar.x[,2])
} else if(array.type=="cDNA") {
var.x[na.point][median.x[na.point] <= basevar.x[1,1]] <- basevar.x[1,2]
var.x[na.point][median.x[na.point] >= basevar.x[quan.n,1]] <- basevar.x[quan.n,2]
}
quan.n <- nrow(basevar.y)
var.y <- approx(basevar.y[,1], basevar.y[,2], median.y)$y
na.point <- (1:ngenes)[is.na(var.y)]
if(array.type=="olig") {
var.y[is.na(var.y)] <- max(basevar.y[,2])
var.y[median.y >= basevar.y[quan.n,1] ] <- min(basevar.y[,2])
} else if(array.type=="cDNA") {
var.y[na.point][median.y[na.point] <= basevar.y[1,1]] <- basevar.y[1,2]
var.y[na.point][median.y[na.point] >= basevar.y[quan.n,1]] <- basevar.y[quan.n,2]
}
if(is.na(sum(var.x)+sum(var.y))) { stop(var.x, var.y) }
std.diff <- sqrt(var.x/n1 + var.y/n2)
pnorm.diff <- pnorm(diff,mean=0,sd=std.diff)
p.out <- 2* apply(cbind(pnorm.diff, 1-pnorm.diff), 1, min)
### outlier checking
var.x <- var.y <- matrix(NA, ngenes,2)
for (i in 1:2) {
# prediction by linear approximation to B-spline fit
var.x[,i] <- approx(basevar.x[,1], basevar.x[,2], x[,i])$y
var.x[is.na(var.x[,i]),i] <- max(basevar.x[,2])
var.x[x[,i] >= basevar.x[nrow(basevar.x),1] ] <- min(basevar.x[,2])
var.y[,i] <- approx(basevar.y[,1], basevar.y[,2], y[,i])$y
var.y[is.na(var.y[,i]),i] <- max(basevar.y[,2])
var.x[y[,i] >= basevar.y[nrow(basevar.y),1] ] <- min(basevar.y[,2])
}
p.val <- matrix(NA, ngenes, 2)
var.diff <- var.x[,1] + var.x[,2] + var.y[,1] + var.y[,2]
diff.xy <- x - y
diff.xy <- (diff.xy[,1] - diff.xy[,2])/2
p.val[,1] <- pnorm(diff.xy,mean=0,sd=sqrt(var.diff))
p.val[,1] <- apply(cbind(p.val[,1], 1-p.val[,1]), 1, min)
diff.xy <- x - y[, 2:1]
diff.xy <- (diff.xy[,1] - diff.xy[,2])/2
p.val[,2] <- pnorm(diff.xy,mean=0,sd=sqrt(var.diff))
p.val[,2] <- apply(cbind(p.val[,2], 1-p.val[,2]), 1, min)
p.outlier <- apply(p.val, 1, min)
flag <- rep(".", ngenes)
flag[p.outlier < .05] <- "*"; flag[p.outlier < .01] <- "**"; flag[p.outlier < .001] <- "***"
return(data.frame(x,median.1 = median.x,y, median.2=median.y,
median.diff=diff,diff.std=std.diff,pvalue=p.out,flag=flag,p.outlier=p.outlier))
}
}
|
|
From: <jas...@us...> - 2003-01-12 22:41:16
|
Update of /cvsroot/genex/genex-server/Genex/XMLUtils
In directory sc8-pr-cvs1:/tmp/cvs-serv27182
Modified Files:
XMLUtils.pm.in
Log Message:
* XMLUtils/XMLUtils.pm.in (Repository):
updated for XML::Xerces 2.0+
Index: XMLUtils.pm.in
===================================================================
RCS file: /cvsroot/genex/genex-server/Genex/XMLUtils/XMLUtils.pm.in,v
retrieving revision 1.29
retrieving revision 1.30
diff -C2 -d -r1.29 -r1.30
*** XMLUtils.pm.in 12 Jan 2003 22:03:03 -0000 1.29
--- XMLUtils.pm.in 12 Jan 2003 22:41:12 -0000 1.30
***************
*** 334,338 ****
my %audit_tables;
my $output;
! my $parser = XML::Xerces::DOMParser->new();
my %docs;
my %inherit_tables;
--- 334,338 ----
my %audit_tables;
my $output;
! my $parser = XML::Xerces::XercesDOMParser->new();
my %docs;
my %inherit_tables;
|
|
From: <jas...@us...> - 2003-01-12 22:07:22
|
Update of /cvsroot/genex/genex-server/Genex/scripts
In directory sc8-pr-cvs1:/tmp/cvs-serv14523
Modified Files:
array-design-insert.pl.in create_genex_class.pl.in
create_genex_db.pl.in xml2sql.pl.in
Log Message:
* scripts/xml2sql.pl.in (Repository):
* scripts/create_genex_db.pl.in (Repository):
* scripts/create_genex_class.pl.in (Repository):
* scripts/array-design-insert.pl.in (Repository):
updated for XML::Xerces 2.0+
Index: array-design-insert.pl.in
===================================================================
RCS file: /cvsroot/genex/genex-server/Genex/scripts/array-design-insert.pl.in,v
retrieving revision 1.14
retrieving revision 1.15
diff -C2 -d -r1.14 -r1.15
*** array-design-insert.pl.in 11 Jan 2003 19:28:40 -0000 1.14
--- array-design-insert.pl.in 12 Jan 2003 22:07:20 -0000 1.15
***************
*** 27,31 ****
use Bio::MAGE 20020902.3 qw(:ALL);
use Bio::MAGE::XMLUtils;
- use XML::Xerces;
$Bio::Genex::ArrayDesign::DEBUG = 1;
--- 27,30 ----
***************
*** 84,91 ****
if exists $OPTIONS{no_reporters} and exists $OPTIONS{reporters_only};
-
- # my $PARSER = XML::Xerces::DOMParser->new();
- # $PARSER->parse($OPTIONS{file});
- # my $DOC = $PARSER->getDocument();
# open up a writeable connection
--- 83,86 ----
Index: create_genex_class.pl.in
===================================================================
RCS file: /cvsroot/genex/genex-server/Genex/scripts/create_genex_class.pl.in,v
retrieving revision 1.20
retrieving revision 1.21
diff -C2 -d -r1.20 -r1.21
*** create_genex_class.pl.in 21 Nov 2002 12:37:29 -0000 1.20
--- create_genex_class.pl.in 12 Jan 2003 22:07:20 -0000 1.21
***************
*** 17,21 ****
# import the fkey constants
use Bio::Genex::Fkey qw(:FKEY);
! use XML::Xerces;
# table type constants
--- 17,21 ----
# import the fkey constants
use Bio::Genex::Fkey qw(:FKEY);
! use XML::Xerces '2.0';
# table type constants
***************
*** 92,99 ****
my $time = localtime;
my (%FILES,%FKEYS);
! my $parser = XML::Xerces::DOMParser->new();
my $handler = XML::Xerces::PerlErrorHandler->new();
$parser->setErrorHandler($handler);
! $parser->setValidationScheme($XML::Xerces::Val_Always);
print STDERR "Using target: $target";
--- 92,99 ----
my $time = localtime;
my (%FILES,%FKEYS);
! my $parser = XML::Xerces::XercesDOMParser->new();
my $handler = XML::Xerces::PerlErrorHandler->new();
$parser->setErrorHandler($handler);
! $parser->setValidationScheme($XML::Xerces::AbstractDOMParser::Val_Always);
print STDERR "Using target: $target";
***************
*** 3042,3057 ****
}
}
- }
-
- package XML::Xerces::DOM_Element;
- sub get_text {
- my $node = shift;
- my @nodes = $node->getChildNodes();
- my $text;
- foreach (@nodes) {
- $text .= $_->getNodeValue()
- if $_->isa('XML::Xerces::DOM_Text');
- }
- return $text;
}
--- 3042,3045 ----
Index: create_genex_db.pl.in
===================================================================
RCS file: /cvsroot/genex/genex-server/Genex/scripts/create_genex_db.pl.in,v
retrieving revision 1.9
retrieving revision 1.10
diff -C2 -d -r1.9 -r1.10
*** create_genex_db.pl.in 23 Nov 2002 10:24:13 -0000 1.9
--- create_genex_db.pl.in 12 Jan 2003 22:07:20 -0000 1.10
***************
*** 10,14 ****
# use blib;
! use XML::Xerces;
use DBI;
use Bio::Genex qw(timestamp);
--- 10,14 ----
# use blib;
! use XML::Xerces '2.0';
use DBI;
use Bio::Genex qw(timestamp);
***************
*** 184,188 ****
# now add the SQL funcions
#
! my $parser = XML::Xerces::DOMParser->new();
eval {$parser->parse($OPTIONS{functions})};
XML::Xerces::error($@) if $@;
--- 184,188 ----
# now add the SQL funcions
#
! my $parser = XML::Xerces::XercesDOMParser->new();
eval {$parser->parse($OPTIONS{functions})};
XML::Xerces::error($@) if $@;
Index: xml2sql.pl.in
===================================================================
RCS file: /cvsroot/genex/genex-server/Genex/scripts/xml2sql.pl.in,v
retrieving revision 1.5
retrieving revision 1.6
diff -C2 -d -r1.5 -r1.6
*** xml2sql.pl.in 9 Nov 2002 00:40:10 -0000 1.5
--- xml2sql.pl.in 12 Jan 2003 22:07:20 -0000 1.6
***************
*** 9,13 ****
use blib;
- use XML::Xerces;
use Bio::Genex::Connect;
use Bio::Genex::XMLUtils;
--- 9,12 ----
|
|
From: <jas...@us...> - 2003-01-12 22:03:09
|
Update of /cvsroot/genex/genex-server/Genex/XMLUtils
In directory sc8-pr-cvs1:/tmp/cvs-serv11391
Modified Files:
XMLUtils.pm.in
Log Message:
* XMLUtils/XMLUtils.pm.in (Repository):
removed references to AM_Spots
updated for XML::Xerces 2.0+
Index: XMLUtils.pm.in
===================================================================
RCS file: /cvsroot/genex/genex-server/Genex/XMLUtils/XMLUtils.pm.in,v
retrieving revision 1.28
retrieving revision 1.29
diff -C2 -d -r1.28 -r1.29
*** XMLUtils.pm.in 12 Jan 2003 19:30:23 -0000 1.28
--- XMLUtils.pm.in 12 Jan 2003 22:03:03 -0000 1.29
***************
*** 13,17 ****
# use WeakRef;
use Bio::Genex qw(:ASSERT error);
! use XML::Xerces '1.7.0';
require Exporter;
--- 13,17 ----
# use WeakRef;
use Bio::Genex qw(:ASSERT error);
! use XML::Xerces '2.0';
require Exporter;
***************
*** 2461,2465 ****
use vars qw(@ISA $DEBUG $AUTOLOAD $ERROR_HANDLER);
use Carp;
! use XML::Xerces;
use File::Basename;
use Class::ObjectTemplate 0.2;
--- 2461,2465 ----
use vars qw(@ISA $DEBUG $AUTOLOAD $ERROR_HANDLER);
use Carp;
! use XML::Xerces '2.0';
use File::Basename;
use Class::ObjectTemplate 0.2;
***************
*** 2482,2486 ****
sub initialize {
my $self = shift;
! my $parser = XML::Xerces::DOMParser->new();
unless (defined $self->error_handler && !$self->error_handler) {
# add a default error handler
--- 2482,2486 ----
sub initialize {
my $self = shift;
! my $parser = XML::Xerces::XercesDOMParser->new();
unless (defined $self->error_handler && !$self->error_handler) {
# add a default error handler
***************
*** 2491,2495 ****
# we validate, handle namespaces, and create XMLDecl nodes and
# EntityReference nodes by default
! $parser->setValidationScheme($XML::Xerces::DOMParser::Val_Always)
unless defined $self->validate && !$self->validate;
--- 2491,2495 ----
# we validate, handle namespaces, and create XMLDecl nodes and
# EntityReference nodes by default
! $parser->setValidationScheme($XML::Xerces::AbstractDOMParser::Val_Always)
unless defined $self->validate && !$self->validate;
***************
*** 2556,2560 ****
$method =~ s/.*://; # strip fully-qualified portion
! # if we couldn't handle it, we'll assume the XML::Xerces::DOMParser can
if ($self->_parser->can($method)) {
no strict 'refs';
--- 2556,2560 ----
$method =~ s/.*://; # strip fully-qualified portion
! # if we couldn't handle it, we'll assume the XML::Xerces::XercesDOMParser can
if ($self->_parser->can($method)) {
no strict 'refs';
***************
*** 3050,3054 ****
# now we grab the version from the DOCTYPE, it will look like:
! # "$Id$"
($USF_VERSION) = $USF_DOCTYPE =~ /\$Id\:(.*)\$/
}
--- 3050,3054 ----
# now we grab the version from the DOCTYPE, it will look like:
! # "$Id$"
($USF_VERSION) = $USF_DOCTYPE =~ /\$Id\:(.*)\$/
}
***************
*** 3057,3064 ****
# initialize()
# Parameters: called by new() with a single argument, the new
! # Bio::Genex::GeneXML object.
#
! # Side Effects: creates a new XML::Xerces::DOMParser object and stores it
! # in the _parser attribute. creates a new XML::Xerces::DOM_Document object
# and stores it in the _doc attribute.
#
--- 3057,3064 ----
# initialize()
# Parameters: called by new() with a single argument, the new
! # Bio::Genex::GeneXML object.
#
! # Side Effects: creates a new XML::Xerces::XercesDOMParser object and stores it
! # in the _parser attribute. creates a new XML::Xerces::DOMDocument object
# and stores it in the _doc attribute.
#
|
|
From: <jas...@us...> - 2003-01-12 19:54:47
|
Update of /cvsroot/genex/genex-server In directory sc8-pr-cvs1:/tmp/cvs-serv22207 Modified Files: ChangeLog Log Message: usual Index: ChangeLog =================================================================== RCS file: /cvsroot/genex/genex-server/ChangeLog,v retrieving revision 1.119 retrieving revision 1.120 diff -C2 -d -r1.119 -r1.120 *** ChangeLog 12 Jan 2003 19:50:33 -0000 1.119 --- ChangeLog 12 Jan 2003 19:54:44 -0000 1.120 *************** *** 2,7 **** * Configure (Repository): ! must create Genex/Config before copying Config.pm there ! 2002-12-05 Jason E. Stewart <ja...@op...> --- 2,8 ---- * Configure (Repository): ! was creating file Genex/Config when copying Config.pm and the dir ! didn't exist ! 2002-12-05 Jason E. Stewart <ja...@op...> |
|
From: <jas...@us...> - 2003-01-12 19:54:32
|
Update of /cvsroot/genex/genex-server
In directory sc8-pr-cvs1:/tmp/cvs-serv22112
Modified Files:
Configure
Log Message:
* Configure (Repository):
was creating file Genex/Config when copying Config.pm and the dir
didn't exist
Index: Configure
===================================================================
RCS file: /cvsroot/genex/genex-server/Configure,v
retrieving revision 1.13
retrieving revision 1.14
diff -C2 -d -r1.13 -r1.14
*** Configure 12 Jan 2003 19:50:06 -0000 1.13
--- Configure 12 Jan 2003 19:54:29 -0000 1.14
***************
*** 1697,1702 ****
# with the rest of the API
my $DIR = 'Genex/Config';
! genex_mkdir($DIR);
! genex_system("cp $CACHE_FILE_NAME $DIR");
print STDOUT <<"EOM";
--- 1697,1702 ----
# with the rest of the API
my $DIR = 'Genex/Config';
! #genex_mkdir($DIR);
! genex_system("cp $CACHE_FILE_NAME $DIR/$CACHE_FILE_NAME");
print STDOUT <<"EOM";
|
|
From: <jas...@us...> - 2003-01-12 19:50:37
|
Update of /cvsroot/genex/genex-server/Genex In directory sc8-pr-cvs1:/tmp/cvs-serv20945/Genex Modified Files: ChangeLog Log Message: usual Index: ChangeLog =================================================================== RCS file: /cvsroot/genex/genex-server/Genex/ChangeLog,v retrieving revision 1.127 retrieving revision 1.128 diff -C2 -d -r1.127 -r1.128 *** ChangeLog 3 Jan 2003 18:15:54 -0000 1.127 --- ChangeLog 12 Jan 2003 19:50:33 -0000 1.128 *************** *** 1,2 **** --- 1,19 ---- + 2003-01-12 Jason E. Stewart <ja...@op...> + + * XMLUtils/XMLUtils.pm.in (Repository): + removed references to AM_Spots + + 2003-01-11 Jason E. Stewart <ja...@op...> + + * scripts/mbad-insert.pl.in (Repository): + unlink files on completion + + * scripts/qtdim-insert.pl.in (Repository): + uses new Bio::MAGE + + * scripts/array-design-insert.pl.in (Repository): + no longer assumes zone info exists + uses new Bio::MAGE + 2002-12-17 Jason E. Stewart <ja...@op...> |
|
From: <jas...@us...> - 2003-01-12 19:50:36
|
Update of /cvsroot/genex/genex-server
In directory sc8-pr-cvs1:/tmp/cvs-serv20945
Modified Files:
ChangeLog
Log Message:
usual
Index: ChangeLog
===================================================================
RCS file: /cvsroot/genex/genex-server/ChangeLog,v
retrieving revision 1.118
retrieving revision 1.119
diff -C2 -d -r1.118 -r1.119
*** ChangeLog 3 Jan 2003 18:04:01 -0000 1.118
--- ChangeLog 12 Jan 2003 19:50:33 -0000 1.119
***************
*** 1,3 ****
! <<<<<<< variant A
2002-12-05 Jason E. Stewart <ja...@op...>
--- 1,7 ----
! 2003-01-12 Jason E. Stewart <ja...@op...>
!
! * Configure (Repository):
! must create Genex/Config before copying Config.pm there
!
2002-12-05 Jason E. Stewart <ja...@op...>
***************
*** 5,9 ****
add 'name' attribute to all identifiable objects
- >>>>>>> variant B
2002-11-19 Harry Mangalam <hj...@ta...>
* more mods to INSTALL doc to bring it up to date (added more pkgs to
--- 9,12 ----
***************
*** 33,38 ****
installation mods.
- ####### Ancestor
- ======= end
2002-11-26 Jason E. Stewart <ja...@op...>
--- 36,39 ----
|
|
From: <jas...@us...> - 2003-01-12 19:50:11
|
Update of /cvsroot/genex/genex-server
In directory sc8-pr-cvs1:/tmp/cvs-serv20828
Modified Files:
Configure
Log Message:
* Configure (Repository):
must create Genex/Config before copying Config.pm there
Index: Configure
===================================================================
RCS file: /cvsroot/genex/genex-server/Configure,v
retrieving revision 1.12
retrieving revision 1.13
diff -C2 -d -r1.12 -r1.13
*** Configure 21 Nov 2002 10:04:03 -0000 1.12
--- Configure 12 Jan 2003 19:50:06 -0000 1.13
***************
*** 1696,1700 ****
# that when build the Perl API the cache file will be installed along
# with the rest of the API
! genex_system("cp $CACHE_FILE_NAME Genex/Config");
print STDOUT <<"EOM";
--- 1696,1702 ----
# that when build the Perl API the cache file will be installed along
# with the rest of the API
! my $DIR = 'Genex/Config';
! genex_mkdir($DIR);
! genex_system("cp $CACHE_FILE_NAME $DIR");
print STDOUT <<"EOM";
|
|
From: <jas...@us...> - 2003-01-12 19:30:28
|
Update of /cvsroot/genex/genex-server/Genex/XMLUtils
In directory sc8-pr-cvs1:/tmp/cvs-serv10851
Modified Files:
XMLUtils.pm.in
Log Message:
* XMLUtils/XMLUtils.pm.in (Repository):
removed references to AM_Spots
Index: XMLUtils.pm.in
===================================================================
RCS file: /cvsroot/genex/genex-server/Genex/XMLUtils/XMLUtils.pm.in,v
retrieving revision 1.27
retrieving revision 1.28
diff -C2 -d -r1.27 -r1.28
*** XMLUtils.pm.in 9 Nov 2002 00:34:05 -0000 1.27
--- XMLUtils.pm.in 12 Jan 2003 19:30:23 -0000 1.28
***************
*** 884,1139 ****
}
! package Bio::Genex::ArrayMeasurement;
! sub db2xml {
! my ($usf_db,$doc) = @_;
! return undef;
! }
!
! sub xml2db {
! my ($class,%args) = @_;
! my ($DOC,$am_node,$am_id,$ID_TABLE,$am_db) =
! Bio::Genex::XMLUtils::xml2db(@_);
! return $am_db if defined $am_db;
!
! # check that we've been given an <array> node as well
! error(caller=>__PACKAGE__ . '::xml2db',
! message=>'must provide an <array> node'
! )
! unless exists $args{array};
!
! # we don't need the node anymore
! delete $args{node};
!
! # copy attributes from the array element to the array measurement
! my %array_attrs = $args{array}->getAttributes();
! my %attrs = $am_node->getAttributes();
! my @attr_list = keys %array_attrs;
! @attrs{@attr_list} = @array_attrs{@attr_list};
!
! # check that all the required attributes are specified
! Bio::Genex::XMLUtils::assert_attrs(__PACKAGE__,
! $am_node,
! \%attrs,
! qw(array_layout_id
! release_date
! type
! ));
!
! # get rid of non-object attributes
! my $array_design_id = $attrs{array_layout_id};
! $attrs{ro_groupname} = $attrs{ro_groupname_id};
! $attrs{rw_groupname} = $attrs{rw_groupname_id};
! my $contact_id = $attrs{owner_contact_id};
! my $sample_id = $attrs{sample_id};
! my $spotter_sw_id = $attrs{spotter_sw_id};
! my $scanner_sw_id = $attrs{scanner_sw_id};
! my $scanner_hw_id = $attrs{scanner_hw_id};
! my $image_analysis_sw_id = $attrs{image_analysis_sw_id};
! $attrs{experiment_date} = $attrs{submission_date};
!
! # we find the channel (if any)
! if (exists $attrs{channel_id}) {
! my ($DOC,$channel_node) = Bio::Genex::XMLUtils::xml2db('Channel',
! doc=>$DOC,
! id=>$attrs{channel_id});
! $attrs{channel_name} = $channel_node->getAttribute('description');
! }
!
! delete @attrs{qw(id
! array_layout_id
! sample_id
! submission_date
! channel_id
! spotter_sw_id
! spotter_hw_id
! scanner_sw_id
! scanner_hw_id
! image_analysis_sw_id
! owner_contact_id
! ro_groupname_id
! rw_groupname_id
! )};
!
! $am_db = Bio::Genex::ArrayMeasurement->new(%attrs);
! $ID_TABLE->{"ArrayMeasurement:$am_id"} = $am_db;
! $am_db->am_pk($am_id);
!
! my $ro_gs_db = Bio::Genex::GroupSec->xml2db(%args,id=>$attrs{ro_groupname});
! $am_db->ro_groupname_obj($ro_gs_db);
! my $rw_gs_db = Bio::Genex::GroupSec->xml2db(%args,id=>$attrs{rw_groupname});
! $am_db->rw_groupname_obj($rw_gs_db);
!
! my $con_db = Bio::Genex::Contact->xml2db(%args,id=>$contact_id);
! $am_db->provider_con_obj($con_db);
!
! my $al_db = Bio::Genex::ArrayDesign->xml2db(%args,id=>$array_design_id);
! $am_db->al_obj($al_db);
!
! if (defined $sample_id) {
! my $samp_db = Bio::Genex::Sample->xml2db(%args,
! id=>$sample_id);
! $am_db->smp_obj($samp_db);
! }
! if (defined $image_analysis_sw_id) {
! my $sw_db = Bio::Genex::Software->xml2db(%args,
! id=>$image_analysis_sw_id);
! $am_db->image_anal_sw_obj($sw_db);
! }
! if (defined $spotter_sw_id) {
! my $sw_db = Bio::Genex::Software->xml2db(%args,
! id=>$spotter_sw_id);
! $am_db->spotter_sw_obj($sw_db);
! }
! if (defined $scanner_sw_id) {
! my $sw_db = Bio::Genex::Software->xml2db(%args,
! id=>$scanner_sw_id);
! $am_db->scan_sw_obj($sw_db);
! }
! if (defined $scanner_hw_id) {
! my $scan_db = Bio::Genex::Scanner->xml2db(%args,
! id=>$scanner_hw_id);
! $am_db->scn_obj($scan_db);
! }
!
! # check if we should process the design spot file
! if ($args{resolve_ext_files}) {
! my ($data_node) = $am_node->getElementsByTagName('data');
! if (defined $data_node) {
! $am_db->am_spots_obj(Bio::Genex::AM_Spots->xml2db(%args,
! node=>$data_node));
! }
! }
! return $am_db;
! }
!
! package Bio::Genex::AM_Spots_DocumentHandler;
! use Bio::Genex::AM_Spots;
! use strict;
! use vars qw(@ISA);
! @ISA = qw(XML::Xerces::PerlDocumentHandler);
!
! sub start_element {
! my ($self,$element,$attr_list) = @_;
! if ($element eq 'spot') {
! my $spot_id = $attr_list->getValue('array_layout_spot_id');
! error(caller=>__PACKAGE__ . '::start_element',
! message=>"No 'array_layout_spot_id' found")
! unless $spot_id ne '';
!
! if ($self->{genex1}) {
! $spot_id =~ s/AL_Spots/Feature/;
! $spot_id =~ s/:NCGR//;
! }
!
! # translate the sequence feature ID into a foreign key
! $self->{hash}->{feature_fk} = $self->{id_table}->{$spot_id};
! } elsif ($element eq 'ratio') {
! $self->{hash}->{value} = $attr_list->getValue('value');
! } elsif ($element eq 'measurement') {
! my %hash = $attr_list->to_hash();
! if (exists $hash{background}) {
! $self->{hash}->{value} = $hash{background}
! } elsif (exists $hash{raw_intensity}) {
! $self->{hash}->{value} = $hash{raw_intensity}
! } elsif (exists $hash{corrected_value}) {
! $self->{hash}->{value} = $hash{corrected_value}
! } else {
! error(caller=>__PACKAGE__ . '::start_element',
! message=>"No spot value found");
! }
! }
! }
!
! sub end_element {
! my ($self,$element) = @_;
! return unless $element eq 'spot';
!
! # store a hash slice of the attributes into the matrix
! push(@{$self->{spots}},
! [$self->{hash}->{feature_fk},$self->{hash}->{value}]);
! undef $self->{hash};
! }
!
! package Bio::Genex::AM_Spots;
! sub db2xml {
! my ($usf_db,$doc) = @_;
! return undef;
! }
!
! sub xml2db {
! use Bio::Genex qw(error);
! use File::Basename;
! use vars qw($MATRIX_HEADER);
! $MATRIX_HEADER = [qw(feature_fk
! spot_value
! )];
!
! my ($class,%args) = @_;
! my $DOC= $args{doc} ||
! error(caller=>__PACKAGE__ . '::xml2db',
! message=>"Must specify 'doc' parameter");
!
! my $data_node= $args{node} ||
! error(caller=>__PACKAGE__ . '::xml2db',
! message=>"Must specify 'node' parameter");
!
! my $ext_id = $data_node->getAttribute('external_file_id') ||
! error(caller=>__PACKAGE__ . '::xml2db',
! message=>"Couldn't find external_file_id for node: "
! . $data_node->serialize);
!
! my $external_file_node = $DOC->getElementById($ext_id) ||
! error(caller=>__PACKAGE__ . '::xml2db',
! message=>"Couldn't find external_file_id for node: "
! . $data_node->serialize);
! error(caller=>__PACKAGE__ . '::xml2db',
! message=>"Bad ID: $ext_id, no such ID in document")
! unless defined $external_file_node;
!
! my $file = $external_file_node->getAttribute('file_name') ||
! error(caller=>__PACKAGE__ . '::xml2db',
! message=>"Couldn't find file_name for node: "
! . $external_file_node->serialize);
!
! # this file path is relative to the file we are parsing
! # to get that info we need the input source
! my $source = $DOC->input_source();
! my $sys_id = $source->getSystemId();
! my $path = (fileparse($sys_id))[1];
! $file = "$path/$file";
!
! # now we create a SAXParser to handle the putting the spot data
! # into a matrix
! my $doc_handler = Bio::Genex::AM_Spots_DocumentHandler->new();
! $doc_handler->{spots} = [$MATRIX_HEADER];
! $doc_handler->{doc} = $DOC;
! $doc_handler->{id_table} = $DOC->id_table();
! $doc_handler->{genex1} = 1
! if exists $args{genex1};
!
! my $SAX = XML::Xerces::SAXParser->new();
! $SAX->setDocumentHandler($doc_handler);
!
! # add an error handler so we don't get Abort's with no message
! my $err_handler = XML::Xerces::PerlErrorHandler->new();
! $SAX->setErrorHandler($err_handler);
!
! my $input_source;
! eval {
! $input_source = XML::Xerces::LocalFileInputSource->new($file);
! };
! error(caller=> __PACKAGE__ . '::xml2db',
! message=>"Couldn't create input source: " . $@->getMessage())
! if $@;
!
! # turn on the parser and let the handler do the work
! eval {
! $SAX->parse($input_source);
! };
! error(caller=> __PACKAGE__ . '::xml2db',
! message=>"Couldn't parse input source: " . $@->getMessage())
! if $@;
! return $doc_handler->{spots};
! }
package Bio::Genex::SF_ExternalDBLink;
--- 884,1139 ----
}
! ### package Bio::Genex::ArrayMeasurement;
! ### sub db2xml {
! ### my ($usf_db,$doc) = @_;
! ### return undef;
! ### }
! ###
! ### sub xml2db {
! ### my ($class,%args) = @_;
! ### my ($DOC,$am_node,$am_id,$ID_TABLE,$am_db) =
! ### Bio::Genex::XMLUtils::xml2db(@_);
! ### return $am_db if defined $am_db;
! ###
! ### # check that we've been given an <array> node as well
! ### error(caller=>__PACKAGE__ . '::xml2db',
! ### message=>'must provide an <array> node'
! ### )
! ### unless exists $args{array};
! ###
! ### # we don't need the node anymore
! ### delete $args{node};
! ###
! ### # copy attributes from the array element to the array measurement
! ### my %array_attrs = $args{array}->getAttributes();
! ### my %attrs = $am_node->getAttributes();
! ### my @attr_list = keys %array_attrs;
! ### @attrs{@attr_list} = @array_attrs{@attr_list};
! ###
! ### # check that all the required attributes are specified
! ### Bio::Genex::XMLUtils::assert_attrs(__PACKAGE__,
! ### $am_node,
! ### \%attrs,
! ### qw(array_layout_id
! ### release_date
! ### type
! ### ));
! ###
! ### # get rid of non-object attributes
! ### my $array_design_id = $attrs{array_layout_id};
! ### $attrs{ro_groupname} = $attrs{ro_groupname_id};
! ### $attrs{rw_groupname} = $attrs{rw_groupname_id};
! ### my $contact_id = $attrs{owner_contact_id};
! ### my $sample_id = $attrs{sample_id};
! ### my $spotter_sw_id = $attrs{spotter_sw_id};
! ### my $scanner_sw_id = $attrs{scanner_sw_id};
! ### my $scanner_hw_id = $attrs{scanner_hw_id};
! ### my $image_analysis_sw_id = $attrs{image_analysis_sw_id};
! ### $attrs{experiment_date} = $attrs{submission_date};
! ###
! ### # we find the channel (if any)
! ### if (exists $attrs{channel_id}) {
! ### my ($DOC,$channel_node) = Bio::Genex::XMLUtils::xml2db('Channel',
! ### doc=>$DOC,
! ### id=>$attrs{channel_id});
! ### $attrs{channel_name} = $channel_node->getAttribute('description');
! ### }
! ###
! ### delete @attrs{qw(id
! ### array_layout_id
! ### sample_id
! ### submission_date
! ### channel_id
! ### spotter_sw_id
! ### spotter_hw_id
! ### scanner_sw_id
! ### scanner_hw_id
! ### image_analysis_sw_id
! ### owner_contact_id
! ### ro_groupname_id
! ### rw_groupname_id
! ### )};
! ###
! ### $am_db = Bio::Genex::ArrayMeasurement->new(%attrs);
! ### $ID_TABLE->{"ArrayMeasurement:$am_id"} = $am_db;
! ### $am_db->am_pk($am_id);
! ###
! ### my $ro_gs_db = Bio::Genex::GroupSec->xml2db(%args,id=>$attrs{ro_groupname});
! ### $am_db->ro_groupname_obj($ro_gs_db);
! ### my $rw_gs_db = Bio::Genex::GroupSec->xml2db(%args,id=>$attrs{rw_groupname});
! ### $am_db->rw_groupname_obj($rw_gs_db);
! ###
! ### my $con_db = Bio::Genex::Contact->xml2db(%args,id=>$contact_id);
! ### $am_db->provider_con_obj($con_db);
! ###
! ### my $al_db = Bio::Genex::ArrayDesign->xml2db(%args,id=>$array_design_id);
! ### $am_db->al_obj($al_db);
! ###
! ### if (defined $sample_id) {
! ### my $samp_db = Bio::Genex::Sample->xml2db(%args,
! ### id=>$sample_id);
! ### $am_db->smp_obj($samp_db);
! ### }
! ### if (defined $image_analysis_sw_id) {
! ### my $sw_db = Bio::Genex::Software->xml2db(%args,
! ### id=>$image_analysis_sw_id);
! ### $am_db->image_anal_sw_obj($sw_db);
! ### }
! ### if (defined $spotter_sw_id) {
! ### my $sw_db = Bio::Genex::Software->xml2db(%args,
! ### id=>$spotter_sw_id);
! ### $am_db->spotter_sw_obj($sw_db);
! ### }
! ### if (defined $scanner_sw_id) {
! ### my $sw_db = Bio::Genex::Software->xml2db(%args,
! ### id=>$scanner_sw_id);
! ### $am_db->scan_sw_obj($sw_db);
! ### }
! ### if (defined $scanner_hw_id) {
! ### my $scan_db = Bio::Genex::Scanner->xml2db(%args,
! ### id=>$scanner_hw_id);
! ### $am_db->scn_obj($scan_db);
! ### }
! ###
! ### # check if we should process the design spot file
! ### if ($args{resolve_ext_files}) {
! ### my ($data_node) = $am_node->getElementsByTagName('data');
! ### if (defined $data_node) {
! ### $am_db->am_spots_obj(Bio::Genex::AM_Spots->xml2db(%args,
! ### node=>$data_node));
! ### }
! ### }
! ### return $am_db;
! ### }
! ###
! ### package Bio::Genex::AM_Spots_DocumentHandler;
! ### use Bio::Genex::AM_Spots;
! ### use strict;
! ### use vars qw(@ISA);
! ### @ISA = qw(XML::Xerces::PerlDocumentHandler);
! ###
! ### sub start_element {
! ### my ($self,$element,$attr_list) = @_;
! ### if ($element eq 'spot') {
! ### my $spot_id = $attr_list->getValue('array_layout_spot_id');
! ### error(caller=>__PACKAGE__ . '::start_element',
! ### message=>"No 'array_layout_spot_id' found")
! ### unless $spot_id ne '';
! ###
! ### if ($self->{genex1}) {
! ### $spot_id =~ s/AL_Spots/Feature/;
! ### $spot_id =~ s/:NCGR//;
! ### }
! ###
! ### # translate the sequence feature ID into a foreign key
! ### $self->{hash}->{feature_fk} = $self->{id_table}->{$spot_id};
! ### } elsif ($element eq 'ratio') {
! ### $self->{hash}->{value} = $attr_list->getValue('value');
! ### } elsif ($element eq 'measurement') {
! ### my %hash = $attr_list->to_hash();
! ### if (exists $hash{background}) {
! ### $self->{hash}->{value} = $hash{background}
! ### } elsif (exists $hash{raw_intensity}) {
! ### $self->{hash}->{value} = $hash{raw_intensity}
! ### } elsif (exists $hash{corrected_value}) {
! ### $self->{hash}->{value} = $hash{corrected_value}
! ### } else {
! ### error(caller=>__PACKAGE__ . '::start_element',
! ### message=>"No spot value found");
! ### }
! ### }
! ### }
! ###
! ### sub end_element {
! ### my ($self,$element) = @_;
! ### return unless $element eq 'spot';
! ###
! ### # store a hash slice of the attributes into the matrix
! ### push(@{$self->{spots}},
! ### [$self->{hash}->{feature_fk},$self->{hash}->{value}]);
! ### undef $self->{hash};
! ### }
! ###
! ### package Bio::Genex::AM_Spots;
! ### sub db2xml {
! ### my ($usf_db,$doc) = @_;
! ### return undef;
! ### }
! ###
! ### sub xml2db {
! ### use Bio::Genex qw(error);
! ### use File::Basename;
! ### use vars qw($MATRIX_HEADER);
! ### $MATRIX_HEADER = [qw(feature_fk
! ### spot_value
! ### )];
! ###
! ### my ($class,%args) = @_;
! ### my $DOC= $args{doc} ||
! ### error(caller=>__PACKAGE__ . '::xml2db',
! ### message=>"Must specify 'doc' parameter");
! ###
! ### my $data_node= $args{node} ||
! ### error(caller=>__PACKAGE__ . '::xml2db',
! ### message=>"Must specify 'node' parameter");
! ###
! ### my $ext_id = $data_node->getAttribute('external_file_id') ||
! ### error(caller=>__PACKAGE__ . '::xml2db',
! ### message=>"Couldn't find external_file_id for node: "
! ### . $data_node->serialize);
! ###
! ### my $external_file_node = $DOC->getElementById($ext_id) ||
! ### error(caller=>__PACKAGE__ . '::xml2db',
! ### message=>"Couldn't find external_file_id for node: "
! ### . $data_node->serialize);
! ### error(caller=>__PACKAGE__ . '::xml2db',
! ### message=>"Bad ID: $ext_id, no such ID in document")
! ### unless defined $external_file_node;
! ###
! ### my $file = $external_file_node->getAttribute('file_name') ||
! ### error(caller=>__PACKAGE__ . '::xml2db',
! ### message=>"Couldn't find file_name for node: "
! ### . $external_file_node->serialize);
! ###
! ### # this file path is relative to the file we are parsing
! ### # to get that info we need the input source
! ### my $source = $DOC->input_source();
! ### my $sys_id = $source->getSystemId();
! ### my $path = (fileparse($sys_id))[1];
! ### $file = "$path/$file";
! ###
! ### # now we create a SAXParser to handle the putting the spot data
! ### # into a matrix
! ### my $doc_handler = Bio::Genex::AM_Spots_DocumentHandler->new();
! ### $doc_handler->{spots} = [$MATRIX_HEADER];
! ### $doc_handler->{doc} = $DOC;
! ### $doc_handler->{id_table} = $DOC->id_table();
! ### $doc_handler->{genex1} = 1
! ### if exists $args{genex1};
! ###
! ### my $SAX = XML::Xerces::SAXParser->new();
! ### $SAX->setDocumentHandler($doc_handler);
! ###
! ### # add an error handler so we don't get Abort's with no message
! ### my $err_handler = XML::Xerces::PerlErrorHandler->new();
! ### $SAX->setErrorHandler($err_handler);
! ###
! ### my $input_source;
! ### eval {
! ### $input_source = XML::Xerces::LocalFileInputSource->new($file);
! ### };
! ### error(caller=> __PACKAGE__ . '::xml2db',
! ### message=>"Couldn't create input source: " . $@->getMessage())
! ### if $@;
! ###
! ### # turn on the parser and let the handler do the work
! ### eval {
! ### $SAX->parse($input_source);
! ### };
! ### error(caller=> __PACKAGE__ . '::xml2db',
! ### message=>"Couldn't parse input source: " . $@->getMessage())
! ### if $@;
! ### return $doc_handler->{spots};
! ### }
package Bio::Genex::SF_ExternalDBLink;
|
|
From: <jas...@us...> - 2003-01-11 21:07:31
|
Update of /cvsroot/genex/genex-server/Genex/scripts
In directory sc8-pr-cvs1:/tmp/cvs-serv4538
Modified Files:
mbad-insert.pl.in
Log Message:
* scripts/mbad-insert.pl.in (Repository):
unlink files on completion
Index: mbad-insert.pl.in
===================================================================
RCS file: /cvsroot/genex/genex-server/Genex/scripts/mbad-insert.pl.in,v
retrieving revision 1.9
retrieving revision 1.10
diff -C2 -d -r1.9 -r1.10
*** mbad-insert.pl.in 23 Nov 2002 22:27:05 -0000 1.9
--- mbad-insert.pl.in 11 Jan 2003 21:07:28 -0000 1.10
***************
*** 307,310 ****
--- 307,311 ----
unless (scalar keys %features) == $count;
print STDERR "Found $count data lines\n" if $OPTIONS{debug};
+ unlink($file);
}
$insert_sth->finish();
|
|
From: <jas...@us...> - 2003-01-11 19:29:18
|
Update of /cvsroot/genex/genex-server/Genex/scripts
In directory sc8-pr-cvs1:/tmp/cvs-serv30951/scripts
Modified Files:
qtdim-insert.pl.in
Log Message:
* scripts/qtdim-insert.pl.in (Repository):
uses new Bio::MAGE
Index: qtdim-insert.pl.in
===================================================================
RCS file: /cvsroot/genex/genex-server/Genex/scripts/qtdim-insert.pl.in,v
retrieving revision 1.4
retrieving revision 1.5
diff -C2 -d -r1.4 -r1.5
*** qtdim-insert.pl.in 15 Nov 2002 22:03:04 -0000 1.4
--- qtdim-insert.pl.in 11 Jan 2003 19:29:15 -0000 1.5
***************
*** 12,15 ****
--- 12,16 ----
# use blib;
use Carp;
+ use Bio::MAGE 20020902.3;
use Bio::MAGE::XMLUtils;
use Getopt::Long;
***************
*** 89,93 ****
unless exists $OPTIONS{data_end_regex};
! my $reader = Bio::MAGE::XMLReader->new();
#### Verify that the input file exists
--- 90,94 ----
unless exists $OPTIONS{data_end_regex};
! my $reader = Bio::MAGE::XML::Reader->new();
#### Verify that the input file exists
|
|
From: <jas...@us...> - 2003-01-11 19:28:43
|
Update of /cvsroot/genex/genex-server/Genex/scripts
In directory sc8-pr-cvs1:/tmp/cvs-serv30274/scripts
Modified Files:
array-design-insert.pl.in
Log Message:
* scripts/array-design-insert.pl.in (Repository):
no longer assumes zone info exists
uses new Bio::MAGE
Index: array-design-insert.pl.in
===================================================================
RCS file: /cvsroot/genex/genex-server/Genex/scripts/array-design-insert.pl.in,v
retrieving revision 1.13
retrieving revision 1.14
diff -C2 -d -r1.13 -r1.14
*** array-design-insert.pl.in 23 Nov 2002 10:56:25 -0000 1.13
--- array-design-insert.pl.in 11 Jan 2003 19:28:40 -0000 1.14
***************
*** 25,31 ****
use Bio::Genex::GenexAdmin;
! use Bio::MAGE qw(:ALL);
! use XML::Xerces;
use Bio::MAGE::XMLUtils;
$Bio::Genex::ArrayDesign::DEBUG = 1;
--- 25,31 ----
use Bio::Genex::GenexAdmin;
! use Bio::MAGE 20020902.3 qw(:ALL);
use Bio::MAGE::XMLUtils;
+ use XML::Xerces;
$Bio::Genex::ArrayDesign::DEBUG = 1;
***************
*** 129,133 ****
push(@args,count=>$OPTIONS{count});
}
! my $reader = Bio::MAGE::XMLReader->new(@args);
my $mage = $reader->read($OPTIONS{file});
--- 129,133 ----
push(@args,count=>$OPTIONS{count});
}
! my $reader = Bio::MAGE::XML::Reader->new(@args);
my $mage = $reader->read($OPTIONS{file});
***************
*** 216,232 ****
#
my @features;
unless (exists $OPTIONS{no_fr_maps}) {
# Bio::Genex::ArrayDesign::insert_db() calls insert_matrix()
# so we push the matrix header as the first item
! push(@features,[qw(feature_identifier
! x_image_location
! y_image_location
! grid_row_image_location
! grid_col_image_location
! rep_fk
! feature_type
! )
! ]
! );
my @mage_fr_maps = ();
unless (exists $mage->packages->{DesignElement}) {
--- 216,233 ----
#
my @features;
+ my @header;
unless (exists $OPTIONS{no_fr_maps}) {
# Bio::Genex::ArrayDesign::insert_db() calls insert_matrix()
# so we push the matrix header as the first item
! @header = qw(feature_identifier
! x_image_location
! y_image_location
! grid_row_image_location
! grid_col_image_location
! rep_fk
! feature_type
! );
! push(@features,\@header);
!
my @mage_fr_maps = ();
unless (exists $mage->packages->{DesignElement}) {
***************
*** 242,245 ****
--- 243,247 ----
}
$start = new Benchmark;
+ my ($row_removed,$x_removed);
foreach my $map (@mage_fr_maps) {
my $reporter = $map->getReporter();
***************
*** 271,293 ****
unless $name;
my $loc = $feature->getFeatureLocation();
! die "Couldn't find location for feature with reporter: $rep_name"
! unless defined $feature;
! my $x = $loc->getRow();
! die "Bad row for location in feature: $name"
! unless $x > -1;
! my $y = $loc->getColumn();
! die "Bad column for location in feature: $name"
! unless $y > -1;
my $zone = $feature->getZone();
! die "Couldn't find zone for feature with reporter: $rep_name"
! unless defined $feature;
! my $row = $zone->getRow();
! die "Bad row for zone in feature: $name"
! unless $row > -1;
! my $column = $zone->getColumn();
! die "Bad column for zone in feature: $name"
! unless $column > -1;
--- 273,319 ----
unless $name;
+ my @args;
my $loc = $feature->getFeatureLocation();
! my ($x,$y);
! if (defined $loc) {
! $x = $loc->getRow();
! die "Bad row for location in feature: $name"
! unless $x > -1;
! $y = $loc->getColumn();
! die "Bad column for location in feature: $name"
! unless $y > -1;
! push(@args,$x,$y);
! } else {
! warn "Couldn't find location for feature with reporter: $rep_name";
!
! unless ($x_removed) {
! # remove the row and col from the feature header
! my @tmp = grep {$_ !~ /^x_image/ and $_ !~ /^y_image/ } @{$features[0]};
! $features[0] = \@tmp;
! $x_removed = 1;
! }
!
! }
my $zone = $feature->getZone();
! my ($row,$column);
! if (defined $zone) {
! $row = $zone->getRow();
! die "Bad row for zone in feature: $name"
! unless $row > -1;
! $column = $zone->getColumn();
! die "Bad column for zone in feature: $name"
! unless $column > -1;
! push(@args,$row,$column);
! } else {
! warn "Couldn't find zone for feature with reporter: $rep_name";
!
! unless ($row_removed) {
! # remove the row and col from the feature header
! my @tmp = grep {$_ !~ /^grid_row/ and $_ !~ /^grid_col/ } @{$features[0]};
! $features[0] = \@tmp;
! $row_removed = 1;
! }
! }
***************
*** 295,302 ****
# so we create a matrix of Feature data, instead of a list of objects
push(@features,[$name, # feature_identifier
! $x, # x_image_location
! $y, # y_image_location
! $row, # grid_row_image_location
! $column, # grid_col_image_location
$rep_fk, # rep_fk
$type, # feature_type
--- 321,325 ----
# so we create a matrix of Feature data, instead of a list of objects
push(@features,[$name, # feature_identifier
! @args,
$rep_fk, # rep_fk
$type, # feature_type
|
|
From: <tw...@us...> - 2003-01-07 22:08:32
|
Update of /cvsroot/genex/genex-server
In directory sc8-pr-cvs1:/tmp/cvs-serv32164
Modified Files:
Tag: Rel-1_0_1-branch
genex_schema.sql
Log Message:
fix order_seq so that 01 is the first number
Index: genex_schema.sql
===================================================================
RCS file: /cvsroot/genex/genex-server/genex_schema.sql,v
retrieving revision 1.3.2.21
retrieving revision 1.3.2.22
diff -C2 -d -r1.3.2.21 -r1.3.2.22
*** genex_schema.sql 3 Jan 2003 21:38:59 -0000 1.3.2.21
--- genex_schema.sql 7 Jan 2003 22:08:15 -0000 1.3.2.22
***************
*** 190,194 ****
-- GRANT SELECT on "sample_smp_pk_seq" to "readonly";
! CREATE SEQUENCE "order_seq" start 1 increment 1 maxvalue 2147483647 minvalue 1 cache 1 ;
REVOKE ALL on "order_seq" from PUBLIC;
--- 190,199 ----
-- GRANT SELECT on "sample_smp_pk_seq" to "readonly";
! -- 2003-01-07 Tom
! -- After experimenting I discovered that start should be 1, and minvalue zero.
! -- This gives the desired result that the first number created is 01.
! -- I wonder if this has something to do with the is_called boolean field?
!
! CREATE SEQUENCE "order_seq" start 1 increment 1 maxvalue 2147483647 minvalue 0 cache 1 ;
REVOKE ALL on "order_seq" from PUBLIC;
***************
*** 2186,2189 ****
--- 2191,2199 ----
GRANT SELECT on "sampletype" to "readonly";
+ --
+ -- Tom 2003-01-03
+ -- It seems silly to have an extraction table that is 1 to 1 with
+ -- many records in file_info.
+ --
create table "file_info" (
***************
*** 2194,2198 ****
"use_as_input" boolean,
"fi_comments" text,
! "fi_checksum" character varying(128)
) without OIDs;
--- 2204,2210 ----
"use_as_input" boolean,
"fi_comments" text,
! "fi_checksum" character varying(128),
! "conds" character varying(128),
! "cond_labels" text
) without OIDs;
|
|
From: <tw...@us...> - 2003-01-07 21:42:56
|
Update of /cvsroot/genex/genex-server/site/webtools
In directory sc8-pr-cvs1:/tmp/cvs-serv19449
Modified Files:
Tag: Rel-1_0_1-branch
choose_order_curator.html choose_order_curator.pl index.pl
sessionlib.pl sql_lib.pl
Added Files:
Tag: Rel-1_0_1-branch
show1_curator.html show1_curator.pl
Log Message:
add single order view to curator options
--- NEW FILE: show1_curator.html ---
<html><head><title>Curator's Single Order Display</title></head>
<body bgcolor="#FFFFFF">
<table width="600" border="0" cellpadding="0" cellspacing="0">
<tr><td valign="top" width="207"><a href="./"><img src="../graphics/genex_logo.jpg" border="0" width="207" height="87"></a></td>
<td> </td>
<td valign="top">Curator's Single Order Display<br><br>
<a href="./">Return to Genex Member Home</a>
</td>
</tr>
</table>
<br>
{oi_form}
<br>
<loop>
<table width="750" border="1" cellpadding="2" cellspacing="0">
<tr>
<td valign="top">
<form name="form" method="post" action="edit_order_curator2.pl">
<table width="100%" border="0" cellpadding="2" cellspacing="0">
<tr>
<td width="30%">
<input type=hidden name="oi_pk" value={oi_pk}>
<div align="right">Owner:</div>
</td>
<td width="30%"> {contact_fname} {contact_lname} ( {login} ) {contact_phone}</td>
<td width="40%"> </td>
<td width="40%"><input type=submit name="submit" value="Update"></td>
</tr>
<tr>
<td bgcolor="#99FFCC">
<div align="right">Locked: </div>
</td>
<td>
<input type="checkbox" name="locked" value="1">
</td>
<td bgcolor="#99FFCC"></td>
<td></td>
</tr>
<tr>
<td bgcolor="#99FFCC">
<div align="right">Order number: </div>
</td>
<td> <b>{order_number}</b></td>
<td bgcolor="#99FFCC">
<div align="right">Number of samples: </div>
</td>
<td> {number_of_samples}</td>
</tr>
<tr>
<td bgcolor="#99FFCC">
<div align="right">Chips Ordered: </div>
</td>
<td>
<input type="checkbox" name="chips_ordered" value="1">
</td>
<td bgcolor="#99FFCC">
<div align="right">Chips Billed: </div>
</td>
<td>
<input type="checkbox" name="chips_billed" value="1">
</td>
</tr>
<tr>
<td bgcolor="#99FFCC">
<div align="right">RNA Iso. Billed: </div>
</td>
<td>
<input type="checkbox" name="rna_isolation_billed" value="1">
</td>
<td bgcolor="#99FFCC">
<div align="right">Analysis Billed: </div>
</td>
<td>
<input type="checkbox" name="analysis_billed" value="1">
</td>
</tr>
<tr>
<td bgcolor="#99FFCC">
<div align="right">Billing code: </div>
</td>
<td>
<input type="text" name="billing_code" value="{billing_code}" maxlength="128">
</td>
<td bgcolor="#99FFCC"></td>
<td></td>
</tr>
</table>
</form>
<font color="#FF0000">{message}</font>
<br>
<table width="100%" border=0 cellpadding=2 cellspacing=0>
<tr bgcolor="#99FFCC">
<td valign="top">smp_pk</td>
<td valign="top">Hyb. Name</td>
<td valign="top">Chip</td>
<td valign="top">Study name</td>
<td valign="top">Protocol name</td>
<td valign="top">Run date</td>
<td valign="top"> </td>
<td valign="top"> </td>
</tr>
<loop2>
<tr>
<td>{smp_pk}</td>
<td>{hybridization_name}</td>
<td>{al_name}</td>
<td>{study_name}</td>
<td>{ec_name}</td>
<td>{timestamp}</td>
<td> </td>
<td>
<form name="form1" method="post" action="load_data1.pl">
<input type="submit" name="Submit" value="Load {hybridization_name}">
<input type="hidden" name="am_pk" value="{am_pk}">
</form>
</td>
</tr>
</loop2>
</table>
</td>
</tr>
</table>
<br>
</loop>
<a href="./">Return to Genex Member Home</a><br><br clear=all><br>
<br>
<br>
</body>
</html>
--- NEW FILE: show1_curator.pl ---
#!/usr/bin/perl
use strict;
use CGI;
use CGI::Carp qw(fatalsToBrowser);
require "sessionlib.pl";
main:
{
my $debug;
my $q = new CGI;
my %ch = $q->Vars();
my $dbh = new_connection(); # sessionlib.pl
my $us_fk = get_us_fk($dbh);
if (! is_curator($dbh, $us_fk))
{
write_log("error: non curator runs choose_order_curator.pl");
my $url = index_url(); # see sessionlib.pl
print "Location: $url\n\n";
}
#
# readtemplate() is in sessionlib.pl
#
(my $allhtml, my $loop_template, my $tween, my $loop_template2) = readtemplate("show1_curator.html");
my $sth = getq("oi_pk_by_number", $dbh);
$sth->execute($ch{order_number});
if ($sth->rows() != 1)
{
my $temp = $sth->rows();
die "Find order_number $ch{order_number} returned $temp record(s).\n";
}
(my $oi_pk) = $sth->fetchrow_array();
my $recordlist = makelist($dbh, $loop_template, $loop_template2, $oi_pk);
my $oi_form = oi_form($dbh); # see sessionlib.pl
$allhtml =~ s/{debug}/$debug/;
$allhtml =~ s/<loop_here>/$recordlist/sg;
$allhtml =~ s/{oi_form}/$oi_form/sg;
print "Content-type: text/html\n\n";
print "$allhtml\n";
$dbh->disconnect;
exit(0);
}
sub makelist
{
my $dbh = $_[0];
my $loop_template = $_[1];
my $loop_template2 = $_[2];
my $oi_pk = $_[3];
# sql statements
my $sql = "select * from order_info where oi_pk=$oi_pk";
my $billing_sql = "select * from billing where oi_fk=?";
my $sample_sql = "select timestamp, exp_condition.name as ec_name, abbrev_name, study.study_name, study.sty_pk from sample,exp_condition,study where study.sty_pk=exp_condition.sty_fk and exp_condition.ec_pk=sample.ec_fk and smp_pk=?";
my $sc_sql = "select count(smp_pk) from sample where oi_fk=?";
my $am_sql = "select hybridization_name,smp_pk,am_pk,al_fk from arraymeasurement,sample,order_info where oi_pk=? and order_info.oi_pk=sample.oi_fk and arraymeasurement.smp_fk=sample.smp_pk order by smp_pk,am_pk";
my $al_sql = "select arraylayout.name as al_name from arraylayout where al_pk=?";
# sth vars
my $sth = $dbh->prepare($sql) ;
my $billing_sth = $dbh->prepare($billing_sql);
my $sample_sth = $dbh->prepare($sample_sql);
my $sc_sth = $dbh->prepare($sc_sql);
my $owner_sth = getq("order_owner_info", $dbh);
my $am_sth = $dbh->prepare($am_sql);
my $al_sth = $dbh->prepare($al_sql);
my $reclist;
#
# Put all necessary data in to the $rec hash, and just loop through
# the keys substituting into the HTML template.
# This assumes that field names, and anything added to the $rec hash
# is unique!
#
$sth->execute() || die "$sql\n$DBI::errstr\n";
my $o_hr; # order_info hash ref
while($o_hr = $sth->fetchrow_hashref())
{
$sc_sth->execute($o_hr->{oi_pk}) || die "$sc_sql\n$DBI::errstr\n";
($o_hr->{number_of_samples}) = $sc_sth->fetchrow_array();
$owner_sth->execute($o_hr->{oi_pk}) || die "Query order_owner_info execute failed. $DBI::errstr\n";
($o_hr->{login},$o_hr->{contact_fname},$o_hr->{contact_lname},$o_hr->{contact_phone},$o_hr->{us_pk}) = $owner_sth->fetchrow_array();
my $loop_instance = $loop_template;
my $reclist2; # list of loop_instance2 records
$reclist2 = "";
$billing_sth->execute($o_hr->{oi_pk}) || die "$billing_sql\n$DBI::errstr\n";
my $b_hr = $billing_sth->fetchrow_hashref();
$am_sth->execute($o_hr->{oi_pk}) || die "$am_sql\n$DBI::errstr\n";
my $s_hr; # Messy. Used for results from several queries.
while($s_hr = $am_sth->fetchrow_hashref())
{
$s_hr->{al_name} = "None selected";
if ($s_hr->{al_fk} > 0)
{
$al_sth->execute($s_hr->{al_fk}) || die "$al_sql\n$DBI::errstr\n";
($s_hr->{al_name}) = $al_sth->fetchrow_array();
}
$sample_sth->execute($s_hr->{smp_pk}) || die "$sample_sql\n$DBI::errstr\n";
($s_hr->{timestamp}, $s_hr->{ec_name}, $s_hr->{abbrev_name}, $s_hr->{study_name}, $s_hr->{sty_pk}) = $sample_sth->fetchrow_array();
{
my $temp = verify_study($dbh, $o_hr->{us_pk}, $s_hr->{sty_pk}, 15, $s_hr->{study_name});
if ($o_hr->{message} !~ m/^$temp|m$temp/)
{
$o_hr->{message} .= $temp;
}
$temp = verify_exp($dbh, $o_hr->{us_pk}, $s_hr->{sty_pk}, 16, $s_hr->{ec_name}, $s_hr->{abbrev_name});
if ($o_hr->{message} !~ m/^$temp|m$temp/)
{
$o_hr->{message} .= $temp;
}
$temp = verify_hyb($dbh, $s_hr->{am_pk});
if ($o_hr->{message} !~ m/^$temp|m$temp/)
{
$o_hr->{message} .= $temp;
}
}
$s_hr->{timestamp} = sql2date($s_hr->{timestamp}); # sql2date() is in sessionlib.pl
my $loop_instance2 = $loop_template2;
#
# Only one of the hash refs will hit, so it is ok
# to have both on the right side of the regexp.
#
$loop_instance2 =~ s/{(.*?)}/$o_hr->{$1}$b_hr->{$1}$s_hr->{$1}/g;
if (check_spots($dbh, $s_hr->{am_pk}) == 1)
{
$loop_instance2 =~ s/<form[^<].*?name=\"form1\".*?form>/Loaded/s;
}
$reclist2 .= $loop_instance2;
}
#
# Turn message param in the form 0m1m2m back into a message text.
# Use the wonderful and dangerous /e switch to eval the right side
# of the regex. See sub messages() in sessionlib.pl
#
$o_hr->{message} =~ s/(\d+)m/messages($1)/eg;
$loop_instance =~ s/{(.*?)}/$o_hr->{$1}$b_hr->{$1}/g;
$loop_instance =~ s/\<loop_here2\>/$reclist2/s; # no g, only one inner loop
$loop_instance = fixradiocheck("locked",
$o_hr->{locked},
"checkbox",
$loop_instance);
$loop_instance = fixradiocheck("chips_ordered",
$o_hr->{chips_ordered},
"checkbox",
$loop_instance);
#
# Oct 11, 2002 Tom: one checkbox is in the order_info table,
# but the rest are in the billing table. Go figure.
#
$loop_instance = fixradiocheck("chips_billed",
$b_hr->{chips_billed},
"checkbox",
$loop_instance);
$loop_instance = fixradiocheck("rna_isolation_billed",
$b_hr->{rna_isolation_billed},
"checkbox",
$loop_instance);
$loop_instance = fixradiocheck("analysis_billed",
$b_hr->{analysis_billed},
"checkbox",
$loop_instance);
$reclist .= $loop_instance;
}
return $reclist;
}
#
# return 1 if any data records were found in any of the spots tables
# for the current am_pk
#
sub check_spots
{
my $dbh = $_[0];
my $am_pk = $_[1];
my $sql;
my $sth;
my @tables = ("am_spots_mas5", "am_spots_mas4", "am_spots_dchip");
foreach my $chtab (@tables)
{
$sql = "select count(*) from $chtab where am_fk=$am_pk";
$sth = $dbh->prepare($sql) || die "$sql\n$DBI::errstr\n";
$sth->execute();
(my $rc) = $sth->fetchrow_array();
if ($rc > 0)
{
return 1; # yes, we're returning from inside a loop.
}
}
return 0;
}
# no longer used?
sub sample_info
{
(my $dbh, my $us_fk, my $oi_pk) = @_;
(my $fclause, my $wclause) = read_where_clause("sample", "smp_pk", $us_fk );
my $sql = "select smp_pk,timestamp, exp_condition.name as ec_name, study.study_name from sample,exp_condition,study,$fclause where study.sty_pk=exp_condition.sty_fk and exp_condition.ec_pk=sample.ec_fk and oi_fk=$oi_pk and $wclause";
my $sth = $dbh->prepare($sql) || die "$sql\n$DBI::errstr\n";
$sth->execute() || die "$sql\n$DBI::errstr\n";
my $hyb_sql = "select count(am_pk) from arraymeasurement where smp_fk=?";
my $hyb_sth = $dbh->prepare($hyb_sql);
my $rec;
my $results;
my $xx = 0;
while($rec = $sth->fetchrow_hashref())
{
$hyb_sth->execute($rec->{smp_pk});
($rec->{number_of_hybridizations}) = $hyb_sth->fetchrow_array();
$rec->{timestamp} = sql2date($rec->{timestamp});
$xx++; # we want a one's based counting number in the line below, so increment here.
$results .= "$xx: $rec->{study_name} / $rec->{ec_name} / $rec->{timestamp} / $rec->{number_of_hybridizations}<br>";
}
return ($results, $xx);
}
Index: choose_order_curator.html
===================================================================
RCS file: /cvsroot/genex/genex-server/site/webtools/Attic/choose_order_curator.html,v
retrieving revision 1.1.2.3
retrieving revision 1.1.2.4
diff -C2 -d -r1.1.2.3 -r1.1.2.4
*** choose_order_curator.html 20 Dec 2002 18:43:49 -0000 1.1.2.3
--- choose_order_curator.html 7 Jan 2003 21:42:44 -0000 1.1.2.4
***************
*** 1,12 ****
! <html><head><title>Choose an order</title></head>
<body bgcolor="#FFFFFF">
<table width="600" border="0" cellpadding="0" cellspacing="0">
<tr><td valign="top" width="207"><a href="./"><img src="../graphics/genex_logo.jpg" border="0" width="207" height="87"></a></td>
<td> </td>
! <td valign="top">GeneX Account Update<br><br>
<a href="./">Return to Genex Member Home</a>
</td>
</tr>
</table>
<loop>
--- 1,16 ----
! <html><head><title>Curator's Order Display</title></head>
<body bgcolor="#FFFFFF">
<table width="600" border="0" cellpadding="0" cellspacing="0">
<tr><td valign="top" width="207"><a href="./"><img src="../graphics/genex_logo.jpg" border="0" width="207" height="87"></a></td>
<td> </td>
! <td valign="top">Curator's Order Display<br><br>
<a href="./">Return to Genex Member Home</a>
</td>
</tr>
</table>
+
+ <br>
+ {oi_form}
+ <br>
<loop>
Index: choose_order_curator.pl
===================================================================
RCS file: /cvsroot/genex/genex-server/site/webtools/Attic/choose_order_curator.pl,v
retrieving revision 1.1.2.2
retrieving revision 1.1.2.3
diff -C2 -d -r1.1.2.2 -r1.1.2.3
*** choose_order_curator.pl 18 Nov 2002 21:20:53 -0000 1.1.2.2
--- choose_order_curator.pl 7 Jan 2003 21:42:47 -0000 1.1.2.3
***************
*** 26,36 ****
--- 26,40 ----
}
+ #
# readtemplate() is in sessionlib.pl
+ #
(my $allhtml, my $loop_template, my $tween, my $loop_template2) = readtemplate("choose_order_curator.html");
my $recordlist = makelist($dbh, $loop_template, $loop_template2);
+ my $oi_form = oi_form($dbh);
$allhtml =~ s/{debug}/$debug/;
$allhtml =~ s/<loop_here>/$recordlist/sg;
+ $allhtml =~ s/{oi_form}/$oi_form/sg;
print "Content-type: text/html\n\n";
Index: index.pl
===================================================================
RCS file: /cvsroot/genex/genex-server/site/webtools/Attic/index.pl,v
retrieving revision 1.1.2.1
retrieving revision 1.1.2.2
diff -C2 -d -r1.1.2.1 -r1.1.2.2
*** index.pl 24 Oct 2002 18:26:53 -0000 1.1.2.1
--- index.pl 7 Jan 2003 21:42:47 -0000 1.1.2.2
***************
*** 33,37 ****
if (is_curator($dbh, $us_fk))
{
! $ch{curator} = "Curators only: <a href=\"choose_order_curator.pl\">Manage Orders</a><br><br>\n";
}
#
--- 33,41 ----
if (is_curator($dbh, $us_fk))
{
! #
! # This is icky, but if we move over to run-time templates, we'll have true conditionals!
! #
! my $oi_form = oi_form($dbh); # see sessionlib.pl
! $ch{curator} = "<hr align=\"left\" width=\"25%\">Curators only:<br>$oi_form<hr align=\"left\" width=\"25%\">";
}
#
Index: sessionlib.pl
===================================================================
RCS file: /cvsroot/genex/genex-server/site/webtools/Attic/sessionlib.pl,v
retrieving revision 1.1.2.24
retrieving revision 1.1.2.25
diff -C2 -d -r1.1.2.24 -r1.1.2.25
*** sessionlib.pl 3 Jan 2003 22:11:58 -0000 1.1.2.24
--- sessionlib.pl 7 Jan 2003 21:42:47 -0000 1.1.2.25
***************
*** 61,64 ****
--- 61,80 ----
}
+ sub oi_form
+ {
+ my $dbh = $_[0];
+ my $result;
+ my $sth = getq("oi_pk_number_all", $dbh);
+ $sth->execute();
+ $result = "<a href=\"choose_order_curator.pl\">View All Orders</a><br><br>\n<form action=\"show1_curator.pl\" method=\"post\">\n<select name=\"order_number\">\n";
+ while( (my $oi_pk, my $order_number) = $sth->fetchrow_array())
+ {
+ $result .= "<option value=\"$order_number\">$order_number</option>\n";
+ }
+ $result .= "</select>\n<input type=\"submit\" name=\"submit\" value=\"Get One Order\"></form>\n";
+ return $result;
+ }
+
+
# called from choose_order.pl
# and delete_order1.pl
Index: sql_lib.pl
===================================================================
RCS file: /cvsroot/genex/genex-server/site/webtools/Attic/sql_lib.pl,v
retrieving revision 1.1.2.30
retrieving revision 1.1.2.31
diff -C2 -d -r1.1.2.30 -r1.1.2.31
*** sql_lib.pl 3 Jan 2003 22:11:58 -0000 1.1.2.30
--- sql_lib.pl 7 Jan 2003 21:42:49 -0000 1.1.2.31
***************
*** 19,23 ****
my $sql;
! if ($q_name eq "select_fi")
{
$sql = "select fi_pk from file_info where file_name=?";
--- 19,31 ----
my $sql;
! if ($q_name eq "oi_pk_number_all")
! {
! $sql = "select oi_pk,order_number from order_info order by order_number desc";
! }
! elsif ($q_name eq "oi_pk_by_number")
! {
! $sql = "select oi_pk from order_info where order_number=?";
! }
! elsif ($q_name eq "select_fi")
{
$sql = "select fi_pk from file_info where file_name=?";
|
|
From: <tw...@us...> - 2003-01-07 19:27:53
|
Update of /cvsroot/genex/genex-server/site
In directory sc8-pr-cvs1:/tmp/cvs-serv27948
Modified Files:
Tag: Rel-1_0_1-branch
background.html
Log Message:
edit text, new interior page design
Index: background.html
===================================================================
RCS file: /cvsroot/genex/genex-server/site/Attic/background.html,v
retrieving revision 1.1.2.2
retrieving revision 1.1.2.3
diff -C2 -d -r1.1.2.2 -r1.1.2.3
*** background.html 10 Dec 2002 19:21:02 -0000 1.1.2.2
--- background.html 7 Jan 2003 19:27:50 -0000 1.1.2.3
***************
*** 11,16 ****
<tr valign="top">
<td width="10"> </td>
! <td width="100"><font face="Verdana, Arial, Helvetica, sans-serif" size="+1"><a href="./index.html">GeneX</a></font></td>
! <td width="490"><font face="Verdana, Arial, Helvetica, sans-serif" size="+1">Background</font><br>
</td>
</tr>
--- 11,17 ----
<tr valign="top">
<td width="10"> </td>
! <td width="100"><font face="Verdana, Arial, Helvetica, sans-serif" size="+1"><a href="./"><img src="graphics/genex_logo.jpg" width="207" height="87" border="0"></a></font></td>
! <td width="490"><font face="Verdana, Arial, Helvetica, sans-serif" size="+1"> Background
! and History</font><br>
</td>
</tr>
***************
*** 18,68 ****
<br>
<table width="600" border="0" cellspacing="0" cellpadding="0">
! <tr valign="top">
! <td width="10"> </td>
! <td width="100"> </td>
! <td width="490"><br>
! The GeneX system is composed of a relational database implemented in the
! freely-distributed PostgreSQL, a Java-based Curation Tool, a Query Tool
! for retrieving all or part of datasets based on user-specified parameters,
! and a few data analysis tools. Some of the analysis tools are based on the
! <a href="http://lib.stat.cmu.edu/R/CRAN/">R Statistical Language</a> and,
! in some cases, Xwindows freeware utilities. The current version of GeneX
! is v1.0 and is currently available via the SourceForge link at left. <br>
! <br>
! <img src="graphics/x.jpg" alt="x" align=LEFT border="0" hspace="0"
! vspace="0" width="14" height="14"> <a href="genex_info.html">Introduction</a>
! <p> <img src="graphics/x.jpg" alt="x" align=LEFT border="0" hspace="0"
! vspace="0" width="14" height="14"> <a href="http://www.ncgr.org/genex/schema.html">GeneX
! data format and model</a> (NCGR site)
! <p> <img src="graphics/x.jpg" alt="x" align=LEFT border="0" hspace="0"
! vspace="0" width="14" height="14"> <a href="http://www.ncgr.org/genex/genexml.html">GeneXML
! Markup Language for Gene Expression</a> (NCGR site)
! <p> <img src="graphics/x.jpg" alt="x" align=LEFT border="0" hspace="0"
! vspace="0" width="14" height="14"> <a href="analysis_tools.html">Analysis
! and Query Tools</a>
! <p> <img src="graphics/x.jpg" alt="x" align=LEFT border="0" hspace="0"
! vspace="0" width="14" height="14"> Sample XML Formats (not up to
! date):
! <ul type=DISC>
! <li>Experimental Metadata <a href="DTD/genexml.dtd"
! target="_parent"> in text format </a> or <a
! href="DTD/genexml-html/genexml-tree.html" target="_parent"> in HTML format
! </a>
! <p>
! <li>Sequence Features <a href="DTD/usf.dtd"
! target="_parent"> in text format </a> or <a
! href="DTD/genexml-html/usf-tree.html" target="_parent"> in HTML format
! </a>
! <p>
! <li>Array Measurement Data <a href="DTD/ams.dtd"
! target="_parent"> in text format </a> or <a
! href="DTD/genexml-html/ams-tree.html" target="_parent"> in HTML format
! </a>
! <p>
! <li>Array Layout Data <a href="DTD/als.dtd"
! target="_parent"> in text format </a> or <a
! href="DTD/genexml-html/als-tree.html" target="_parent"> in HTML format</a>
</ul>
! </td>
</tr>
</table>
--- 19,125 ----
<br>
<table width="600" border="0" cellspacing="0" cellpadding="0">
! <tr valign="top">
! <td width="8"> </td>
! <td width="20" bgcolor="990066"> </td>
! <td width="8"> </td>
! <td width="573">
! <p><b>Va GeneX Components and Description</b></p>
! <p>VA Genex has a relational database, a web interface, and an analysis
! suite. There is also a repository for each user's files, and an comprehensive
! security system. The gene expression workflow begins with a researcher
! describing an experimental protocol in a minimal fashion. When samples
! are ready, the researcher creates or order for the microarray research
! center which at UVa is the BRF. The BRF hybridizes the samples as specified
! by the researcher, and imports the resulting data into GeneX. At this
! stage the data is available to the researcher. Data can be exported and/or
! analyzed. Our innovative Analysis Tree package allows users to build a
! flow chart (yes, there is a graphical flow chart on the screen) of routines
! to analyze data and produce reports. Except for system administrators,
! all interaction with the system is via secure web pages. No special software
! is required for end users. All data is warehoused on powerful, secure
! servers. We expect to have MIAME compliance soon.</p>
! <p>Data is loaded by curators (personnel in the microarray center) via a
! web interface. Data is visible only to the researcher who owns it, unless
! the researcher explicitly allows group read permissions. The security
! system allows all users to create groups, to control group membership,
! and to enable/disable group read and/or write permissions. Permissions
! apply separately to studies/experimental conditions, orders, data, and
! derived data (files).</p>
! <p>Our Analysis Tree allows the user to build a graphical representation
! of the flow of data through various modules of an analysis. This system
! will be documented elsewhere.</p>
! <p>The servers are running Red Hat Linux. VA GeneX is written in Perl. Most
! of the analysis routines are written in R, some in C, and some in Perl.
! We use PostgreSQL as our relational database. Its abilities to do transactions,
! and its high availability were critical to the project. Users must login
! to the system. All the web pages are accessed via SSL so that all data
! traveling between the user's web browser and the server is secure from
! eavesdropping. </p>
! <p>Several Perl modules that aren't standard in Perl 5.8 are required. R
! is required, and of course Apache. All of the Perl used by VA Genex amounts
! to only 11,000 lines of code. VA GeneX is compact. Installation has been
! vastly simplified and should only take a few hours.</p>
! <p>While VA GeneX is theoretically portable to Windows NT, 2000, or XP,
! there are a few aspects that would be nontrivial.</p>
! <p><b>History of GeneX</b></p>
! <p>There are currently three parallel GeneX projects. All three systems
! are composed of a relational database, a web-based user interface, and
! an analysis system. All three teams interact on a regular basis, and share
! as much technology as possible. We also get help from several other groups
! for additional analysis modules and testing. The three projects are:</p>
! <ul>
! <li>GeneX-Lite</li>
! <li>VA Genex (previously known as GeneX 1.x)</li>
! <li>GeneX 2</li>
</ul>
! <p>GeneX began as a project at the National Center for Genome Resources.
! Known as NCGR you can find their web site at: <a href="http://www.ncgr.org/">http://www.ncgr.org/</a>
! <br>
! </p>
! <p>The first useful version was GeneX 1.4, which NCGR released to the public
! domain. An open source project was started and hosted via Sourceforge.
! A smaller open source project continued at NCGR, and has become GeneX-Lite.
! </p>
! <p>A small team here at the University of Virginia tried to rush GeneX 1.x
! into production, but we found it necessary to make extensive changes.
! GeneX 1.x has been renamed VA GeneX.</p>
! <p>In the meantime, Caltech and Open Informatics began work on GeneX 2 by
! modifying the 1.4 schema to have a high degree of MAGE compliance.</p>
! <p><b>GeneX-Lite</b></p>
! <p>GeneX-Lite is NCGR's latest contribution to the NSF grant effort. The
! design of GeneX-Lite is based on lessons learned from the GeneX 1.x system.
! The primary problems with the prototype system were mainly with the Curation
! Tool, system installation and data loading. Many parts of the GeneX 1.x
! system were good such as the web interface and integration with<br>
! the analysis tools. We are currently working with the TIGR Multiple Experiment
! Viewer to provide an interface to GeneX-Lite. This tool has many normalization
! and analysis tools built in and provides a simple interface to add more.
! <p>GeneX-Lite was built with a simple data loading mechanism as the heart.
! This data loading mechanism can process tab-delimited files of arbitrary
! format. The storage of the data in the database is much more efficient
! than was the case for GeneX 1.x. Consequently, data loading with GeneX-Lite
! is much quicker than with GeneX 1.x.</p>
! <p>Annotation is very generalized in GeneX-Lite. Annotation of any kind
! may be attached to Experiments, Array_Layouts, Array Measurements, Features
! and Measurement Factors. The annotation mechanism is currently being enhanced
! to provide the controlled vocabularies similar to the original GeneX 1.x
! system. When this is accomplished correctly, the system will be MIAME
! and MAGE compliant.</p>
! <p>Installation of the GeneX-Lite system is much easier than the original
! system. Minimal configuration is required to have GeneX-Lite up and running.</p>
! <p>Another important feature of GeneX-Lite is that the core functions are
! all accessible via the command line. This means that repetitive loading
! and annotation could be automated through the use of scripts. The core
! functions are also wrapped with a user-friendly GUI.</p>
! <p>A web interface is being developed as well as integration with analysis
! and visualization tools. Enhanced security is also planned. The current
! GeneX-Lite works with both Postgres and Oracle databases. Porting to another
! database would not be difficult due to the simple and flexible design
! of GeneX-Lite.</p>
! <p></p>
! <p></p>
! <p></p>
! <p>GeneX-Lite is supported on Solaris, Linux, Windows and MacIntosh (OS-X).</p>
! </td>
</tr>
</table>
|
|
From: <tw...@us...> - 2003-01-03 22:12:01
|
Update of /cvsroot/genex/genex-server/site/webtools
In directory sc8-pr-cvs1:/tmp/cvs-serv14042
Modified Files:
Tag: Rel-1_0_1-branch
get_data2.pl sql_lib.pl sessionlib.pl
Log Message:
new fields (conds, cond_labels) in file_info, code fills in fields
Index: get_data2.pl
===================================================================
RCS file: /cvsroot/genex/genex-server/site/webtools/Attic/get_data2.pl,v
retrieving revision 1.1.2.3
retrieving revision 1.1.2.4
diff -C2 -d -r1.1.2.3 -r1.1.2.4
*** get_data2.pl 12 Dec 2002 20:50:26 -0000 1.1.2.3
--- get_data2.pl 3 Jan 2003 22:11:57 -0000 1.1.2.4
***************
*** 23,30 ****
my $file_name = create_valid_fn($dbh, $q);
- # Write a labels file.
-
# Write the data file.
! my $recs = write_data_file($dbh, \%ana, $file_name, $q->param("comments"));
(my $all_html) = readtemplate("get_data2.html");
--- 23,28 ----
my $file_name = create_valid_fn($dbh, $q);
# Write the data file.
! my $recs = write_data_file($dbh, $q, \%ana, $file_name);
(my $all_html) = readtemplate("get_data2.html");
***************
*** 93,111 ****
}
! sub write_lables_file
! {
! my $dbh = $_[0];
! my %ana = %{$_[1]};
!
!
! }
!
sub write_data_file
{
my $dbh = $_[0];
! my %ana = %{$_[1]};
! my $file_name = $_[2];
! my $comments = $_[3];
my @am_pk_list;
# generate the SQL
--- 91,105 ----
}
! #
! # Write labels and data
! #
sub write_data_file
{
my $dbh = $_[0];
! my $q = $_[1];
! my %ana = %{$_[2]};
! my $file_name = $_[3];
my @am_pk_list;
+ my %ch = $q->Vars();
# generate the SQL
***************
*** 119,129 ****
# build the ordered list of am_pk's
foreach my $ec_pk (keys(%ana))
{
foreach my $am_pk (@{$ana{$ec_pk}})
{
push(@am_pk_list,$am_pk);
! # write_log("pushing $am_pk");
}
}
my $signal_name;
--- 113,135 ----
# build the ordered list of am_pk's
+ my $cond_label = "";
+ # first cond label has no leading tween. See $cond_tween below.
+ my $cond_tween = "";
+ my $curr_cond_count;
+ my $col_head = "probe_set_name";
+ my $cname_sth = getq("hyb_info", $dbh);
foreach my $ec_pk (keys(%ana))
{
+ $curr_cond_count = 0;
foreach my $am_pk (@{$ana{$ec_pk}})
{
+ $curr_cond_count++;
push(@am_pk_list,$am_pk);
! $cname_sth->execute($am_pk);
! my $hr = $cname_sth->fetchrow_hashref();
! $col_head .= "\t$hr->{hybridization_name}";
}
+ $cond_label .= "$cond_tween$curr_cond_count";
+ $cond_tween = ",";
}
my $signal_name;
***************
*** 147,159 ****
$sql_template =~ s/<join>/$j_tween $join<join>/;
}
-
$sql_template =~ s/<.*?>//g;
- # write_log("$sql_template");
! # fetch and write data to a file
my $sth = $dbh->prepare($sql_template) || die "gd prep: $sql_template\n$DBI::errstr\n";
$sth->execute() || die "$sql_template\n$DBI::errstr\n";
! my @data; # a single record
open(OUT, "> $file_name") || die "Can't open $file_name\n";
my $rec_count = 0;
while( @data = $sth->fetchrow_array())
--- 153,172 ----
$sql_template =~ s/<join>/$j_tween $join<join>/;
}
$sql_template =~ s/<.*?>//g;
! # fetch data
my $sth = $dbh->prepare($sql_template) || die "gd prep: $sql_template\n$DBI::errstr\n";
$sth->execute() || die "$sql_template\n$DBI::errstr\n";
!
open(OUT, "> $file_name") || die "Can't open $file_name\n";
+
+ # write headers.
+ # Lets start by writing headers into the file, and also writing them
+ # table extraction.
+ # Add conditional headers later.
+ print OUT "$cond_label\n$col_head\n";
+
+ # write data
+ my @data; # a single record
my $rec_count = 0;
while( @data = $sth->fetchrow_array())
***************
*** 171,175 ****
$sth->finish() || die "finish error $DBI::errstr\n";
my $us_fk = get_us_fk($dbh);
! fi_update($dbh, $us_fk, $us_fk, $file_name, $comments);
return $rec_count;
--- 184,201 ----
$sth->finish() || die "finish error $DBI::errstr\n";
my $us_fk = get_us_fk($dbh);
!
! #
! # Tom 2002-12-23
! # Hmmm. It looks like we need to
! # send $col_head and $cond_label as additional args to
! # fi_update().
! #
! my $fi_pk = fi_update($dbh,
! $us_fk,
! $us_fk,
! $file_name,
! $ch{comments},
! $cond_label, # bad var name. Known elsewhere as conds
! $col_head); # bad var name. Known elsehwere as cond_labels
return $rec_count;
Index: sql_lib.pl
===================================================================
RCS file: /cvsroot/genex/genex-server/site/webtools/Attic/sql_lib.pl,v
retrieving revision 1.1.2.29
retrieving revision 1.1.2.30
diff -C2 -d -r1.1.2.29 -r1.1.2.30
*** sql_lib.pl 23 Dec 2002 19:59:39 -0000 1.1.2.29
--- sql_lib.pl 3 Jan 2003 22:11:58 -0000 1.1.2.30
***************
*** 19,23 ****
my $sql;
! if ($q_name eq "select_tree")
{
my $us_fk = get_us_fk($dbh);
--- 19,35 ----
my $sql;
! if ($q_name eq "select_fi")
! {
! $sql = "select fi_pk from file_info where file_name=?";
! }
! elsif ($q_name eq "insert_fi")
! {
! $sql = "insert into file_info (file_name, fi_comments, fi_checksum, conds, cond_labels) values (trim(?), trim(?), trim(?), trim(?), trim(?))";
! }
! elsif ($q_name eq "update_fi")
! {
! $sql = "update file_info set fi_comments=trim('?'), fi_checksum=?, conds=trim(?), cond_labels=trim(?) where fi_pk=?";
! }
! elsif ($q_name eq "select_tree")
{
my $us_fk = get_us_fk($dbh);
***************
*** 151,154 ****
--- 163,167 ----
elsif ($q_name eq "hyb_info")
{
+ # used in multiple locations!
$sql = "select am_pk,hybridization_name,al_fk from arraymeasurement where am_pk=?";
}
Index: sessionlib.pl
===================================================================
RCS file: /cvsroot/genex/genex-server/site/webtools/Attic/sessionlib.pl,v
retrieving revision 1.1.2.23
retrieving revision 1.1.2.24
diff -C2 -d -r1.1.2.23 -r1.1.2.24
*** sessionlib.pl 20 Dec 2002 16:43:18 -0000 1.1.2.23
--- sessionlib.pl 3 Jan 2003 22:11:58 -0000 1.1.2.24
***************
*** 670,673 ****
--- 670,674 ----
#
# Comments are passed in from the UI
+ # conds and cond_labels passed in from elsewhere too.
#
sub fi_update
***************
*** 678,695 ****
my $file_name = $_[3];
my $fi_comments = $_[4];
my $fi_pk;
! my $sql = "select fi_pk from file_info where file_name='$file_name'";
! my $sth;
! if (! ($sth = $dbh->prepare($sql)))
! {
! write_log("prepare fails:$sql\n$DBI::errstr\n");
! exit();
! }
! if (! ($sth->execute()))
! {
! write_log("execute fails:$sql\n$DBI::errstr\n");
! exit();
! }
my $md5 = `md5sum $file_name`;
--- 679,688 ----
my $file_name = $_[3];
my $fi_comments = $_[4];
+ my $conds = $_[5];
+ my $cond_labels = $_[6];
my $fi_pk;
! my $sth = getq("select_fi", $dbh);
! $sth->execute($file_name) || die "Query select_fi execute fails.\n$DBI::errstr\n";
my $md5 = `md5sum $file_name`;
***************
*** 697,725 ****
my $r = $sth->rows();
- # write_log("rows: $r");
if ($sth->rows() >= 1)
{
($fi_pk) = $sth->fetchrow_array();
!
! $sql = "update file_info set fi_comments=trim('$fi_comments'), fi_checksum=? where fi_pk=$fi_pk";
!
! if (! ($sth = $dbh->prepare($sql)))
! {
! write_log("prepare fails: $sql\n$DBI::errstr\n");
! exit();
! }
! if (! ($sth->execute($md5)))
! {
! write_log("execute fails: $sql\n$DBI::errstr\n");
! exit();
! }
! # write_log("update completed: $sql");
}
else
{
! $sql = "insert into file_info (file_name, fi_comments, fi_checksum) values (trim(?), trim(?), trim(?))";
! $sth = $dbh->prepare($sql);
! $sth->execute($file_name, $fi_comments, $md5);
$fi_pk = insert_security($dbh, $us_fk, $gs_fk, 0);
}
--- 690,714 ----
my $r = $sth->rows();
+ #
+ # Yikes. Is > 1 really valid?
+ #
if ($sth->rows() >= 1)
{
($fi_pk) = $sth->fetchrow_array();
! $sth = getq("update_fi", $dbh);
! $sth->execute($md5,
! $conds,
! $cond_labels,
! $fi_pk) || die "Query update_fi execute fails.\n$DBI::errstr\n";
}
else
{
! $sth = getq("insert_fi", $dbh);
! $sth->execute($file_name,
! $fi_comments,
! $md5,
! $conds,
! $cond_labels) || die "Query insert_fi execute fails.\n$DBI::errstr\n";
$fi_pk = insert_security($dbh, $us_fk, $gs_fk, 0);
}
|
|
From: <tw...@us...> - 2003-01-03 21:39:02
|
Update of /cvsroot/genex/genex-server
In directory sc8-pr-cvs1:/tmp/cvs-serv2208
Modified Files:
Tag: Rel-1_0_1-branch
genex_schema.sql
Log Message:
fix to new table extraction
Index: genex_schema.sql
===================================================================
RCS file: /cvsroot/genex/genex-server/genex_schema.sql,v
retrieving revision 1.3.2.20
retrieving revision 1.3.2.21
diff -C2 -d -r1.3.2.20 -r1.3.2.21
*** genex_schema.sql 23 Dec 2002 21:48:08 -0000 1.3.2.20
--- genex_schema.sql 3 Jan 2003 21:38:59 -0000 1.3.2.21
***************
*** 2861,2866 ****
CREATE TABLE "extraction" (
"fi_data_fk" integer,
! "conds" text,
! "cond_labels" character varying(128)
) without OIDs;
--- 2861,2866 ----
CREATE TABLE "extraction" (
"fi_data_fk" integer,
! "conds" character varying(128),
! "cond_labels" text
) without OIDs;
|
|
From: <jas...@us...> - 2003-01-03 18:29:21
|
Update of /cvsroot/genex/genex-server/Genex/FeatureExtraction In directory sc8-pr-cvs1:/tmp/cvs-serv19681/FeatureExtraction Removed Files: .cvsignore Log Message: cruft --- .cvsignore DELETED --- |
|
From: <jas...@us...> - 2003-01-03 18:22:29
|
Update of /cvsroot/genex/genex-server/Genex/AM_Spots In directory sc8-pr-cvs1:/tmp/cvs-serv16358/Genex/AM_Spots Removed Files: .cvsignore AM_Spots.pm Makefile.PL Log Message: cruft --- .cvsignore DELETED --- --- AM_Spots.pm DELETED --- --- Makefile.PL DELETED --- |
|
From: <jas...@us...> - 2003-01-03 18:15:57
|
Update of /cvsroot/genex/genex-server/Genex In directory sc8-pr-cvs1:/tmp/cvs-serv13253/Genex Modified Files: ChangeLog Log Message: usual Index: ChangeLog =================================================================== RCS file: /cvsroot/genex/genex-server/Genex/ChangeLog,v retrieving revision 1.126 retrieving revision 1.127 diff -C2 -d -r1.126 -r1.127 *** ChangeLog 25 Nov 2002 21:49:59 -0000 1.126 --- ChangeLog 3 Jan 2003 18:15:54 -0000 1.127 *************** *** 1,2 **** --- 1,7 ---- + 2002-12-17 Jason E. Stewart <ja...@op...> + + * Connect/Connect.pm.in (Repository): + added some more string types to ontology_type2sql_type() + 2002-11-23 Jason E. Stewart <ja...@op...> |
|
From: <jas...@us...> - 2003-01-03 18:15:42
|
Update of /cvsroot/genex/genex-server/DB/curated_data/hatfield-experiment In directory sc8-pr-cvs1:/tmp/cvs-serv13156/DB/curated_data/hatfield-experiment Added Files: .cvsignore Log Message: usual --- NEW FILE: .cvsignore --- Hatfield-Ecoli-K12-IHF.xml Hatfield-Ecoli-K12-IHF_ALS_01.ext Hatfield-Ecoli-K12-IHF_AMS_01.ext Hatfield-Ecoli-K12-IHF_AMS_02.ext Hatfield-Ecoli-K12-IHF_AMS_03.ext Hatfield-Ecoli-K12-IHF_AMS_04.ext Hatfield-Ecoli-K12-IHF_AMS_05.ext Hatfield-Ecoli-K12-IHF_AMS_06.ext Hatfield-Ecoli-K12-IHF_AMS_07.ext Hatfield-Ecoli-K12-IHF_AMS_08.ext Hatfield-Ecoli-K12-IHF_AMS_09.ext Hatfield-Ecoli-K12-IHF_AMS_10.ext Hatfield-Ecoli-K12-IHF_AMS_11.ext Hatfield-Ecoli-K12-IHF_AMS_12.ext Hatfield-Ecoli-K12-IHF_AMS_13.ext Hatfield-Ecoli-K12-IHF_AMS_14.ext Hatfield-Ecoli-K12-IHF_AMS_15.ext Hatfield-Ecoli-K12-IHF_AMS_16.ext Hatfield-Ecoli-K12-IHF_AMS_17.ext Hatfield-Ecoli-K12-IHF_AMS_18.ext Hatfield-Ecoli-K12-IHF_AMS_19.ext Hatfield-Ecoli-K12-IHF_AMS_20.ext Hatfield-Ecoli-K12-IHF_AMS_21.ext Hatfield-Ecoli-K12-IHF_AMS_22.ext Hatfield-Ecoli-K12-IHF_AMS_23.ext Hatfield-Ecoli-K12-IHF_AMS_24.ext Hatfield-Ecoli-K12-IHF_AMS_25.ext Hatfield-Ecoli-K12-IHF_AMS_26.ext Hatfield-Ecoli-K12-IHF_AMS_27.ext Hatfield-Ecoli-K12-IHF_AMS_28.ext Hatfield-Ecoli-K12-IHF_AMS_29.ext Hatfield-Ecoli-K12-IHF_AMS_30.ext Hatfield-Ecoli-K12-IHF_AMS_31.ext Hatfield-Ecoli-K12-IHF_AMS_32.ext Hatfield-Ecoli-K12-IHF_AMS_33.ext Hatfield-Ecoli-K12-IHF_AMS_34.ext Hatfield-Ecoli-K12-IHF_AMS_35.ext Hatfield-Ecoli-K12-IHF_AMS_36.ext Hatfield-Ecoli-K12-IHF_AMS_37.ext Hatfield-Ecoli-K12-IHF_USF_01.ext |
|
From: <jas...@us...> - 2003-01-03 18:14:58
|
Update of /cvsroot/genex/genex-server/CyberT-dist In directory sc8-pr-cvs1:/tmp/cvs-serv12850/CyberT-dist Modified Files: .cvsignore Log Message: new files Index: .cvsignore =================================================================== RCS file: /cvsroot/genex/genex-server/CyberT-dist/.cvsignore,v retrieving revision 1.8 retrieving revision 1.9 diff -C2 -d -r1.8 -r1.9 *** .cvsignore 20 Dec 2002 05:13:42 -0000 1.8 --- .cvsignore 3 Jan 2003 18:14:55 -0000 1.9 *************** *** 3,18 **** CyberT-6.2.C+E.form.pl CyberT-6.2.paired.form.pl CyberT.html CyberTDB-6.2.C+E.pl CyberTDB-6.2.paired.pl genex_reaper.pl hdarray index.inc munge4R.pl xgobi - CyberTDB-7.0.pl - CyberT-7.0.form.pl - cyberfilter.pl xgobi.R ! index.html ! hdarray_3.66 --- 3,22 ---- CyberT-6.2.C+E.form.pl CyberT-6.2.paired.form.pl + CyberT-7.0.form.pl + CyberT-7.1.form.pl CyberT.html CyberTDB-6.2.C+E.pl CyberTDB-6.2.paired.pl + CyberTDB-7.0.pl + CyberTDB-7.1.pl + cyberfilter.pl genex_reaper.pl hdarray + hdarray_3.66 + index.html + index.html index.inc munge4R.pl xgobi xgobi.R ! xgobi.R |
|
From: <jas...@us...> - 2003-01-03 18:04:05
|
Update of /cvsroot/genex/genex-server
In directory sc8-pr-cvs1:/tmp/cvs-serv7660
Modified Files:
ChangeLog
Log Message:
merged
Index: ChangeLog
===================================================================
RCS file: /cvsroot/genex/genex-server/ChangeLog,v
retrieving revision 1.117
retrieving revision 1.118
diff -C2 -d -r1.117 -r1.118
*** ChangeLog 20 Dec 2002 05:35:04 -0000 1.117
--- ChangeLog 3 Jan 2003 18:04:01 -0000 1.118
***************
*** 1,2 ****
--- 1,9 ----
+ <<<<<<< variant A
+ 2002-12-05 Jason E. Stewart <ja...@op...>
+
+ * DB/scripts/tab2AD.pl (Repository):
+ add 'name' attribute to all identifiable objects
+
+ >>>>>>> variant B
2002-11-19 Harry Mangalam <hj...@ta...>
* more mods to INSTALL doc to bring it up to date (added more pkgs to
***************
*** 26,29 ****
--- 33,38 ----
installation mods.
+ ####### Ancestor
+ ======= end
2002-11-26 Jason E. Stewart <ja...@op...>
***************
*** 651,785 ****
made <scanner>:id optional
- 2001-04-28 Harry Mangalam, hj...@nc...
- * in CyberT changed form and script to allow formatting of output to required
- significant digits. filter is applicable to any kind of mixed numeric or
- alphabetic tablular form.
-
- 2001-04-27 Harry Mangalam, hj...@nc...
- * in CyberT changed both form and script to handle external estimate of
- Paired expression levels.
-
- 2001-04-27 Jason E. Stewart <ja...@op...>
-
- * DTD/genexml.dtd (Repository):
- <contact>:sec_id => security_id
-
- * DB/xml/ContactType.xml (Repository):
- fixed broken primary key. The combination of con_fk and type
- should be unique, not just con_fk
-
- * DB/curated_data/software.xml (Repository):
- updated to use new API
-
- * DB/curated_data/spotter.xml (Repository):
- * DB/curated_data/contact-db.xml (Repository):
- changed sec_id to security_id
-
- * DTD/genexml.dtd (Repository):
- DB_foreign_key => db_xref
- added <spotter>:security_id
- added <software>:security_id
- <spotter>:id is now #IMPLIED. If it's not referenced by another
- object (such as in DB creation) no id is needed
-
- * INSTALL (Repository):
- * README (Repository):
- Added text that exim is a suitable replacement for sendmail
-
- * DB/curated_data/contact-db.xml (Repository):
- fixed security entries to all be 'public'
-
- * DB/curated_data/spotter.xml (Repository):
- made it a genexml file, and added contact info
-
- * DB/xml/functions-sql.xml (Repository):
- removed unnecessary variables
-
- * DB/xml/TableAdmin.xml (Repository):
- stupid typo, made modification_date a datetime
-
- 2001-04-26 Jason E. Stewart <ja...@op...>
-
- * DB/xml/Citation.xml (Repository):
- removed sec_fk. Should have the same security as the
- ExperimentSet.
-
- 2001-04-14 Harry Mangalam, hj...@nc...
- * the Bayesian analysis can't be used on paired data as is, so remove the
- Bayesian query part of the form if it's Paired query.
-
- 2001-04-08 Jason E. Stewart <ja...@op...>
-
- * install-all.pl (Repository):
- Fixed Server Version
-
- * top_level/index.shtml.in (Repository):
- Added perl API documentation link
-
- 2001-04-07 Harry Mangalam <hj...@nc... || man...@ho...>
- * changes in CyberT's hdarray to calculate p correctly (thanks She-pin)
-
- 2001-04-03 Harry Mangalam <hj...@nc... || man...@ho...>
- * changed CyberT analysis script to sort the output on p so that genes are
- presented in order of probability of being significantly different (in both
- SIGGENES and ALLGENES).
- * added a tab in front of data lines so that they'll be offset by a column when
- imported in a spreadsheet. This allows users to immediately start sorting
- their data without having to rearrange or delete the header text.
-
-
- 2001-04-03 Harry Mangalam <hj...@nc... || man...@ho...>
- * Anne Rafferty caught a number of bad links in the GeneX tree - corrected
- them in CVS and also on genex.ncgr.org by direct editing.
- -download link
- http://genex.ncgr.org/download/index.shtml ->
- http://genex.ncgr.org/genex/download/
- -bugtracking link
- http://genex.ncgr.org:8080 ->
- http://genex.ncgr.org/bugzilla
- -SourceForge GeneX Development Site remaned to GeneX Development Site
- and linked to http://genex.ncgr.org
- -number of download-link-related changes in the rcluster branch
- -removed link to Old GeneX index (why was THAT there?)
- -updated contacts to reflect reality
-
- 2001-03-31 Harry Mangalam <hj...@nc... || man...@ho...>
- * CyberT - large changes in collapsing the Paired and Control/Experimental
- forms and analysis scripts into one each. Small changes required in the
- last query script. Added xgobi tutorial and some small other help
- stanzas In installing in other locations, other servers, small errors
- made some things rcluster fail (if install in non 'genex' location)
- Will correct in next set of work).
- * also changed hdarray to recalc p_raw correctly and re-sorting on p_raw
- rather than t as was previously.
-
- 2001-04-11 Jason E. Stewart <ja...@op...>
-
- * genex-loader/loader.pl.in (Repository):
- now uses XML::Xerces
-
- * login/createLogin.pl.in (Repository):
- Fixed to use new API
- Now allows any password up to 15 characters
-
- * login/accountAccess.pl.in (Repository):
- Fixed to use new API
-
- 2001-04-10 Jason E. Stewart <ja...@op...>
-
- * DTD/table.dtd (Repository):
- New DTD. Defines RDBMS tables in XML
-
- 2001-04-09 Jason E. Stewart <ja...@op...>
-
- * DB/curated_data/species.xml (Repository):
- added genome_size to ecoli for test
-
- 2001-06-15 Jason E. Stewart <ja...@op...>
-
- * install-all.pl (Repository):
- logic error forced use of Unix sockets even if the user specified
- tcp/ip sockets.
-
2001-06-07 Harry Mangalam, hj...@nc...
* more updates to the INSTALL file detailing changes, bugfixes.
--- 660,663 ----
***************
*** 801,805 ****
writable
-
2001-05-30 Harry Mangalam, hj...@nc...
* Added native Excel Export to CyberT
--- 679,682 ----
***************
*** 882,885 ****
--- 759,803 ----
removed sec_fk. Should have the same security as the
ExperimentSet.
+
+ 2001-04-14 Harry Mangalam, hj...@nc...
+ * the Bayesian analysis can't be used on paired data as is, so remove the
+ Bayesian query part of the form if it's Paired query.
+
+ 2001-04-07 Harry Mangalam <hj...@nc... || man...@ho...>
+ * changes in CyberT's hdarray to calculate p correctly (thanks She-pin)
+
+ 2001-04-03 Harry Mangalam <hj...@nc... || man...@ho...>
+ * changed CyberT analysis script to sort the output on p so that genes are
+ presented in order of probability of being significantly different (in both
+ SIGGENES and ALLGENES).
+ * added a tab in front of data lines so that they'll be offset by a column when
+ imported in a spreadsheet. This allows users to immediately start sorting
+ their data without having to rearrange or delete the header text.
+
+
+ 2001-04-03 Harry Mangalam <hj...@nc... || man...@ho...>
+ * Anne Rafferty caught a number of bad links in the GeneX tree - corrected
+ them in CVS and also on genex.ncgr.org by direct editing.
+ -download link
+ http://genex.ncgr.org/download/index.shtml ->
+ http://genex.ncgr.org/genex/download/
+ -bugtracking link
+ http://genex.ncgr.org:8080 ->
+ http://genex.ncgr.org/bugzilla
+ -SourceForge GeneX Development Site remaned to GeneX Development Site
+ and linked to http://genex.ncgr.org
+ -number of download-link-related changes in the rcluster branch
+ -removed link to Old GeneX index (why was THAT there?)
+ -updated contacts to reflect reality
+
+ 2001-03-31 Harry Mangalam <hj...@nc... || man...@ho...>
+ * CyberT - large changes in collapsing the Paired and Control/Experimental
+ forms and analysis scripts into one each. Small changes required in the
+ last query script. Added xgobi tutorial and some small other help
+ stanzas In installing in other locations, other servers, small errors
+ made some things rcluster fail (if install in non 'genex' location)
+ Will correct in next set of work).
+ * also changed hdarray to recalc p_raw correctly and re-sorting on p_raw
+ rather than t as was previously.
2001-04-14 Harry Mangalam, hj...@nc...
|