Changeset 114 for trunk/SRC/ToBeReviewed


Ignore:
Timestamp:
06/19/06 16:14:56 (18 years ago)
Author:
smasson
Message:

new compilation options (compile_opt idl2, strictarrsubs) in each routine

Location:
trunk/SRC/ToBeReviewed
Files:
218 edited

Legend:

Unmodified
Added
Removed
  • trunk/SRC/ToBeReviewed/CALCULS/curl.pro

    r25 r114  
    5858;------------------------------------------------------------ 
    5959FUNCTION curl, uu, vv 
     60; 
     61  compile_opt idl2, strictarrsubs 
     62; 
    6063@common 
    6164   tempsun = systime(1)         ; pour key_performance 
     
    142145;------------------------------------------------------------ 
    143146         if NOT keyword_set(key_periodic)  OR nx NE jpi then begin 
    144             psi(0, *, *) = !values.f_nan 
    145             psi(nx-1, *, *) = !values.f_nan 
     147            psi[0, *, *] = !values.f_nan 
     148            psi[nx-1, *, *] = !values.f_nan 
    146149         endif 
    147          psi(*, 0, *) = !values.f_nan 
    148          psi(*, ny-1, *) = !values.f_nan 
     150         psi[*, 0, *] = !values.f_nan 
     151         psi[*, ny-1, *] = !values.f_nan 
    149152; 
    150153         if n_elements(valmask) EQ 0 THEN valmask = 1e20 
     
    222225;------------------------------------------------------------ 
    223226         if NOT keyword_set(key_periodic) OR nx NE jpi then begin 
    224             psi(0, *, *) = !values.f_nan 
    225             psi(nx-1, *, *) = !values.f_nan 
     227            psi[0, *, *] = !values.f_nan 
     228            psi[nx-1, *, *] = !values.f_nan 
    226229         endif 
    227          psi(*, 0, *) = !values.f_nan 
    228          psi(*, ny-1, *) = !values.f_nan 
     230         psi[*, 0, *] = !values.f_nan 
     231         psi[*, ny-1, *] = !values.f_nan 
    229232         if n_elements(valmask) EQ 0 THEN valmask = 1e20 
    230233         terref =  where(tabf EQ 0) 
     
    295298;------------------------------------------------------------ 
    296299         if  NOT keyword_set(key_periodic) OR nx NE jpi then begin 
    297             psi(0, *) = !values.f_nan 
    298             psi(nx-1, *) = !values.f_nan 
     300            psi[0, *] = !values.f_nan 
     301            psi[nx-1, *] = !values.f_nan 
    299302         endif 
    300          psi(*, 0) = !values.f_nan 
    301          psi(*, ny-1) = !values.f_nan 
     303         psi[*, 0] = !values.f_nan 
     304         psi[*, ny-1] = !values.f_nan 
    302305; 
    303306         if n_elements(valmask) EQ 0 THEN valmask = 1e20 
  • trunk/SRC/ToBeReviewed/CALCULS/depth2floatlevel.pro

    r25 r114  
    4242;------------------------------------------------------------ 
    4343FUNCTION depth2floatlevel, tab, NOMASK = nomask 
     44; 
     45  compile_opt idl2, strictarrsubs 
     46; 
    4447   tempsun = systime(1)         ; pour key_performance 
    4548@common 
  • trunk/SRC/ToBeReviewed/CALCULS/depth2level.pro

    r25 r114  
    5050FUNCTION depth2level, tab, LOWER = lower, UPPER = upper, CLOSER = closer $ 
    5151                      , NOMASK = nomask, _extra = ex 
     52; 
     53  compile_opt idl2, strictarrsubs 
     54; 
    5255   tempsun = systime(1)         ; pour key_performance 
    5356@common 
  • trunk/SRC/ToBeReviewed/CALCULS/depth2mask.pro

    r25 r114  
    4747FUNCTION depth2mask, tab, _extra = ex 
    4848;------------------------------------------------------------ 
     49; 
     50  compile_opt idl2, strictarrsubs 
     51; 
    4952   tempsun = systime(1)         ; pour key_performance 
    5053@common 
  • trunk/SRC/ToBeReviewed/CALCULS/determ2.pro

    r25 r114  
    3333;- 
    3434FUNCTION determ2, a, b, c, d 
     35; 
     36  compile_opt idl2, strictarrsubs 
     37; 
    3538  CASE n_params() OF 
    3639    1:res = a[0, 0, *]*a[1, 1, *]-a[0, 1, *]*a[1, 0, *] 
  • trunk/SRC/ToBeReviewed/CALCULS/determ3.pro

    r25 r114  
    3838;- 
    3939FUNCTION determ3, in00, in01, in02, in10, in11, in12, in20, in21, in22 
     40; 
     41  compile_opt idl2, strictarrsubs 
     42; 
    4043  IF n_params() EQ 1 THEN BEGIN 
    4144    in00save = temporary(in00) 
  • trunk/SRC/ToBeReviewed/CALCULS/div.pro

    r25 r114  
    5454;------------------------------------------------------------ 
    5555FUNCTION div, uu, vv 
     56; 
     57  compile_opt idl2, strictarrsubs 
     58; 
    5659   tempsun = systime(1)         ; pour key_performance 
    5760@common 
     
    139142;------------------------------------------------------------ 
    140143         if  NOT keyword_set(key_periodic) OR nx NE jpi then begin 
    141             zdiv(0, *, *) = !values.f_nan 
    142             zdiv(nx-1, *, *) = !values.f_nan 
     144            zdiv[0, *, *] = !values.f_nan 
     145            zdiv[nx-1, *, *] = !values.f_nan 
    143146         endif 
    144          zdiv(*, 0, *) = !values.f_nan 
    145          zdiv(*, ny-1, *) = !values.f_nan 
     147         zdiv[*, 0, *] = !values.f_nan 
     148         zdiv[*, ny-1, *] = !values.f_nan 
    146149; 
    147150         zdiv = temporary(zdiv) 
     
    213216;------------------------------------------------------------ 
    214217         if  NOT keyword_set(key_periodic) OR nx NE jpi then begin 
    215             zdiv(0, *, *) = !values.f_nan 
    216             zdiv(nx-1, *, *) = !values.f_nan 
     218            zdiv[0, *, *] = !values.f_nan 
     219            zdiv[nx-1, *, *] = !values.f_nan 
    217220         endif 
    218          zdiv(*, 0, *) = !values.f_nan 
    219          zdiv(*, ny-1, *) = !values.f_nan 
     221         zdiv[*, 0, *] = !values.f_nan 
     222         zdiv[*, ny-1, *] = !values.f_nan 
    220223; 
    221224         if n_elements(valmask) EQ 0 THEN valmask = 1e20 
     
    286289;------------------------------------------------------------ 
    287290         if  NOT keyword_set(key_periodic) OR nx NE jpi then begin 
    288             zdiv(0, *) = !values.f_nan 
    289             zdiv(nx-1, *) = !values.f_nan 
     291            zdiv[0, *] = !values.f_nan 
     292            zdiv[nx-1, *] = !values.f_nan 
    290293         endif 
    291          zdiv(*, 0) = !values.f_nan 
    292          zdiv(*, ny-1) = !values.f_nan 
     294         zdiv[*, 0] = !values.f_nan 
     295         zdiv[*, ny-1] = !values.f_nan 
    293296; 
    294297         zdiv = temporary(zdiv)*1e6 
  • trunk/SRC/ToBeReviewed/CALCULS/floatlevel2depth.pro

    r25 r114  
    4040;------------------------------------------------------------ 
    4141FUNCTION floatlevel2depth, tab, NOMASK = nomask 
     42; 
     43  compile_opt idl2, strictarrsubs 
     44; 
    4245   tempsun = systime(1)         ; pour key_performance 
    4346@common 
  • trunk/SRC/ToBeReviewed/CALCULS/fsfzpt.pro

    r97 r114  
    1414;- 
    1515FUNCTION fsfzpt, pfs, pfp 
     16; 
     17  compile_opt idl2, strictarrsubs 
     18; 
    1619  RETURN, ( -0.0575 + 1.710523e-3 * sqrt(pfs) - 2.154996e-4 * pfs  ) * pfs - 7.53e-4 * pfp 
    1720END 
  • trunk/SRC/ToBeReviewed/CALCULS/grad.pro

    r25 r114  
    3232;------------------------------------------------------------ 
    3333FUNCTION grad, field, direc 
     34; 
     35  compile_opt idl2, strictarrsubs 
     36; 
    3437@common 
    3538;------------------------------------------------------------ 
  • trunk/SRC/ToBeReviewed/CALCULS/grossemoyenne.pro

    r25 r114  
    113113                        , _extra = ex 
    114114;--------------------------------------------------------- 
     115; 
     116  compile_opt idl2, strictarrsubs 
     117; 
    115118@cm_4mesh 
    116119@cm_4data 
     
    613616  terre = where(divi EQ 0) 
    614617  IF terre[0] NE -1 THEN BEGIN  
    615     res(temporary(terre)) = 1e+20 
     618    res[temporary(terre)] = 1e+20 
    616619  ENDIF  
    617620;------------------------------------------------------------ 
  • trunk/SRC/ToBeReviewed/CALCULS/hdyn.pro

    r25 r114  
    6969;------------------------------------------------------------ 
    7070FUNCTION hdyn,  tabsn, tabtn, TREF = tref,  SREF = sref, PROFREF = profref, LEVEL = level, GILL = gill, SURFACE_LEVEL = surface_level 
     71; 
     72  compile_opt idl2, strictarrsubs 
     73; 
    7174   tempsun = systime(1)         ; pour key_performance 
    7275@common 
  • trunk/SRC/ToBeReviewed/CALCULS/level2depth.pro

    r25 r114  
    3838;------------------------------------------------------------ 
    3939FUNCTION level2depth, tab, NOMASK = nomask 
     40; 
     41  compile_opt idl2, strictarrsubs 
     42; 
    4043   tempsun = systime(1)         ; pour key_performance 
    4144@common 
  • trunk/SRC/ToBeReviewed/CALCULS/level2index.pro

    r25 r114  
    4343; level etant donne, pour chaque points de level on connait i, j et k, 
    4444; on peut donc calculer l''indice. 
     45; 
     46  compile_opt idl2, strictarrsubs 
     47; 
    4548   taille = size(level) 
    4649   nx = taille[1] 
  • trunk/SRC/ToBeReviewed/CALCULS/level2mask.pro

    r25 r114  
    4242FUNCTION level2mask, tab 
    4343;------------------------------------------------------------ 
     44; 
     45  compile_opt idl2, strictarrsubs 
     46; 
    4447   tempsun = systime(1)         ; pour key_performance 
    4548@common 
  • trunk/SRC/ToBeReviewed/CALCULS/moyenne.pro

    r25 r114  
    9595                  , _extra = ex 
    9696;--------------------------------------------------------- 
     97; 
     98  compile_opt idl2, strictarrsubs 
     99; 
    97100@cm_4mesh 
    98101@cm_4data 
     
    575578  terre = where(divi EQ 0) 
    576579  IF terre[0] NE -1 THEN BEGIN 
    577     res(terre) = 1e+20 
     580    res[terre] = 1e+20 
    578581  ENDIF   
    579582;------------------------------------------------------------ 
  • trunk/SRC/ToBeReviewed/CALCULS/norme.pro

    r25 r114  
    7070FUNCTION norme, composanteu, composantev, BOXZOOM = boxzoom, DIREC = direc, _extra = ex 
    7171;--------------------------------------------------------- 
     72; 
     73  compile_opt idl2, strictarrsubs 
     74; 
    7275@cm_4mesh 
    7376@cm_4data 
     
    197200; construction de u et v aux pts T 
    198201;----------------------------------------------------------- 
    199          a=u(0,*,*) 
     202         a=u[0,*,*] 
    200203         u=(u+shift(u,1,0,0))/2. 
    201          if NOT keyword_set(key_periodic) OR nx NE jpi then u(0,*,*)=a 
    202          a=v(*,0,*) 
     204         if NOT keyword_set(key_periodic) OR nx NE jpi then u[0,*,*]=a 
     205         a=v[*,0,*] 
    203206         v=(v+shift(v,0,1,0))/2. 
    204          if NOT keyword_set(key_periodic) OR nx NE jpi then v(*,0,*)=a 
     207         if NOT keyword_set(key_periodic) OR nx NE jpi then v[*,0,*]=a 
    205208;---------------------------------------------------------------------------- 
    206209; attribution du mask et des tableau de longitude et latitude 
     
    215218         if landv[0] NE -1 then v[landv] = 0 
    216219         res=sqrt(u^2+v^2) 
    217          if NOT keyword_set(key_periodic) OR nx NE jpi then res(0,*, *)=!values.f_nan 
    218          res(*,0, *)=!values.f_nan 
     220         if NOT keyword_set(key_periodic) OR nx NE jpi then res[0,*, *]=!values.f_nan 
     221         res[*,0, *]=!values.f_nan 
    219222         mask = where(mask eq 0) 
    220          IF mask[0] NE -1 THEN res(mask) = valmask 
     223         IF mask[0] NE -1 THEN res[mask] = valmask 
    221224; moyennes en tous genres 
    222225         domdef, (glamt[indice2d])[0, 0], (glamu[indice2d])[nx-1, 0],(gphit[indice2d])[0, 0], (gphiv[indice2d])[0, ny-1], vert1, vert2, /meme 
     
    257260; construction de u et v aux pts T 
    258261;----------------------------------------------------------- 
    259          a=u(0,*,*) 
     262         a=u[0,*,*] 
    260263         u=(u+shift(u,1,0,0))/2. 
    261          if NOT keyword_set(key_periodic) OR nx NE jpi then u(0,*,*)=a 
    262          a=v(*,0,*) 
     264         if NOT keyword_set(key_periodic) OR nx NE jpi then u[0,*,*]=a 
     265         a=v[*,0,*] 
    263266         v=(v+shift(v,0,1,0))/2. 
    264          if NOT keyword_set(key_periodic) OR nx NE jpi then v(*,0,*)=a 
     267         if NOT keyword_set(key_periodic) OR nx NE jpi then v[*,0,*]=a 
    265268;---------------------------------------------------------------------------- 
    266269; attribution du mask et des tableau de longitude et latitude 
     
    280283         if landv[0] NE -1 then v[landv] = 0 
    281284         res=sqrt(u^2+v^2) 
    282          if NOT keyword_set(key_periodic) OR nx NE jpi then res(0,*, *)=!values.f_nan 
    283          res(*,0, *)=!values.f_nan 
     285         if NOT keyword_set(key_periodic) OR nx NE jpi then res[0,*, *]=!values.f_nan 
     286         res[*,0, *]=!values.f_nan 
    284287         mask = where(mask eq 0) 
    285288         IF mask[0] NE -1 THEN BEGIN  
     
    288291            mask = (temporary(mask))[*]#replicate(1, jpt) 
    289292            mask =temporary(mask[*]) + temporary(coeftps[*]) 
    290             res(temporary(mask)) = valmask 
     293            res[temporary(mask)] = valmask 
    291294         ENDIF 
    292295; moyennes en tous genres 
     
    344347; construction de u et v aux pts T 
    345348;----------------------------------------------------------- 
    346          a=u(0,*,*,*) 
     349         a=u[0,*,*,*] 
    347350         u=(u+shift(u,1,0,0,0))/2. 
    348          if NOT keyword_set(key_periodic) OR nx NE jpi then u(0,*,*,*)=a 
    349          a=v(*,0,*,*) 
     351         if NOT keyword_set(key_periodic) OR nx NE jpi then u[0,*,*,*]=a 
     352         a=v[*,0,*,*] 
    350353         v=(v+shift(v,0,1,0,0))/2. 
    351          if NOT keyword_set(key_periodic) OR nx NE jpi then v(*,0,*,*)=a 
     354         if NOT keyword_set(key_periodic) OR nx NE jpi then v[*,0,*,*]=a 
    352355;---------------------------------------------------------------------------- 
    353356; attribution du mask et des tableau de longitude et latitude 
     
    362365         if landv[0] NE -1 then v[landv] = 0 
    363366         res=sqrt(u^2+v^2) 
    364          if NOT keyword_set(key_periodic) OR nx NE jpi then res(0,*, *, *)=!values.f_nan 
    365          res(*,0, *, *)=!values.f_nan 
     367         if NOT keyword_set(key_periodic) OR nx NE jpi then res[0,*, *, *]=!values.f_nan 
     368         res[*,0, *, *]=!values.f_nan 
    366369         mask = where(mask eq 0) 
    367370         IF mask[0] NE -1 THEN BEGIN  
     
    370373            mask = (temporary(mask))[*]#replicate(1, jpt) 
    371374            mask =temporary(mask[*]) + temporary(coeftps[*]) 
    372             res(temporary(mask)) = valmask 
     375            res[temporary(mask)] = valmask 
    373376         ENDIF 
    374377; moyennes en tous genres 
     
    416419; construction de u et v aux pts T 
    417420;----------------------------------------------------------- 
    418          a=u(0,*) 
     421         a=u[0,*] 
    419422         u=(u+shift(u,1,0))/2. 
    420          if NOT keyword_set(key_periodic) OR nx NE jpi then u(0,*)=a 
    421          a=v(*,0) 
     423         if NOT keyword_set(key_periodic) OR nx NE jpi then u[0,*]=a 
     424         a=v[*,0] 
    422425         v=(v+shift(v,0,1))/2. 
    423          if NOT keyword_set(key_periodic) OR nx NE jpi then v(*,0)=a 
     426         if NOT keyword_set(key_periodic) OR nx NE jpi then v[*,0]=a 
    424427;---------------------------------------------------------------------------- 
    425428; attribution du mask et des tableau de longitude et latitude 
     
    439442         if landv[0] NE -1 then v[landv] = 0 
    440443         res=sqrt(u^2+v^2) 
    441          if NOT keyword_set(key_periodic) OR nx NE jpi then res(0,*)=!values.f_nan 
    442          res(*,0)=!values.f_nan 
     444         if NOT keyword_set(key_periodic) OR nx NE jpi then res[0,*]=!values.f_nan 
     445         res[*,0]=!values.f_nan 
    443446         mask = where(mask eq 0) 
    444          IF mask[0] NE -1 THEN res(mask) = valmask 
     447         IF mask[0] NE -1 THEN res[mask] = valmask 
    445448; moyennes en tous genres 
    446449         domdef, (glamt[indice2d])[0, 0], (glamu[indice2d])[nx-1, 0],(gphit[indice2d])[0, 0], (gphiv[indice2d])[0, ny-1], vert1, vert2, /meme 
  • trunk/SRC/ToBeReviewed/CALCULS/projectondepth.pro

    r25 r114  
    5353;------------------------------------------------------------ 
    5454FUNCTION projectondepth, arrayin, depthin 
     55; 
     56  compile_opt idl2, strictarrsubs 
     57; 
    5558   tempsun = systime(1)         ; pour key_performance 
    5659@common 
  • trunk/SRC/ToBeReviewed/CALCULS/remplit.pro

    r97 r114  
    1717;- 
    1818FUNCTION remplit, zinput, NAN = nan, NITER = niter, BASIQUE = basique, mask = mask, FILLXDIR = fillxdir, FILLYDIR = fillydir, FILLVAL = fillval, _extra = ex 
     19; 
     20  compile_opt idl2, strictarrsubs 
     21; 
    1922@common 
    2023  tempsun = systime(1)          ; pour key_performance 
  • trunk/SRC/ToBeReviewed/CALCULS/rhon.pro

    r97 r114  
    99;- 
    1010FUNCTION rhon, sn, tn, INSITU = insitu, SIGMA_N = sigma_n 
     11; 
     12  compile_opt idl2, strictarrsubs 
     13; 
    1114@common 
    1215   tempsun = systime(1)         ; pour key_performance 
     
    7780         END  
    7881      endcase 
    79       if n_elements(sigma_n) NE 0 then zh = 1000.*sigma_n ELSE zh = gdept(jk) 
     82      if n_elements(sigma_n) NE 0 then zh = 1000.*sigma_n ELSE zh = gdept[jk] 
    8083; ...   square root salinity 
    8184      zsr= sqrt(abs(zs)) 
     
    9093      case taille[0] of 
    9194         0: zrhop    = (zr4*zs + zr3*zsr + zr2)*zs + zr1 
    92          1: zrhop(jk)= (zr4*zs + zr3*zsr + zr2)*zs + zr1 
     95         1: zrhop[jk]= (zr4*zs + zr3*zsr + zr2)*zs + zr1 
    9396         2:BEGIN  
    9497            if jpt EQ 1 then zrhop = (zr4*zs + zr3*zsr + zr2)*zs + zr1 $ 
    95             ELSE zrhop(jk, *)= (zr4*zs + zr3*zsr + zr2)*zs + zr1 
     98            ELSE zrhop[jk, *]= (zr4*zs + zr3*zsr + zr2)*zs + zr1 
    9699         END 
    97100         3:BEGIN  
    98             if jpt EQ 1 then zrhop(*, *,jk)= (zr4*zs + zr3*zsr + zr2)*zs + zr1 $ 
     101            if jpt EQ 1 then zrhop[*, *,jk]= (zr4*zs + zr3*zsr + zr2)*zs + zr1 $ 
    99102             ELSE zrhop = (zr4*zs + zr3*zsr + zr2)*zs + zr1 
    100103         END 
    101          4: zrhop(*, *,jk, *)= (zr4*zs + zr3*zsr + zr2)*zs + zr1 
     104         4: zrhop[*, *,jk, *]= (zr4*zs + zr3*zsr + zr2)*zs + zr1 
    102105      endcase 
    103106 
     
    121124         case taille[0] of 
    122125            0: zrhop = zrhop / (1.0-zh/(zk0-zh*(za-zh*zb))) 
    123             1: zrhop(jk) = zrhop(jk) / (1.0-zh/(zk0-zh*(za-zh*zb))) 
     126            1: zrhop[jk] = zrhop[jk] / (1.0-zh/(zk0-zh*(za-zh*zb))) 
    124127            2:BEGIN  
    125128               if jpt EQ 1 then zrhop = zrhop / (1.0-zh/(zk0-zh*(za-zh*zb))) $ 
    126                ELSE zrhop(jk, *) = zrhop(jk, *) / (1.0-zh/(zk0-zh*(za-zh*zb))) 
     129               ELSE zrhop[jk, *] = zrhop[jk, *] / (1.0-zh/(zk0-zh*(za-zh*zb))) 
    127130            END 
    128131            3:BEGIN  
    129                if jpt EQ 1 then zrhop(*, *,jk) = zrhop(*, *,jk) / (1.0-zh/(zk0-zh*(za-zh*zb))) $ 
     132               if jpt EQ 1 then zrhop[*, *,jk] = zrhop[*, *,jk] / (1.0-zh/(zk0-zh*(za-zh*zb))) $ 
    130133               ELSE zrhop = zrhop / (1.0-zh/(zk0-zh*(za-zh*zb))) 
    131134            END 
    132             4: zrhop(*, *,jk, *) = zrhop(*, *,jk, *) / (1.0-zh/(zk0-zh*(za-zh*zb))) 
     135            4: zrhop[*, *,jk, *] = zrhop[*, *,jk, *] / (1.0-zh/(zk0-zh*(za-zh*zb))) 
    133136         endcase 
    134137          
  • trunk/SRC/ToBeReviewed/CALENDRIER/def_month.pro

    r9 r114  
    22; 
    33; translate month number in string 
     4; 
     5; 
     6  compile_opt idl2, strictarrsubs 
    47; 
    58   IF strpos(date, '_') GT -1 THEN date = strmid(date, 0, strpos(date, '_')) 
  • trunk/SRC/ToBeReviewed/COULEURS/color24.pro

    r19 r114  
    4646 
    4747FUNCTION COLOR24, number 
     48; 
     49  compile_opt idl2, strictarrsubs 
     50; 
    4851 
    4952   ; This FUNCTION accepts a [red, green, blue] triple that 
     
    6972num24bit = 0L 
    7073 
    71 FOR j=0,2 DO num24bit = num24bit + ((number(j) MOD 16) * base16(0,j)) + $ 
    72    (Fix(number(j)/16) * base16(1,j)) 
     74FOR j=0,2 DO num24bit = num24bit + ((number[j] MOD 16) * base16[0,j]) + $ 
     75   (Fix(number[j]/16) * base16[1,j]) 
    7376    
    7477RETURN, num24bit 
  • trunk/SRC/ToBeReviewed/COULEURS/colorbar.pro

    r19 r114  
    121121              PSCOLOR=pscolor, CB_TITLE=cb_title, VERTICAL=vertical, TOP=top, RIGHT=right, CB_LOG = CB_log, _extra = ex 
    122122                                ; Is the PostScript device selected? 
     123; 
     124  compile_opt idl2, strictarrsubs 
     125; 
    123126 
    124127   postScriptDevice = (!D.NAME EQ 'PS') 
     
    207210                                ; Get starting locations in DEVICE coordinates. 
    208211 
    209    xstart = position(0) * !D.X_VSIZE 
    210    ystart = position(1) * !D.Y_VSIZE 
     212   xstart = position[0] * !D.X_VSIZE 
     213   ystart = position[1] * !D.Y_VSIZE 
    211214 
    212215                                ; Get the size of the bar in DEVICE coordinates. 
    213216 
    214    xsize = (position(2) - position(0)) * !D.X_VSIZE 
    215    ysize = (position(3) - position(1)) * !D.Y_VSIZE 
     217   xsize = (position[2] - position[0]) * !D.X_VSIZE 
     218   ysize = (position[3] - position[1]) * !D.Y_VSIZE 
    216219 
    217220                                ; For PostScript output only, draw the annotation in !P.COLOR 
  • trunk/SRC/ToBeReviewed/COULEURS/getcolor.pro

    r19 r114  
    181181 
    182182FUNCTION COLOR24, number 
     183; 
     184  compile_opt idl2, strictarrsubs 
     185; 
    183186 
    184187   ; This FUNCTION accepts a [red, green, blue] triple that 
     
    204207num24bit = 0L 
    205208 
    206 FOR j=0,2 DO num24bit = num24bit + ((number(j) MOD 16) * base16(0,j)) + $ 
    207    (Fix(number(j)/16) * base16(1,j)) 
     209FOR j=0,2 DO num24bit = num24bit + ((number[j] MOD 16) * base16[0,j]) + $ 
     210   (Fix(number[j]/16) * base16[1,j]) 
    208211 
    209212RETURN, num24bit 
     
    214217FUNCTION GETCOLOR, thisColor, index, TRUE=truecolor, $ 
    215218   NAMES=colornames, LOAD=load, START=start 
     219; 
     220  compile_opt idl2, strictarrsubs 
     221; 
    216222 
    217223   ; Set up the color vectors. 
     
    315321 
    316322varInfo = SIZE(thisColor) 
    317 IF varInfo(varInfo(0) + 1) NE 7 THEN $ 
     323IF varInfo[varInfo[0] + 1] NE 7 THEN $ 
    318324   MESSAGE, 'The color name must be a string.' 
    319325thisColor = STRUPCASE(thisColor) 
     
    326332   ; set the index to a YELLOW color, and continue. 
    327333 
    328 IF colorIndex(0) LT 0 THEN BEGIN 
     334IF colorIndex[0] LT 0 THEN BEGIN 
    329335   MESSAGE, "Can't find color. Returning YELLOW.", /INFORMATIONAL 
    330336   colorIndex = 3 
     
    333339   ; Get the color triple. 
    334340 
    335 r = rvalue(colorIndex) 
    336 g = gvalue(colorIndex) 
    337 b = bvalue(colorIndex) 
     341r = rvalue[colorIndex] 
     342g = gvalue[colorIndex] 
     343b = bvalue[colorIndex] 
    338344returnColor = REFORM([r, g, b], 1, 3) 
    339345 
  • trunk/SRC/ToBeReviewed/COULEURS/lct.pro

    r19 r114  
    3535;------------------------------------------------------------ 
    3636PRO lct, numero, GET_NAME = get_name, LIGHTNESS = Lightness, _EXTRA = ex 
     37; 
     38  compile_opt idl2, strictarrsubs 
     39; 
    3740@common 
    3841; le mot cle file est passe par l''intermediere de EXTRA? 
  • trunk/SRC/ToBeReviewed/COULEURS/newpalette.pro

    r19 r114  
    4040; le mot cle file est passe par l''intermediere de EXTRA? 
    4141; definition du mon du fichier qui contient les palettes de couleur 
     42; 
     43  compile_opt idl2, strictarrsubs 
     44; 
    4245   if n_elements(ex) NE 0 then BEGIN  
    4346      if (where(tag_names(ex) EQ 'FILE'))[0] NE -1 then nompal=ex.FILE ELSE nompal='palette.tbl' 
  • trunk/SRC/ToBeReviewed/COULEURS/palit.pro

    r97 r114  
    88;- 
    99PRO palit, coef, red, green, blue 
     10; 
     11  compile_opt idl2, strictarrsubs 
     12; 
    1013   IF n_elements(coef) EQ 0 THEN coef = 0.5 
    1114   IF n_elements(red) EQ 0 THEN tvlct, red, green, blue, /get 
  • trunk/SRC/ToBeReviewed/COULEURS/xlct.pro

    r19 r114  
    66PRO XLCT_PSAVE                  ;Save/Restore our plotting state. 
    77;  Swaps our state with the current state each time its called. 
     8; 
     9  compile_opt idl2, strictarrsubs 
     10; 
    811 
    912COMMON xlct_com, r0, g0, b0, tfun, state, filename, cps, psave, pnt, $ 
     
    2528 
    2629pro xlct_alert_caller 
     30; 
     31  compile_opt idl2, strictarrsubs 
     32; 
    2733COMMON xlct_com, r0, g0, b0, tfun, state, filename, cps, psave, pnt, $ 
    2834        top, bot, silent, chop, lock, g_lbl, vbot, vtop, g_slider, $ 
     
    5157; Redraw the ramp image. 
    5258PRO xlct_show 
     59; 
     60  compile_opt idl2, strictarrsubs 
     61; 
    5362COMMON xlct_com, r0, g0, b0, tfun, state, filename, cps, psave, pnt, $ 
    5463        top, bot, silent, chop, lock, g_lbl, vbot, vtop, g_slider, $ 
     
    6877 
    6978PRO xlct_draw_cps, i, c 
     79; 
     80  compile_opt idl2, strictarrsubs 
     81; 
    7082COMMON colors, r_orig, g_orig, b_orig, r_curr, g_curr, b_curr 
    7183COMMON xlct_com, r0, g0, b0, tfun, state, filename, cps, psave, pnt, $ 
     
    8698 
    8799PRO xlct_transfer, UPDATE=update 
     100; 
     101  compile_opt idl2, strictarrsubs 
     102; 
    88103COMMON colors, r_orig, g_orig, b_orig, r_curr, g_curr, b_curr 
    89104COMMON xlct_com, r0, g0, b0, tfun, state, filename, cps, psave, pnt, $ 
     
    115130 
    116131PRO xlct_event, event 
     132; 
     133  compile_opt idl2, strictarrsubs 
     134; 
    117135COMMON colors, r_orig, g_orig, b_orig, r_curr, g_curr, b_curr 
    118136COMMON xlct_com, r0, g0, b0, tfun, state, filename, cps, psave, pnt, $ 
     
    430448          MODAL=modal, BLOCK=block, UPDATECALLBACK=updt_cb_name, $ 
    431449          UPDATECBDATA=updt_cb_data 
     450; 
     451  compile_opt idl2, strictarrsubs 
     452; 
    432453 
    433454   COMMON colors, r_orig, g_orig, b_orig, r_curr, g_curr, b_curr 
  • trunk/SRC/ToBeReviewed/COULEURS/xpal.pro

    r19 r114  
    157157; color maps and set !P appropriately. Returns 1 if the colors changed, 
    158158; 0 otherwise. 
     159; 
     160  compile_opt idl2, strictarrsubs 
     161; 
    159162  common xp_com, xpw, state 
    160163 
     
    176179 
    177180pro XP_ALERT_CALLER 
     181; 
     182  compile_opt idl2, strictarrsubs 
     183; 
    178184 
    179185  common xp_com, xpw, state 
     
    200206  ; For visuals with static colormaps, update the graphics 
    201207  ; after a change by XLOADCT. 
     208; 
     209  compile_opt idl2, strictarrsubs 
     210; 
    202211  if ((COLORMAP_APPLICABLE(redrawRequired) GT 0) and $ 
    203212        (redrawRequired GT 0)) then begin 
     
    208217 
    209218pro XP_REDRAW 
     219; 
     220  compile_opt idl2, strictarrsubs 
     221; 
    210222 
    211223  common xp_com, xpw, state 
     
    227239;       - 'G': Draw the data part of the Green plot 
    228240;       - 'B': Draw the data part of the Blue plot 
     241; 
     242  compile_opt idl2, strictarrsubs 
     243; 
    229244 
    230245  common xp_com, xpw, state 
     
    303318;       - 'G': ... 
    304319;       - 'B': ... 
     320; 
     321  compile_opt idl2, strictarrsubs 
     322; 
    305323  common xp_com, xpw, state 
    306324  common colors, r_orig, g_orig, b_orig, r_curr, g_curr, b_curr 
     
    348366 
    349367pro XP_BUTTON_EVENT, event 
     368; 
     369  compile_opt idl2, strictarrsubs 
     370; 
    350371 
    351372   common xp_com, xpw, state 
     
    461482 
    462483PRO xp_button_event_event, ev 
     484; 
     485  compile_opt idl2, strictarrsubs 
     486; 
    463487COMMON basecommon,  bas212, bas222,  bas232 
    464488  WIDGET_CONTROL, ev.id,  GET_UVALUE = uval 
     
    485509 
    486510pro XP_EVENT, event 
     511; 
     512  compile_opt idl2, strictarrsubs 
     513; 
    487514 
    488515   common xp_com, xpw, state 
     
    532559pro XPAL, group=group, BLOCK=block, UPDATECALLBACK=updt_cb_name, $ 
    533560        UPDATECBDATA=updt_cb_data 
     561; 
     562  compile_opt idl2, strictarrsubs 
     563; 
    534564 
    535565 
  • trunk/SRC/ToBeReviewed/GRILLE/changegrid.pro

    r69 r114  
    11function changegrid, newgrid 
     2; 
     3; 
     4  compile_opt idl2, strictarrsubs 
    25; 
    36@cm_4mesh 
  • trunk/SRC/ToBeReviewed/GRILLE/cmpgrid.pro

    r74 r114  
    11FUNCTION cmpgrid, newgrid 
     2; 
     3; 
     4  compile_opt idl2, strictarrsubs 
    25; 
    36@common 
  • trunk/SRC/ToBeReviewed/GRILLE/decoupeterre.pro

    r14 r114  
    5050PRO decoupeterre, mask, glam, gphi, gdep, TYPE = type, TRI = tri, INDICEZOOM = indicezoom, COINMONTE = coinmonte, COINDESCEND = coindescend, WDEPTH = wdepth, REALSECTION = realsection, USETRI = usetri, _extra = ex 
    5151;--------------------------------------------------------- 
     52; 
     53  compile_opt idl2, strictarrsubs 
     54; 
    5255@cm_4mesh 
    5356@cm_4data 
  • trunk/SRC/ToBeReviewed/GRILLE/domdef.pro

    r96 r114  
    105105;------------------------------------------------------------ 
    106106; include commons 
     107; 
     108  compile_opt idl2, strictarrsubs 
     109; 
    107110@cm_4mesh 
    108111  IF NOT keyword_set(key_forgetold) THEN BEGIN 
  • trunk/SRC/ToBeReviewed/GRILLE/f2v.pro

    r13 r114  
    3939FUNCTION f2v, temp 
    4040;--------------------------------------------------------- 
     41; 
     42  compile_opt idl2, strictarrsubs 
     43; 
    4144@cm_4mesh 
    4245@cm_4data 
  • trunk/SRC/ToBeReviewed/GRILLE/fmask.pro

    r13 r114  
    2626FUNCTION fmask 
    2727;--------------------------------------------------------- 
     28; 
     29  compile_opt idl2, strictarrsubs 
     30; 
    2831@cm_4mesh 
    2932  IF NOT keyword_set(key_forgetold) THEN BEGIN 
  • trunk/SRC/ToBeReviewed/GRILLE/grille.pro

    r69 r114  
    6464;------------------------------------------------------------ 
    6565; include commons 
     66; 
     67  compile_opt idl2, strictarrsubs 
     68; 
    6669@cm_4mesh 
    6770@cm_4data 
  • trunk/SRC/ToBeReviewed/GRILLE/t2v.pro

    r13 r114  
    3939FUNCTION t2v, temp 
    4040;--------------------------------------------------------- 
     41; 
     42  compile_opt idl2, strictarrsubs 
     43; 
    4144@cm_4mesh 
    4245@cm_4data 
  • trunk/SRC/ToBeReviewed/GRILLE/tracegrille.pro

    r13 r114  
    5959                 , _extra = extra 
    6060;--------------------------------------------------------- 
     61; 
     62  compile_opt idl2, strictarrsubs 
     63; 
    6164@cm_4mesh 
    6265@cm_4data 
  • trunk/SRC/ToBeReviewed/GRILLE/u2t.pro

    r13 r114  
    3939FUNCTION u2t, temp 
    4040;--------------------------------------------------------- 
     41; 
     42  compile_opt idl2, strictarrsubs 
     43; 
    4144@cm_4mesh 
    4245@cm_4data 
  • trunk/SRC/ToBeReviewed/GRILLE/umask.pro

    r13 r114  
    4040FUNCTION umask 
    4141;--------------------------------------------------------- 
     42; 
     43  compile_opt idl2, strictarrsubs 
     44; 
    4245@cm_4mesh 
    4346  IF NOT keyword_set(key_forgetold) THEN BEGIN 
  • trunk/SRC/ToBeReviewed/GRILLE/v2t.pro

    r13 r114  
    3939FUNCTION v2t, temp 
    4040;--------------------------------------------------------- 
     41; 
     42  compile_opt idl2, strictarrsubs 
     43; 
    4144@cm_4mesh 
    4245@cm_4data 
  • trunk/SRC/ToBeReviewed/GRILLE/vmask.pro

    r13 r114  
    2626;------------------------------------------------------------ 
    2727FUNCTION vmask 
     28; 
     29  compile_opt idl2, strictarrsubs 
     30; 
    2831@common 
    2932  tempsun = systime(1)          ; pour key_performance 
  • trunk/SRC/ToBeReviewed/HOPE/.idlwave_catalog

    r76 r114  
    99   ("computehopegrid" pro nil (lib "computehopegrid.pro" nil "saxo") "%s, xaxis, yaxis, zaxis, linetype" (nil ("FIRSTS") ("FORTHEMASK") ("LASTS") ("PTTYPE") ("WPOINT"))) 
    1010   ("createhopestruct" fun nil (lib "createhopestruct.pro" nil "saxo") "Result = %s(event)" (nil)) 
    11    ("testwid_event" pro nil (lib "cw_selectinterval.pro" nil "saxo") "%s, event" (nil)) 
    12    ("testwid" pro nil (lib "cw_selectinterval.pro" nil "saxo") "%s" (nil ("_extra"))) 
    1311   ("cw_selectinterval_get_value" fun nil (lib "cw_selectinterval.pro" nil "saxo") "Result = %s(id)" (nil)) 
    1412   ("cw_selectinterval_event" fun nil (lib "cw_selectinterval.pro" nil "saxo") "Result = %s(event)" (nil)) 
  • trunk/SRC/ToBeReviewed/HOPE/completetype.pro

    r53 r114  
    11 
    22function completetype, typein 
     3; 
     4  compile_opt idl2, strictarrsubs 
     5; 
    36   type=typein 
    47   case type of 
  • trunk/SRC/ToBeReviewed/HOPE/computehopegrid.pro

    r53 r114  
    3333PRO computehopegrid, xaxis, yaxis, zaxis, linetype, FORTHEMASK = forthemask, WPOINT = wpoint, FIRSTS = firsts, LASTS = lasts, PTTYPE = pttype 
    3434;--------------------------------------------------------- 
     35; 
     36  compile_opt idl2, strictarrsubs 
     37; 
    3538@cm_4mesh 
    3639@cm_4data 
  • trunk/SRC/ToBeReviewed/HOPE/createhopestruct.pro

    r53 r114  
    11FUNCTION createhopestruct, event 
     2; 
     3  compile_opt idl2, strictarrsubs 
     4; 
    25   widget_control, event.top, get_uvalue=top_uvalue 
    36; find the selected variable 
  • trunk/SRC/ToBeReviewed/HOPE/cw_selectinterval.pro

    r53 r114  
    11 
    2 PRO testwid_event, event 
    3    widget_control, event.id, get_uvalue=uval 
    4    if n_elements(uval) EQ 0 then return 
    5    case uval of 
    6       'done':widget_control, event.top, /destroy 
    7       'get':BEGIN 
    8          id = widget_info(event.top,find_by_uname = 'discret') 
    9          widget_control, id, get_value = value1 
    10          help, value1 
    11          print, 'value1', value1 
    12          id = widget_info(event.top,find_by_uname = 'continus') 
    13          widget_control, id, get_value = value2 
    14          help, value2 
    15          print, 'value2', value2 
    16       END 
    17       ELSE: 
    18    endcase 
    19    return 
    20 end 
    21 PRO testwid, _extra = ex 
    22    base=widget_base(/COLUMN) 
    23    nothing = widget_label(base, value = 'beginning of the test') 
    24 ; 
    25    nothing = cw_selectinterval(base, 10+indgen(5), _extra = ex, uname = 'discret', uvalue = 'discret') 
    26    print, nothing 
    27    nothing = cw_selectinterval(base, indgen(20), _extra = ex, uname = 'continus', uvalue = 'continus') 
    28    print, nothing 
    29 ; 
    30    nothing = widget_button(base, value = 'get', uvalue = 'get') 
    31    nothing = widget_button(base, value = 'done', uvalue = 'done') 
    32    widget_control, base, /REALIZE 
    33    xmanager,'testwid', base, /no_block 
    34    return 
    35 end 
     2; PRO testwid_event, event 
     3; ; 
     4;   compile_opt idl2, strictarrsubs 
     5; ; 
     6;    widget_control, event.id, get_uvalue=uval 
     7;    if n_elements(uval) EQ 0 then return 
     8;    case uval of 
     9;       'done':widget_control, event.top, /destroy 
     10;       'get':BEGIN 
     11;          id = widget_info(event.top,find_by_uname = 'discret') 
     12;          widget_control, id, get_value = value1 
     13;          help, value1 
     14;          print, 'value1', value1 
     15;          id = widget_info(event.top,find_by_uname = 'continus') 
     16;          widget_control, id, get_value = value2 
     17;          help, value2 
     18;          print, 'value2', value2 
     19;       END 
     20;       ELSE: 
     21;    endcase 
     22;    return 
     23; end 
     24; PRO testwid, _extra = ex 
     25; ; 
     26;   compile_opt idl2, strictarrsubs 
     27; ; 
     28;    base=widget_base(/COLUMN) 
     29;    nothing = widget_label(base, value = 'beginning of the test') 
     30; ; 
     31;    nothing = cw_selectinterval(base, 10+indgen(5), _extra = ex, uname = 'discret', uvalue = 'discret') 
     32;    print, nothing 
     33;    nothing = cw_selectinterval(base, indgen(20), _extra = ex, uname = 'continus', uvalue = 'continus') 
     34;    print, nothing 
     35; ; 
     36;    nothing = widget_button(base, value = 'get', uvalue = 'get') 
     37;    nothing = widget_button(base, value = 'done', uvalue = 'done') 
     38;    widget_control, base, /REALIZE 
     39;    xmanager,'testwid', base, /no_block 
     40;    return 
     41; end 
    3642;-------------------------------------------------------------------------- 
    3743;-------------------------------------------------------------------------- 
    3844;-------------------------------------------------------------------------- 
    3945function cw_selectinterval_get_value, id 
     46; 
     47  compile_opt idl2, strictarrsubs 
     48; 
    4049   bgroupid=widget_info(id, find_by_uname = 'bgroup') 
    4150; the widget is a set of button 
     
    6069;-------------------------------------------------------------------------- 
    6170function cw_selectinterval_event, event 
     71; 
     72  compile_opt idl2, strictarrsubs 
     73; 
    6274   widget_control, event.id, get_uvalue=uval 
    6375   case uval.name of 
     
    7789;-------------------------------------------------------------------------- 
    7890function cw_selectinterval, parent, vecteur, _extra = ex 
     91; 
     92  compile_opt idl2, strictarrsubs 
     93; 
    7994 
    8095   base = widget_base(parent $ 
  • trunk/SRC/ToBeReviewed/HOPE/domainpart.pro

    r53 r114  
    11pro domainpart, top_uvalue, basedomain, selected, DESTROY = destroy 
     2; 
     3  compile_opt idl2, strictarrsubs 
     4; 
    25 
    36   if keyword_set(destroy) then BEGIN 
  • trunk/SRC/ToBeReviewed/HOPE/findlineandpointtype.pro

    r53 r114  
    2222;                 lonThighodd:modulo = " " ; 
    2323; } 
     24; 
     25  compile_opt idl2, strictarrsubs 
     26; 
    2427   jpi = n_elements(xaxis) 
    2528   jpj = n_elements(yaxis) 
  • trunk/SRC/ToBeReviewed/HOPE/read_hope.pro

    r53 r114  
    111111; 
    112112pro read_hope_event, event 
     113; 
     114  compile_opt idl2, strictarrsubs 
     115; 
    113116   widget_control, event.id, get_uvalue=uval 
    114117   widget_control, event.top, get_uvalue=top_uvalue 
     
    297300; 
    298301FUNCTION read_hope, typein, varnamein, FILENAME = filename, XLIMITS = xlimits, YLIMITS = ylimits,  ZLIMITS = zlimits, TLIMITS = tlimits, ODDPT = oddpt, ODDEVENPT = oddevenpt, EVENPT = evenpt, _extra = ex 
     302; 
     303  compile_opt idl2, strictarrsubs 
     304; 
    299305@common                         ; usefull only for the definition of iodir  
    300306  if n_elements(filename) EQ 0 then filename = isafile(iodirectory = iodir, _extra = ex) 
  • trunk/SRC/ToBeReviewed/HOPE/rh_alldomains.pro

    r53 r114  
    11PRO rh_alldomains, topid, selected 
     2; 
     3  compile_opt idl2, strictarrsubs 
     4; 
    25 
    36   widget_control, topid, get_uvalue=top_uvalue 
  • trunk/SRC/ToBeReviewed/HOPE/sortdim.pro

    r53 r114  
    1717; 
    1818; 
     19; 
     20  compile_opt idl2, strictarrsubs 
     21; 
    1922   tosort = dims 
    2023   if n_elements(tosort) eq 1 then $ 
  • trunk/SRC/ToBeReviewed/HOPE/xrh.pro

    r53 r114  
    11; procedure to call read_hope in the widget mode 
    22PRO xrh, _extra = ex 
     3; 
     4  compile_opt idl2, strictarrsubs 
     5; 
    36   a = read_hope(_extra = ex) 
    47   return 
  • trunk/SRC/ToBeReviewed/IMAGE/animgif.pro

    r74 r114  
    4242;------------------------------------------------------------ 
    4343PRO animgif, nomfic 
     44; 
     45  compile_opt idl2, strictarrsubs 
     46; 
    4447@common 
    4548; 
  • trunk/SRC/ToBeReviewed/IMAGE/image_viewer.pro

    r23 r114  
    4848;THIS PROCEDURE IS CALLED WHEN A USER SELECTS "File > Open Picture Files" FROM THE MAIN MENU 
    4949;error handling: 
     50; 
     51  compile_opt idl2, strictarrsubs 
     52; 
    5053!ERROR_STATE.CODE=0 
    5154CATCH,error 
     
    126129;THIS PROCEDURE IS CALLED WHEN A USER SELECTS "File > Open All In Folder" FROM THE MAIN MENU 
    127130;error handling: 
     131; 
     132  compile_opt idl2, strictarrsubs 
     133; 
    128134!ERROR_STATE.CODE=0 
    129135CATCH,error 
     
    204210PRO IMAGE_VIEWER_CANCEL,event 
    205211;obtain state structure for top-level-base from its UVALUE: 
     212; 
     213  compile_opt idl2, strictarrsubs 
     214; 
    206215WIDGET_CONTROL,event.top,GET_UVALUE=pState 
    207216;shut-off timer: 
     
    214223PRO IMAGE_VIEWER_TIMER,event 
    215224;obtain state structure for top-level-base from its UVALUE: 
     225; 
     226  compile_opt idl2, strictarrsubs 
     227; 
    216228WIDGET_CONTROL,event.top,GET_UVALUE=pState 
    217229if (*pState).timer EQ 1 then begin ;continue processing files: 
     
    884896;THIS PROCEDURE IS CALLED WHEN A USER SELECTS "File > Exit" FROM THE MAIN MENU 
    885897;terminate the program by destroying the top-level-base (widgetID always stored in event.top): 
     898; 
     899  compile_opt idl2, strictarrsubs 
     900; 
    886901WIDGET_CONTROL,event.top,/DESTROY 
    887902END 
     
    894909;FROM THE MAIN MENU 
    895910;display a simple message: 
     911; 
     912  compile_opt idl2, strictarrsubs 
     913; 
    896914messageStr=['IMAGE_VIEWER written by AEB, 2002.','',$ 
    897915            'The purpose of this program is to provide an interactive tool that can be used',$ 
     
    909927;THIS PROCEDURE IS CALLED WHEN A USER CLICKS ON ONE OF THE THUMBNAIL PICTURES 
    910928;error handling: 
     929; 
     930  compile_opt idl2, strictarrsubs 
     931; 
    911932!ERROR_STATE.CODE=0 
    912933CATCH,error 
     
    953974;THIS PROCEDURE IS CALLED WHEN THE PROGRAM IS TERMINATED AND XMANAGER REGISTERS A CLEANUP: 
    954975;obtain state structure for top-level-base from its uvalue: 
     976; 
     977  compile_opt idl2, strictarrsubs 
     978; 
    955979WIDGET_CONTROL,widgetID,GET_UVALUE=pState 
    956980;test for validity of state structure pointer: 
     
    9781002;THIS PROCEDURE IS CALLED WHEN A USER RESIZES THE TOP-LEVEL BASE 
    9791003;error handling: 
     1004; 
     1005  compile_opt idl2, strictarrsubs 
     1006; 
    9801007!ERROR_STATE.CODE=0 
    9811008CATCH,error 
     
    9971024PRO IMAGE_VIEWER 
    9981025;error handling: 
     1026; 
     1027  compile_opt idl2, strictarrsubs 
     1028; 
    9991029!ERROR_STATE.CODE=0 
    10001030CATCH,error 
  • trunk/SRC/ToBeReviewed/IMAGE/imdisp.pro

    r23 r114  
    11;------------------------------------------------------------------------------- 
    22FUNCTION IMDISP_GETPOS, ASPECT, POSITION=POSITION, MARGIN=MARGIN 
     3; 
     4  compile_opt idl2, strictarrsubs 
     5; 
    36 
    47;- Compute a position vector given an aspect ratio (called by IMDISP_IMSIZE) 
     
    4649FUNCTION IMDISP_IMSCALE, IMAGE, RANGE=RANGE, BOTTOM=BOTTOM, NCOLORS=NCOLORS, $ 
    4750  NEGATIVE=NEGATIVE 
     51; 
     52  compile_opt idl2, strictarrsubs 
     53; 
    4854 
    4955;- Byte-scale an image (called by IMDISP) 
     
    7379;------------------------------------------------------------------------------- 
    7480FUNCTION IMDISP_IMREGRID, DATA, NX, NY, INTERP=INTERP 
     81; 
     82  compile_opt idl2, strictarrsubs 
     83; 
    7584 
    7685;- Regrid a 2D array (called by IMDISP) 
     
    112121PRO IMDISP_IMSIZE, IMAGE, X0, Y0, XSIZE, YSIZE, ASPECT=ASPECT, $ 
    113122  POSITION=POSITION, MARGIN=MARGIN 
     123; 
     124  compile_opt idl2, strictarrsubs 
     125; 
    114126 
    115127;- Compute the size and offset for an image (called by IMDISP) 
     
    171183  BACKGROUND=BACKGROUND, ERASE=ERASE, $ 
    172184  AXIS=AXIS, NEGATIVE=NEGATIVE, _EXTRA=EXTRA_KEYWORDS 
     185; 
     186  compile_opt idl2, strictarrsubs 
     187; 
    173188 
    174189;+ 
  • trunk/SRC/ToBeReviewed/IMAGE/saveimage.pro

    r69 r114  
    11PRO SAVEIMAGE, FILE, BMP=BMP, PNG=PNG, PICT=PICT, JPEG=JPEG, TIFF=TIFF, $ 
    22  QUALITY=QUALITY, DITHER=DITHER, CUBE=CUBE, QUIET=QUIET, MULTIPLE = multiple 
     3; 
     4  compile_opt idl2, strictarrsubs 
     5; 
    36 
    47;+ 
  • trunk/SRC/ToBeReviewed/IMAGE/showimage.pro

    r69 r114  
    11PRO SHOWIMAGE, FILE, DITHER=DITHER, CURRENT=CURRENT 
     2; 
     3  compile_opt idl2, strictarrsubs 
     4; 
    25 
    36;+ 
  • trunk/SRC/ToBeReviewed/INIT/initncdf.pro

    r69 r114  
    9191              , XYINDEX = xyindex, ZINDEX = zindex $ 
    9292              , _EXTRA = ex 
     93; 
     94; 
     95  compile_opt idl2, strictarrsubs 
    9396; 
    9497@common 
  • trunk/SRC/ToBeReviewed/LECTURE/GRIB/bit2int.pro

    r67 r114  
    11FUNCTION bit2int, bitin, checkneg = checkneg 
     2; 
     3  compile_opt idl2, strictarrsubs 
     4; 
    25 
    36  res = 0L 
  • trunk/SRC/ToBeReviewed/LECTURE/GRIB/read_grib.pro

    r69 r114  
    11function read_grib, varcode, date1, date2, file = file 
     2; 
     3  compile_opt idl2, strictarrsubs 
     4; 
    25@common 
    36; http://www.wmo.ch/web/www/WDM/Guides/Guide-binary-2.html 
  • trunk/SRC/ToBeReviewed/LECTURE/GRIB/read_grib_bds.pro

    r67 r114  
    11FUNCTION read_grib_bds, num, recstart, ni, nj 
     2; 
     3; 
     4  compile_opt idl2, strictarrsubs 
    25; 
    36  offset = recstart+8 
  • trunk/SRC/ToBeReviewed/LECTURE/GRIB/read_grib_end.pro

    r67 r114  
    11PRO read_grib_end,  num, offset 
     2; 
     3  compile_opt idl2, strictarrsubs 
     4; 
    25 
    36  a = assoc(num, bytarr(4, /nozero), offset) 
  • trunk/SRC/ToBeReviewed/LECTURE/GRIB/read_grib_gds.pro

    r67 r114  
    11FUNCTION read_grib_gds, num, recstart 
     2; 
     3; 
     4  compile_opt idl2, strictarrsubs 
    25; 
    36  offset = recstart+8 
  • trunk/SRC/ToBeReviewed/LECTURE/GRIB/read_grib_is.pro

    r67 r114  
    11FUNCTION read_grib_is, num, offset 
     2; 
     3  compile_opt idl2, strictarrsubs 
     4; 
    25 
    36  infofile = fstat(num) 
  • trunk/SRC/ToBeReviewed/LECTURE/GRIB/read_grib_pds.pro

    r67 r114  
    11FUNCTION read_grib_pds, num, recstart 
     2; 
     3; 
     4  compile_opt idl2, strictarrsubs 
    25; 
    36  offset = recstart+8 
  • trunk/SRC/ToBeReviewed/LECTURE/GRIB/read_gribtable.pro

    r67 r114  
    4040PRO read_gribtable,tablename,parmtabl=parmtabl,center=center,$ 
    4141                   subcenter=subcenter,tablnum=tablnum 
     42; 
     43  compile_opt idl2, strictarrsubs 
     44; 
    4245   
    4346ON_ERROR,2 
  • trunk/SRC/ToBeReviewed/LECTURE/GRIB/scan_grib_code.pro

    r67 r114  
    11FUNCTION scan_grib_code, num, recstart 
     2; 
     3; 
     4  compile_opt idl2, strictarrsubs 
    25; 
    36  nrec =  n_elements(recstart) 
  • trunk/SRC/ToBeReviewed/LECTURE/GRIB/scan_grib_date.pro

    r67 r114  
    11FUNCTION scan_grib_date, num, recstart 
     2; 
     3; 
     4  compile_opt idl2, strictarrsubs 
    25; 
    36  nrec =  n_elements(recstart) 
  • trunk/SRC/ToBeReviewed/LECTURE/GRIB/scan_grib_messize.pro

    r67 r114  
    11FUNCTION scan_grib_messize, num, recstart 
     2; 
     3; 
     4  compile_opt idl2, strictarrsubs 
    25; 
    36  nrec =  n_elements(recstart) 
  • trunk/SRC/ToBeReviewed/LECTURE/GRIB/scan_grib_nbits.pro

    r67 r114  
    11FUNCTION scan_grib_nbits, num, recstart 
     2; 
     3  compile_opt idl2, strictarrsubs 
     4; 
    25 
    36; 
  • trunk/SRC/ToBeReviewed/LECTURE/GRIB/scan_grib_recstart.pro

    r67 r114  
    11FUNCTION scan_grib_recstart, num 
     2; 
     3  compile_opt idl2, strictarrsubs 
     4; 
    25 
    36  infofile = fstat(num) 
  • trunk/SRC/ToBeReviewed/LECTURE/binary.pro

    r97 r114  
    3838;- 
    3939function binary, number 
     40; 
     41  compile_opt idl2, strictarrsubs 
     42; 
    4043  s = size(number) 
    4144  type = s[s[0] + 1] 
  • trunk/SRC/ToBeReviewed/LECTURE/changeread.pro

    r44 r114  
    11FUNCTION changeread, newread 
     2; 
     3; 
     4  compile_opt idl2, strictarrsubs 
    25; 
    36@common 
  • trunk/SRC/ToBeReviewed/LECTURE/inverse_binary.pro

    r44 r114  
    6262FUNCTION inverse_binary, binnumb 
    6363; 
     64; 
     65  compile_opt idl2, strictarrsubs 
     66; 
    6467  s = size(binnumb, /dimensions) 
    6568  IF n_elements(s) EQ 1 THEN numbofbit = 8 ELSE numbofbit = 8*s[1] 
  • trunk/SRC/ToBeReviewed/LECTURE/litchamp.pro

    r44 r114  
    105105FUNCTION litchamp, struct, GRID = grid, NAME = name, UNIT = unit, EXP = exp, DATE = date $ 
    106106                   , LEVEL = level, MASK = mask 
     107; 
     108  compile_opt idl2, strictarrsubs 
     109; 
    107110@common 
    108111;------------------------------------------------------------ 
  • trunk/SRC/ToBeReviewed/LECTURE/ncdf_lec.pro

    r44 r114  
    4242;------------------------------------------------------------ 
    4343function ncdf_lec,nom,ATT=att,DIM=dim,VAR=var, IODIR = iodir, _extra = ex 
     44; 
     45  compile_opt idl2, strictarrsubs 
     46; 
    4447   res = -1 
    4548;------------------------------------------------------------ 
     
    124127          then begin 
    125128            print,'variable numero: ',strtrim(varid,1),', nom:',varcontent.name $ 
    126              ,', type:' ,varcontent.datatype,', dimensions:',nomdim(varcontent.dim) 
     129             ,', type:' ,varcontent.datatype,', dimensions:',nomdim[varcontent.dim] 
    127130            if strlowcase(att) eq strlowcase(varcontent.name) then begin 
    128131               for attiq=0,varcontent.natts-1 do begin 
  • trunk/SRC/ToBeReviewed/LECTURE/read_ncdf.pro

    r74 r114  
    7878                    , GRID = grid, FBASE2TBASE = fbase2tbase, _EXTRA = ex 
    7979;--------------------------------------------------------- 
     80; 
     81  compile_opt idl2, strictarrsubs 
     82; 
    8083@cm_4mesh 
    8184@cm_4data 
  • trunk/SRC/ToBeReviewed/LECTURE/xncdf_lec.pro

    r44 r114  
    1818;------------------------------------------------------------ 
    1919;------------------------------------------------------------ 
     20; 
     21  compile_opt idl2, strictarrsubs 
     22; 
    2023   COMMON wididbase, base 
    2124   COMMON resultat, res 
     
    200203;------------------------------------------------------------ 
    201204;------------------------------------------------------------ 
     205; 
     206  compile_opt idl2, strictarrsubs 
     207; 
    202208   COMMON resultat, res 
    203209   COMMON infovariable, cdfid, listename, contient, nomdim, tailledim, varid, varcontient 
     
    306312;------------------------------------------------------------ 
    307313;------------------------------------------------------------ 
     314; 
     315  compile_opt idl2, strictarrsubs 
     316; 
    308317   COMMON resultat, res 
    309318   COMMON infovariable, cdfid, listename, contient, nomdim, tailledim, varid, varcontient 
     
    408417;------------------------------------------------------------ 
    409418FUNCTION xncdf_lec, nom, ATT = att, COUNT = count, GROUP = group, OFFSET = offset, IODIR = iodir, SHIFT = shift,  STRIDE = stride, VAR = var 
     419; 
     420  compile_opt idl2, strictarrsubs 
     421; 
    410422   COMMON wididbase, base 
    411423   COMMON infovariable, cdfid, listename, contient, nomdim, tailledim, varid, varcontient 
  • trunk/SRC/ToBeReviewed/MATRICE/cmapply.pro

    r31 r114  
    149149;   OUT             FLOAT     = Array[10, 10] 
    150150; 
    151 ;   (OUT(i,j) is the median value of IN(i,j,*)) 
     151;   (OUT[i,j] is the median value of IN[i,j,*]) 
    152152; 
    153153; MODIFICATION HISTORY: 
     
    175175;; Utility function, adapted from CMPRODUCT 
    176176function cmapply_product, x 
     177; 
     178  compile_opt idl2, strictarrsubs 
     179; 
    177180  sz = size(x) 
    178   n = sz(1) 
     181  n = sz[1] 
    179182 
    180183  while n GT 1 do begin 
    181       if (n mod 2) EQ 1 then x(0,*) = x(0,*) * x(n-1,*) 
     184      if (n mod 2) EQ 1 then x[0,*] = x[0,*] * x[n-1,*] 
    182185      n2 = floor(n/2) 
    183       x = x(0:n2-1,*) * x(n2:*,*) 
     186      x = x[0:n2-1,*] * x[n2:*,*] 
    184187      n = n2 
    185188  endwhile 
    186   return, reform(x(0,*), /overwrite) 
     189  return, reform(x[0,*], /overwrite) 
    187190end 
    188191 
    189192;; Utility function, used to collect collaped dimensions 
    190193pro cmapply_redim, newarr, dimapply, dimkeep, nkeep, totcol, totkeep 
     194; 
     195  compile_opt idl2, strictarrsubs 
     196; 
    191197  sz = size(newarr) 
    192198  ;; First task: rearrange dimensions so that the dimensions 
    193199  ;; that are "kept" (ie, uncollapsed) are at the back 
    194   dimkeep = where(histogram(dimapply,min=1,max=sz(0)) ne 1, nkeep) 
     200  dimkeep = where(histogram(dimapply,min=1,max=sz[0]) ne 1, nkeep) 
    195201  if nkeep EQ 0 then return 
    196202 
    197203  newarr = transpose(temporary(newarr), [dimapply-1, dimkeep]) 
    198204  ;; totcol is the total number of collapsed elements 
    199   totcol = sz(dimapply(0)) 
    200   for i = 1, n_elements(dimapply)-1 do totcol = totcol * sz(dimapply(i)) 
    201   totkeep = sz(dimkeep(0)+1) 
    202   for i = 1, n_elements(dimkeep)-1 do totkeep = totkeep * sz(dimkeep(i)+1) 
     205  totcol = sz[dimapply[0]] 
     206  for i = 1, n_elements(dimapply)-1 do totcol = totcol * sz[dimapply[i]] 
     207  totkeep = sz[dimkeep[0]+1] 
     208  for i = 1, n_elements(dimkeep)-1 do totkeep = totkeep * sz[dimkeep[i]+1] 
    203209 
    204210  ;; this new array has two dimensions: 
     
    213219function cmapply, op, array, dimapply, double=dbl, type=type, $ 
    214220                  functargs=functargs, nocatch=nocatch 
     221; 
     222  compile_opt idl2, strictarrsubs 
     223; 
    215224 
    216225  if n_params() LT 2 then begin 
     
    227236  ;; 1) the dimensions of the array 
    228237  sz = size(array) 
    229   if sz(0) EQ 0 then $ 
     238  if sz[0] EQ 0 then $ 
    230239    message, 'ERROR: ARRAY must be an array!' 
    231240 
    232241  ;; 2) The type of the array 
    233   if sz(sz(0)+1) EQ 0 OR sz(sz(0)+1) EQ 7 OR sz(sz(0)+1) EQ 8 then $ 
     242  if sz[sz[0]+1] EQ 0 OR sz[sz[0]+1] EQ 7 OR sz[sz[0]+1] EQ 8 then $ 
    234243    message, 'ERROR: Cannot apply to UNDEFINED, STRING, or STRUCTURE' 
    235   if n_elements(type) EQ 0 then type = sz(sz(0)+1) 
     244  if n_elements(type) EQ 0 then type = sz[sz[0]+1] 
    236245 
    237246  ;; 3) The type of the operation 
    238247  szop = size(op) 
    239   if szop(szop(0)+1) NE 7 then $ 
     248  if szop[szop[0]+1] NE 7 then $ 
    240249    message, 'ERROR: operation OP was not a string' 
    241250 
     
    243252  if n_params() EQ 2 then dimapply = 1 
    244253  dimapply = [ dimapply ] 
    245   dimapply = dimapply(sort(dimapply))   ; Sort in ascending order 
     254  dimapply = dimapply[sort(dimapply)]   ; Sort in ascending order 
    246255  napply = n_elements(dimapply) 
    247256 
     
    254263  newop = strupcase(op) 
    255264  newarr = array 
    256   newarr = reform(newarr, sz(1:sz(0)), /overwrite) 
     265  newarr = reform(newarr, sz[1:sz[0]], /overwrite) 
    257266  case 1 of 
    258267 
     
    260269      (newop EQ '+'): begin 
    261270          for i = 0L, napply-1 do begin 
    262               newarr = total(temporary(newarr), dimapply(i)-i, double=dbl) 
     271              newarr = total(temporary(newarr), dimapply[i]-i, double=dbl) 
    263272          endfor 
    264273      end 
     
    269278          if nkeep EQ 0 then begin 
    270279              newarr = reform(newarr, n_elements(newarr), 1, /overwrite) 
    271               return, (cmapply_product(newarr))(0) 
     280              return, (cmapply_product(newarr))[0] 
    272281          endif 
    273282 
    274283          result = cmapply_product(newarr) 
    275           result = reform(result, sz(dimkeep+1), /overwrite) 
     284          result = reform(result, sz[dimkeep+1], /overwrite) 
    276285          return, result 
    277286      end 
     
    282291          totelt = 1L 
    283292          for i = 0L, napply-1 do begin 
    284               newarr = total(temporary(newarr), dimapply(i)-i) 
    285               totelt = totelt * sz(dimapply(i)) 
     293              newarr = total(temporary(newarr), dimapply[i]-i) 
     294              totelt = totelt * sz[dimapply[i]] 
    286295          endfor 
    287296          if newop EQ 'AND' then return, (round(newarr) EQ totelt) 
     
    305314          if totcol LT totkeep then begin 
    306315              ;; Iterate over the number of collapsed elements 
    307               result(0) = reform(newarr(0,*),totkeep,/overwrite) 
     316              result[0] = reform(newarr[0,*],totkeep,/overwrite) 
    308317              case newop of  
    309318                  'MAX': for i = 1L, totcol-1 do $ 
    310                     result(0) = result > newarr(i,*) 
     319                    result[0] = result > newarr[i,*] 
    311320                  'MIN': for i = 1L, totcol-1 do $ 
    312                     result(0) = result < newarr(i,*) 
     321                    result[0] = result < newarr[i,*] 
    313322              endcase 
    314323          endif else begin 
    315324              ;; Iterate over the number of output elements 
    316325              case newop of  
    317                   'MAX': for i = 0L, totkeep-1 do result(i) = max(newarr(*,i)) 
    318                   'MIN': for i = 0L, totkeep-1 do result(i) = min(newarr(*,i)) 
     326                  'MAX': for i = 0L, totkeep-1 do result[i] = max(newarr[*,i]) 
     327                  'MIN': for i = 0L, totkeep-1 do result[i] = min(newarr[*,i]) 
    319328              endcase 
    320329          endelse 
    321330 
    322           result = reform(result, sz(dimkeep+1), /overwrite) 
     331          result = reform(result, sz[dimkeep+1], /overwrite) 
    323332          return, result 
    324333      end 
     
    343352          if n_elements(functargs) GT 0 then begin 
    344353              for i = 0L, totkeep-1 do $ 
    345                 result(i) = call_function(functname, newarr(*,i), _EXTRA=functargs) 
     354                result[i] = call_function(functname, newarr[*,i], _EXTRA=functargs) 
    346355          endif else begin 
    347356              for i = 0L, totkeep-1 do $ 
    348                 result(i) = call_function(functname, newarr(*,i)) 
     357                result[i] = call_function(functname, newarr[*,i]) 
    349358          endelse 
    350359 
    351           result = reform(result, sz(dimkeep+1), /overwrite) 
     360          result = reform(result, sz[dimkeep+1], /overwrite) 
    352361          return, result 
    353362      end 
     
    357366 
    358367  newsz = size(newarr) 
    359   if type EQ newsz(newsz(0)+1) then return, newarr 
     368  if type EQ newsz[newsz[0]+1] then return, newarr 
    360369 
    361370  ;; Cast the result into the desired type, if necessary 
     
    363372             'DOUBLE', 'COMPLEX', 'UNDEF', 'UNDEF', 'DCOMPLEX' ] 
    364373  if type GE 1 AND type LE 3 then $ 
    365     return, call_function(castfns(type), round(newarr)) $ 
     374    return, call_function(castfns[type], round(newarr)) $ 
    366375  else $ 
    367     return, call_function(castfns(type), newarr) 
     376    return, call_function(castfns[type], newarr) 
    368377end 
    369378   
  • trunk/SRC/ToBeReviewed/MATRICE/cmset_op.pro

    r84 r114  
    154154;   if keyword_set(sortit) then begin 
    155155;       ;; Sort it manually 
    156 ;       ii = sort(a) & b = a(ii) 
     156;       ii = sort(a) & b = a[ii] 
    157157;       if keyword_set(non) then wh = where(b EQ shift(b, sh), ct) $ 
    158158;       else                     wh = where(b NE shift(b, sh), ct) 
    159 ;       if ct GT 0 then return, ii(wh) 
     159;       if ct GT 0 then return, ii[wh] 
    160160;   endif else begin 
    161161;       ;; Use the user's values directly 
     
    171171;; "first" value, whatever that may mean. 
    172172function cmset_op_uniq, a 
     173; 
     174  compile_opt idl2, strictarrsubs 
     175; 
    173176  if n_elements(a) LE 1 then return, 0L 
    174177 
    175   ii = sort(a) & b = a(ii) 
     178  ii = sort(a) & b = a[ii] 
    176179  wh = where(b NE shift(b, +1L), ct) 
    177   if ct GT 0 then return, ii(wh) 
     180  if ct GT 0 then return, ii[wh] 
    178181 
    179182  return, 0L 
     
    182185function cmset_op, a, op0, b, not1=not1, not2=not2, count=count, $ 
    183186              empty1=empty1, empty2=empty2, maxarray=ma, index=index 
     187; 
     188  compile_opt idl2, strictarrsubs 
     189; 
    184190 
    185191  on_error, 2 ;; return on error 
     
    204210  ;; Check the operation 
    205211  sz = size(op0) 
    206   if sz(sz(0)+1) NE 7 then begin 
     212  if sz[sz[0]+1] NE 7 then begin 
    207213      OP_ERR: 
    208214      message, "ERROR: OP must be 'AND', 'OR' or 'XOR'" 
     
    247253         if count GT 0 then return, a1 else return, -1L 
    248254     endif 
    249      if count GT 0 then return, a(a1) else return, -1L 
     255     if count GT 0 then return, a[a1] else return, -1L 
    250256     RET_B1: 
    251257     count = n2 
     
    253259         if count GT 0 then return, b1+n1 else return, -1L 
    254260     endif          
    255      if count GT 0 then return, b(b1) else return, -1L 
     261     if count GT 0 then return, b[b1] else return, -1L 
    256262 endif 
    257263 
     
    266272 
    267273  ;; Check types of operands 
    268   sz1 = size(a) & tp1 = sz1(sz1(0)+1) 
    269   sz2 = size(b) & tp2 = sz2(sz2(0)+1) 
     274  sz1 = size(a) & tp1 = sz1[sz1[0]+1] 
     275  sz2 = size(b) & tp2 = sz2[sz2[0]+1] 
    270276  if tp1 LT 0 OR tp1 GE 16 OR tp2 LT 0 OR tp2 GE 16 then begin 
    271277      message, 'ERROR: unrecognized data types for operands' 
    272278      return, -1 
    273279  endif 
    274   if basetype(tp1) NE basetype(tp2) then begin 
     280  if basetype[tp1] NE basetype[tp2] then begin 
    275281      TYPE1_ERR: 
    276282      message, 'ERROR: both A and B must be of the same type' 
     
    297303              count = n_elements(index0) 
    298304              if kind then return, index0 
    299               return, uu(index0) 
     305              return, uu[index0] 
    300306          end 
    301307 
     
    305311              bi = cmset_op_uniq(b) & nb = n_elements(bi) 
    306312              ui = [ai, bi+n1] 
    307               uu = [a,b]    & uu = uu(ui) ;; Raw union... 
    308               us = sort(uu) & uu = uu(us) ;; ...and sort 
    309               if kind then ui = ui(temporary(us)) else ui = 0 
     313              uu = [a,b]    & uu = uu[ui] ;; Raw union... 
     314              us = sort(uu) & uu = uu[us] ;; ...and sort 
     315              if kind then ui = ui[temporary(us)] else ui = 0 
    310316 
    311317              ;; Values in one set only will not have duplicates 
    312318              wh1 = where(uu NE shift(uu, -1), count1) 
    313319              if count1 EQ 0 then return, -1L 
    314               wh = where(wh1(1:*)-wh1 EQ 1, count) 
    315               if wh1(0) EQ 0 then begin 
     320              wh = where(wh1[1:*]-wh1 EQ 1, count) 
     321              if wh1[0] EQ 0 then begin 
    316322                  if count GT 0 then wh = [-1L, wh] else wh = [-1L] 
    317323                  count = n_elements(wh) 
    318324              endif 
    319325              if count EQ 0 then return, -1 
    320               if kind then return, ui(wh1(wh+1)) 
    321               return, uu(wh1(wh+1)) 
     326              if kind then return, ui[wh1[wh+1]] 
     327              return, uu[wh1[wh+1]] 
    322328          end 
    323329 
     
    327333              bi = cmset_op_uniq(b) & nb = n_elements(bi) 
    328334              ui = [ai, bi+n1] 
    329               uu = [a,b]    & uu = uu(ui)  ;; Raw union... 
    330               us = sort(uu) & uu = uu(us)  ;; ...and sort 
    331               if kind then ui = ui(us) else ui = 0 
     335              uu = [a,b]    & uu = uu[ui]  ;; Raw union... 
     336              us = sort(uu) & uu = uu[us]  ;; ...and sort 
     337              if kind then ui = ui[us] else ui = 0 
    332338 
    333339              if NOT keyword_set(not1) AND NOT keyword_set(not2) then begin 
     
    336342                  ;; they are equal, then the SHIFT() technique below 
    337343                  ;; fails.  Do this one by hand. 
    338                   if na EQ 1 AND nb EQ 1 AND uu(0) EQ uu(1) then begin 
     344                  if na EQ 1 AND nb EQ 1 AND uu[0] EQ uu[1] then begin 
    339345                      count = 1L 
    340346                      if kind then return, 0L 
    341                       return, [uu(0)] 
     347                      return, [uu[0]] 
    342348                  endif 
    343349 
     
    348354                  ;; This should always select the element from A 
    349355                  ;; rather than B (the smaller of the two) 
    350                   if kind then return, (ui(wh) < ui(wh+1)) 
    351                   return, uu(wh) 
     356                  if kind then return, (ui[wh] < ui[wh+1]) 
     357                  return, uu[wh] 
    352358              endif 
    353359 
    354360              ;; For "NOT" cases, we need to identify by set 
    355361              ii = make_array(na+nb, value=1b) 
    356               if keyword_set(not1) then ii(0:na-1) = 0 
    357               if keyword_set(not2) then ii(na:*)   = 0 
    358               ii = ii(temporary(us)) 
     362              if keyword_set(not1) then ii[0:na-1] = 0 
     363              if keyword_set(not2) then ii[na:*]   = 0 
     364              ii = ii[temporary(us)] 
    359365 
    360366              ;; Remove any duplicates 
    361367              wh1 = where(uu EQ shift(uu, -1L), count1) ;; Find non-unique 
    362               if count1 GT 0 then ii([wh1, wh1+1]) = 0 
     368              if count1 GT 0 then ii[wh1, wh1+1] = 0 
    363369              ;; Remainder is the desired set 
    364370              wh = where(ii, count) 
    365371              if count EQ 0 then return, -1L 
    366               if kind then return, ui(wh) 
    367               return, uu(wh) 
     372              if kind then return, ui[wh] 
     373              return, uu[wh] 
    368374          end 
    369375 
     
    380386      minn = min1 < min2 & maxx = max1 > max2 
    381387      nbins = maxx-minn+1 
    382       if (maxx-minn) GT floor(ma(0)) then goto, SLOW_SET_OP 
     388      if (maxx-minn) GT floor(ma[0]) then goto, SLOW_SET_OP 
    383389 
    384390      ;; Work around a stupidity in the built-in IDL HISTOGRAM routine 
     
    405411      result = temporary(wh+minn) 
    406412      if tp1 NE tp2 then return, result 
    407       szr = size(result) & tpr = szr(szr(0)+1) 
     413      szr = size(result) & tpr = szr[szr[0]+1] 
    408414 
    409415      ;; Cast to the original type if necessary 
    410416      if tpr NE tp1 then begin 
    411417          fresult = make_array(n_elements(result), type=tp1) 
    412           fresult(0) = temporary(result) 
     418          fresult[0] = temporary(result) 
    413419          result = temporary(fresult) 
    414420      endif 
     
    424430;     works, but is complicated, so I forced it to go to SLOW_SET_OP. 
    425431;     ha = histogram(a, min=minn, max=maxx, reverse=ra) < 1 
    426 ;     rr = ra(0:nbins) & mask = rr NE rr(1:*) & ra = ra(rr)*mask-1L+mask 
     432;     rr = ra[0:nbins] & mask = rr NE rr[1:*] & ra = ra[rr]*mask-1L+mask 
    427433;     hb = histogram(b, min=minn, max=maxx, reverse=rb) < 1 
    428 ;     rr = rb(0:nbins) & mask = rr NE rr(1:*) & rb = rb(rr)*mask-1L+mask 
     434;     rr = rb[0:nbins] & mask = rr NE rr[1:*] & rb = rb[rr]*mask-1L+mask 
    429435;     ...  AND/OR/XOR NOT masking here ... 
    430 ;     ra = ra(wh) & rb = rb(wh) 
     436;     ra = ra[wh] & rb = rb[wh] 
    431437;     return, ra*(ra GE 0) + (rb+n1)*(ra LT 0) ;; is last 'ra' right? 
    432438 
  • trunk/SRC/ToBeReviewed/MATRICE/colle.pro

    r31 r114  
    7070;------------------------------------------------------------ 
    7171   PRO UNDEFINE, varname   
     72; 
     73  compile_opt idl2, strictarrsubs 
     74; 
    7275      tempvar = SIZE(TEMPORARY(varname)) 
    7376   END 
     
    7578;------------------------------------------------------------ 
    7679FUNCTION colle, a0, a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20, SAUVE = sauve 
     80; 
     81  compile_opt idl2, strictarrsubs 
     82; 
    7783   res = -1 
    7884;------------------------------------------------------------ 
  • trunk/SRC/ToBeReviewed/MATRICE/congridseb.pro

    r31 r114  
    5151;------------------------------------------------------------ 
    5252function congridseb, tableau, x, y 
     53; 
     54  compile_opt idl2, strictarrsubs 
     55; 
    5356   res=tableau 
    5457   taille = size(tableau) 
  • trunk/SRC/ToBeReviewed/MATRICE/different.pro

    r31 r114  
    4747;------------------------------------------------------------ 
    4848FUNCTION different, a, b   
     49; 
     50  compile_opt idl2, strictarrsubs 
     51; 
    4952 
    5053   ; = a and (not b) = elements in A but not in B 
  • trunk/SRC/ToBeReviewed/MATRICE/extrait.pro

    r31 r114  
    8585FUNCTION extrait, tab, indicex, indicey, indicez, indicet 
    8686;------------------------------------------------------------ 
     87; 
     88  compile_opt idl2, strictarrsubs 
     89; 
    8790   taille = size(tab) 
    8891;------------------------------------------------------------ 
  • trunk/SRC/ToBeReviewed/MATRICE/inter.pro

    r31 r114  
    4949FUNCTION inter, a, b 
    5050; 
     51; 
     52  compile_opt idl2, strictarrsubs 
     53; 
    5154   case 1 of 
    5255      n_elements(a) EQ 0:return,  -1 
  • trunk/SRC/ToBeReviewed/MATRICE/make_selection.pro

    r31 r114  
    9595            only_valid=only_valid,required=required,  $ 
    9696            quiet=quiet 
     97; 
     98  compile_opt idl2, strictarrsubs 
     99; 
    97100  
    98101  
  • trunk/SRC/ToBeReviewed/MATRICE/union.pro

    r31 r114  
    4747;------------------------------------------------------------ 
    4848FUNCTION union, a, b 
     49; 
     50  compile_opt idl2, strictarrsubs 
     51; 
    4952IF a[0] LT 0 THEN RETURN, b    ;A union NULL = a 
    5053IF b[0] LT 0 THEN RETURN, a    ;B union NULL = b 
  • trunk/SRC/ToBeReviewed/MATRICE/zeroun.pro

    r31 r114  
    3535;------------------------------------------------------------ 
    3636function zeroun, n1,n2 
     37; 
     38  compile_opt idl2, strictarrsubs 
     39; 
    3740   CASE N_PARAMS() OF 
    3841      1:return, findgen(n1) mod 2 
  • trunk/SRC/ToBeReviewed/PLOTS/DESSINE/bar_plot.pro

    r97 r114  
    131131          outline=outline,overplot=overplot,background=background, $ 
    132132          rotate=rotate, _EXTRA = ex 
     133; 
     134  compile_opt idl2, strictarrsubs 
     135; 
    133136if (n_params(d) eq 0) then begin  ;Print call & return if no parameters 
    134137  print,'bar_test,values,baselines=baselines,colors=colors,barnames=barnames,$' 
  • trunk/SRC/ToBeReviewed/PLOTS/DESSINE/plt.pro

    r67 r114  
    304304;--------------------------------------------------------- 
    305305; include common 
     306; 
     307  compile_opt idl2, strictarrsubs 
     308; 
    306309@cm_4mesh 
    307310@cm_4data 
  • trunk/SRC/ToBeReviewed/PLOTS/DESSINE/plt1d.pro

    r74 r114  
    160160;--------------------------------------------------------- 
    161161; include common 
     162; 
     163  compile_opt idl2, strictarrsubs 
     164; 
    162165@cm_4mesh 
    163166@cm_4data 
     
    239242    notanum = where(finite(z1d) EQ 0) 
    240243    z1d[notanum] = 0 
    241     mask(where(z1d LT valmask/10)) = 1 
     244    mask[where(z1d LT valmask/10)] = 1 
    242245    z1d[notanum] = !values.f_nan 
    243   ENDIF ELSE mask(where(z1d LT valmask/10)) = 1 
     246  ENDIF ELSE mask[where(z1d LT valmask/10)] = 1 
    244247;----------------------------------------------------------------------------- 
    245248; determination du min et du max apres la moyenne 
  • trunk/SRC/ToBeReviewed/PLOTS/DESSINE/pltbase.pro

    r67 r114  
    135135             , _EXTRA = ex 
    136136;--------------------------------------------------------- 
     137; 
     138  compile_opt idl2, strictarrsubs 
     139; 
    137140@cm_4mesh 
    138141  IF NOT keyword_set(key_forgetold) THEN BEGIN 
     
    215218; ds le cas on unsur2 est active on reduit levels 
    216219    if NOT keyword_set(nocontour) then begin 
    217       IF keyword_set(unsur2) THEN levels = levels(where(zeroun(n_elements(levels) ) eq 1)) 
     220      IF keyword_set(unsur2) THEN levels = levels[where(zeroun(n_elements(levels) ) eq 1)] 
    218221; unlabsur est active?  C_LABEL est passe via _EXTRA? 
    219222      if keyword_set(unlabsur) THEN IF chkstru(ex, 'C_LABELS') THEN $ 
  • trunk/SRC/ToBeReviewed/PLOTS/DESSINE/pltsc.pro

    r35 r114  
    33; 
    44; scatter plot (inspired from plt1d) 
     5; 
     6; 
     7  compile_opt idl2, strictarrsubs 
    58; 
    69 
  • trunk/SRC/ToBeReviewed/PLOTS/DESSINE/pltt.pro

    r74 r114  
    306306;--------------------------------------------------------- 
    307307; include common 
     308; 
     309  compile_opt idl2, strictarrsubs 
     310; 
    308311@cm_4mesh 
    309312@cm_4data 
  • trunk/SRC/ToBeReviewed/PLOTS/DESSINE/pltz.pro

    r35 r114  
    266266;--------------------------------------------------------- 
    267267; include common 
     268; 
     269  compile_opt idl2, strictarrsubs 
     270; 
    268271@cm_4mesh 
    269272@cm_4data 
  • trunk/SRC/ToBeReviewed/PLOTS/DESSINE/sbar_plot.pro

    r69 r114  
    5151 
    5252PRO sbar_plot, Values, COLORS = colors, NOREINITPLT = noreinitplt, _extra = ex  
     53; 
     54  compile_opt idl2, strictarrsubs 
     55; 
    5356@common 
    5457; 1) je reinitialise l''environnememt graphique (les variables !x, !y et !p):  
  • trunk/SRC/ToBeReviewed/PLOTS/DESSINE/scontour.pro

    r35 r114  
    4141;------------------------------------------------------------ 
    4242PRO scontour, x, y, z, NOREINITPLT = noreinitplt, _EXTRA = ex 
     43; 
     44  compile_opt idl2, strictarrsubs 
     45; 
    4346@common 
    4447; 1) je reinitialise l''environnememt graphique (les variables !x, !y et !p):  
  • trunk/SRC/ToBeReviewed/PLOTS/DESSINE/splot.pro

    r67 r114  
    4646;------------------------------------------------------------ 
    4747PRO splot,  x, y, NOREINITPLT = noreinitplt, _EXTRA = ex 
     48; 
     49  compile_opt idl2, strictarrsubs 
     50; 
    4851@common 
    4952; 1) je reinitialise l''environnememt graphique (les variables !x, !y et !p):  
  • trunk/SRC/ToBeReviewed/PLOTS/DESSINE/tvplus.pro

    r69 r114  
    8686            , MIN = min, MAX = max, MASK = mask, OFFSET = offset, NOUSEINFOS = NOUSEINFOS $ 
    8787            , NCOLORS = ncolors, NOINTERP = nointerp, _EXTRA = ex 
     88; 
     89; 
     90  compile_opt idl2, strictarrsubs 
    8891; 
    8992  IF n_elements(z2d) EQ 0 THEN return 
     
    136139    if abs(mask) LT 1e6 then BEGIN  
    137140      masked = where(arr EQ mask) 
    138       if masked[0] NE -1 then arr(masked) = min(arr(where(arr NE mask))) 
     141      if masked[0] NE -1 then arr[masked] = min(arr[where(arr NE mask)]) 
    139142    ENDIF ELSE BEGIN  
    140143      masked = where(abs(arr) GE abs(mask)/10.) 
    141       if masked[0] NE -1 then arr(masked) = min(arr(where(abs(arr) LT abs(mask)/10.))) 
     144      if masked[0] NE -1 then arr[masked] = min(arr[where(abs(arr) LT abs(mask)/10.)]) 
    142145    ENDELSE 
    143146  ENDIF ELSE masked = -1 
  • trunk/SRC/ToBeReviewed/PLOTS/DIVERS/addaxe.pro

    r37 r114  
    3737;------------------------------------------------------------ 
    3838PRO addaxe, endpoints, type, posfenetre, _EXTRA = ex 
     39; 
     40  compile_opt idl2, strictarrsubs 
     41; 
    3942@common 
    4043;--------------------------------------- 
  • trunk/SRC/ToBeReviewed/PLOTS/DIVERS/autoscale.pro

    r37 r114  
    4242; ce CI est un multiple de l'unite en unite log de 10. 
    4343; 
     44; 
     45  compile_opt idl2, strictarrsubs 
     46; 
    4447    ci = (max-min)/20. 
    4548    ci = 10.^floor(alog10(ci)) 
  • trunk/SRC/ToBeReviewed/PLOTS/DIVERS/axis4pltz.pro

    r74 r114  
    4141; 
    4242; include common 
     43; 
     44  compile_opt idl2, strictarrsubs 
     45; 
    4346@cm_4mesh 
    4447  IF NOT keyword_set(key_forgetold) THEN BEGIN 
  • trunk/SRC/ToBeReviewed/PLOTS/DIVERS/barrecouleur.pro

    r37 r114  
    2525                  , CB_SUBTITLE = cb_subtitle, POST = post, _extra = ex 
    2626;------------------------------------------------------------ 
     27; 
     28  compile_opt idl2, strictarrsubs 
     29; 
    2730@cm_general 
    2831  IF NOT keyword_set(key_forgetold) THEN BEGIN 
  • trunk/SRC/ToBeReviewed/PLOTS/DIVERS/checkfield.pro

    r69 r114  
    4040;------------------------------------------------------------ 
    4141FUNCTION err_1d, type, n1, name, n2 
     42; 
     43  compile_opt idl2, strictarrsubs 
     44; 
    4245  return, report(['Error in "' + type + '" type plot with a 1D input array:' $ 
    4346                  , 'the number of elements of the input vector ('+strtrim(n1, 1)+') ' $ 
     
    4649; 
    4750FUNCTION err_2d, type, sz, nx, ny, nz 
     51; 
     52  compile_opt idl2, strictarrsubs 
     53; 
    4854  @cm_4mesh 
    4955  @cm_4cal 
     
    5965; 
    6066FUNCTION err_3d, type, sz, nx, ny, nz 
     67; 
     68  compile_opt idl2, strictarrsubs 
     69; 
    6170  @cm_4mesh 
    6271  @cm_4cal 
     
    7483FUNCTION checkfield, field, procedure, TYPE = type, BOXZOOM = boxzoom, DIREC = direc, NOQUESTION = noquestion, VECTEUR = vecteur, WDEPTH = wdepth, _EXTRA = ex 
    7584;-------------------------------------------------------------- 
     85; 
     86  compile_opt idl2, strictarrsubs 
     87; 
    7688; include commons 
    7789@cm_4mesh 
  • trunk/SRC/ToBeReviewed/PLOTS/DIVERS/checktypeminmax.pro

    r37 r114  
    3636                     , XINDEX = xindex, YINDEX = yindex $ 
    3737                     , ENDPOINTS = endpoints, _extra = ex 
     38; 
     39; 
     40  compile_opt idl2, strictarrsubs 
    3841; 
    3942@common 
  • trunk/SRC/ToBeReviewed/PLOTS/DIVERS/determineminmax.pro

    r37 r114  
    4444;------------------------------------------------------------ 
    4545PRO determineminmax, tab, mask, vraimin, vraimax, glam, gphi, MAXIN = maxin, MININ = minin, INTERVALLE = intervalle, usetri = usetri, ZEROMIDDLE = zeromiddle, _extra = ex 
     46; 
     47  compile_opt idl2, strictarrsubs 
     48; 
    4649@common 
    4750;----------------------------------------------------------------------------- 
     
    7174  endif 
    7275; ma et mi : max et min sur les points mer 
    73   vraimax = max(tab(mer), min = vraimin, _extra = ex) 
     76  vraimax = max(tab[mer], min = vraimin, _extra = ex) 
    7477  sameminmax = testvar(var = minin) EQ testvar(var = maxin)  
    7578  if n_elements(maxin) EQ 0 OR sameminmax then maxin = vraimax 
  • trunk/SRC/ToBeReviewed/PLOTS/DIVERS/givewindowsize.pro

    r37 r114  
    33;------------------------------------------------------------ 
    44; include commons 
     5; 
     6  compile_opt idl2, strictarrsubs 
     7; 
    58@cm_4ps 
    69IF NOT keyword_set(key_forgetold) THEN BEGIN 
  • trunk/SRC/ToBeReviewed/PLOTS/DIVERS/meridienparallele.pro

    r37 r114  
    2323;------------------------------------------------------------ 
    2424PRO meridienparallele, coupe 
     25; 
     26  compile_opt idl2, strictarrsubs 
     27; 
    2528@common 
    2629;------------------------------------------------------------ 
  • trunk/SRC/ToBeReviewed/PLOTS/DIVERS/placecolor.pro

    r37 r114  
    4242;------------------------------------------------------------ 
    4343; include commons 
     44; 
     45  compile_opt idl2, strictarrsubs 
     46; 
    4447@cm_4ps 
    4548   IF NOT keyword_set(key_forgetold) THEN BEGIN 
  • trunk/SRC/ToBeReviewed/PLOTS/DIVERS/placedessin.pro

    r69 r114  
    5656;--------------------------------------------------------- 
    5757; include common 
     58; 
     59  compile_opt idl2, strictarrsubs 
     60; 
    5861@cm_4ps 
    5962@cm_4mesh 
  • trunk/SRC/ToBeReviewed/PLOTS/DIVERS/projsegment.pro

    r37 r114  
    5050FUNCTION projsegment, vecteur, bornes, MP = mp 
    5151;-------------------------------------------------------------- 
     52; 
     53  compile_opt idl2, strictarrsubs 
     54; 
    5255   a1 = float(vecteur[0]) 
    5356   b1 = float(vecteur[n_elements(vecteur)-1]) 
  • trunk/SRC/ToBeReviewed/PLOTS/DIVERS/restoreatt.pro

    r37 r114  
    2929;------------------------------------------------------------ 
    3030PRO restoreatt, struct 
     31; 
     32  compile_opt idl2, strictarrsubs 
     33; 
    3134@common 
    3235;------------------------------------------------------------ 
  • trunk/SRC/ToBeReviewed/PLOTS/DIVERS/rotation.pro

    r37 r114  
    2828 
    2929PRO ROTATION,X,Y,DEG,NX,NY 
     30; 
     31  compile_opt idl2, strictarrsubs 
     32; 
    3033ang=deg*!dtor 
    3134 
     
    3538;get angle in for loop so that zero radii will be left as zero angle 
    3639for i = 0,n_elements(r)-1 do $ 
    37 if r(i) ne 0 then theta(i) = atan(y(i),x(i))  ;range from -pi to +pi 
     40if r[i] ne 0 then theta[i] = atan(y[i],x[i])  ;range from -pi to +pi 
    3841; 
    3942;add rotation angle 
  • trunk/SRC/ToBeReviewed/PLOTS/DIVERS/saveatt.pro

    r37 r114  
    2626;------------------------------------------------------------ 
    2727FUNCTION saveatt 
     28; 
     29  compile_opt idl2, strictarrsubs 
     30; 
    2831@common 
    2932   return, {n:varname,g:vargrid,d:vardate,e:varexp,u:varunit,m:valmask} 
  • trunk/SRC/ToBeReviewed/PLOTS/DIVERS/terminedessin.pro

    r37 r114  
    3434PRO terminedessin, POST = post, SMALL = small, _extra = ex 
    3535;--------------------------------------------------------- 
     36; 
     37  compile_opt idl2, strictarrsubs 
     38; 
    3639@cm_4ps 
    3740  IF NOT keyword_set(key_forgetold) THEN BEGIN 
  • trunk/SRC/ToBeReviewed/PLOTS/LABEL/label.pro

    r39 r114  
    5050pro label, cas, min, max, ncontour, level_z2d, colnumb, NLEVEL = nlevel $ 
    5151          ,INTERVALLE=intervalle, STRICTFILL = strictfill 
     52; 
     53  compile_opt idl2, strictarrsubs 
     54; 
    5255@common 
    5356   if !d.name EQ 'PS' OR !d.name EQ 'Z' then BEGIN 
     
    8386         level_z2d = min + intervalle*findgen(Ncontour)  
    8487         colnumb   = ncoul*(findgen(Ncontour))/Ncontour+ncoul/(2*ncontour) 
    85          max=level_z2d(Ncontour-1)+intervalle 
     88         max=level_z2d[Ncontour-1]+intervalle 
    8689      end 
    8790; label pour faire les memes sss que dessier 
  • trunk/SRC/ToBeReviewed/PLOTS/LABEL/label_date.pro

    r97 r114  
    9999FUNCTION LABEL_DATE, axis, index, x, DATE_FORMAT = format, MONTHS = months, $ 
    100100              OFFSET= offs, _EXTRA = ex 
     101; 
     102  compile_opt idl2, strictarrsubs 
     103; 
    101104COMMON label_date_com, fmt, month_chr, offset 
    102105 
  • trunk/SRC/ToBeReviewed/PLOTS/LABEL/label_gmt.pro

    r39 r114  
    33; 
    44PRO label_gmt, min, max, intervalle, ncoul, ncontour, level_z2d, coul 
     5; 
     6  compile_opt idl2, strictarrsubs 
     7; 
    58@common 
    69@com_eg 
     
    2225      ncontour  = fix((max-min)/intervalle) 
    2326      level_z2d = min + intervalle*findgen(Ncontour)  
    24       max=level_z2d(Ncontour-1)+intervalle 
     27      max=level_z2d[Ncontour-1]+intervalle 
    2528 
    2629      print, '     Number of contour intervals, plotting min & max ', ncontour, min, max 
     
    4043           ; difference plot : lighter below first negative interval 
    4144            red[51:98] = long((100.-float(grey_shade_2))/100.*255.) 
    42             red(1:48) = long((100.-float(grey_shade))/100.*255.) 
     45            red[1:48] = long((100.-float(grey_shade))/100.*255.) 
    4346            red[50] = 255 
    4447 
  • trunk/SRC/ToBeReviewed/PLOTS/LABEL/lataxe.pro

    r39 r114  
    3838;------------------------------------------------------------ 
    3939; on ramenne value ds le segment [0,180] 
     40; 
     41  compile_opt idl2, strictarrsubs 
     42; 
    4043   lat=value mod 360 
    4144   if lat lt 0 then lat=lat+360 
  • trunk/SRC/ToBeReviewed/PLOTS/LABEL/lonaxe.pro

    r39 r114  
    3838;------------------------------------------------------------ 
    3939; on ramenne value ds le segment [0,360[ 
     40; 
     41  compile_opt idl2, strictarrsubs 
     42; 
    4043   lon=value mod 360 
    4144   if lon lt 0 then lon=lon+360 
  • trunk/SRC/ToBeReviewed/PLOTS/VECTEUR/ajoutvect.pro

    r41 r114  
    5454;------------------------------------------------------------ 
    5555pro ajoutvect,vecteur, vectlegende, UNVECTSUR=unvectsur,VECTMIN=vectmin, VECTMAX=vectmax, _EXTRA = ex 
     56; 
     57  compile_opt idl2, strictarrsubs 
     58; 
    5659@common 
    5760   tempsun = systime(1)         ; pour key_performance 
     
    128131; construction de u et v aux pts T 
    129132;----------------------------------------------------------- 
    130       a=u(0,*) 
     133      a=u[0,*] 
    131134      u=(u+shift(u,1,0))/2. 
    132       if NOT keyword_set(key_periodic) OR nx NE jpi then u(0,*)=a 
    133       a=v(*,0) 
     135      if NOT keyword_set(key_periodic) OR nx NE jpi then u[0,*]=a 
     136      a=v[*,0] 
    134137      v=(v+shift(v,0,1))/2. 
    135       if NOT keyword_set(key_periodic) OR nx NE jpi then v(*,0)=a 
     138      if NOT keyword_set(key_periodic) OR nx NE jpi then v[*,0]=a 
    136139;---------------------------------------------------------------------------- 
    137140; attribution du mask et des tableau de longitude et latitude 
     
    191194   if interpolle then t2 = msku*shift(msku,1,0)*mskv*shift(mskv,0,1) $ 
    192195   ELSE t2 = tmask[firstxt:lastxt,firstyt:lastyt,firstzt] 
    193    if NOT keyword_set(key_periodic) OR nx NE jpi then t2(0, *)=0. 
    194    t2(*,0)=0. 
     196   if NOT keyword_set(key_periodic) OR nx NE jpi then t2[0, *]=0. 
     197   t2[*,0]=0. 
    195198   terre=where(t2 eq 0) 
    196199   if terre[0] ne -1 then begin 
    197       u(terre)=1e5 
    198       v(terre)=1e5 
     200      u[terre]=1e5 
     201      v[terre]=1e5 
    199202   ENDIF 
    200203;----------------------------------------------------------- 
  • trunk/SRC/ToBeReviewed/PLOTS/VECTEUR/vecteur.pro

    r41 r114  
    8181; angle peut etre un tableau. 
    8282; 
     83; 
     84  compile_opt idl2, strictarrsubs 
     85; 
    8386@common 
    8487; quelle est la longeur en coordonnees normales d''un trait qui fera 1 
     
    103106; normalise le vecteur 
    104107; 
     108; 
     109  compile_opt idl2, strictarrsubs 
     110; 
    105111   IF n_elements(w) NE 0 THEN BEGIN  
    106112      norme = sqrt(u^2.+v^2.+w^2.) 
    107113      ind = where(norme NE 0) 
    108       u(ind) = u(ind)/norme[ind] 
    109       v(ind) = v(ind)/norme[ind] 
    110       w(ind) = w(ind)/norme[ind] 
     114      u[ind] = u[ind]/norme[ind] 
     115      v[ind] = v[ind]/norme[ind] 
     116      w[ind] = w[ind]/norme[ind] 
    111117   ENDIF ELSE BEGIN 
    112118      norme = sqrt(u^2.+v^2.) 
    113119      ind = where(norme NE 0) 
    114       u(ind) = u(ind)/norme[ind] 
    115       v(ind) = v(ind)/norme[ind] 
     120      u[ind] = u[ind]/norme[ind] 
     121      v[ind] = v[ind]/norme[ind] 
    116122   ENDELSE  
    117123END 
     
    120126             , VECTCOLOR = vectcolor, VECTTHICK = vectthick, VECTREFPOS = vectrefpos $ 
    121127             , VECTREFFORMAT = vectrefformat, NOVECTREF = novectref, _extra = extra 
     128; 
     129  compile_opt idl2, strictarrsubs 
     130; 
    122131@common 
    123132   tempsun = systime(1)         ; pour key_performance 
     
    202211   r = cv_coord(from_sphere=coord_sphe,/to_rect,/degrees) 
    203212; 
    204    x0 = reform(r(0, *), nx, ny) 
    205    y0 = reform(r(1, *), nx, ny) 
    206    z0 = reform(r(2, *), nx, ny) 
     213   x0 = reform(r[0, *], nx, ny) 
     214   y0 = reform(r[1, *], nx, ny) 
     215   z0 = reform(r[2, *], nx, ny) 
    207216; 
    208217; etape 1, b) 
    209218; 
    210219; Construction du vecteur nu (resp. nv), vecteur norme porte par 
    211 ; l''axe des points u(i,j) et u(i-1,j) (resp v(i,j) et v(i,j-1)) 
     220; l''axe des points u[i,j] et u[i-1,j] (resp v[i,j] et v[i,j-1]) 
    212221; qui definissent pour chaque point sur la shere les directions locales 
    213222; associee a u et v. ces vecteurs definissent un repere orthonorme 
     
    219228   radius = replicate(1,nxgd*nygd) 
    220229   IF finite(glamu[0]*gphiu[0]) NE 0 THEN $ 
    221      coord_sphe = transpose([ [(glamu[indice2d])[*]], [(gphiu[indice2d])[*]], [radius(*)] ]) $ 
    222    ELSE coord_sphe = transpose([ [(glamf[indice2d])[*]], [(gphit[indice2d])[*]], [radius(*)] ]) 
     230     coord_sphe = transpose([ [(glamu[indice2d])[*]], [(gphiu[indice2d])[*]], [radius[*]] ]) $ 
     231   ELSE coord_sphe = transpose([ [(glamf[indice2d])[*]], [(gphit[indice2d])[*]], [radius[*]] ]) 
    223232   r = cv_coord(from_sphere=coord_sphe,/to_rect,/degrees) 
    224233; coordonnes de points de la grille u en cartesien 
    225    ux = reform(r(0, *), nxgd, nygd) 
    226    uy = reform(r(1, *), nxgd, nygd) 
    227    uz = reform(r(2, *), nxgd, nygd) 
     234   ux = reform(r[0, *], nxgd, nygd) 
     235   uy = reform(r[1, *], nxgd, nygd) 
     236   uz = reform(r[2, *], nxgd, nygd) 
    228237; calcul de nu  
    229238   nux = ux-shift(ux, 1, 0) 
     
    242251; definition de nv 
    243252   IF finite(glamv[0]*gphiv[0]) NE 0 THEN $ 
    244    coord_sphe = transpose([ [(glamv[indice2d])[*]], [(gphiv[indice2d])[*]], [radius(*)] ]) $ 
    245    ELSE coord_sphe = transpose([ [(glamt[indice2d])[*]], [(gphif[indice2d])[*]], [radius(*)] ])                 
     253   coord_sphe = transpose([ [(glamv[indice2d])[*]], [(gphiv[indice2d])[*]], [radius[*]] ]) $ 
     254   ELSE coord_sphe = transpose([ [(glamt[indice2d])[*]], [(gphif[indice2d])[*]], [radius[*]] ])                 
    246255   r = cv_coord(from_sphere=coord_sphe,/to_rect,/degrees) 
    247256; coordonnes de points de la grille v en cartesien 
    248    vx = reform(r(0, *), nxgd, nygd) 
    249    vy = reform(r(1, *), nxgd, nygd) 
    250    vz = reform(r(2, *), nxgd, nygd) 
     257   vx = reform(r[0, *], nxgd, nygd) 
     258   vy = reform(r[1, *], nxgd, nygd) 
     259   vz = reform(r[2, *], nxgd, nygd) 
    251260; calcul de nv  
    252261   nvx = vx-shift(vx, 0, 1) 
     
    290299; coordonnees de la pointe en spherique 
    291300 
    292    coord_rect = transpose([ [x1(*)], [y1(*)], [z1(*)] ]) 
     301   coord_rect = transpose([ [x1[*]], [y1[*]], [z1[*]] ]) 
    293302   r = cv_coord(from_rect=coord_rect,/to_sphere,/degrees) 
    294    glam1 = reform(r(0, *), nx, ny) 
    295    gphi1 = reform(r(1, *), nx, ny) 
     303   glam1 = reform(r[0, *], nx, ny) 
     304   gphi1 = reform(r[1, *], nx, ny) 
    296305 
    297306; 
     
    303312; 
    304313   ind = where(glam1 LT !x.range[0] AND glam1+360. LE !x.range[1]) 
    305    if ind[0] NE -1 then glam1(ind) = glam1(ind)+360. 
     314   if ind[0] NE -1 then glam1[ind] = glam1[ind]+360. 
    306315   ind = where(glam1 GT !x.range[1] AND glam1-360. GE !x.range[0]) 
    307    if ind[0] NE -1 then glam1(ind) = glam1(ind)-360. 
     316   if ind[0] NE -1 then glam1[ind] = glam1[ind]-360. 
    308317 
    309318   ind = where(glam LT !x.range[0] AND glam+360. LE !x.range[1]) 
    310    if ind[0] NE -1 then glam(ind) = glam(ind)+360. 
     319   if ind[0] NE -1 then glam[ind] = glam[ind]+360. 
    311320   ind = where(glam  GT !x.range[1] AND glam-360. GE !x.range[0]) 
    312    if ind[0] NE -1 then glam(ind) = glam(ind)-360. 
     321   if ind[0] NE -1 then glam[ind] = glam[ind]-360. 
    313322; 
    314323; 
     
    316325; 
    317326   r = convert_coord(glam,gphi,/data,/to_normal)  
    318    x0 = r(0, *)                 ; coordonnes normales du debut de la fleche 
    319    y0 = r(1, *)                 ;  
     327   x0 = r[0, *]                 ; coordonnes normales du debut de la fleche 
     328   y0 = r[1, *]                 ;  
    320329    
    321330   r = convert_coord(glam1,gphi1,/data,/to_normal)  
    322    x1 = r(0, *)                 ; coordonnes normales de la fin de la fleche (avant scaling) 
    323    y1 = r(1, *)                 ;  
     331   x1 = r[0, *]                 ; coordonnes normales de la fin de la fleche (avant scaling) 
     332   y1 = r[1, *]                 ;  
    324333; 
    325334; tests pour eviter que des fleches soient dessineees hors du domaine 
     
    384393; 
    385394   r = cv_coord(from_polar = transpose([ [dirpol[*]], [norme[*]] ]), /to_rect) 
    386    composantex = r(0, *) 
    387    composantey = r(1, *) 
     395   composantex = r[0, *] 
     396   composantey = r[1, *] 
    388397; 
    389398   x1 = x0+composantex 
     
    395404 
    396405   points = where(msk EQ 1) 
    397    IF points[0] NE -1 THEN arrow, x0(points), y0(points), x1(points), y1(points), /norm $ 
     406   IF points[0] NE -1 THEN arrow, x0[points], y0[points], x1[points], y1[points], /norm $ 
    398407    , hsize = -.2, COLOR = vectcolor, THICK = vectthick 
    399408; 
  • trunk/SRC/ToBeReviewed/PLOTS/VECTEUR/velovect.pro

    r97 r114  
    100100PRO VELOVECT,U,V,X,Y, Missing = Missing, Length = length, Dots = dots,  $ 
    101101        Color=color, CLIP=clip, NOCLIP=noclip, OVERPLOT=overplot, _EXTRA=extra 
     102; 
     103  compile_opt idl2, strictarrsubs 
     104; 
    102105        on_error,2                      ;Return to caller if an error occurs 
    103106        s = size(u) 
  • trunk/SRC/ToBeReviewed/PLOTS/axe.pro

    r42 r114  
    5050;------------------------------------------------------------ 
    5151PRO axe, coupe,tempsmin,tempsmax, REVERSE_X = reverse_x, REVERSE_Y = reverse_y, SIN = sin, SEPDATE = sepdate, DIGITSYEAR = digitsyear, _EXTRA = ex 
     52; 
     53  compile_opt idl2, strictarrsubs 
     54; 
    5255@common 
    5356   tempsun = systime(1)         ; pour key_performance 
  • trunk/SRC/ToBeReviewed/PLOTS/legende.pro

    r42 r114  
    4747            , INTERVALLE = intervalle, TYPE_YZ = type_yz, VARNAME2 = varname2 $ 
    4848            , NPTS = npts, _EXTRA = ex 
     49; 
     50  compile_opt idl2, strictarrsubs 
     51; 
    4952@common 
    5053   tempsun = systime(1)         ; pour key_performance 
  • trunk/SRC/ToBeReviewed/PLOTS/plotsym.pro

    r97 r114  
    3232                  angle=angle, box=box, line=line, scale=scale, $ 
    3333                  _extra=extra 
     34; 
     35  compile_opt idl2, strictarrsubs 
     36; 
    3437if not keyword_set(scale) then scale=1.0 
    3538if not keyword_set(angle) then angle=0.0 
  • trunk/SRC/ToBeReviewed/PLOTS/reinitplt.pro

    r42 r114  
    4141pro reinitplt, all=all,x=x,y=y,z=z,p=p, invert=invert 
    4242;------------------------------------------------------------ 
     43; 
     44  compile_opt idl2, strictarrsubs 
     45; 
    4346        clearx = 0 
    4447        cleary = 0 
  • trunk/SRC/ToBeReviewed/PLOTS/style.pro

    r42 r114  
    4444;------------------------------------------------------------ 
    4545pro style,labstyle,level_z2d,linestyle,thick 
     46; 
     47  compile_opt idl2, strictarrsubs 
     48; 
    4649   case labstyle of 
    4750      0: begin 
     
    7578         a=replicate(0,n_elements(level_z2d)-n) 
    7679         c=replicate(2,n)          
    77          if seuil eq level_z2d(n) then begin 
     80         if seuil eq level_z2d[n] then begin 
    7881            thick=[replicate(1,n),2,replicate(1,n_elements(level_z2d)-1-n)] 
    7982            linestyle=[c,a] 
     
    8689      3: begin 
    8790         n = n_elements(level_z2d) 
    88          seuil = level_z2d(1+n/2) 
     91         seuil = level_z2d[1+n/2] 
    8992 
    9093         thick = intarr(n) 
    91          thick(indgen((n)/4)*4) = 1 
    92          thick(indgen((n)/4)*4+1) = 1 
    93          thick(indgen((n)/4)*4+2) = 2 
    94          thick(indgen((n)/4)*4+3) = 1 
     94         thick[indgen(n/4)*4] = 1 
     95         thick[indgen(n/4)*4+1] = 1 
     96         thick[indgen(n/4)*4+2] = 2 
     97         thick[indgen(n/4)*4+3] = 1 
    9598 
    9699         linestyle = intarr(n) 
    97          linestyle(indgen((n)/4)*4) = 3 
    98          linestyle(indgen((n)/4)*4+1) = 0 
    99          linestyle(indgen((n)/4)*4+2) = 0 
    100          linestyle(indgen((n)/4)*4+3) = 0 
     100         linestyle[indgen(n/4)*4] = 3 
     101         linestyle[indgen(n/4)*4+1] = 0 
     102         linestyle[indgen(n/4)*4+2] = 0 
     103         linestyle[indgen(n/4)*4+3] = 0 
    101104 
    102105         labels = intarr(n) 
    103          labels(indgen((n)/2)*2) = 1 
    104          labels(n/2) = 0 
     106         labels[indgen(n/2)*2] = 1 
     107         labels[n/2] = 0 
    105108 
    106109         return 
  • trunk/SRC/ToBeReviewed/PLOTS/symbols.pro

    r42 r114  
    5050;- 
    5151pro symbols,nsym,scale,color=col 
     52; 
     53  compile_opt idl2, strictarrsubs 
     54; 
    5255on_error,2 
    5356fill = 0 
     
    6568                      xarr = fltarr(5) 
    6669                      yarr = xarr 
    67                       xarr(1) = 10. 
    68                       xarr(2) = 6. 
    69                       yarr(2) = 2. 
     70                      xarr[1] = 10. 
     71                      xarr[2] = 6. 
     72                      yarr[2] = 2. 
    7073                      ;nsyms greater than 10 should be filled arrows 
    7174                      if nsym gt 10 then begin 
    72                          xarr(3) = 6.  
    73                          xarr(4) = 10. 
    74                          yarr(3) = -2. 
     75                         xarr[3] = 6.  
     76                         xarr[4] = 10. 
     77                         yarr[3] = -2. 
    7578                         fill = 1 
    7679                      endif else begin 
    77                          xarr(3) = 10. 
    78                          xarr(4) = 6. 
    79                          yarr(4) = -2. 
     80                         xarr[3] = 10. 
     81                         xarr[4] = 6. 
     82                         yarr[4] = -2. 
    8083                      endelse 
    8184                      case 1 of 
     
    8588                            xarr = extrac(xarr,0,11) 
    8689                            yarr = extrac(yarr,0,11) 
    87                             yarr(6) = 0.5 
    88                             xarr(7) = 6 
    89                             yarr(7) = 0.5 
    90                             xarr(8) = 6 
    91                             yarr(8) = -0.5 
    92                             yarr(9) = -0.5 
     90                            yarr[6] = 0.5 
     91                            xarr[7] = 6 
     92                            yarr[7] = 0.5 
     93                            xarr[8] = 6 
     94                            yarr[8] = -0.5 
     95                            yarr[9] = -0.5 
    9396                            if nsym eq 12 then begin 
    9497                               rotation,xarr,yarr,180,nx,ny 
     
    124127                      xarr = fltarr(5) + 3 
    125128                      yarr = xarr 
    126                       xarr(1) = -3. 
    127                       xarr(2) = -3. 
    128                       yarr(2) = -3. 
    129                       yarr(3) = -3. 
     129                      xarr[1] = -3. 
     130                      xarr[2] = -3. 
     131                      yarr[2] = -3. 
     132                      yarr[3] = -3. 
    130133                      if (nsym eq 21)+(nsym eq 31) then begin 
    131134                         rotation,xarr,yarr,45,nx,ny 
     
    139142                      yarr = fltarr(4) - 6./4. 
    140143                      xarr = fltarr(4) - 6./2. 
    141                       xarr(1) = 6./2. 
    142                       xarr(2) = 0. 
    143                       yarr(2) = 6.*sqrt(3.)/2. - 6./4. 
     144                      xarr[1] = 6./2. 
     145                      xarr[2] = 0. 
     146                      yarr[2] = 6.*sqrt(3.)/2. - 6./4. 
    144147                      if nsym eq 32 then fill = 1 
    145148                                    end 
     
    147150                      xarr = fltarr(2) + 1 
    148151                      yarr = xarr * 0. 
    149                       xarr(1) = -1. 
     152                      xarr[1] = -1. 
    150153                                    end 
    151154endcase 
  • trunk/SRC/ToBeReviewed/POSTSCRIPT/calibre.pro

    r16 r114  
    8888             , LANDSCAPE = lanscape, _extra = ex 
    8989;--------------------------------------------------------- 
     90; 
     91  compile_opt idl2, strictarrsubs 
     92; 
    9093@cm_4ps 
    9194  IF NOT keyword_set(key_forgetold) THEN BEGIN 
  • trunk/SRC/ToBeReviewed/POSTSCRIPT/chcolps.pro

    r74 r114  
    11PRO format_colortable_hexa, table 
     2; 
     3  compile_opt idl2, strictarrsubs 
     4; 
    25 
    36    tvlct, r, g, b, /get 
     
    2225; 
    2326; Fabrique le bloc de colortable 
     27; 
     28; 
     29  compile_opt idl2, strictarrsubs 
    2430; 
    2531 
     
    4955; 
    5056; recupere les palettes 
     57; 
     58; 
     59  compile_opt idl2, strictarrsubs 
    5160; 
    5261    lct, n1 
  • trunk/SRC/ToBeReviewed/STATISTICS/a_correlate2d.pro

    r21 r114  
    6161 
    6262FUNCTION Auto_Cov2d, X, Lag, Double = Double, zero2nan = zero2nan 
     63; 
     64  compile_opt idl2, strictarrsubs 
     65; 
    6366   XDim = SIZE(X, /dimensions) 
    6467   nx = XDim[0] 
     
    7679 
    7780FUNCTION A_Correlate2d, X, Lag, Covariance = Covariance, Double = Double 
     81; 
     82  compile_opt idl2, strictarrsubs 
     83; 
    7884 
    7985;Compute the sample-autocorrelation or autocovariance of (Xt, Xt+l) 
  • trunk/SRC/ToBeReviewed/STATISTICS/a_timecorrelate.pro

    r21 r114  
    7979FUNCTION TimeAuto_Cov, X, M, nT, Double = Double, zero2nan = zero2nan 
    8080;Sample autocovariance function 
     81; 
     82  compile_opt idl2, strictarrsubs 
     83; 
    8184   TimeDim = size(X, /n_dimensions) 
    8285   Xmean = TOTAL(X, TimeDim, Double = Double) / nT 
     
    107110 
    108111FUNCTION A_TimeCorrelate, X, Lag, COVARIANCE = Covariance, DOUBLE = Double 
     112; 
     113  compile_opt idl2, strictarrsubs 
     114; 
    109115 
    110116;Compute the sample-autocorrelation or autocovariance of (Xt, Xt+l) 
  • trunk/SRC/ToBeReviewed/STRING/.idlwave_catalog

    r76 r114  
    1515   ("putfile" pro nil (lib "putfile.pro" nil "saxo") "%s, file, s" (nil ("error") ("help"))) 
    1616   ("STR_SIZE" fun nil (lib "str_size.pro" nil "saxo") "Result = %s(string, targetWidth)" (nil ("INITSIZE") ("STEP"))) 
    17    ("Strcnt" fun nil (lib "strcnt.pro" nil "saxo") "Result = %s(strn, substrn, startpos)" (nil ("HELP"))) 
     17   ("strcnt" fun nil (lib "strcnt.pro" nil "saxo") "Result = %s(strn, substrn, startpos)" (nil ("HELP"))) 
    1818   ("too_cool" fun nil (lib "string2struct.pro" nil "saxo") "Result = %s" (nil ("_extra"))) 
    1919   ("string2struct" fun nil (lib "string2struct.pro" nil "saxo") "Result = %s(strVal)" (nil)) 
  • trunk/SRC/ToBeReviewed/STRING/chkeywd.pro

    r18 r114  
    7373;------------------------------------------------------------ 
    7474FUNCTION chkeywd, stringin, keywdname, keywdvalue, SEPARATOR = separator, AFTER = after 
     75; 
     76  compile_opt idl2, strictarrsubs 
     77; 
    7578 
    7679   stringout = stringin 
  • trunk/SRC/ToBeReviewed/STRING/lenstr.pro

    r97 r114  
    2727 
    2828function lenstr,str 
     29; 
     30  compile_opt idl2, strictarrsubs 
     31; 
    2932   dsave=!d.name 
    3033 
     
    5457         w=fltarr(nn) 
    5558         for i=0,nn-1 do begin 
    56             xyouts,0,0,/device,str(i),width=ww 
    57             w(i)=ww 
     59            xyouts,0,0,/device,str[i],width=ww 
     60            w[i]=ww 
    5861         endfor 
    5962      end 
  • trunk/SRC/ToBeReviewed/STRING/str_size.pro

    r18 r114  
    6464 
    6565FUNCTION STR_SIZE, string, targetWidth, INITSIZE=initsize, STEP=step 
     66; 
     67  compile_opt idl2, strictarrsubs 
     68; 
    6669 
    6770ON_ERROR, 1 
  • trunk/SRC/ToBeReviewed/STRING/strcnt.pro

    r18 r114  
    4848;  This code comes with absolutely NO warranty; see DISCLAIMER for details. 
    4949;- 
    50 FUNCTION Strcnt, strn, substrn, startpos, $ 
     50FUNCTION strcnt, strn, substrn, startpos, $ 
    5151                 HELP=Help 
     52; 
     53  compile_opt idl2, strictarrsubs 
     54; 
    5255 
    5356; Return to caller if error. 
     
    8891    IF strlen(substrn) EQ 1 THEN BEGIN 
    8992        tmpstrn = byte(TmpStrn) 
    90         count = n_elements(where(TmpStrn EQ (byte(substrn))(0)))  
     93        count = n_elements(where(TmpStrn EQ (byte(substrn))[0]))  
    9194    ENDIF ELSE BEGIN  
    9295        count = 0L 
  • trunk/SRC/ToBeReviewed/STRING/string2struct.pro

    r97 r114  
    44; 
    55function too_cool,_extra=extra 
     6; 
     7  compile_opt idl2, strictarrsubs 
     8; 
    69return,extra 
    710end 
     
    6871 
    6972function string2struct,strVal 
     73; 
     74  compile_opt idl2, strictarrsubs 
     75; 
    7076r = execute('extra = too_cool(' + strVal[0] +')') 
    7177;if r = 0 then user did not enter keywords correctly so 
  • trunk/SRC/ToBeReviewed/STRING/strkeywd.pro

    r18 r114  
    7171;------------------------------------------------------------ 
    7272FUNCTION strkeywd, struct 
     73; 
     74  compile_opt idl2, strictarrsubs 
     75; 
    7376   if size(struct, /type) NE 8 then return,  '' 
    7477   tname = tag_names(struct) 
  • trunk/SRC/ToBeReviewed/STRING/strrepl.pro

    r18 r114  
    7676 
    7777function strrepl,str,agument1,rchar 
     78; 
     79  compile_opt idl2, strictarrsubs 
     80; 
    7881    
    7982   if (n_elements(str) eq 0) then return,'' 
  • trunk/SRC/ToBeReviewed/STRING/strright.pro

    r18 r114  
    5252 
    5353function strright,s,lastn 
     54; 
     55  compile_opt idl2, strictarrsubs 
     56; 
    5457  
    5558    on_error,2   ; return to caller 
  • trunk/SRC/ToBeReviewed/STRING/strsci.pro

    r18 r114  
    106106function StrSci, Data, Format=Format, POT_Only=POT_Only, $ 
    107107             MANTISSA_ONLY=MANTISSA_ONLY,SHORT=SHORT,TRIM=TRIM 
     108; 
     109  compile_opt idl2, strictarrsubs 
     110; 
    108111 
    109112   ;==================================================================== 
  • trunk/SRC/ToBeReviewed/STRING/strtok.pro

    r18 r114  
    5959FUNCTION Strtok, string, token, $ 
    6060                 TRIM=trim, HELP=Help 
     61; 
     62  compile_opt idl2, strictarrsubs 
     63; 
    6164 
    6265; Back to the caller if error occurs. 
  • trunk/SRC/ToBeReviewed/STRING/strtrans.pro

    r18 r114  
    6060FUNCTION strtrans, InputString, from, to, ned,  $ 
    6161                   HELP=Help 
     62; 
     63  compile_opt idl2, strictarrsubs 
     64; 
    6265 
    6366; Bomb out to caller if error. 
  • trunk/SRC/ToBeReviewed/STRING/strwhere.pro

    r18 r114  
    6060 
    6161function strwhere,str,schar,Count 
     62; 
     63  compile_opt idl2, strictarrsubs 
     64; 
    6265  
    6366  
  • trunk/SRC/ToBeReviewed/STRING/tostr.pro

    r18 r114  
    5050;------------------------------------------------------------ 
    5151FUNCTION tostr, input 
     52; 
     53  compile_opt idl2, strictarrsubs 
     54; 
    5255 
    5356   case 1 of 
  • trunk/SRC/ToBeReviewed/STRUCTURE/chkstru.pro

    r27 r114  
    2727;        INDEX --> a named variable that will contain the indices of 
    2828;             the required field names in the structure. They can then 
    29 ;             be assessed through structure.(index(i)) . Index will 
     29;             be assessed through structure.(index[i]) . Index will 
    3030;             contain -1 for all fields entries that are not in the 
    3131;             structure. 
     
    7575 
    7676function chkstru,structure,fields,index=index,verbose=verbose, extract = extract 
     77; 
     78  compile_opt idl2, strictarrsubs 
     79; 
    7780  
    7881 
     
    9194  
    9295     s = size(structure) 
    93      if (s(1+s(0)) ne 8) then begin 
     96     if (s[1+s[0]] ne 8) then begin 
    9497         if(keyword_set(verbose)) then $ 
    9598             ras = report('CHKSTRU: ** No structure passed ! **') 
     
    109112 
    110113     for i=0,n_elements(fields)-1 do begin 
    111          ind = where(names eq strupcase(fields(i))) 
    112          if (ind(0) lt 0) then begin 
     114         ind = where(names eq strupcase(fields[i])) 
     115         if (ind[0] lt 0) then begin 
    113116             if(keyword_set(verbose)) then $ 
    114                 ras = report('CHKSTRU: ** Cannot find field '+fields(i)+' ! **')   
    115          endif else index(i) = ind(0) 
     117                ras = report('CHKSTRU: ** Cannot find field '+fields[i]+' ! **') 
     118         endif else index[i] = ind[0] 
    116119     endfor 
    117120  
  • trunk/SRC/ToBeReviewed/STRUCTURE/extractstru.pro

    r27 r114  
    6060;------------------------------------------------------------ 
    6161FUNCTION extractstru, stru, liste, GARDE = garde, VIRE = vire 
     62; 
     63  compile_opt idl2, strictarrsubs 
     64; 
    6265   if size(stru, /type) NE 8 then return,  -1 
    6366   if size(liste, /type) NE 7 then return,  -1 
  • trunk/SRC/ToBeReviewed/STRUCTURE/mixstru.pro

    r74 r114  
    6060;------------------------------------------------------------ 
    6161FUNCTION mixstru, stru1, stru2 
     62; 
     63  compile_opt idl2, strictarrsubs 
     64; 
    6265@cm_general 
    6366 
  • trunk/SRC/ToBeReviewed/STRUCTURE/struct2string.pro

    r27 r114  
    4545;------------------------------------------------------------ 
    4646FUNCTION struct2string, struct, CUT_IN_STRING = cut_in_string, MAX_STRUCT_LENGTH = max_struct_length, DIRECT2STRING = direct2string  
     47; 
     48  compile_opt idl2, strictarrsubs 
     49; 
    4750   if size(struct, /type) NE 8 then return,  '' 
    4851   if NOT keyword_set(max_struct_length) then max_struct_length = 10000l 
  • trunk/SRC/ToBeReviewed/STRUCTURE/where_tag.pro

    r97 r114  
    5555                                        RANGE=range, VALUES=values 
    5656;First check required parameters... 
     57; 
     58  compile_opt idl2, strictarrsubs 
     59; 
    5760 
    5861        Ntag = N_tags( Struct ) 
  • trunk/SRC/ToBeReviewed/TRIANGULATION/ciseauxtri.pro

    r29 r114  
    3939FUNCTION ciseauxtri, triang, glam, gphi, TOUT = tout, _EXTRA = ex 
    4040;--------------------------------------------------------- 
     41; 
     42  compile_opt idl2, strictarrsubs 
     43; 
    4144@cm_4mesh 
    4245  IF NOT keyword_set(key_forgetold) THEN BEGIN 
  • trunk/SRC/ToBeReviewed/TRIANGULATION/completecointerre.pro

    r29 r114  
    3636;------------------------------------------------------------ 
    3737PRO draw_corner_triangle, lons, lats, seuil, CONT_COLOR = cont_color, _extra = ex 
     38; 
     39  compile_opt idl2, strictarrsubs 
     40; 
    3841@cm_4mesh 
    3942; the triangle must not be out of the domain 
     
    5558                       , CONT_COLOR = cont_color, INDICEZOOM = indicezoom $ 
    5659                       , _extra = ex 
     60; 
     61  compile_opt idl2, strictarrsubs 
     62; 
    5763@common 
    5864;------------------------------------------------------------ 
  • trunk/SRC/ToBeReviewed/TRIANGULATION/definetri.pro

    r29 r114  
    8989;- 
    9090FUNCTION definetri, nx, ny, downward 
     91; 
     92  compile_opt idl2, strictarrsubs 
     93; 
    9194   nx = long(nx) 
    9295   ny = long(ny) 
     
    109112; the lower-left corner of the rectangle. 
    110113      upward = bytarr(nx, ny)+1 
    111       upward(*, ny-1) = 0 
    112       upward(nx-1, *) = 0 
     114      upward[*, ny-1] = 0 
     115      upward[nx-1, *] = 0 
    113116      if n_elements(downward) NE 0 then upward[downward] = 0 
    114117      upward = where(upward EQ 1) 
  • trunk/SRC/ToBeReviewed/TRIANGULATION/definetri_e.pro

    r29 r114  
    11function numtri, index, nx, ny 
     2; 
     3  compile_opt idl2, strictarrsubs 
     4; 
    25 
    36   y=index/nx 
     
    5659;- 
    5760FUNCTION definetri_e, nx, ny, singular, SHIFTED = shifted 
     61; 
     62  compile_opt idl2, strictarrsubs 
     63; 
    5864   nx = long(nx) 
    5965   ny = long(ny) 
  • trunk/SRC/ToBeReviewed/TRIANGULATION/dessinetri.pro

    r29 r114  
    5454 
    5555PRO dessinetri, tri, x, y, WAIT = wait, ONEBYONE = onebyone, FILL = fill, CHANGECOLOR = changecolor, _extra = ex 
     56; 
     57  compile_opt idl2, strictarrsubs 
     58; 
    5659@common 
    5760   tempsun = systime(1)         ; pour key_performance 
  • trunk/SRC/ToBeReviewed/TRIANGULATION/drawcoast_c.pro

    r29 r114  
    11PRO drawcoast_c, mask, xf, yf, nx, ny, COAST_COLOR = coast_color, COAST_THICK = coast_thick, YSEUIL = yseuil, XSEUIL = xseuil, _extra = ex 
    22;--------------------------------------------------------- 
     3; 
     4  compile_opt idl2, strictarrsubs 
     5; 
    36@cm_4mesh 
    47  IF NOT keyword_set(key_forgetold) THEN BEGIN 
  • trunk/SRC/ToBeReviewed/TRIANGULATION/drawcoast_e.pro

    r29 r114  
    11PRO drawcoast_e, mask, xf, yf, nx, ny, COAST_COLOR = coast_color, COAST_THICK = coast_thick, YSEUIL = yseuil, XSEUIL = xseuil, onemore = onemore, _extra = ex 
    22;--------------------------------------------------------- 
     3; 
     4  compile_opt idl2, strictarrsubs 
     5; 
    36@cm_4mesh 
    47  IF NOT keyword_set(key_forgetold) THEN BEGIN 
  • trunk/SRC/ToBeReviewed/TRIANGULATION/drawsectionbottom.pro

    r67 r114  
    4646                       , OVERPLOT = overplot, _extra = ex 
    4747;--------------------------------------------------------- 
     48; 
     49  compile_opt idl2, strictarrsubs 
     50; 
    4851@cm_general 
    4952  IF NOT keyword_set(key_forgetold) THEN BEGIN 
     
    9295; appens when the bottom limit is defined between T[k] and W[k] 
    9396; points) 
    94   IF min(depthsin) GT -1 THEN BEGIN 
     97  IF min(depthsin) GT -1 OR max(total(mask, 2)) EQ nz THEN BEGIN 
    9598    zmin = min(!y.range)-deltaz 
    9699    depths = [[replicate(zmin, nx)], [depths]] 
  • trunk/SRC/ToBeReviewed/TRIANGULATION/fillcornermask.pro

    r67 r114  
    3838                    , CONT_COLOR = cont_color, INDICEZOOM = indicezoom $ 
    3939                    , _extra = ex 
     40; 
     41  compile_opt idl2, strictarrsubs 
     42; 
    4043@common 
    4144;------------------------------------------------------------ 
  • trunk/SRC/ToBeReviewed/TRIANGULATION/section.pro

    r29 r114  
    3939;--------------------------------------------------------- 
    4040; include common 
     41; 
     42  compile_opt idl2, strictarrsubs 
     43; 
    4144@cm_4mesh 
    4245@cm_4data 
     
    342345    xsave = !x 
    343346    ysave = !y 
    344     plt, findgen(nx, ny), /nodata, /nofill, /rempli, title = '', subtitle = '', coast_thick = 2, window = showbuild 
     347    plt, findgen(nx, ny), /nodata, /nofill, /rempli, title = '', subtitle = '' $ 
     348         , coast_thick = 2, window = showbuild 
    345349    !p.title = '' 
    346350    !p.subtitle = '' 
     
    356360    plots, float(points2), imaginary(points2), color = 150, psym = 1 
    357361    plots, float(inter), imaginary(inter), color = 250, psym = 1 
    358      
    359     IF terre[0] NE -1 THEN plots, float(inter[terre]), imaginary(inter[terre]), color = 0, psym = 1 
    360      
     362 
     363;  ?? bug ??    IF terre[0] NE -1 THEN plots, float(terre[inter]), imaginary(terre[inter]), color = 0, psym = 1 
     364      
    361365;      dummy = '' 
    362366;      read, dummy,  prompt = 'press return to continue' 
  • trunk/SRC/ToBeReviewed/TRIANGULATION/tracecote.pro

    r29 r114  
    5555;-------------------------------------------------------------- 
    5656; include commons 
     57; 
     58  compile_opt idl2, strictarrsubs 
     59; 
    5760@cm_4data 
    5861@cm_4mesh 
     
    9093; de projection choisie et du suport surlequel on fait le dessin 
    9194; (ecran ou postscript) 
    92    z = convert_coord(xf(*),yf(*),/data,/to_normal)  
     95   z = convert_coord(xf[*],yf[*],/data,/to_normal)  
    9396   xf = reform(z[0, *], nx, ny) 
    9497   yf = reform(z[1, *], nx, ny) 
  • trunk/SRC/ToBeReviewed/TRIANGULATION/tracemask.pro

    r29 r114  
    4040;------------------------------------------------------------ 
    4141PRO tracemask, maskentree, xin, yin, COAST_COLOR = coast_color, COAST_THICK = coast_thick, OVERPLOT = overplot, _extra = ex 
     42; 
     43; 
     44  compile_opt idl2, strictarrsubs 
    4245; 
    4346   if keyword_set(overplot) then return 
  • trunk/SRC/ToBeReviewed/TRIANGULATION/triangule.pro

    r29 r114  
    11FUNCTION triangule, maskentree, BASIC = basic, COINMONTE = coinmonte, COINDESCEND = coindescend, _extra = ex 
     2; 
     3  compile_opt idl2, strictarrsubs 
     4; 
    25@common 
    36; 
  • trunk/SRC/ToBeReviewed/TRIANGULATION/triangule_c.pro

    r29 r114  
    8282;------------------------------------------------------------ 
    8383FUNCTION triangule_c, maskentree, COINMONTE = coinmonte, COINDESCEND = coindescend, BASIC = basic, KEEP_CONT = keep_cont 
     84; 
     85  compile_opt idl2, strictarrsubs 
     86; 
    8487   tempsun = systime(1)         ; pour key_performance 
    8588;--------------------------------------------------------- 
     
    175178      tempdeux = systime(1)     ; pour key_performance =2 
    176179      pts_downward = pts_downward[1:n_elements(pts_downward)-1] 
    177       pts_downward = pts_downward(uniq(pts_downward, sort(pts_downward))) 
     180      pts_downward = pts_downward[uniq(pts_downward, sort(pts_downward))] 
    178181; aucun rectangle ne peut avoir comme coin en bas a gauche un element 
    179182; de la derniere colonne ou de la derniere ligne. 
  • trunk/SRC/ToBeReviewed/TRIANGULATION/triangule_e.pro

    r29 r114  
    3434                  , SHIFTED = shifted, BASIC = basic 
    3535;--------------------------------------------------------- 
     36; 
     37  compile_opt idl2, strictarrsubs 
     38; 
    3639@cm_4mesh 
    3740  IF NOT keyword_set(key_forgetold) THEN BEGIN 
  • trunk/SRC/ToBeReviewed/UTILITAIRE/fitintobox.pro

    r11 r114  
    5353;------------------------------------------------------------ 
    5454FUNCTION err_mess, sz, jpi, nx, jpj, ny, jpk, nz, jpt 
     55; 
     56  compile_opt idl2, strictarrsubs 
     57; 
    5558  IF n_elements(sz EQ 1) THEN $ 
    5659    RETURN, report(['Error: ' $ 
     
    7679;------------------------------------------------------------ 
    7780; include commons 
     81; 
     82  compile_opt idl2, strictarrsubs 
     83; 
    7884@cm_4mesh 
    7985@cm_4cal 
  • trunk/SRC/ToBeReviewed/UTILITAIRE/get_extra.pro

    r11 r114  
    2323 
    2424FUNCTION get_extra, _extra = extra 
     25; 
     26  compile_opt idl2, strictarrsubs 
     27; 
    2528    return, extra 
    2629END  
  • trunk/SRC/ToBeReviewed/UTILITAIRE/linearequation.pro

    r11 r114  
    4646;------------------------------------------------------------ 
    4747FUNCTION linearequation, point1, point2 
     48; 
     49  compile_opt idl2, strictarrsubs 
     50; 
    4851 
    4952   if size(point1, /type) EQ 6 OR size(point1, /type) EQ 9 then begin 
  • trunk/SRC/ToBeReviewed/UTILITAIRE/lineintersection.pro

    r11 r114  
    5454FUNCTION lineintersection, abc1, abc2, FLOAT = float 
    5555; 
     56; 
     57  compile_opt idl2, strictarrsubs 
     58; 
    5659   a1 = float(reform(abc1[0, *])) 
    5760   b1 = float(reform(abc1[1, *])) 
  • trunk/SRC/ToBeReviewed/UTILITAIRE/pwd.pro

    r11 r114  
    1818;------------------------------------------------------------ 
    1919PRO pwd 
     20; 
     21  compile_opt idl2, strictarrsubs 
     22; 
    2023   cd, current = pwd 
    2124   print, pwd 
  • trunk/SRC/ToBeReviewed/UTILITAIRE/report.pro

    r11 r114  
    6060;------------------------------------------------------------ 
    6161FUNCTION report, text, DEFAULT_NO = default_no, PARENT = parent, QUESTION = question, SIMPLE = simple, _extra = ex 
     62; 
     63  compile_opt idl2, strictarrsubs 
     64; 
    6265   res = -1                     ; 
    6366; on separe le texte en differentes lignes (separees par !C) si ce 
  • trunk/SRC/ToBeReviewed/UTILITAIRE/routine_name.pro

    r11 r114  
    5252FUNCTION routine_name,  remonte 
    5353; 
     54; 
     55  compile_opt idl2, strictarrsubs 
     56; 
    5457  help,  /traceback, output = name 
    5558  name = strtrim(name, 1)     ; on enleve les blancs en debut de ligne 
  • trunk/SRC/ToBeReviewed/UTILITAIRE/test.pro

    r11 r114  
    11pro test,ok=ok 
     2; 
     3  compile_opt idl2, strictarrsubs 
     4; 
    25if keyword_set(ok) then print,'OK' else print, 'No' 
    36return 
  • trunk/SRC/ToBeReviewed/UTILITAIRE/testvar.pro

    r11 r114  
    3838;------------------------------------------------------------ 
    3939FUNCTION testvar, var = var 
     40; 
     41  compile_opt idl2, strictarrsubs 
     42; 
    4043   if keyword_set(var) then return, var ELSE return,  0 
    4144end 
  • trunk/SRC/ToBeReviewed/UTILITAIRE/text_box.pro

    r97 r114  
    1717; keywords 
    1818;  pos          4 element vector specifying the box position and size 
    19 ;               pos(0),pos(1) specify the lower left corner coordinate 
    20 ;               pos(2),pos(3) specify the upper right corner coordinate 
     19;               pos[0],pos[1] specify the lower left corner coordinate 
     20;               pos[2],pos[3] specify the upper right corner coordinate 
    2121;               data window normalized coordinates are use 
    2222; 
     
    4343               center=center,right=right,box=box,vert_space=vert_space, _EXTRA = ex 
    4444; 
     45; 
     46  compile_opt idl2, strictarrsubs 
     47; 
    4548        ON_ERROR, 2 
    4649; 
     
    6366  xx2=xx1+nx 
    6467  yy2=yy1+ny 
    65   pos=[(xx1-nnx(0))/(nnx(1)-nnx(0)),(yy1-nny(0))/(nny(1)-nny(0)),$ 
    66        (xx2-nnx(0))/(nnx(1)-nnx(0)),(yy2-nny(0))/(nny(1)-nny(0))] 
     68  pos=[(xx1-nnx[0])/(nnx[1]-nnx[0]),(yy1-nny[0])/(nny[1]-nny[0]),$ 
     69       (xx2-nnx[0])/(nnx[1]-nnx[0]),(yy2-nny[0])/(nny[1]-nny[0])] 
    6770  posstring=string(form='(a,4(f5.2,a))',$ 
    68            ',pos=[',pos(0),',',pos(1),',',pos(2),',',pos(3),']') 
     71           ',pos=[',pos[0],',',pos[1],',',pos[2],',',pos[3],']') 
    6972  print,strcompress(posstring,/remove_all) 
    7073 
     
    7275endif else begin 
    7376   
    74   xx1 = nnx(0)+pos(0)*(nnx(1)-nnx(0)) 
    75   xx2 = nnx(0)+pos(2)*(nnx(1)-nnx(0)) 
    76   yy1 = nny(0)+pos(1)*(nny(1)-nnx(0)) 
    77   yy2 = nny(0)+pos(3)*(nny(1)-nnx(0)) 
     77  xx1 = nnx[0]+pos[0]*(nnx[1]-nnx[0]) 
     78  xx2 = nnx[0]+pos[2]*(nnx[1]-nnx[0]) 
     79  yy1 = nny[0]+pos[1]*(nny[1]-nnx[0]) 
     80  yy2 = nny[0]+pos[3]*(nny[1]-nnx[0]) 
    7881 
    7982endelse 
     
    107110;   print,f='(8a8)','charsz','i','ilines','n_lines','lpnt','wlen','sum','xwdth' 
    108111    for i=0,nwords-1 do begin 
    109       sum=sum+wlen(i)+blen 
     112      sum=sum+wlen[i]+blen 
    110113      if sum+3*blen gt xx2-xx1 then begin 
    111114        ilines=ilines+1 
    112         sum=wlen(i)+blen 
     115        sum=wlen[i]+blen 
    113116      endif 
    114       lpnt(i)=ilines         
     117      lpnt[i]=ilines         
    115118       
    116 ;      print,f='(f8.2,4i8,3f8.2)',charsize,i,ilines,n_lines,lpnt(i),$ 
    117 ;                 wlen(i)+blen,sum+3*blen,xx2-xx1 
     119;      print,f='(f8.2,4i8,3f8.2)',charsize,i,ilines,n_lines,lpnt[i],$ 
     120;                 wlen[i]+blen,sum+3*blen,xx2-xx1 
    118121    endfor         
    119122    case 1 of 
     
    131134for i=0,n_lines-1 do begin 
    132135  ii=where(lpnt eq i,nc) 
    133   maxlen=(total(wlen(ii))+nc*blen)>maxlen 
    134   lines(i)=string(f='(200a)',words(ii)+' ') 
    135 ; print,i,words(ii) 
    136 ; print,i,lines(i) 
     136  maxlen=(total(wlen[ii])+nc*blen)>maxlen 
     137  lines[i]=string(f='(200a)',words[ii]+' ') 
     138; print,i,words[ii] 
     139; print,i,lines[i] 
    137140endfor 
    138141 
     
    160163  for i_line = 0,n_lines-1 do begin 
    161164    yy = yy-dy 
    162 ;   print,xx,yy,lines(i_line),charsize 
    163     xyouts, xx, yy, lines(i_line), /device, charsize=charsize, $ 
     165;   print,xx,yy,lines[i_line],charsize 
     166    xyouts, xx, yy, lines[i_line], /device, charsize=charsize, $ 
    164167      alignment=align, color=color, font=-1, _extra = ex 
    165168  endfor 
  • trunk/SRC/ToBeReviewed/UTILITAIRE/undefine.pro

    r11 r114  
    3737;------------------------------------------------------------ 
    3838   PRO UNDEFINE, varname   
     39; 
     40  compile_opt idl2, strictarrsubs 
     41; 
    3942   tempvar = SIZE(TEMPORARY(varname)) 
    4043   END 
  • trunk/SRC/ToBeReviewed/UTILITAIRE/xfile.pro

    r11 r114  
    3030;------------------------------------------------------------ 
    3131PRO xfile, filename, _extra = ex 
     32; 
     33  compile_opt idl2, strictarrsubs 
     34; 
    3235pfile = strlowcase(filename) 
    3336; 
  • trunk/SRC/ToBeReviewed/UTILITAIRE/xhelp.pro

    r11 r114  
    4949;- 
    5050PRO xhelp, filename, _extra=ex 
     51; 
     52  compile_opt idl2, strictarrsubs 
     53; 
    5154 
    5255; filename est bien un string? 
     
    9194         if strpos(c,';-') eq 0 then readon=0 
    9295         if readon then begin 
    93             dum=where(byte(c) eq 9b,ntab) ; count tab characters 
    94             xsize=xsize > (strlen(c)+8*ntab) 
    95             a(i) = strmid(c,1,200) 
     96            dum=where(byte[c] eq 9b,ntab) ; count tab characters 
     97            xsize=xsize > (strlen[c]+8*ntab) 
     98            a[i] = strmid(c,1,200) 
    9699            i = i + 1 
    97100         endif 
     
    100103      if i EQ 0 then $ 
    101104         ras = report('le programme a etait mal ecrit, il n''y a pas d''en-tete... utiliser xfile.pro.') ELSE BEGIN  
    102          a = a(0:i-1) 
     105         a = a[0:i-1] 
    103106; on ecrit le contenu de a ds un widget 
    104107         xdisplayfile,'toto',text = a,title=pfile[n-1], _extra = ex 
  • trunk/SRC/ToBeReviewed/WIDGET/AUTOUR_de_XXX/buildcmd.pro

    r74 r114  
    3737; we get back the ids of the widget parts 
    3838;------------------------------------------------------------ 
     39; 
     40  compile_opt idl2, strictarrsubs 
     41; 
    3942  txtcmdid = widget_info(base, find_by_uname = 'txtcmd') 
    4043  domainid = widget_info(base, find_by_uname = 'domain') 
  • trunk/SRC/ToBeReviewed/WIDGET/AUTOUR_de_XXX/buildreadcmd.pro

    r74 r114  
    3333FUNCTION buildreadcmd, base, snameexp, procedure, type, BOXZOOM = boxzoom $ 
    3434                       , COMPLETE = complete, NAMEFIELD = namefield 
     35; 
     36; 
     37  compile_opt idl2, strictarrsubs 
    3538; 
    3639@cm_4cal ; for key_caltype 
  • trunk/SRC/ToBeReviewed/WIDGET/AUTOUR_de_XXX/changefield.pro

    r69 r114  
    11PRO changefield, base, newfieldname, BOXZOOM = boxzoom 
     2; 
     3; 
     4  compile_opt idl2, strictarrsubs 
    25; 
    36  widget_control, base, get_uvalue = top_uvalue 
  • trunk/SRC/ToBeReviewed/WIDGET/AUTOUR_de_XXX/changefile.pro

    r74 r114  
    11PRO changefile, base, newfilename, BOXZOOM = boxzoom, DATE1 = date1, DATE2 = date2, FIELDNAME = fieldname 
     2; 
     3; 
     4  compile_opt idl2, strictarrsubs 
    25; 
    36  widget_control, base, /hourglass 
     
    710  ELSE newfile = newfilename    ; it is already the index of the new file 
    811  if newfile EQ -1 then begin 
    9     nothing, report('invalid filename') 
     12    nothing = report('invalid filename') 
    1013    return 
    1114  endif 
  • trunk/SRC/ToBeReviewed/WIDGET/AUTOUR_de_XXX/createhistory.pro

    r69 r114  
    33;------------------------------------------------------------- 
    44; we save globalcommand in globaloldcommand 
     5; 
     6  compile_opt idl2, strictarrsubs 
     7; 
    58   widget_control,base, get_uvalue = top_uvalue 
    69   globalcommand = extractatt(top_uvalue, 'globalcommand') 
  • trunk/SRC/ToBeReviewed/WIDGET/AUTOUR_de_XXX/cutcmd.pro

    r69 r114  
    11PRO cutcmd, widcmd, toread, numberofread, prefix, nameexp, ending 
     2; 
     3; 
     4  compile_opt idl2, strictarrsubs 
    25; 
    36  dummy = where(byte(widcmd) EQ (byte('"'))[0], nbdblquote)  
  • trunk/SRC/ToBeReviewed/WIDGET/AUTOUR_de_XXX/definedefaultextra.pro

    r49 r114  
    11FUNCTION definedefaultextra, nomvariable 
     2; 
     3  compile_opt idl2, strictarrsubs 
     4; 
    25   case strlowcase(nomvariable) of 
    36;       'sn':BEGIN 
  • trunk/SRC/ToBeReviewed/WIDGET/AUTOUR_de_XXX/doubleclickaction.pro

    r69 r114  
    11PRO doubleclickaction, event 
    22;------------------------------------------------------------ 
     3; 
     4  compile_opt idl2, strictarrsubs 
     5; 
    36   widget_control, event.id , get_uvalue = uval 
    47   widget_control, event.top, get_uvalue = top_uvalue 
  • trunk/SRC/ToBeReviewed/WIDGET/AUTOUR_de_XXX/extractatt.pro

    r49 r114  
    11FUNCTION extractatt, top_uvalue, name 
     2; 
     3  compile_opt idl2, strictarrsubs 
     4; 
    25   taille = size(top_uvalue) 
    36   j = -1 
  • trunk/SRC/ToBeReviewed/WIDGET/AUTOUR_de_XXX/findline.pro

    r49 r114  
    11FUNCTION findline, top_uvalue, name 
     2; 
     3  compile_opt idl2, strictarrsubs 
     4; 
    25   taille = size(top_uvalue) 
    36   j = -1 
  • trunk/SRC/ToBeReviewed/WIDGET/AUTOUR_de_XXX/identifyclick.pro

    r49 r114  
    11FUNCTION identifyclick, event 
     2; 
     3  compile_opt idl2, strictarrsubs 
     4; 
    25   widget_control, event.id, get_uvalue=uval, /no_copy 
    36   thisEvent = TAG_NAMES(event, /Structure) 
  • trunk/SRC/ToBeReviewed/WIDGET/AUTOUR_de_XXX/inserthistory.pro

    r69 r114  
    11PRO inserthistory,  base, text, line1, line2 
    22;------------------------------------------------------------- 
     3; 
     4  compile_opt idl2, strictarrsubs 
     5; 
    36   widget_control,base, get_uvalue = top_uvalue 
    47   globalcommand = extractatt(top_uvalue, 'globalcommand') 
  • trunk/SRC/ToBeReviewed/WIDGET/AUTOUR_de_XXX/letsdraw.pro

    r69 r114  
    3636 
    3737PRO letsdraw, base, COMMANDE = commande, _extra = ex 
     38; 
     39  compile_opt idl2, strictarrsubs 
     40; 
    3841@common 
    3942; on recupere la uvalue de base 
  • trunk/SRC/ToBeReviewed/WIDGET/AUTOUR_de_XXX/loadgrid.pro

    r69 r114  
    22; 
    33;  
     4; 
     5  compile_opt idl2, strictarrsubs 
     6; 
    47@cm_4mesh 
    58  ccmeshparameters.filename = meshfilein 
  • trunk/SRC/ToBeReviewed/WIDGET/AUTOUR_de_XXX/longclickaction.pro

    r69 r114  
    11PRO longclickaction, event 
     2; 
     3  compile_opt idl2, strictarrsubs 
     4; 
    25  widget_control, event.id, get_uvalue = uval 
    36  widget_control, event.top, get_uvalue = top_uvalue 
  • trunk/SRC/ToBeReviewed/WIDGET/AUTOUR_de_XXX/read_vermair.pro

    r69 r114  
    11FUNCTION read_vermair, name, debut, fin, nomexp, PARENT = parent, BOXZOOM=boxzoom, _EXTRA = ex 
     2; 
     3  compile_opt idl2, strictarrsubs 
     4; 
    25@common 
    36;------------------------------------------------------------  
  • trunk/SRC/ToBeReviewed/WIDGET/AUTOUR_de_XXX/scanfile.pro

    r74 r114  
    3333;------------------------------------------------------------ 
    3434FUNCTION scanfile, namefile, GRID = GRID, _extra = ex 
     35; 
     36  compile_opt idl2, strictarrsubs 
     37; 
    3538@common 
    3639;------------------------------------------------------------ 
  • trunk/SRC/ToBeReviewed/WIDGET/AUTOUR_de_XXX/selectfile.pro

    r74 r114  
    11;********************************************************************* 
    22PRO selectfile_event, event 
     3; 
     4; 
     5  compile_opt idl2, strictarrsubs 
    36; 
    47@common 
     
    142145;********************************************************************* 
    143146FUNCTION selectfile, datafilename, idlfile, argspro, _extra = ex 
     147; 
     148; 
     149  compile_opt idl2, strictarrsubs 
    144150; 
    145151@common 
  • trunk/SRC/ToBeReviewed/WIDGET/AUTOUR_de_XXX/singleclickaction.pro

    r69 r114  
    11PRO singleclickaction, event 
     2; 
     3  compile_opt idl2, strictarrsubs 
     4; 
    25@cm_4mesh 
    36@cm_4data 
  • trunk/SRC/ToBeReviewed/WIDGET/AUTOUR_de_XXX/tracecadre.pro

    r49 r114  
    33; determination de la colonne et de la ligne correspondant au small en 
    44; entree 
     5; 
     6  compile_opt idl2, strictarrsubs 
     7; 
    58   numdessin = small[2]-1 
    69   numligne = numdessin/small[0] 
  • trunk/SRC/ToBeReviewed/WIDGET/AUTOUR_de_XXX/updatewidget.pro

    r69 r114  
    11PRO updatewidget, base, NOBOXZOOM = noboxzoom, NODATES = nodates, NOTYPE = notype 
    22;---------------------------------------------------------------------- 
     3; 
     4  compile_opt idl2, strictarrsubs 
     5; 
    36   widget_control,base, get_uvalue = top_uvalue 
    47   smallin = extractatt(top_uvalue, 'smallin') 
  • trunk/SRC/ToBeReviewed/WIDGET/AUTOUR_de_XXX/xcreateanim.pro

    r74 r114  
    11pro xcreateanim_event, event  
     2; 
     3  compile_opt idl2, strictarrsubs 
     4; 
    25@common 
    36; on recupere les aguments contenus ds le widget 
     
    139142;---------------------------------------------------------------- 
    140143PRO xcreateanim, parent 
     144; 
     145  compile_opt idl2, strictarrsubs 
     146; 
    141147@common 
    142148; 
  • trunk/SRC/ToBeReviewed/WIDGET/AUTOUR_de_XXX/xxxmenubar_event.pro

    r74 r114  
    11;------------------------------------------------ 
    22PRO xxxmenubar_event, event 
     3; 
     4  compile_opt idl2, strictarrsubs 
     5; 
    36@common 
    47 
  • trunk/SRC/ToBeReviewed/WIDGET/COMPOUND_WIDGET/cw_bgroup.pro

    r69 r114  
    132132 
    133133pro CW_BGROUP_SETV, id, value 
    134   compile_opt hidden 
     134  compile_opt hidden, idl2, strictarrsubs 
    135135 
    136136  ON_ERROR, 2                       ;return to caller 
     
    162162function CW_BGROUP_GETV, id, value 
    163163 
    164   compile_opt hidden 
     164  compile_opt hidden, idl2, strictarrsubs 
    165165  ON_ERROR, 2                       ;return to caller 
    166166 
     
    190190 
    191191function CW_BGROUP_EVENT, ev 
    192   compile_opt hidden 
     192  compile_opt hidden, idl2, strictarrsubs 
    193193  WIDGET_CONTROL, ev.handler, GET_UVALUE=stash 
    194194  WIDGET_CONTROL, stash, GET_UVALUE=state, /NO_COPY 
  • trunk/SRC/ToBeReviewed/WIDGET/COMPOUND_WIDGET/cw_combobox_pm.pro

    r69 r114  
    145145;---------------------------------------------------------------------- 
    146146PRO cw_combobox_pm_set_value, id, value 
     147; 
     148  compile_opt idl2, strictarrsubs 
     149; 
    147150   ComboboxId = widget_info(id,find_by_uname = 'Combobox') 
    148151   if size(value, /type) eq 8 then BEGIN ; this is a structure 
     
    163166;---------------------------------------------------------------------- 
    164167FUNCTION cw_combobox_pm_get_value, id 
     168; 
     169  compile_opt idl2, strictarrsubs 
     170; 
    165171   ComboboxId = widget_info(id,find_by_uname = 'Combobox') 
    166172   widget_control, ComboboxId, get_value = cmbbval 
     
    174180;---------------------------------------------------------------------- 
    175181FUNCTION cw_combobox_pm_event, event 
     182; 
     183  compile_opt idl2, strictarrsubs 
     184; 
    176185   widget_control, event.id, get_uvalue=uval 
    177186; 
     
    205214;---------------------------------------------------------------------- 
    206215FUNCTION cw_combobox_pm, parent, VALUE = value, UVALUE = uvalue, UNAME = uname, ROW = row, COLUMN = column, _extra = ex 
     216; 
     217  compile_opt idl2, strictarrsubs 
     218; 
    207219 
    208220   IF (N_PARAMS() NE 1) THEN MESSAGE, 'Incorrect number of arguments' 
  • trunk/SRC/ToBeReviewed/WIDGET/COMPOUND_WIDGET/cw_domain.pro

    r69 r114  
    4040;********************************************************************* 
    4141pro cw_domain_set_value, id, value 
     42; 
     43  compile_opt idl2, strictarrsubs 
     44; 
    4245@cm_4mesh 
    4346; 
     
    257260;********************************************************************* 
    258261FUNCTION cw_domain_get_value, id 
     262; 
     263  compile_opt idl2, strictarrsubs 
     264; 
    259265   box = lonarr(6) 
    260266   possiblecase = ['lon1', 'lon2', 'lat1', 'lat2', 'depth1', 'depth2'] 
     
    268274;********************************************************************* 
    269275FUNCTION cw_domain_event, event 
     276; 
     277  compile_opt idl2, strictarrsubs 
     278; 
    270279@common 
    271280; help,  /struct, event 
     
    411420FUNCTION cw_domain, parent, BOXZOOM = boxzoom, STRICT = strict, UVALUE = uvalue, UNAME = uname, UNZOOM = unzoom, _extra = ex 
    412421; 
     422; 
     423  compile_opt idl2, strictarrsubs 
     424; 
    413425@cm_4mesh 
    414426@cm_4data 
     
    449461  min = floor(min([glamt, glamf], max = max)) 
    450462  max = ceil(max) 
    451   IF max-min EQ 361 AND keyword_set(key_periodic) THEN max = max-1 
     463  IF max-min GT 360 AND keyword_set(key_periodic) THEN max = min+360 
    452464  lonbase = widget_base(baseh1, column = 2, space = 0, uname = 'lonbase', uvalue = {name:'geographic'}) 
    453465  lon1id = cw_slider_pm(lonbase, value = min > boxzoom[0] < ((boxzoom[1] < max)-keyword_set(strict)) $ 
  • trunk/SRC/ToBeReviewed/WIDGET/COMPOUND_WIDGET/cw_droplist_pm.pro

    r51 r114  
    144144;---------------------------------------------------------------------- 
    145145PRO cw_droplist_pm_set_value, id, value 
     146; 
     147  compile_opt idl2, strictarrsubs 
     148; 
    146149   DroplistId = widget_info(id,find_by_uname = 'Droplist') 
    147150   if size(value, /type) eq 8 then BEGIN ; this is a structure 
     
    160163;---------------------------------------------------------------------- 
    161164FUNCTION cw_droplist_pm_get_value, id 
     165; 
     166  compile_opt idl2, strictarrsubs 
     167; 
    162168   DroplistId = widget_info(id,find_by_uname = 'Droplist') 
    163169   return, {droplist_number:widget_info(DroplistId, /droplist_number) $ 
     
    167173;---------------------------------------------------------------------- 
    168174FUNCTION cw_droplist_pm_event, event 
     175; 
     176  compile_opt idl2, strictarrsubs 
     177; 
    169178   widget_control, event.id, get_uvalue=uval 
    170179; 
     
    191200;---------------------------------------------------------------------- 
    192201FUNCTION cw_droplist_pm, parent,UVALUE = uvalue, UNAME = uname, ROW = row, COLUMN = column, _extra = ex 
     202; 
     203  compile_opt idl2, strictarrsubs 
     204; 
    193205 
    194206   IF (N_PARAMS() NE 1) THEN MESSAGE, 'Incorrect number of arguments' 
  • trunk/SRC/ToBeReviewed/WIDGET/COMPOUND_WIDGET/cw_pagelayout.pro

    r69 r114  
    22;********************************************************************* 
    33FUNCTION cw_pagelayout_event, event 
     4; 
     5  compile_opt idl2, strictarrsubs 
     6; 
    47 
    58   widget_control, event.id, get_uvalue=uval 
     
    7881FUNCTION cw_pagelayout, parent, small, UVALUE = uvalue, UNAME = uname, UNZOOM = unzoom, COLUMN = column, ROW = row, _extra = ex 
    7982;------------------------------------------------ 
     83; 
     84  compile_opt idl2, strictarrsubs 
     85; 
    8086  row = keyword_set(row)*(1-keyword_set(column))   
    8187  if NOT keyword_set(uvalue) then uvalue = '' 
  • trunk/SRC/ToBeReviewed/WIDGET/COMPOUND_WIDGET/cw_slide_slice.pro

    r51 r114  
    11pro cw_slide_slice_set_value, id, value 
     2; 
     3  compile_opt idl2, strictarrsubs 
     4; 
    25@common 
    36   topid = findtopid(id) 
     
    3437;---------------------------------------------------------------------- 
    3538FUNCTION cw_slide_slice_event,  event 
     39; 
     40  compile_opt idl2, strictarrsubs 
     41; 
    3642@common 
    3743   widget_control, event.id, get_uvalue=uval 
     
    104110;-------------------------------------------------------------------------------- 
    105111FUNCTION cw_slide_slice, parent, boxzoom = boxzoom, UVALUE = uvalue, UNAME = uname, FRAME = frame, ROW = row, COLUMN = column, _extra = ex 
     112; 
     113  compile_opt idl2, strictarrsubs 
     114; 
    106115@common 
    107116;------------------------------------------------ 
  • trunk/SRC/ToBeReviewed/WIDGET/COMPOUND_WIDGET/cw_slider_pm.pro

    r69 r114  
    136136;---------------------------------------------------------------------- 
    137137FUNCTION decvalue, value 
     138; 
     139  compile_opt idl2, strictarrsubs 
     140; 
    138141  a = float(value[0]) 
    139142  return, strtrim(string(floor(a) + 0.1*indgen(10), format = '(f15.1)'), 2) 
     
    141144;---------------------------------------------------------------------- 
    142145FUNCTION decind, value 
     146; 
     147  compile_opt idl2, strictarrsubs 
     148; 
    143149  a = float(value[0]) 
    144150  return, round(10*(a - floor(a))) ; !! computation accuracy 
     
    146152;---------------------------------------------------------------------- 
    147153PRO cw_slider_pm_set_value, id, value 
     154; 
     155  compile_opt idl2, strictarrsubs 
     156; 
    148157  sbid = widget_info(id, find_by_uname = 'SliderBar') 
    149158  dcid = widget_info(id, find_by_uname = 'decimal') 
     
    195204;---------------------------------------------------------------------- 
    196205FUNCTION cw_slider_pm_get_value, id 
     206; 
     207  compile_opt idl2, strictarrsubs 
     208; 
    197209  sbid = widget_info(id, find_by_uname = 'SliderBar') 
    198210  dcid = widget_info(id, find_by_uname = 'decimal') 
     
    203215;---------------------------------------------------------------------- 
    204216FUNCTION cw_slider_pm_event, event 
     217; 
     218  compile_opt idl2, strictarrsubs 
     219; 
    205220  widget_control, event.id, get_uvalue = uval 
    206221; 
     
    237252                       , STRMINLEN = strminlen, VALUE = value, UVALUE = uvalue $ 
    238253                       , UNAME = uname, title = title, _extra = ex 
     254; 
     255  compile_opt idl2, strictarrsubs 
     256; 
    239257 
    240258  IF (N_PARAMS() NE 1) THEN MESSAGE, 'Incorrect number of arguments' 
  • trunk/SRC/ToBeReviewed/WIDGET/COMPOUND_WIDGET/cw_specifie.pro

    r74 r114  
    22;***************************************************** 
    33PRO cw_specifie_set_value, id, value 
     4; 
     5  compile_opt idl2, strictarrsubs 
     6; 
    47@cm_general 
    58   if size(value, /type) NE 8 then return 
     
    2629;***************************************************** 
    2730FUNCTION cw_specifie_get_value, id 
     31; 
     32  compile_opt idl2, strictarrsubs 
     33; 
    2834@cm_general 
    2935   widget_control, widget_info(id,find_by_uname='min'), get_value = min 
     
    5359;------------------------------------------------------------ 
    5460;------------------------------------------------------------ 
     61; 
     62  compile_opt idl2, strictarrsubs 
     63; 
    5564  widget_control, event.id, get_uvalue = uval 
    5665  widget_control, event.top, get_uvalue = top_uvalue 
     
    8796FUNCTION cw_specifie, parent, ROW = row, COLUMN = column, UVALUE = uvalue, UNAME = uname, FRAME = frame, FORXXX = forxxx, _extra = ex 
    8897; cheking exclusive keywords 
     98; 
     99  compile_opt idl2, strictarrsubs 
     100; 
    89101   column = keyword_set(column)*(1-keyword_set(row)) 
    90102   row = keyword_set(row)*(1-keyword_set(column)) +(keyword_set(row) EQ column)  
  • trunk/SRC/ToBeReviewed/WIDGET/findtopid.pro

    r52 r114  
    3434;------------------------------------------------------------ 
    3535FUNCTION findtopid,  identite 
     36; 
     37  compile_opt idl2, strictarrsubs 
     38; 
    3639   id = long(identite) 
    3740;    exist = widget_info(id, /managed) 
  • trunk/SRC/ToBeReviewed/WIDGET/slec.pro

    r52 r114  
    22;--------------------------------------------------------- 
    33; include common 
     4; 
     5  compile_opt idl2, strictarrsubs 
     6; 
    47@cm_4data 
    58  IF NOT keyword_set(key_forgetold) THEN BEGIN 
  • trunk/SRC/ToBeReviewed/WIDGET/xnotice.pro

    r52 r114  
    4242; on separe le text en differentes lignes (separees par !C) si ce 
    4343; n''est pas deja fait... 
     44; 
     45  compile_opt idl2, strictarrsubs 
     46; 
    4447   if n_elements(text) EQ 1 then text = str_sep(text, '!C', /trim) 
    4548; 
  • trunk/SRC/ToBeReviewed/WIDGET/xquestion.pro

    r52 r114  
    5454;------------------------------------------------------------------------- 
    5555pro xquestion_event, event 
     56; 
     57  compile_opt idl2, strictarrsubs 
     58; 
    5659; we get the answer 
    5760   widget_control, widget_info(event.top, find_by_uname = 'text') $ 
     
    6669;------------------------------------------------------------------------- 
    6770FUNCTION xquestion, question, proposedanswer, CHKWIDGET = chkwidget, _extra = ex ; 
     71; 
     72  compile_opt idl2, strictarrsubs 
     73; 
    6874; is separate line a scalar? we must cut it into pieces?  
    6975   if n_elements(question) EQ 1 then question = str_sep(question, '!C', /trim) 
  • trunk/SRC/ToBeReviewed/WIDGET/xx.pro

    r52 r114  
    11 
    22PRO xx,  JOUR = jour, MESHFILENAME = meshfilename,  LISTVAR = listvar, LISTGRID = listgrid, FUNCLEC_NAME = funclec_name, CALENDAR = calendar, _extra = ex 
     3; 
     4; 
     5  compile_opt idl2, strictarrsubs 
    36; 
    47@common 
     
    2023   ENDIF 
    2124; calendrier a utiliser (en jours juliens d''IDL    
    22    if NOT keyword_set(calendar) then BEGIN  
    23       if keyword_set(jour) then calendar = calendriertotem(/julian_day) ELSE calendar = calendriertotem(/julian_day, /mensuel) 
    24    ENDIF 
     25;++++    if NOT keyword_set(calendar) then BEGIN  
     26;++++       if keyword_set(jour) then calendar = calendriertotem(/julian_day) ELSE calendar = calendriertotem(/julian_day, /mensuel) 
     27;++++    ENDIF 
    2528; nom du fichier se rapportant au masque 
    2629   if NOT keyword_set(meshfilename) then meshfilename = '/usr1/com/smasson/IDL/INIT/inittotem.pro' 
    27    meshparameters = whichgrid(meshfilename) 
     30;++++   meshparameters = whichgrid(meshfilename) 
    2831; parameteres specifiant comment doit etre lu le champ 
    2932   readparameters= {funclec_name: funclec_name $ 
  • trunk/SRC/ToBeReviewed/WIDGET/xxx.pro

    r74 r114  
    4242PRO xxx_event, event 
    4343;------------------------------------------------------------ 
     44; 
     45  compile_opt idl2, strictarrsubs 
     46; 
    4447@common 
    4548;------------------------------------------------------------ 
     
    129132         , RESTORE = restore, _EXTRA = ex 
    130133;------------------------------------------------------------ 
     134; 
     135  compile_opt idl2, strictarrsubs 
     136; 
    131137@all_cm 
    132138;------------------------------------------------------------ 
Note: See TracChangeset for help on using the changeset viewer.