Subversion Repositories bdplot

Rev

Rev 22 | Rev 29 | Go to most recent revision | Only display areas with differences | Ignore whitespace | Details | Blame | Last modification | View Log | RSS feed

Rev 22 Rev 28
1
### bdplot.R
1
### bdplot.R
2
#### This is a collection of functions that must bpre reachable by the user This is called 
2
#### This is a collection of functions that must bpre reachable by the user This is called 
3
 
3
 
4
 
4
 
5
 
5
 
6
## strategy missing for xytype
6
## strategy missing for xytype
7
## Could we test if there is an active graphics device? And if not, run bdopen()?
7
## Could we test if there is an active graphics device? And if not, run bdopen()?
8
bdplot <- function(x, y=NULL, z=NULL,
8
bdplot <- function(x, y=NULL, z=NULL,
9
                   ## The rest is irrelevant for the user
9
                   ## The rest is irrelevant for the user
10
                   cex.plot=bdp()$cex.plot,
10
                   cex.plot=bdp()$cex.plot,
11
                   xaxt="n",
11
                   xaxt="n",
12
                   xlab=bdp()$xlab, ylab=bdp()$ylab,
12
                   xlab=bdp()$xlab, ylab=bdp()$ylab,
13
                   xlim=NULL,
13
                   xlim=NULL,
14
                   ylim=NULL,
14
                   ylim=NULL,
15
                   col=bdp()$col,main=NULL,
15
                   col=bdp()$col,main=NULL,
16
                   ## only used in case of plot mode
16
                   ## only used in case of plot mode
17
                   type=bdp()$type,
17
                   type=bdp()$type,
18
                   ## Only used in case of histogram plotting
18
                   ## Only used in case of histogram plotting
19
                   border=bdp()$border,
19
                   border=bdp()$border,
20
                   ...)
20
                   ...)
21
{
21
{
22
  prm <- bdp()
22
  prm <- bdp()
23
 
23
 
24
 
24
 
25
  par(cex.main=prm$cex.main, cex.lab=prm$cex.lab, cex.axis=prm$cex.axis)
25
  par(cex.main=prm$cex.main, cex.lab=prm$cex.lab, cex.axis=prm$cex.axis)
26
  par(tcl=prm$tcl)
26
  par(tcl=prm$tcl)
27
  par(lwd=prm$lwd)
27
  par(lwd=prm$lwd)
28
  par(bty=prm$bty)
28
  par(bty=prm$bty)
29
 
29
 
30
  
30
  
31
  ##Set margins
31
  ##Set margins
32
  mar <- prm$mar.nolab
32
  mar <- prm$mar.nolab
33
  if( !is.na(prm$xlab) ){ mar[1] <- prm$mar.lab[1] }
33
  if( !is.na(prm$xlab) ){ mar[1] <- prm$mar.lab[1] }
34
  if( !is.na(prm$ylab) ){ mar[2] <- prm$mar.lab[2] }
34
  if( !is.na(prm$ylab) ){ mar[2] <- prm$mar.lab[2] }
35
  if( any(!is.na(prm$toplab),!is.null(main)) ) { mar[3] <- prm$mar.lab[3] }
35
  if( any(!is.na(prm$toplab),!is.null(main)) ) { mar[3] <- prm$mar.lab[3] }
36
  if( !is.na(prm$rightlab) ){ mar[4] <- prm$mar.lab[4] }
36
  if( !is.na(prm$rightlab) ){ mar[4] <- prm$mar.lab[4] }
37
  par(mar=mar)
37
  par(mar=mar)
38
 
38
 
39
  par(mgp=prm$mgp.global)
39
  par(mgp=prm$mgp.global)
40
  
40
  
41
  ## Do the plot
41
  ## Do the plot
42
  if(!is.null(y)){
42
  if(!is.null(y)){
43
    ##       cat("The Bacher/Delff Plotting System (R), (C), TM operating in xy-plotting mode.\n")
43
    ##       cat("The Bacher/Delff Plotting System (R), (C), TM operating in xy-plotting mode.\n")
44
 
44
 
45
    if(is.null(xlim))
45
    if(is.null(xlim))
46
      xlim <- range(x,bdp()$xlim,na.rm=TRUE)
46
      xlim <- range(x,bdp()$xlim,na.rm=TRUE)
47
    if(is.null(ylim))
47
    if(is.null(ylim))
48
      ylim <- range(y,bdp()$ylim,na.rm=TRUE)
48
      ylim <- range(y,bdp()$ylim,na.rm=TRUE)
49
    
49
    
50
    plot(x, y,
50
    plot(x, y,
51
         type=type,
51
         type=type,
52
         xaxt=xaxt, yaxt="n",
52
         xaxt=xaxt, yaxt="n",
53
         cex=cex.plot,
53
         cex=cex.plot,
54
         xlab=xlab,
54
         xlab=xlab,
55
         ylab=ylab,
55
         ylab=ylab,
56
         xlim=xlim,
56
         xlim=xlim,
57
         ylim=ylim,
57
         ylim=ylim,
58
         col=col,
58
         col=col,
59
         main=main,
59
         main=main,
60
         ...)
60
         ...)
61
  } else if (is.numeric(x)){
61
  } else if (is.numeric(x)){
62
    if(prm$method=="barplot"){
62
    if(prm$method=="barplot"){
63
      barplot(height=x,
63
      barplot(height=x,
64
              ## maybe these two are wrong/stupid?
64
              ## maybe these two are wrong/stupid?
65
              cex.axis=prm$cex.lab,
65
              cex.axis=prm$cex.lab,
66
              cex.names=prm$cex.lab,
66
              cex.names=prm$cex.lab,
67
              col=bdp()$hcol,
67
              col=bdp()$hcol,
68
              border=border,
68
              border=border,
69
              xlab=xlab,
69
              xlab=xlab,
70
              ylab=ylab,
70
              ylab=ylab,
71
              main=main,
71
              main=main,
72
              ...)
72
              ...)
73
      prm$draw.xaxis <- FALSE
73
      prm$draw.xaxis <- FALSE
74
      prm$draw.yaxis <- FALSE
74
      prm$draw.yaxis <- FALSE
75
      
75
      
76
    } else {
76
    } else {
77
 
77
 
78
      if(is.null(xlim))
78
      if(is.null(xlim))
79
        xlim <- range(c(1:length(x),bdp()$xlim),na.rm=TRUE)
79
        xlim <- range(c(1:length(x),bdp()$xlim),na.rm=TRUE)
80
 
80
 
81
      if(is.null(ylim))
81
      if(is.null(ylim))
82
        ylim <- range(x,bdp()$ylim,na.rm=TRUE)
82
        ylim <- range(x,bdp()$ylim,na.rm=TRUE)
83
      
83
      
84
      plot(x,
84
      plot(x,
85
           type=type,
85
           type=type,
86
           xaxt="n", yaxt="n",
86
           xaxt="n", yaxt="n",
87
           cex=cex.plot,
87
           cex=cex.plot,
88
           xlab=xlab,
88
           xlab=xlab,
89
           ylab=ylab,
89
           ylab=ylab,
90
           xlim=xlim,
90
           xlim=xlim,
91
           ylim=ylim,
91
           ylim=ylim,
92
           col=col,
92
           col=col,
93
           main=main,
93
           main=main,
94
           ...)
94
           ...)
95
    }
95
    }
96
  } else if( class(x) == "acf"){
96
  } else if( class(x) == "acf"){
97
    ## Not cleaned up/checked
97
    ## Not cleaned up/checked
98
    plot(x, xlab="", ylab="", xaxt="n", yaxt="n", cex=prm$cex.plot, xlim=prm$xlim, ylim=prm$ylim,col=col,...)
98
    plot(x, xlab="", ylab="", xaxt="n", yaxt="n", cex=prm$cex.plot, xlim=prm$xlim, ylim=prm$ylim,col=col,...)
99
  }
-
 
100
  else if( class(x) == "histogram"){
99
  }  else if( class(x) == "histogram"){
101
    ## Notice: the color of the bars can ONLY be set width bdp(hcol="color").
100
    ## Notice: the color of the bars can ONLY be set width bdp(hcol="color").
102
    plot(x,
101
    plot(x,
103
         xlab=xlab, ylab=ylab,
102
         xlab=xlab, ylab=ylab,
104
         main=prm$main,
103
         main=prm$main,
105
         xaxt="n",yaxt="n",col=bdp()$hcol,
104
         xaxt="n",yaxt="n",col=bdp()$hcol,
106
         border=border,
105
         border=border,
107
         ...)
106
         ...)
108
  } else if( class(x) == "trellis"){
107
  } else if( class(x) == "trellis"){
109
    ## Not cleaned up/checked
108
    ## Not cleaned up/checked
110
    ## very experimental
109
    ## very experimental
111
    cat("The Bacher/Delff Plotting System (R), (C), TM operating in lattice mode.\n Remeber that labels must written in the lattice object.\n")
110
    cat("The Bacher/Delff Plotting System (R), (C), TM operating in lattice mode.\n Remeber that labels must written in the lattice object.\n")
112
    ##lattice.options(layout.widths = prm$lattice.width,
111
    ##lattice.options(layout.widths = prm$lattice.width,
113
    ##                layout.heights = prm$lattice.height)
112
    ##                layout.heights = prm$lattice.height)
114
    trellis.par.set(prm$myLatticeSettings()) 
113
    trellis.par.set(prm$myLatticeSettings()) 
115
    plot(x,col=col,...)
114
    plot(x,col=col,...)
116
    ## with lattice/trellis, the axis drawing doesn't work.
115
    ## with lattice/trellis, the axis drawing doesn't work.
117
    prm$draw.xaxis <- FALSE
116
    prm$draw.xaxis <- FALSE
118
    prm$draw.yaxis <- FALSE
117
    prm$draw.yaxis <- FALSE
-
 
118
  } else if (class(x)=="princomp") {
119
  }
119
    plot(x,
-
 
120
         main=prm$main,
-
 
121
         ...)
120
  else if (prm$method=="image.plot"){
122
  } else if (prm$method=="image.plot"){
121
    ### This could be checked in the beginning by is.null(z)
123
    ### This could be checked in the beginning by is.null(z)
122
    cat("The Bacher/Delff Plotting System (R), (C), TM operating in image plotting mode.\nx and y axis can not be configured.\n")
124
    cat("The Bacher/Delff Plotting System (R), (C), TM operating in image plotting mode.\nx and y axis can not be configured.\n")
123
    image.plot(x=x,y=y,z=z,
125
    image.plot(x=x,y=y,z=z,
124
               xlab=xlab,
126
               xlab=xlab,
125
               ylab=ylab,
127
               ylab=ylab,
126
               ...)
128
               ...)
127
  }
129
  } 
128
  
130
  
129
  ## We could make default values for grid.v og grid.h. Man maa kunne lave noget kvalificeret ud fra range og noget heltalsdivision
131
  ## We could make default values for grid.v og grid.h. Man maa kunne lave noget kvalificeret ud fra range og noget heltalsdivision
130
  
132
  
131
  ##Grid stuff
133
  ##Grid stuff
132
  if( prm$grid ){
134
  if( prm$grid ){
133
    grid(col=prm$grid.col)
135
    grid(col=prm$grid.col)
134
  }
136
  }
135
  ## vertical lines
137
  ## vertical lines
136
  if( !is.na(prm$grid.v) ){
138
  if( !is.na(prm$grid.v) ){
137
    if(prm$grid.v=="Def"){
139
    if(prm$grid.v=="Def"){
138
      grid(nx=NULL,ny=NA,col=prm$grid.col)
140
      grid(nx=NULL,ny=NA,col=prm$grid.col)
139
    } else
141
    } else
140
    {
142
    {
141
      abline(v=prm$grid.v, lty="dotted", col=prm$grid.col)
143
      abline(v=prm$grid.v, lty="dotted", col=prm$grid.col)
142
    }
144
    }
143
  }
145
  }
144
 
146
 
145
  if( !is.na(prm$grid.h) ){
147
  if( !is.na(prm$grid.h) ){
146
    if(prm$grid.h=="Def"){
148
    if(prm$grid.h=="Def"){
147
      grid(nx=NA,ny=NULL,col=prm$grid.col)
149
      grid(nx=NA,ny=NULL,col=prm$grid.col)
148
    }else{
150
    }else{
149
      abline(h=prm$grid.h, lty="dotted", col=prm$grid.col)}
151
      abline(h=prm$grid.h, lty="dotted", col=prm$grid.col)}
150
    }
152
    }
151
 
153
 
152
  ## Axis stuff
154
  ## Axis stuff
153
  if(prm$draw.xaxis){
155
  if(prm$draw.xaxis){
154
    ##    mgp.old <- par()$mgp
156
    ##    mgp.old <- par()$mgp
155
    ##    par(mgp) <- mgp.xaxis
157
    ##    par(mgp) <- mgp.xaxis
156
    options(warn=-1)
158
    options(warn=-1)
157
    if( "POSIXt"%in%class(x[1])){
159
    if( "POSIXt"%in%class(x[1])){
158
      axis.POSIXct(1, x,mgp=prm$mgp.xaxis, lwd=prm$lwd)
160
      axis.POSIXct(1, x,mgp=prm$mgp.xaxis, lwd=prm$lwd)
159
    } else {
161
    } else {
160
      axis(1, mgp=prm$mgp.xaxis, lwd=prm$lwd)
162
      axis(1, mgp=prm$mgp.xaxis, lwd=prm$lwd)
161
    }
163
    }
162
    options(warn=0)
164
    options(warn=0)
163
    
165
    
164
  }
166
  }
165
  if(prm$draw.yaxis){ axis(2, mgp=prm$mgp.yaxis, lwd=prm$lwd) }
167
  if(prm$draw.yaxis){ axis(2, mgp=prm$mgp.yaxis, lwd=prm$lwd) }
166
  ## axis to the right
168
  ## axis to the right
167
  if(prm$draw.raxis){ axis(4, mgp=prm$mgp.raxis, lwd=prm$lwd) }
169
  if(prm$draw.raxis){ axis(4, mgp=prm$mgp.raxis, lwd=prm$lwd) }
168
  ##Title stuff
170
  ##Title stuff
169
  ## Hvorfor??
171
  ## Hvorfor??
170
  scale <- 1
172
  scale <- 1
171
  ##  if( prm$type=="hist" & !is.na(prm$xlab) )
173
  ##  if( prm$type=="hist" & !is.na(prm$xlab) )
172
#  if( !is.na(prm$xlab)  ){ mtext(prm$xlab, line=prm$xlabLine, side=1, cex=prm$cex.lab/scale) }
174
#  if( !is.na(prm$xlab)  ){ mtext(prm$xlab, line=prm$xlabLine, side=1, cex=prm$cex.lab/scale) }
173
  ##  if( prm$type=="hist" &!is.na(prm$ylab) )
175
  ##  if( prm$type=="hist" &!is.na(prm$ylab) )
174
#  if( !is.na(prm$ylab)  ){ mtext(prm$ylab, line=prm$ylabLine, side=2, cex=prm$cex.lab/scale) }
176
#  if( !is.na(prm$ylab)  ){ mtext(prm$ylab, line=prm$ylabLine, side=2, cex=prm$cex.lab/scale) }
175
  if( !is.na(prm$toplab) ){ mtext(prm$toplab, side=3, line=0.25, cex=prm$cex.lab/scale) }
177
  if( !is.na(prm$toplab) ){ mtext(prm$toplab, side=3, line=0.25, cex=prm$cex.lab/scale) }
176
  if( !is.na(prm$rightlab) ){
178
  if( !is.na(prm$rightlab) ){
177
    mtext(prm$rightlab, side=4, line=0.75, cex=prm$cex.lab/scale,mgp=prm$mgp.raxis)
179
    mtext(prm$rightlab, side=4, line=0.75, cex=prm$cex.lab/scale,mgp=prm$mgp.raxis)
178
##    mtext(rightlab, side=4, line=0.5, cex=bdp()$cex.lab,mgp=bdp()$mgp.raxis)
180
##    mtext(rightlab, side=4, line=0.5, cex=bdp()$cex.lab,mgp=bdp()$mgp.raxis)
179
  }
181
  }
180
}
182
}
181
 
183
 
182
 
184
 
183
 
185
 
184
 
186