Subversion Repositories bdplot

Rev

Go to most recent revision | Details | Last modification | View Log | RSS feed

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