source: trunk/SRC/ToBeReviewed/PLOTS/VECTEUR/vecteur.pro @ 495

Last change on this file since 495 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: 15.8 KB
Line 
1;+
2;
3; @file_comments
4;
5; @categories
6;
7; @param angle
8;
9; @returns
10;
11; @restrictions
12;
13; @examples
14;
15; @history
16;
17; @version
18; $Id$
19;
20;-
21FUNCTION cv_cm2normal, angle
22;
23; Give the length in normal coordinates of a trait oriented of an angle
24; by rapport at the x axis and which must do 1 cm on the drawing.
25; Angle can be an array.
26;
27  compile_opt idl2, strictarrsubs
28;
29@common
30; What is the length in normal coordinates of a trait which will do 1 cm
31; on the paper an which is parallel to x?
32  mipgsz = min(page_size, max = mapgsz)
33   sizexfeuille = mipgsz*key_portrait+mapgsz*(1-key_portrait)
34   sizeyfeuille = mapgsz*key_portrait+mipgsz*(1-key_portrait)
35   cm_en_normal = 1./sizexfeuille
36;
37; If the aspect ratio of the window is not equal to 1, the length in
38; normalized coordinates of  a trait of 1 cm vary following the polar
39; angle of this trait.
40;
41   aspect = sizexfeuille/sizeyfeuille
42   cm_en_normal = cm_en_normal*sqrt( 1 +(aspect^2-1)*sin(angle)^2 )
43;
44   return, cm_en_normal
45END
46;
47;+
48;
49; @file_comments
50;
51; @categories
52;
53; @param u
54;
55; @param v
56;
57; @param w
58;
59; @restrictions
60;
61; @examples
62;
63; @history
64;
65; @version
66; $Id$
67;
68;-
69PRO normalise, u, v, w
70;
71; normalize the vector
72;
73  compile_opt idl2, strictarrsubs
74;
75   IF n_elements(w) NE 0 THEN BEGIN
76      norme = sqrt(u^2.+v^2.+w^2.)
77      ind = where(norme NE 0)
78      u[ind] = u[ind]/norme[ind]
79      v[ind] = v[ind]/norme[ind]
80      w[ind] = w[ind]/norme[ind]
81   ENDIF ELSE BEGIN
82      norme = sqrt(u^2.+v^2.)
83      ind = where(norme NE 0)
84      u[ind] = u[ind]/norme[ind]
85      v[ind] = v[ind]/norme[ind]
86   ENDELSE
87END
88;
89;+
90;
91; @file_comments
92; Trace vectors (even if they are on a deformed grid) on any projection.
93; In this way, all vectors have a comparable norme on the drawing (to be
94; clear, a vector which measure 1 cm measure it, no matter the projection
95; and is position on the sphere).
96;
97; @categories
98; Graphics
99;
100; @param composanteu {in}{required}
101; It is the u component of the vector to be traced. This 2d array has the
102; same dimension that reduitindice2d (see further)
103;
104; @param composantev {in}{required}
105; It is the v component of the vector to be traced. This 2d array has the
106; same dimension that reduitindice2d (see further)
107;
108; @param normevecteur
109;
110; @param indice2d {in}{required}
111; It in an index allowing to to pass from an jpi or jpj array to the zoom
112; on which we do the drawing
113;
114; @param reduitindice2d {in}{required}
115; It is an index allowing to pass from an array defined by indice2d to the
116; array for which we really have vectors to be traced (to be clear, it is
117; for example when we trace only one vector on two).
118;
119; @keyword CMREF {default=between .5 and 1.5 cm}
120; The length in cm that must measure the arrow normed normeref. By default,
121; it is adjusted to other drawing and included between .5 and 1.5 cm.
122;
123; @keyword MISSING
124; The value of a missing value. Do not use this keyword. Fixed at 1e5 by
125; ajoutvect.pro
126;
127; @keyword NORMEREF
128; The norme of the reference arrow.
129;
130; @keyword VECTCOLOR {default=0}
131; The color of the arrow. Black by default (color 0)
132;
133; @keyword VECTNORMCOLOR
134; a 2 elements vector used to specify the color of the vector according to
135; its norm. Vector norm will be scaled to color numbers (1 to 254) by using
136; the following rule: VECTNORMCOLOR[0] corresponds to 1 and VECTNORMCOLOR[1] to 254
137;
138; @keyword VECTTHICK {default=1}
139; The thick of the arrow.
140;
141; @keyword VECTREFPOS
142; Vector composed of 2 elements specifying the position on DATA coordinates
143; from the beginning of the reference vector. By default at the right bottom
144; of the drawing.
145;
146; @keyword VECTREFFORMAT
147; The format to be used to specify the norme of the reference vector.
148;
149; @keyword VECTREFCHARSIZE
150; Character size of the legend of the reference arrow
151;
152; @keyword VECTREFCHARSIZE
153; Character thickness of the legend of the reference arrow
154;
155; @keyword NOVECTREF
156; To delete the display of the reference vector.
157;
158; @keyword _EXTRA
159; Used to pass keywords
160;
161; @uses
162; <pro>common</pro>
163;
164; @history
165;  Creation : 13/02/98 G. Roullet (grlod\@lodyc.jussieu.fr)
166;  Modification : 14/01/99 realise la transformation
167;  spherique<->cartesien G. Roullet
168;                 12/03/99 verification de la routine G. Roullet
169;  8/11/1999:
170;  G. Roullet et Sebastien Masson (smasson\@lodyc.jussieu.fr)
171;  adaptation pour les zoom. reverification...traitement separe de la
172;  direction et de la norme des vecteurs. mots cles NORMEREF et CMREF.
173;
174; @version
175; $Id$
176;
177;-
178PRO vecteur, composanteu, composantev, normevecteur, indice2d, reduitindice2d $
179             , CMREF = cmref, MISSING = missing, NORMEREF = normeref $
180             , VECTCOLOR = vectcolor, VECTTHICK = vectthick $
181             , VECTREFPOS = vectrefpos, VECTNORMCOLOR = vectnormcolor $
182             , VECTREFFORMAT = vectrefformat, NOVECTREF = novectref $
183             , VECTREFCHARSIZE = vectrefcharsize, VECTREFCHARTHICK = vectrefcharthick $
184             , _EXTRA = extra
185;
186  compile_opt idl2, strictarrsubs
187;
188@common
189  tempsun = systime(1)          ; For key_performance
190;
191  taille = size(composanteu)
192  nx = taille[1]
193  ny = taille[2]
194  if n_elements(reduitindice2d) EQ 0 then reduitindice2d = lindgen(nx, ny)
195  zu = composanteu
196  zv = composantev
197  norme = normevecteur
198  taille = size(indice2d)
199  nxgd = taille[1]
200  nygd = taille[2]
201;
202  msk = replicate(1, nx, ny)
203  if keyword_set(missing) then terre = where(abs(zu) GE missing/10) ELSE terre = -1
204  if terre[0] NE -1  then BEGIN
205    msk[terre] = 0
206    zu[terre] = 0
207    zv[terre] = 0
208    norme[terre] = 0
209  ENDIF
210;
211; Stage 1:
212;
213; Given that the directions and the sense that the vector has on the sphere,
214; we have to try to determinate this direction and the sense that the vector
215; will have on the screen once it will have been projected.
216;
217; In theory: on the sphere, a vector in a given point has for direction the
218; tangent at the circle passing by the center of the Earth and by the vector.
219; So, find the direction once the projection is done, it is find the tangent
220; to the curve representing the projection of the circle on the 2d plan at the
221; point representing the projection of the starting point of the sphere on the
222; 2d plan.
223;
224; In practice we do no know the definition of the curve given by the projection
225; of a circle so find its tangente in a point...
226;
227; What we do:
228; In a 3d cartesian reference,
229;       a) We find coordinates of the point T (starting of the arrow) situated
230;       on the sphere.
231;       b) To each point T, we determine local directions defined by the grid
232;       on this point and on which coordinates (u,v) of the vector refer to.
233;       These local directions are defined by gradients of glam and gphi. Once
234;       we have obtain these directions, we consider them like orthogonal and
235;       by norming them, we build an orthonormal reference (nu,nv) on which
236;       coordinates (u,v) of the vector refer to. In the starting 3d cartesian
237;       reference, the vector is defined by:
238;       V=u*nu+v*nv
239;       (where V, nu and nv are 3d vectors and u and v are scalars).
240;       c) To approximate the tangente to the circle by the chord defined by
241;       the beginning and the ending of the arrow, we will normalize V, and
242;       then divide it by 100.
243;       d) This allows us to determine coordinates of extremities of the chord
244;       in the 3d cartesian reference. We pass them in spherical coordinates in
245;       order to recuperate latitude and longitude position of these points on
246;       the sphere.
247;       e) We pass coordinates of these points in normalized coordinates, then
248;       in polar coordinates in order to find the angle and the direction they
249;       determine on the drawing.
250;
251; Stage 1, a)
252;
253; coordinates of the point T (beginning of the arrow) in spherical coordinates.
254  glam = glamt[indice2d[reduitindice2d]]
255  gphi = gphit[indice2d[reduitindice2d]]
256;
257; Coordinates of the point T (beginning of the arrow) in the cartesian reference.
258; For the sphere, we use a sphere with a radius of 1.
259;
260  radius = replicate(1, nx*ny)
261  coord_sphe = transpose([ [glam[*]], [gphi[*]], [radius[*]] ])
262  r = cv_coord(from_sphere = coord_sphe, /to_rect, /degrees)
263;
264  x0 = reform(r[0, *], nx, ny)
265  y0 = reform(r[1, *], nx, ny)
266  z0 = reform(r[2, *], nx, ny)
267;
268; Stage 1, b)
269;
270; Construction of a vector nu (resp. nv), vector normed carried by the axis of
271; points u[i,j] and u[i-1,j] (resp v[i,j] and v[i,j-1]) which define, for each
272; point on the sphere, local directions associated with u and v. These vectors
273; define a local orthonormal reference.
274; These vectors are built in a cartesian reference (cv_coord). We have choose a
275; unity radius of the Earth (unit).
276;
277; definition of nu
278  radius = replicate(1, nxgd*nygd)
279  IF finite(glamu[0]*gphiu[0]) NE 0 THEN $
280     coord_sphe = transpose([ [(glamu[indice2d])[*]], [(gphiu[indice2d])[*]], [radius[*]] ]) $
281  ELSE coord_sphe = transpose([ [(glamf[indice2d])[*]], [(gphit[indice2d])[*]], [radius[*]] ])
282  r = cv_coord(from_sphere = coord_sphe, /to_rect, /degrees)
283; coordinates of points of the grid u in cartesian.
284  ux = reform(r[0, *], nxgd, nygd)
285  uy = reform(r[1, *], nxgd, nygd)
286  uz = reform(r[2, *], nxgd, nygd)
287; calculation of nu
288  nux = ux-shift(ux, 1, 0)
289  nuy = uy-shift(uy, 1, 0)
290  nuz = uz-shift(uz, 1, 0)
291; conditions at extremities.
292  if NOT keyword_set(key_periodic) OR nxgd NE jpi then begin
293    nux[0, *] = nux[1, *]
294    nuy[0, *] = nuy[1, *]
295    nuz[0, *] = nuz[1, *]
296  ENDIF
297; reduction of the grid
298  nux = nux[reduitindice2d]
299  nuy = nuy[reduitindice2d]
300  nuz = nuz[reduitindice2d]
301; definition of nv
302  IF finite(glamv[0]*gphiv[0]) NE 0 THEN $
303     coord_sphe = transpose([ [(glamv[indice2d])[*]], [(gphiv[indice2d])[*]], [radius[*]] ]) $
304  ELSE coord_sphe = transpose([ [(glamt[indice2d])[*]], [(gphif[indice2d])[*]], [radius[*]] ])
305  r = cv_coord(from_sphere = coord_sphe, /to_rect, /degrees)
306; coordinates of points of the grid in cartesian.
307  vx = reform(r[0, *], nxgd, nygd)
308  vy = reform(r[1, *], nxgd, nygd)
309  vz = reform(r[2, *], nxgd, nygd)
310; calcul of nv
311  nvx = vx-shift(vx, 0, 1)
312  nvy = vy-shift(vy, 0, 1)
313  nvz = vz-shift(vz, 0, 1)
314; conditions at extremities
315  nvx[*, 0] = nvx[*, 1]
316  nvy[*, 0] = nvy[*, 1]
317  nvz[*, 0] = nvz[*, 1]
318; reduction of the grid
319  nvx = nvx[reduitindice2d]
320  nvy = nvy[reduitindice2d]
321  nvz = nvz[reduitindice2d]
322;
323; normalization
324;
325  normalise, nux, nuy, nuz
326  normalise, nvx, nvy, nvz
327;
328; Stage 1, c)
329;
330; coordinates of the vector V in the cartesian reference
331;
332  direcx = zu*nux + zv*nvx
333  direcy = zu*nuy + zv*nvy
334  direcz = zu*nuz + zv*nvz
335; normalization of the vector V
336  normalise, direcx, direcy, direcz
337; on divide by 100
338  direcx = direcx/100.
339  direcy = direcy/100.
340  direcz = direcz/100.
341;
342; Stage 1, d)
343; coordinates of the point of the arrow in the cartesian reference.
344
345  x1 = x0 + direcx
346  y1 = y0 + direcy
347  z1 = z0 + direcz
348
349; coordinates of the point of the arrow in spherical coordinates.
350
351  coord_rect = transpose([ [x1[*]], [y1[*]], [z1[*]] ])
352  r = cv_coord(from_rect = coord_rect, /to_sphere, /degrees)
353  glam1 = reform(r[0, *], nx, ny)
354  gphi1 = reform(r[1, *], nx, ny)
355
356;
357; modification of glams. Everything take place at the level of the line
358; of changing of date... BEWARE, do not cut arrow which goes out of the
359; window!
360; test: If it goes out of the frame, but, thanks to +/- 360° it come in,
361; we modify it
362;
363  ind = where(glam1 LT !x.range[0] AND glam1+360. LE !x.range[1])
364  if ind[0] NE -1 then glam1[ind] = glam1[ind]+360.
365  ind = where(glam1 GT !x.range[1] AND glam1-360. GE !x.range[0])
366  if ind[0] NE -1 then glam1[ind] = glam1[ind]-360.
367
368  ind = where(glam LT !x.range[0] AND glam+360. LE !x.range[1])
369  if ind[0] NE -1 then glam[ind] = glam[ind]+360.
370  ind = where(glam  GT !x.range[1] AND glam-360. GE !x.range[0])
371  if ind[0] NE -1 then glam[ind] = glam[ind]-360.
372;
373; Stage 1, e)
374;
375  r = convert_coord(glam, gphi, /data, /to_normal)
376  x0 = r[0, *]                  ; normal coordinates of the beginning of the array.
377  y0 = r[1, *]                  ;
378
379  r = convert_coord(glam1, gphi1, /data, /to_normal)
380  x1 = r[0, *]                  ; normal coordinates of the ending of the array (Before scaling).
381  y1 = r[1, *]                  ;
382;
383; tests to avoid that arrows be drawing out of the domain.
384;
385  out = where(x0 LT !p.position[0] OR x0 GT !p.position[2]  $
386              OR y0 LT !p.position[1] OR y0 GT !p.position[3])
387  if out[0] NE -1 THEN x0[out] = !values.f_nan
388;
389; Following projections, there may are points at NaN when we pass in normal coordinates.
390; We delete these points.
391;
392  nan = finite(x0*y0*x1*y1)
393  number = where(nan EQ 1)
394  x0 = x0[number] & x1 = x1[number]
395  y0 = y0[number] & y1 = y1[number]
396  msk = msk[number]
397  norme = norme[number]
398;
399  points = where(msk EQ 1)
400  IF points[0] NE -1 THEN BEGIN
401
402  x0 = x0[points] & x1 = x1[points]
403  y0 = y0[points] & y1 = y1[points]
404  msk = msk[points]
405  norme = norme[points]
406
407; We define the vector direction in the normalize reference.
408;
409    dirx = x1-x0
410    diry = y1-y0
411;
412;We pass in polar coordinates to recuperate the angle which wasb the goal of all the first stage!!!
413;
414    dirpol = cv_coord(from_rect = transpose([ [dirx[*]], [diry[*]] ]), /to_polar)
415    dirpol = msk*dirpol[0, *]
416;
417; Stage 2
418;
419; Now we take care of the norme...
420;
421; Automatic putting at the scale
422;
423    if NOT keyword_set(cmref) then BEGIN
424      mipgsz = min(page_size, max = mapgsz)
425      sizexfeuille = mipgsz*key_portrait+mapgsz*(1-key_portrait)
426      sizexfeuille = 10.*sizexfeuille
427      cmref = 5 > floor(sizexfeuille/10.) < 15
428      cmref = cmref/10.
429    ENDIF
430    if NOT keyword_set(normeref) then BEGIN
431      value = max(norme)
432      puissance10 = 10.^floor(alog10(value))
433      normeref = puissance10*floor(value/puissance10)
434    endif
435    cm = 1.*normeref/cmref
436;
437; We modify the array norme to an element having the value cm be represented
438; by a line of length 1 cm on the paper. Norme contains the norm of vectors
439; we want to draw.
440;
441; define colors before norme is changed...
442    IF NOT KEYWORD_SET(vectcolor) THEN vectcolor = 0
443    IF keyword_set(vectnormcolor) THEN BEGIN
444      mp = projsegment([vectnormcolor], [1, 254], /mp)
445      colors = byte(round(mp[0] * norme +  mp[1] ))
446    ENDIF ELSE colors = byte(vectcolor)
447;
448    norme = 1/(1.*cm)*norme*cv_cm2normal(dirpol)
449;
450; Stage 3
451; Now that we have the angle and the norm, we recuperate coordinates in
452; rectangular and we draw arrows.
453;
454    r = cv_coord(from_polar = transpose([ [dirpol[*]], [norme[*]] ]), /to_rect)
455    composantex = r[0, *]
456    composantey = r[1, *]
457;
458    x1 = x0+composantex
459    y1 = y0+composantey
460;
461; Drawing
462;
463    points = where(msk EQ 1)
464    IF n_elements(colors) GT 1 THEN BEGIN
465      FOR i = 0, n_elements(colors)-1 DO arrow, x0[i], y0[i], x1[i], y1[i], /norm, hsize = -.2, COLOR = colors[i], THICK = vectthick
466    ENDIF ELSE arrow, x0, y0, x1, y1, /norm, hsize = -.2, COLOR = colors, THICK = vectthick
467;
468;  Draw an arrow at the right bottom of the drawing as a caption.
469;
470    if NOT keyword_set(novectref) then BEGIN
471      dx = cmref*cv_cm2normal(0) ; Length of the vector of reference in normalized coordinates.
472      if keyword_set(vectrefformat) then $
473         normelegende = strtrim(string(normeref, format = vectrefformat), 1)+' ' $
474      ELSE normelegende = strtrim(normeref, 1)+' '
475;
476      if keyword_set(vectrefpos) then begin
477        r = convert_coord(vectrefpos, /data, /to_normal)
478        x0 = r[0]
479        y0 = r[1]
480      ENDIF ELSE BEGIN
481        x0 = !x.window[1]-dx
482        r = convert_coord(!d.x_ch_size, !d.y_ch_size, /device, /to_normal)
483        dy = 3*r[1]*!p.charsize
484        y0 = !y.window[0]-dy
485      ENDELSE
486
487      arrow, x0, y0, x0+dx, y0, /norm, hsize = -.2, color = 0
488      IF NOT keyword_set(vectrefcharsize) THEN vectrefcharsize = !p.charsize
489      IF NOT keyword_set(vectrefcharthick) THEN vectrefcharthick = !p.charthick
490      xyouts, x0, y0, normelegende, /norm, align = 1, charsize = vectrefcharsize, charthick = vectrefcharthick, color = 0
491
492    endif
493  endif
494;
495  if keyword_set(key_performance) NE 0 THEN print, 'temps vecteur', systime(1)-tempsun
496;------------------------------------------------------------
497;------------------------------------------------------------
498  return
499END
Note: See TracBrowser for help on using the repository browser.