Changeset 429 for IOIPSL/trunk


Ignore:
Timestamp:
10/23/08 12:17:05 (15 years ago)
Author:
bellier
Message:

added dynamic debug (see ipsldbg in errioipsl)

File:
1 edited

Legend:

Unmodified
Added
Removed
  • IOIPSL/trunk/src/histcom.f90

    r427 r429  
    1212  USE fliocom,  ONLY : flio_dom_file,flio_dom_att 
    1313  USE calendar 
    14   USE errioipsl, ONLY : ipslerr 
     14  USE errioipsl, ONLY : ipslerr,ipsldbg 
    1515!- 
    1616  IMPLICIT NONE 
     
    236236  INTEGER,INTENT(IN),OPTIONAL :: domain_id 
    237237!- 
    238   LOGICAL :: check = .FALSE. 
    239 !- 
    240238  REAL,ALLOCATABLE,DIMENSION(:,:) :: lon_tmp,lat_tmp 
    241 !--------------------------------------------------------------------- 
    242   IF (check) WRITE(*,*) "histbeg_totreg" 
     239  LOGICAL :: l_dbg 
     240!--------------------------------------------------------------------- 
     241  CALL ipsldbg (old_status=l_dbg) 
     242!- 
     243  IF (l_dbg) WRITE(*,*) "histbeg_totreg" 
    243244!- 
    244245  ALLOCATE (lon_tmp(pim,pjm),lat_tmp(pim,pjm)) 
     
    328329  CHARACTER(LEN=30) :: timenow 
    329330  LOGICAL :: rectilinear 
    330 !- 
    331   LOGICAL :: check = .FALSE. 
    332 !--------------------------------------------------------------------- 
     331  LOGICAL :: l_dbg 
     332!--------------------------------------------------------------------- 
     333  CALL ipsldbg (old_status=l_dbg) 
     334!- 
    333335  nb_files = nb_files+1 
    334336  pfileid  = nb_files 
     
    336338! 1.0 Transfering into the common for future use 
    337339!- 
    338   IF (check) WRITE(*,*) "histbeg_regular 1.0" 
     340  IF (l_dbg) WRITE(*,*) "histbeg_regular 1.0" 
    339341!- 
    340342  itau0(pfileid) = pitau0 
     
    350352! 2.0 Initializes all variables for this file 
    351353!- 
    352   IF (check) WRITE(*,*) "histbeg_regular 2.0" 
     354  IF (l_dbg) WRITE(*,*) "histbeg_regular 2.0" 
    353355!- 
    354356  IF (nb_files > nb_files_max) THEN 
     
    368370! 3.0 Opening netcdf file and defining dimensions 
    369371!- 
    370   IF (check) WRITE(*,*) "histbeg_regular 3.0" 
     372  IF (l_dbg) WRITE(*,*) "histbeg_regular 3.0" 
    371373!- 
    372374! Add DOMAIN number and ".nc" suffix in file name if needed 
     
    387389! 4.0 Declaring the geographical coordinates and other attributes 
    388390!- 
    389   IF (check) WRITE(*,*) "histbeg_regular 4.0" 
     391  IF (l_dbg) WRITE(*,*) "histbeg_regular 4.0" 
    390392!- 
    391393! 4.3 Global attributes 
     
    400402! 5.0 Saving some important information on this file in the common 
    401403!- 
    402   IF (check) WRITE(*,*) "histbeg_regular 5.0" 
     404  IF (l_dbg) WRITE(*,*) "histbeg_regular 5.0" 
    403405!- 
    404406  IF (PRESENT(domain_id)) THEN 
     
    476478  CHARACTER(LEN=120) :: file 
    477479  CHARACTER(LEN=30) :: timenow 
    478 !- 
    479   LOGICAL :: check = .FALSE. 
    480 !--------------------------------------------------------------------- 
     480  LOGICAL :: l_dbg 
     481!--------------------------------------------------------------------- 
     482  CALL ipsldbg (old_status=l_dbg) 
     483!- 
    481484  nb_files = nb_files+1 
    482485  pfileid  = nb_files 
     
    484487! 1.0 Transfering into the common for future use 
    485488!- 
    486   IF (check) WRITE(*,*) "histbeg_irregular 1.0" 
     489  IF (l_dbg) WRITE(*,*) "histbeg_irregular 1.0" 
    487490!- 
    488491  itau0(pfileid) = pitau0 
     
    492495! 2.0 Initializes all variables for this file 
    493496!- 
    494   IF (check) WRITE(*,*) "histbeg_irregular 2.0" 
     497  IF (l_dbg) WRITE(*,*) "histbeg_irregular 2.0" 
    495498!- 
    496499  IF (nb_files > nb_files_max) THEN 
     
    510513! 3.0 Opening netcdf file and defining dimensions 
    511514!- 
    512   IF (check) WRITE(*,*) "histbeg_irregular 3.0" 
     515  IF (l_dbg) WRITE(*,*) "histbeg_irregular 3.0" 
    513516!- 
    514517! Add DOMAIN number and ".nc" suffix in file name if needed 
     
    524527! 4.0 Declaring the geographical coordinates and other attributes 
    525528!- 
    526   IF (check) WRITE(*,*) "histbeg_irregular 4.0" 
     529  IF (l_dbg) WRITE(*,*) "histbeg_irregular 4.0" 
    527530!- 
    528531! 4.3 Global attributes 
     
    537540! 5.0 Saving some important information on this file in the common 
    538541!- 
    539   IF (check) WRITE(*,*) "histbeg_irregular 5.0" 
     542  IF (l_dbg) WRITE(*,*) "histbeg_irregular 5.0" 
    540543!- 
    541544  IF (PRESENT(domain_id)) THEN 
     
    602605  INTEGER :: iret,ncid 
    603606  LOGICAL :: rectilinear 
    604 !- 
    605   LOGICAL :: check = .FALSE. 
    606 !--------------------------------------------------------------------- 
     607  LOGICAL :: l_dbg 
     608!--------------------------------------------------------------------- 
     609  CALL ipsldbg (old_status=l_dbg) 
    607610!- 
    608611! 1.0 Check that all fits in the buffers 
     
    624627! 1.1 Create all the variables needed 
    625628!- 
    626   IF (check) WRITE(*,*) "histhori_regular 1.0" 
     629  IF (l_dbg) WRITE(*,*) "histhori_regular 1.0" 
    627630!- 
    628631  ncid = ncdf_ids(pfileid) 
     
    660663! 2.0 Longitude 
    661664!- 
    662   IF (check) WRITE(*,*) "histhori_regular 2.0" 
     665  IF (l_dbg) WRITE(*,*) "histhori_regular 2.0" 
    663666!- 
    664667  IF (rectilinear) THEN 
     
    681684! 3.0 Latitude 
    682685!- 
    683   IF (check) WRITE(*,*) "histhori_regular 3.0" 
     686  IF (l_dbg) WRITE(*,*) "histhori_regular 3.0" 
    684687!- 
    685688  IF (rectilinear) THEN 
     
    704707! 4.0 storing the geographical coordinates 
    705708!- 
    706   IF (check) WRITE(*,*) "histhori_regular 4.0" 
     709  IF (l_dbg) WRITE(*,*) "histhori_regular 4.0" 
    707710!- 
    708711  orix = slab_ori(pfileid,1) 
     
    778781  LOGICAL :: transp = .FALSE. 
    779782  REAL,ALLOCATABLE,DIMENSION(:,:) :: bounds_trans 
    780 !- 
    781   LOGICAL :: check = .FALSE. 
    782 !--------------------------------------------------------------------- 
     783  LOGICAL :: l_dbg 
     784!--------------------------------------------------------------------- 
     785  CALL ipsldbg (old_status=l_dbg) 
    783786!- 
    784787! 1.0 Check that all fits in the buffers 
     
    794797! 1.1 Create all the variables needed 
    795798!- 
    796   IF (check) WRITE(*,*) 'histhori_irregular 1.0' 
     799  IF (l_dbg) WRITE(*,*) 'histhori_irregular 1.0' 
    797800!- 
    798801  ncid = ncdf_ids(pfileid) 
     
    842845! 2.0 Longitude 
    843846!- 
    844   IF (check) WRITE(*,*) "histhori_irregular 2.0" 
     847  IF (l_dbg) WRITE(*,*) "histhori_irregular 2.0" 
    845848!- 
    846849  iret = NF90_DEF_VAR (ncid,lon_name,NF90_FLOAT,dims(1:ndim),nlonid) 
     
    864867! 3.0 Latitude 
    865868!- 
    866   IF (check) WRITE(*,*) "histhori_irregular 3.0" 
     869  IF (l_dbg) WRITE(*,*) "histhori_irregular 3.0" 
    867870!- 
    868871  iret = NF90_DEF_VAR (ncid,lat_name,NF90_FLOAT,dims(1:ndim),nlatid) 
     
    888891! 4.0 storing the geographical coordinates 
    889892!- 
    890   IF (check) WRITE(*,*) "histhori_irregular 4.0" 
     893  IF (l_dbg) WRITE(*,*) "histhori_irregular 4.0" 
    891894!- 
    892895! 4.1 Write the longitude 
     
    960963  CHARACTER(LEN=20) :: direction 
    961964  INTEGER :: iret,leng,ncid 
    962   LOGICAL :: check = .FALSE. 
    963 !--------------------------------------------------------------------- 
     965  LOGICAL :: l_dbg 
     966!--------------------------------------------------------------------- 
     967  CALL ipsldbg (old_status=l_dbg) 
    964968!- 
    965969! 1.0 Verifications : 
     
    967971!    Is the name already in use ? 
    968972!- 
    969   IF (check) WRITE(*,*) "histvert : 1.0 Verifications", & 
     973  IF (l_dbg) WRITE(*,*) "histvert : 1.0 Verifications", & 
    970974 &                      pzaxname,'---',pzaxunit,'---',pzaxtitle 
    971975!- 
     
    10181022! 2.0 Add the information to the file 
    10191023!- 
    1020   IF (check) & 
     1024  IF (l_dbg) & 
    10211025 &  WRITE(*,*) "histvert : 2.0 Add the information to the file" 
    10221026!- 
     
    10511055!- 3.0 add the information to the common 
    10521056!- 
    1053   IF (check) & 
     1057  IF (l_dbg) & 
    10541058  &  WRITE(*,*) "histvert : 3.0 add the information to the common" 
    10551059!- 
     
    11321136  REAL :: tmp_scal(nbopp_max),un_an,un_jour,test_fopp,test_fwrt 
    11331137  INTEGER :: pos,buff_sz 
    1134 !- 
    1135   LOGICAL :: check = .FALSE. 
    1136 !--------------------------------------------------------------------- 
     1138  LOGICAL :: l_dbg 
     1139!--------------------------------------------------------------------- 
     1140  CALL ipsldbg (old_status=l_dbg) 
     1141!- 
    11371142  ex_topps = 'ave, inst, t_min, t_max, t_sum, once, never, l_max, l_min' 
    11381143!- 
     
    11501155!     and verify that it does not already exist 
    11511156!- 
    1152   IF (check) WRITE(*,*) "histdef : 1.0" 
     1157  IF (l_dbg) WRITE(*,*) "histdef : 1.0" 
    11531158!- 
    11541159  IF (iv > 1) THEN 
     
    11961201! 2.0 Put the size of the variable in the common and check 
    11971202!- 
    1198   IF (check) & 
     1203  IF (l_dbg) & 
    11991204 &  WRITE(*,*) "histdef : 2.0",pfileid,iv,nbopp(pfileid,iv), & 
    12001205 &    sopps(pfileid,iv,1:nbopp(pfileid,iv)), & 
     
    12911296!     If it is instantaneous output then we do not use the buffer 
    12921297!- 
    1293   IF (check) WRITE(*,*) "histdef : 3.0" 
     1298  IF (l_dbg) WRITE(*,*) "histdef : 3.0" 
    12941299!- 
    12951300! 3.1 We get the size of the arrays histwrite will get and check 
     
    13061311    point(pfileid,iv) = buff_pos+1 
    13071312    buff_pos = buff_pos+buff_sz 
    1308     IF (check) THEN 
     1313    IF (l_dbg) THEN 
    13091314      WRITE(*,*) "histdef : 3.2 bufpos for iv = ",iv, & 
    13101315 &               " pfileid = ",pfileid," is = ",point(pfileid,iv) 
     
    13171322!     The strategy is to bring it back to seconds for the tests 
    13181323!- 
    1319   IF (check) WRITE(*,*) "histdef : 4.0" 
     1324  IF (l_dbg) WRITE(*,*) "histdef : 4.0" 
    13201325!- 
    13211326  freq_opp(pfileid,iv) = pfreq_opp 
     
    14011406! 5.0 Initialize other variables of the common 
    14021407!- 
    1403   IF (check) WRITE(*,*) "histdef : 5.0" 
     1408  IF (l_dbg) WRITE(*,*) "histdef : 5.0" 
    14041409!- 
    14051410  hist_wrt_rng(pfileid,iv) = (PRESENT(var_range)) 
     
    14271432! 6.0 Get the time axis for this variable 
    14281433!- 
    1429   IF (check) WRITE(*,*) "histdef : 6.0" 
     1434  IF (l_dbg) WRITE(*,*) "histdef : 6.0" 
    14301435!- 
    14311436  IF (freq_wrt(pfileid,iv) > 0) THEN 
     
    14531458    ENDIF 
    14541459  ELSE 
    1455     IF (check)   WRITE(*,*) "histdef : 7.0 ",TRIM(tmp_topp),'----' 
     1460    IF (l_dbg)   WRITE(*,*) "histdef : 7.0 ",TRIM(tmp_topp),'----' 
    14561461    var_axid(pfileid,iv) = -99 
    14571462  ENDIF 
     
    14961501 &     'JUL','AUG','SEP','OCT','NOV','DEC' /) 
    14971502  CHARACTER(LEN=7) :: tmp_opp 
    1498 !- 
    1499   LOGICAL :: check = .FALSE. 
    1500 !--------------------------------------------------------------------- 
     1503  LOGICAL :: l_dbg 
     1504!--------------------------------------------------------------------- 
     1505  CALL ipsldbg (old_status=l_dbg) 
     1506!- 
    15011507  ncid = ncdf_ids(pfileid) 
    15021508!- 
    15031509! 1.0 Create the time axes 
    15041510!- 
    1505   IF (check) WRITE(*,*) "histend : 1.0" 
     1511  IF (l_dbg) WRITE(*,*) "histend : 1.0" 
    15061512!--- 
    15071513  iret = NF90_DEF_DIM (ncid,'time_counter',NF90_UNLIMITED,tid(pfileid)) 
     
    15671573! 2.0 declare the variables 
    15681574!- 
    1569   IF (check) WRITE(*,*) "histend : 2.0" 
     1575  IF (l_dbg) WRITE(*,*) "histend : 2.0" 
    15701576!- 
    15711577  DO iv=1,nb_var(pfileid) 
     
    15951601        ELSE 
    15961602          ndim = dim_cnt+2 
    1597           dims(dim_cnt+1:dim_cnt+2) = (/ zax_ids(pfileid,ziv),tid(pfileid) /) 
     1603          dims(dim_cnt+1:dim_cnt+2) = (/zax_ids(pfileid,ziv),tid(pfileid)/) 
    15981604        ENDIF 
    15991605      ELSE 
     
    16571663        assoc = TRIM(str30)//' '//TRIM(assoc) 
    16581664!- 
    1659         IF (check) THEN 
     1665        IF (l_dbg) THEN 
    16601666          WRITE(*,*) "histend : 2.0.n, freq_opp, freq_wrt", & 
    16611667 &                   freq_opp(pfileid,iv),freq_wrt(pfileid,iv) 
     
    16791685! 3.0 Put the netcdf file into write mode 
    16801686!- 
    1681   IF (check) WRITE(*,*) "histend : 3.0" 
     1687  IF (l_dbg) WRITE(*,*) "histend : 3.0" 
    16821688!- 
    16831689  iret = NF90_ENDDEF (ncid) 
     
    16851691! 4.0 Give some informations to the user 
    16861692!- 
    1687   IF (check) WRITE(*,*) "histend : 4.0" 
     1693  IF (l_dbg) WRITE(*,*) "histend : 4.0" 
    16881694!- 
    16891695  WRITE(str70,'("All variables have been initialized on file :",I3)') pfileid 
     
    17521758  CHARACTER(LEN=7) :: tmp_opp 
    17531759  CHARACTER(LEN=13) :: c_nam 
    1754 !- 
    1755   LOGICAL :: check = .FALSE. 
    1756 !--------------------------------------------------------------------- 
     1760  LOGICAL :: l_dbg 
     1761!--------------------------------------------------------------------- 
     1762  CALL ipsldbg (old_status=l_dbg) 
     1763!- 
    17571764  l1d=PRESENT(pdata_1d); l2d=PRESENT(pdata_2d); l3d=PRESENT(pdata_3d); 
    17581765  IF      (l1d) THEN 
     
    18651872!- 
    18661873    IF (.NOT.ALLOCATED(buff_tmp)) THEN 
    1867       IF (check) THEN 
     1874      IF (l_dbg) THEN 
    18681875        WRITE(*,*) & 
    18691876 &       c_nam//" : allocate buff_tmp for buff_sz = ", & 
     
    18731880      buff_tmp_sz = datasz_max(pfileid,varid) 
    18741881    ELSE IF (datasz_max(pfileid,varid) > buff_tmp_sz) THEN 
    1875       IF (check) THEN 
     1882      IF (l_dbg) THEN 
    18761883        WRITE(*,*) & 
    18771884 &       c_nam//" : re-allocate buff_tmp for buff_sz = ", & 
     
    19441951  REAL,ALLOCATABLE,SAVE :: buffer_used(:) 
    19451952  INTEGER,SAVE          :: buffer_sz 
    1946 !- 
    1947   LOGICAL :: check = .FALSE. 
    1948 !--------------------------------------------------------------------- 
    1949   IF (check) THEN 
    1950     WRITE(*,*) "histwrite 0.0 :  VAR : ",name(pfileid,varid) 
     1953  LOGICAL :: l_dbg 
     1954!--------------------------------------------------------------------- 
     1955  CALL ipsldbg (old_status=l_dbg) 
     1956!- 
     1957  IF (l_dbg) THEN 
     1958    WRITE(*,*) "histwrite 0.0 : VAR : ",name(pfileid,varid) 
    19511959    WRITE(*,*) "histwrite 0.0 : nbindex,nindex :", & 
    1952     &  nbindex,nindex(1:MIN(3,nbindex)),'...',nindex(MAX(1,nbindex-3):nbindex) 
     1960 &  nbindex,nindex(1:MIN(3,nbindex)),'...',nindex(MAX(1,nbindex-3):nbindex) 
    19531961  ENDIF 
    19541962!- 
    19551963! The sizes which can be encoutered 
    19561964!- 
    1957   tsz = zsize(pfileid,varid,1)*zsize(pfileid,varid,2)*zsize(pfileid,varid,3) 
     1965  tsz =  zsize(pfileid,varid,1) & 
     1966 &      *zsize(pfileid,varid,2) & 
     1967 &      *zsize(pfileid,varid,3) 
    19581968!- 
    19591969! 1.0 We allocate the memory needed to store the data between write 
     
    19621972!- 
    19631973  IF (.NOT. ALLOCATED(buffer)) THEN 
    1964     IF (check) WRITE(*,*) "histwrite_real 1.0 allocate buffer ",buff_pos 
     1974    IF (l_dbg) WRITE(*,*) "histwrite_real 1.0 allocate buffer ",buff_pos 
    19651975    ALLOCATE(buffer(buff_pos)) 
    19661976    buffer_sz = buff_pos 
    19671977    buffer(:)=0.0 
    19681978  ELSE IF (buffer_sz < buff_pos) THEN 
    1969     IF (check) WRITE(*,*) "histwrite_real 1.0.1 re-allocate buffer for ",buff_pos," instead of ",SIZE(buffer) 
     1979    IF (l_dbg) THEN 
     1980      WRITE(*,*) "histwrite_real 1.0.1 re-allocate buffer for ", & 
     1981 &      buff_pos," instead of ",SIZE(buffer) 
     1982    ENDIF 
    19701983    IF (SUM(buffer)/=0.0) THEN 
    1971       IF (check) WRITE (*,*) ' histwrite : buffer has been used. We have to save it before re-allocating it ' 
     1984      IF (l_dbg) WRITE (*,*) 'histwrite : buffer has been used. ', & 
     1985 &      'We have to save it before re-allocating.' 
    19721986      ALLOCATE (buffer_used(buffer_sz)) 
    19731987      buffer_used(:)=buffer(:) 
     
    19791993      DEALLOCATE (buffer_used) 
    19801994    ELSE 
    1981       IF (check) WRITE (*,*) ' histwrite : buffer has not been used. We have just to re-allocating it ' 
     1995      IF (l_dbg) WRITE (*,*) 'histwrite : buffer has not been used. ', & 
     1996 &      'We have just to re-allocate it.' 
    19821997      DEALLOCATE (buffer) 
    19831998      ALLOCATE (buffer(buff_pos)) 
     
    19912006!- 
    19922007  IF (.NOT.ALLOCATED(buff_tmp2)) THEN 
    1993     IF (check) THEN 
     2008    IF (l_dbg) THEN 
    19942009      WRITE(*,*) "histwrite_real 1.1 allocate buff_tmp2 ",SIZE(buff_tmp) 
    19952010    ENDIF 
     
    19972012    buff_tmp2_sz = datasz_max(pfileid,varid) 
    19982013  ELSE IF (datasz_max(pfileid,varid) > buff_tmp2_sz) THEN 
    1999     IF (check) THEN 
     2014    IF (l_dbg) THEN 
    20002015      WRITE(*,*) "histwrite_real 1.2 re-allocate buff_tmp2 : ", & 
    20012016     & SIZE(buff_tmp)," instead of ",SIZE(buff_tmp2) 
     
    20112026! 3.0 Do the operations or transfer the slab of data into buff_tmp 
    20122027!- 
    2013   IF (check) WRITE(*,*) "histwrite: 3.0",pfileid 
     2028  IF (l_dbg) WRITE(*,*) "histwrite: 3.0",pfileid 
    20142029!- 
    20152030! 3.1 DO the Operations only if needed 
     
    20272042      CALL mathop(sopps(i,varid,io),nbin,buff_tmp,missing_val, & 
    20282043 &      nbindex,nindex,scal(i,varid,io),nbout,buff_tmp2) 
    2029       IF (check) THEN 
     2044      IF (l_dbg) THEN 
    20302045        WRITE(*,*) & 
    20312046 &       "histwrite: 3.4a nbout : ",nbin,nbout,sopps(i,varid,io) 
     
    20362051      CALL mathop(sopps(i,varid,io+1),nbin,buff_tmp2,missing_val, & 
    20372052 &      nbindex,nindex,scal(i,varid,io+1),nbout,buff_tmp) 
    2038       IF (check) THEN 
     2053      IF (l_dbg) THEN 
    20392054        WRITE(*,*) & 
    20402055 &       "histwrite: 3.4b nbout : ",nbin,nbout,sopps(i,varid,io+1) 
     
    20442059!   3.5 Zoom into the data 
    20452060!- 
    2046     IF (check) THEN 
     2061    IF (l_dbg) THEN 
    20472062      WRITE(*,*) & 
    20482063 &     "histwrite: 3.5 size(buff_tmp) : ",SIZE(buff_tmp) 
     
    20662081!-- 4.0 Get the min and max of the field (buff_tmp) 
    20672082!- 
    2068     IF (check) WRITE(*,*) "histwrite: 4.0 buff_tmp",pfileid,varid, & 
    2069  &    TRIM(tmp_opp),'----',LEN_TRIM(tmp_opp),nbindex 
     2083    IF (l_dbg) WRITE(*,*) "histwrite: 4.0 buff_tmp",pfileid,varid, & 
     2084 &    TRIM(tmp_opp),' ---- ',LEN_TRIM(tmp_opp),nbindex 
    20702085!- 
    20712086    IF (hist_calc_rng(pfileid,varid)) THEN 
     
    20812096!--     output we do not transfer to the buffer. 
    20822097!- 
    2083     IF (check) WRITE(*,*) "histwrite: 5.0",pfileid,"tsz :",tsz 
     2098    IF (l_dbg) WRITE(*,*) "histwrite: 5.0",pfileid,"tsz :",tsz 
    20842099!- 
    20852100    ipt = point(pfileid,varid) 
     
    21002115! 6.0 Write to file if needed 
    21012116!- 
    2102   IF (check) WRITE(*,*) "histwrite: 6.0",pfileid 
     2117  IF (l_dbg) WRITE(*,*) "histwrite: 6.0",pfileid 
    21032118!- 
    21042119  IF (do_write) THEN 
     
    21092124!-- 6.1 Do the operations that are needed before writting 
    21102125!- 
    2111     IF (check) WRITE(*,*) "histwrite: 6.1",pfileid 
     2126    IF (l_dbg) WRITE(*,*) "histwrite: 6.1",pfileid 
    21122127!- 
    21132128    IF (     (TRIM(tmp_opp) /= "inst") & 
     
    21222137   &    .AND.(TRIM(tmp_opp) /= "once") ) THEN 
    21232138!- 
    2124       IF (check) WRITE(*,*) "histwrite: 6.2",pfileid 
     2139      IF (l_dbg) WRITE(*,*) "histwrite: 6.2",pfileid 
    21252140!- 
    21262141      itax = var_axid(pfileid,varid) 
     
    21392154!       we do not write the buffer. 
    21402155!- 
    2141     IF (check) THEN 
     2156    IF (l_dbg) THEN 
    21422157      WRITE(*,*) "histwrite: 6.3",pfileid,ncid,ncvarid,varid,itime 
    21432158    ENDIF 
     
    22192234  INTEGER      :: ib,sp,nx,pos 
    22202235  CHARACTER(LEN=70) :: str70 
    2221 !- 
    2222   LOGICAL :: check = .FALSE. 
    2223 !--------------------------------------------------------------------- 
    2224   IF (check) THEN 
     2236  LOGICAL :: l_dbg 
     2237!--------------------------------------------------------------------- 
     2238  CALL ipsldbg (old_status=l_dbg) 
     2239!- 
     2240  IF (l_dbg) THEN 
    22252241    WRITE(*,*) 'histvar_seq, start of the subroutine :',learning(pfid) 
    22262242  ENDIF 
     
    23312347  ENDIF 
    23322348!- 
    2333   IF (check) THEN 
     2349  IF (l_dbg) THEN 
    23342350    WRITE(*,*) & 
    23352351 &   'histvar_seq, end of the subroutine :',TRIM(pvarname),pvid 
     
    23542370!- 
    23552371  LOGICAL :: file_exists 
    2356   LOGICAL :: check = .FALSE. 
    2357 !--------------------------------------------------------------------- 
    2358   IF (check) WRITE(*,*) 'Entering loop on files :',nb_files 
     2372  LOGICAL :: l_dbg 
     2373!--------------------------------------------------------------------- 
     2374  CALL ipsldbg (old_status=l_dbg) 
     2375!- 
     2376  IF (l_dbg) WRITE(*,*) 'Entering loop on files : ',nb_files 
    23592377!- 
    23602378! 1.The loop on files to synchronise 
     
    23692387!- 
    23702388    IF (file_exists) THEN 
    2371       IF (check) THEN 
     2389      IF (l_dbg) THEN 
    23722390        WRITE(*,*) 'Synchronising specified file number :',file 
    23732391      ENDIF 
     
    23952413  INTEGER :: start_loop,end_loop 
    23962414  CHARACTER(LEN=70) :: str70 
    2397 !- 
    2398   LOGICAL :: check=.FALSE. 
    2399 !--------------------------------------------------------------------- 
    2400   IF (check) WRITE(*,*) 'Entering loop on files :',nb_files 
     2415  LOGICAL :: l_dbg 
     2416!--------------------------------------------------------------------- 
     2417  CALL ipsldbg (old_status=l_dbg) 
     2418!- 
     2419  IF (l_dbg) WRITE(*,*) 'Entering loop on files :',nb_files 
    24012420!- 
    24022421  IF (PRESENT(fid)) THEN 
     
    24092428!- 
    24102429  DO ifile=start_loop,end_loop 
    2411     IF (check) WRITE(*,*) 'Closing specified file number :',ifile 
     2430    IF (l_dbg) WRITE(*,*) 'Closing specified file number :',ifile 
    24122431    ncid = ncdf_ids(ifile) 
    24132432    iret = NF90_REDEF (ncid) 
     
    24152434!-- 1. Loop on the number of variables to add some final information 
    24162435!--- 
    2417     IF (check) WRITE(*,*) 'Entering loop on vars : ',nb_var(ifile) 
     2436    IF (l_dbg) WRITE(*,*) 'Entering loop on vars : ',nb_var(ifile) 
    24182437    DO iv=1,nb_var(ifile) 
    24192438      IF (hist_wrt_rng(ifile,iv)) THEN 
    2420         IF (check) THEN 
     2439        IF (l_dbg) THEN 
    24212440          WRITE(*,*) 'min value for file :',ifile,' var n. :',iv, & 
    24222441         &           ' is : ',hist_minmax(ifile,iv,1) 
     
    24362455!-- 2. Close the file 
    24372456!--- 
    2438     IF (check) WRITE(*,*) 'close file :',ncid 
     2457    IF (l_dbg) WRITE(*,*) 'close file :',ncid 
    24392458    iret = NF90_CLOSE (ncid) 
    24402459    IF (iret /= NF90_NOERR) THEN 
Note: See TracChangeset for help on using the changeset viewer.