source: trunk/SRC/ToBeReviewed/PLOTS/legende.pro

Last change on this file was 495, checked in by pinsard, 10 years ago

fix thanks to coding rules; typo; dupe empty lines; trailing blanks

  • Property svn:eol-style set to native
  • Property svn:keywords set to Id
File size: 10.5 KB
RevLine 
[2]1;+
2;
[142]3; @file_comments
4; Provide caption
[2]5;
[142]6; @categories
[157]7; Graphics
[2]8;
[142]9; @param MI {in}{required}
10; The min of the drawing
[231]11;
[142]12; @param MA {in}{required}
13; The max of the plot
[2]14;
[163]15; @param COUPE {type=string}
[378]16; Character containing two letters giving the type of the cut for example: 'xz'
[2]17;
[231]18; @keyword CONTOUR
19; If we want to trace contours of a different field than the one
20; whose we have the colored drawing (by example E-P in color and QSR in contours).
[2]21;
[495]22; It must be a field respecting same characteristics than the argument number
[378]23; one of plt.
24;
[142]25; @keyword ENDPOINTS
26; Used when we do vertical cuts in diagonal.
[2]27;
[142]28; @keyword _EXTRA
[231]29; Used to pass keywords
30;
[142]31; @uses
[369]32; <pro>common</pro>
[2]33;
[142]34; @restrictions
[495]35; The use of the global variable language allows to change the language and
[378]36; the caption easily.
[2]37;
[142]38; @history
[157]39;  Sebastien Masson (smasson\@lodyc.jussieu.fr)
[2]40;                       14/8/98
[157]41;                       Eric Guilyardi (ericg\@lodyc.jussieu.fr) GB version
[2]42;                       11/6/99
[142]43;
44; @version
45; $Id$
46;
[2]47;-
[327]48PRO legende, mi, ma, coupe, CONTOUR=contour, ENDPOINTS=endpoints, DIREC=direc $
49           , VECTLEGENDE=vectlegende $
50           , INTERVALLE=intervalle, TYPE_YZ=type_yz, VARNAME2=varname2 $
51           , NPTS=npts, _EXTRA=ex
[114]52;
53  compile_opt idl2, strictarrsubs
54;
[2]55@common
[152]56  tempsun = systime(1)          ; pour key_performance
[2]57;------------------------------------------------------------
[152]58  grille, -1, -1, -1, gdep, nx, ny, nz
[2]59;
60; English legends
61;
[152]62  fmt_mm = '(f12.2)'
63  fmt_bt = '(f7.1)'
64  colorf = ''
65  contourf = 'Contour plot,'
66  vecteurf = 'Vector norm  '
67  expf = ''
68  datef = '   '
69  fieldf = '   '
70  depthf = '   '
71  endpointsf = 'Diag. Section'
72  zonalf = ''
73  IF key_onearth THEN latintf = 'latitudes in ' ELSE latintf = 'j index in '
74  timintf = 'time in '
75  onf = ' - '
76  depthf2 = 'Depth (m)'
77  Meridf = 'Zonal Mean  '
78  IF key_onearth THEN lonintf = 'longitudes in ' ELSE lonintf = 'i in '
79  hovxt = 'XT-plot   '
80  diaghovxt = 'Diag. XT-plot   '
81  depintf = 'depths in '
82  timef = 'Time'
83  hovyt = 'YT-plot   '
84  diaghovyt = 'Diag. YT-plot   '
85  hovzt = 'ZT-plot   '
86  hovt = ''
87  IF key_onearth THEN lontitle = 'Longitude' ELSE lontitle = 'i index'
88  IF key_onearth THEN lattitle = 'Latitude' ELSE lattitle = 'j index'
[231]89
[152]90  IF keyword_set(TYPE_YZ) THEN BEGIN
[344]91    vertz = type_yz
92    legniv = ' '+type_yz
[495]93  ENDIF ELSE BEGIN
[344]94    vertz = depthf2
95    legniv = ' m'
[495]96  ENDELSE
[2]97;
98; Start legende
99;
100;------------------------------------------------------------
[142]101; definition and possible complement of !p.subtitle
[2]102;------------------------------------------------------------
[152]103  if n_elements(varunit) ne 0 then unite = '('+varunit+')' else unite = ''
104  !p.subtitle = colorf+unite+': Min= '+strtrim(string(format = fmt_mm, mi), 2)$
105                +', Max= '+strtrim(string(format = fmt_mm, ma), 2)
106  if keyword_set(intervalle) then BEGIN
107    if intervalle NE -1 then $
108       !p.subtitle = !p.subtitle+', Int= '+strtrim(string(format = fmt_mm, intervalle), 2)
109  endif
[231]110  if size(contour, /type) EQ 8 then BEGIN ; it is a structure
[152]111    unite = '('+contour.(1)+')'
112    !p.subtitle = !p.subtitle+'!C '+contourf+unite $
113                  +': Min= '+strtrim(string(format = fmt_mm, contour.(0)[0]), 2)$
114                  +', Max= '+strtrim(string(format = fmt_mm, contour.(0)[1]), 2)
115    if contour.inter NE -1  then $
116       !p.subtitle = !p.subtitle+', Int= '+strtrim(string(format = fmt_mm, contour.inter), 2)
117  ENDIF
118  if size(vectlegende, /type) EQ 8  then begin
119    unite = '('+vectlegende.(1)+')'
120    !p.subtitle = !p.subtitle+'!C '+vecteurf+unite $
121                  +': Min= '+strtrim(string(format = fmt_mm, vectlegende.(0)[0]), 2)$
122                  +', Max= '+strtrim(string(format = fmt_mm, vectlegende.(0)[1]), 2)
123  endif
[2]124;------------------------------------------------------------
[493]125; Shaping of subdomain 's dimensions
[231]126;------------------------------------------------------------
[152]127  la1 = strtrim(string(format = fmt_bt, lat1), 2)
128  la2 = strtrim(string(format = fmt_bt, lat2), 2)
129  lo1 = strtrim(string(format = fmt_bt, lon1), 2)
130  lo2 = strtrim(string(format = fmt_bt, lon2), 2)
131  pr1 = strtrim(string(format = fmt_bt, vert1), 2)
132  pr2 = strtrim(string(format = fmt_bt, vert2), 2)
[2]133;------------------------------------------------------------
[142]134; Management of the date
[231]135;------------------------------------------------------------
[152]136  if n_elements(vardate) EQ 0 then vardate = ''
137  if NOT keyword_set(direc) then direc = ''
138  if strpos(direc, 't') NE -1 then begin
139    svardate = strtrim(vairdate(time[0]), 1)+' - '+strtrim(vairdate(time[jpt-1]), 1)
140  ENDIF ELSE svardate = vardate
[2]141;------------------------------------------------------------
[142]142; case on the caes where the caption is applied
[231]143;------------------------------------------------------------
[152]144  case coupe of
[231]145    'xy':begin
[152]146      if strupcase(vargrid) EQ 'W' then firstz = firstzw $
147      ELSE firstz = firstzt
148      if(strpos(direc, 'z') EQ -1 AND firstz NE 0) then BEGIN
149        prof = strtrim(round(gdep[0]), 1)
150        !p.title = expf+varexp+datef+svardate+fieldf+varname+depthf+prof+legniv
151      ENDIF ELSE !p.title = expf+varexp+datef+svardate+fieldf+varname
152      !x.title = lontitle
153      !y.title = lattitle
154    end
[2]155
[152]156    'xz':begin
157      IF keyword_set(npts) THEN n = strtrim(npts, 1) ELSE n = strtrim(ny, 1)
158      IF long(n) LE 3 THEN zonalf = 'Section   '
159      if keyword_set(endpoints) AND lat1 NE lat2 then $
160         !p.title = endpointsf+varexp+datef+svardate+fieldf+varname ELSE $
161            !p.title = zonalf+varexp+datef+svardate+fieldf+varname
162      !x.title = lontitle
[231]163      if keyword_set(endpoints) AND lat1 EQ lat2 then BEGIN
[152]164        IF key_onearth THEN !x.title = !x.title+' at '+strtrim(lataxe(0, 0, lat1), 1) ELSE !x.title = !x.title+' at j index '+strtrim(lat1, 1)
165      ENDIF
[344]166      !y.title = vertz
[152]167    end
[2]168
[152]169    'yz':begin
170      IF keyword_set(npts) THEN n = strtrim(npts, 1) ELSE n = strtrim(nx, 1)
171      IF long(n) LE 3 THEN meridf = ''
172      if keyword_set(endpoints) AND lon1 NE lon2 then $
173         !p.title = endpointsf+varexp+datef+svardate+fieldf+varname ELSE $
174            !p.title = meridf+varexp+datef+svardate+fieldf+varname
175      !y.title = vertz
176      !x.title = lattitle
[231]177      if keyword_set(endpoints) AND lon1 EQ lon2 then BEGIN
[152]178        IF key_onearth THEN !x.title = !x.title+' at '+strtrim(lonaxe(0, 0, lon1), 1) ELSE !x.title = !x.title+' at i index '+strtrim(lon1, 1)
179      ENDIF
180    end
[2]181
[152]182    'xt':begin
[2]183;         IF keyword_set(npts) THEN n = strtrim(npts, 1)
[152]184      if keyword_set(endpoints) AND lat1 NE lat2 then $
185         !p.title = diaghovxt+varexp+fieldf+varname ELSE $
186            !p.title  =     hovxt+varexp+fieldf+varname
187      IF (time[(size(time))[0]-1] - time[0]) GE 10 THEN !y.title = timef
188      !x.title = lontitle
[231]189      if keyword_set(endpoints) AND lat1 EQ lat2 then BEGIN
[152]190        IF key_onearth THEN !x.title = !x.title+' at '+strtrim(lataxe(0, 0, lat1), 1) ELSE !x.title = !x.title+' at j index '+strtrim(lat1, 1)
191      ENDIF
192    end
[2]193
[152]194    'yt':begin
[231]195;         IF keyword_set(npts) THEN n = strtrim(npts, 1)
[152]196      if keyword_set(endpoints) AND lon1 NE lon2 then $
197         !p.title = diaghovyt+varexp+fieldf+varname ELSE $
198            !p.title  =     hovyt+varexp+fieldf+varname
199      IF (time[(size(time))[0]-1] - time[0]) GE 10 THEN !x.title = timef
200      !y.title = lattitle
[231]201      if keyword_set(endpoints) AND lon1 EQ lon2 then BEGIN
[152]202        IF key_onearth THEN !x.title = !x.title+' at '+strtrim(lonaxe(0, 0, lon1), 1) ELSE !x.title = !x.title+' at i index '+strtrim(lon1, 1)
203      ENDIF
204    end
[2]205
[152]206    'zt':begin
[2]207;         IF keyword_set(npts) THEN n = strtrim(npts, 1) ELSE n=strtrim(nx*ny, 1)
[152]208      !p.title = hovzt+varexp+fieldf+varname
[344]209      !y.title = vertz
[152]210      IF (time[(size(time))[0]-1] - time[0]) GE 10 THEN !x.title = timef
211    end
212    't':begin
[231]213;         IF keyword_set(npts) THEN n = strtrim(npts, 1) ELSE BEGIN
[2]214;            if keyword_set(integration3d) then n=strtrim(nx*ny*nz, 1) ELSE n=strtrim(nx*ny, 1)
[231]215;         ENDELSE
[152]216      !p.title = hovt+varexp+fieldf+varname
217      !y.title = varname
218      IF (time[(size(time))[0]-1] - time[0]) GE 10 THEN !x.title = timef
219    end
[231]220    'x':begin
[2]221;         IF keyword_set(npts) THEN n = strtrim(npts, 1) ELSE n=strtrim(ny*nz, 1)
[152]222      if keyword_set(endpoints) AND lat1 NE lat2 then $
223         !p.title = endpointsf+varexp+datef+svardate+fieldf+varname ELSE $
224            !p.title  =            varexp+datef+svardate+fieldf+varname
225      !x.title = lontitle
[231]226      if keyword_set(endpoints) AND lat1 EQ lat2 then BEGIN
[152]227        IF key_onearth THEN !x.title = !x.title+' at '+strtrim(lataxe(0, 0, lat1), 1) ELSE !x.title = !x.title+' at j index '+strtrim(lat1, 1)
228      ENDIF
229      !y.title = varname
230    end
[231]231    'y':begin
[2]232;         IF keyword_set(npts) THEN n = strtrim(npts, 1) ELSE n=strtrim(nx*nz, 1)
[152]233      if keyword_set(endpoints) AND lon1 NE lon2 then $
234         !p.title = endpointsf+varexp+datef+svardate+fieldf+varname ELSE $
235            !p.title  =            varexp+datef+svardate+fieldf+varname
236      !x.title = lattitle
[231]237      if keyword_set(endpoints) AND lon1 EQ lon2 then BEGIN
[152]238        IF key_onearth THEN !x.title = !x.title+' at '+strtrim(lonaxe(0, 0, lon1), 1) ELSE !x.title = !x.title+' at i index '+strtrim(lon1, 1)
239      ENDIF
240      !y.title = varname
241    end
242    'z':begin
243      IF keyword_set(npts) THEN n = strtrim(npts, 1) ELSE n = strtrim(nx*ny, 1)
244      !p.title = varexp+datef+svardate+fieldf+varname
[344]245      !y.title = vertz
[152]246      !x.title = varname
247    end
248    'yfx': BEGIN
249      IF keyword_set(npts) THEN n = strtrim(npts, 1) ELSE n = strtrim(nx*ny*nz, 1)
250      !p.title = varexp+datef+svardate+varunit
251      !x.title = varname2
252      !y.title = varname
[231]253    END
[152]254    else:
255  ENDCASE
256  if keyword_set(direc) then BEGIN
257    if strpos(direc, 'x') NE -1 then $
[2]258       !p.subtitle = lonintf+'['+lo1+', '+lo2+']'+onf+'('+strtrim(nx, 1)+' points)  !C' +!p.subtitle
[152]259    if strpos(direc, 'y') NE -1 then BEGIN
260      if strpos(!p.subtitle, '[') EQ -1 then $
261         !p.subtitle = latintf+'['+la1+', '+la2+']'+onf+'('+strtrim(ny, 1)+' points)  !C'+!p.subtitle $
262      ELSE !p.subtitle = latintf+'['+la1+', '+la2+']'+onf+'('+strtrim(ny, 1)+' points)  '+!p.subtitle
263    ENDIF
[231]264    if strpos(direc, 'z') NE -1 AND (nz NE 1 OR coupe NE 'xy') then BEGIN
[152]265      if strpos(!p.subtitle, '[') EQ -1 then $
266         !p.subtitle = depintf+'['+pr1+', '+pr2+']'+onf+'('+strtrim(nz, 1)+' points)  !C'+!p.subtitle $
267      ELSE !p.subtitle = depintf+'['+pr1+', '+pr2+']'+onf+'('+strtrim(nz, 1)+' points)  '+!p.subtitle
268    ENDIF
269  ENDIF
270  if keyword_set(endpoints) AND coupe NE 'yt' AND lat1 NE lat2 then !p.title = !p.title+'!C!C'
[231]271
272  if keyword_set(key_performance) THEN print, 'temps legende', systime(1)-tempsun
[152]273  return
[2]274end
Note: See TracBrowser for help on using the repository browser.