Browse code

setting up git-svn bridge

Bioconductor Git-SVN Bridge authored on 31/08/2014 21:28:19
Showing 1 changed files
1 1
new file mode 100644
... ...
@@ -0,0 +1,125 @@
1
+
2
+
3
+
4
+rcModelPLM <- function(y,row.effects=NULL, input.scale=NULL){
5
+  if (!is.matrix(y))
6
+    stop("argument should be matrix")
7
+  PsiCode <- 0
8
+  PsiK <- 1.345
9
+  if (is.null(row.effects)){
10
+    .Call("R_rlm_rma_default_model",y,PsiCode,PsiK,input.scale,PACKAGE="preprocessCore")
11
+  } else {
12
+    if (length(row.effects) != nrow(y)){
13
+       stop("row.effects parameter should be same length as number of rows")
14
+    }  
15
+    if (abs(sum(row.effects)) > length(row.effects)*.Machine$double.eps){
16
+       stop("row.effects should sum to zero")
17
+    }
18
+    .Call("R_rlm_rma_given_probe_effects",y,as.double(row.effects),PsiCode,PsiK,input.scale,PACKAGE="preprocessCore") 
19
+  }	
20
+}
21
+
22
+
23
+
24
+rcModelWPLM <- function(y, w, row.effects=NULL, input.scale=NULL){
25
+  if (!is.matrix(y))
26
+    stop("argument should be matrix")
27
+  if (is.vector(w)){
28
+    if (length(w) != prod(dim(y))){
29
+      stop("weights are not correct length")
30
+    }
31
+  } else if (is.matrix(w)){
32
+    if (!all(dim(w) == dim(y))){
33
+      stop("weights should be same dimension as input matrix")
34
+    }
35
+
36
+  }
37
+  if (any(w < 0)){
38
+    stop("weights should be no negative")
39
+  }
40
+
41
+  
42
+    
43
+  PsiCode <- 0
44
+  PsiK <- 1.345 
45
+  if (is.null(row.effects)){
46
+     .Call("R_wrlm_rma_default_model",y,PsiCode,PsiK,as.double(w),input.scale,PACKAGE="preprocessCore")
47
+  } else {
48
+    if (length(row.effects) != nrow(y)){
49
+       stop("row.effects parameter should be same length as number of rows")
50
+    }  
51
+    if (abs(sum(row.effects)) > length(row.effects)*.Machine$double.eps){
52
+       stop("row.effects should sum to zero")
53
+    }
54
+    .Call("R_wrlm_rma_given_probe_effects",y,as.double(row.effects),PsiCode,PsiK,as.double(w),input.scale,PACKAGE="preprocessCore") 
55
+  }	
56
+
57
+}
58
+
59
+
60
+
61
+rcModelMedianPolish <- function(y){
62
+  if (!is.matrix(y))
63
+    stop("argument should be matrix")
64
+  PsiCode <- 0
65
+  PsiK <- 1.345
66
+  .Call("R_medianpolish_rma_default_model",y,PACKAGE="preprocessCore")
67
+}
68
+
69
+
70
+
71
+
72
+subrcModelMedianPolish <- function(y,group.labels){
73
+
74
+  if (!is.matrix(y))
75
+    stop("argument should be matrix")
76
+
77
+  if (!is.double(y) & is.numeric(y))
78
+    y <- matrix(as.double(y),dim(y)[1],dim(y)[2])
79
+  else if (!is.numeric(y))
80
+    stop("argument should be numeric matrix")
81
+
82
+  rowIndexList <- convert.group.labels(group.labels)
83
+  
84
+  x <- .Call("R_sub_rcModelSummarize_medianpolish", y, rowIndexList,PACKAGE="preprocessCore")
85
+
86
+  names(x) <- names(rowIndexList)
87
+  x
88
+}
89
+
90
+
91
+
92
+
93
+
94
+subrcModelPLM <- function(y,group.labels,row.effects=NULL, input.scale=NULL){
95
+
96
+  if (!is.matrix(y))
97
+    stop("argument should be matrix")  
98
+
99
+  if (!is.double(y) & is.numeric(y))
100
+    y <- matrix(as.double(y),dim(y)[1],dim(y)[2])
101
+  else if (!is.numeric(y))
102
+    stop("argument should be numeric matrix")
103
+   
104
+  rowIndexList <- convert.group.labels(group.labels)
105
+ 
106
+  PsiCode <- 0
107
+  PsiK <- 1.345
108
+
109
+  if (is.null(row.effects)){
110
+    x <- .Call("R_sub_rcModelSummarize_plm", y, rowIndexList, PsiCode, PsiK, input.scale,PACKAGE="preprocessCore")
111
+    names(x) <- names(rowIndexList)
112
+    x
113
+
114
+  } else {
115
+    stop("row.effects not yet implemented for subrcModelPLM")
116
+    if (length(row.effects) != nrow(y)){
117
+       stop("row.effects parameter should be same length as number of rows")
118
+    }  
119
+    if (abs(sum(row.effects)) > 10*.Machine$double.eps){
120
+       stop("row.effects should sum to zero")
121
+    }
122
+    .Call("R_rlm_rma_given_probe_effects",y,as.double(row.effects),PsiCode,PsiK,input.scale,PACKAGE="preprocessCore") 
123
+  }	
124
+}
125
+