Ignore:
Timestamp:
07/25/08 12:58:01 (16 years ago)
Author:
bellier
Message:
  • Updating for more compliance with CF Metadata Convention.
  • Some cleaning
File:
1 edited

Legend:

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

    r329 r362  
    171171!!   Attributes        Values 
    172172!!   'axis'            "Z" 
    173 !!   'standard_name'   "level" 
     173!!   'standard_name'   "model_level_number" 
    174174!!   'units'           "sigma_level" 
    175175!!   'long_name'       "Sigma Levels" 
     
    613613!! which are spatio-temporal coordinates (x/y/z/t). 
    614614!! 
    615 !!-- Rule 1 : we look for a correct "axis" attribute 
     615!!-- Rule 1 : we look for a variable with one dimension 
     616!!--          and which has the same name as its dimension 
     617!! 
     618!!-- Rule 2 : we look for a correct "axis" attribute 
    616619!! 
    617620!!  Axis       Axis attribute             Number of dimensions 
     
    623626!!    t         T                         1 
    624627!! 
    625 !!-- Rule 2 : we look for a specific name 
    626 !! 
    627 !!  Axis       Names 
    628 !! 
    629 !!    x        'nav_lon' 'lon'     'longitude' 
    630 !!    y        'nav_lat' 'lat'     'latitude' 
    631 !!    z        'depth'   'deptht'  'height'       'level' 
    632 !!             'lev'     'plev'    'sigma_level'  'layer' 
    633 !!    t        'time'    'tstep'   'timesteps' 
    634 !! 
    635 !!-- Rule 3 : we look for a variable with one dimension 
    636 !!--          and which has the same name as its dimension 
     628!!-- Rule 3 : we look for a correct "standard_name" attribute 
     629!! 
     630!!  Axis       Axis attribute          Number of dimensions 
     631!!             (case insensitive) 
     632!! 
     633!!    x         longitude              1/2 
     634!!    y         latitude               1/2 
     635!!    z         model_level_number     1 
     636!!    t         time                   1 
     637!! 
     638!!-- Rule 4 : we look for a specific name 
     639!! 
     640!!  Axis   Names 
     641!! 
     642!!    x    'nav_lon' 'lon'    'longitude' 
     643!!    y    'nav_lat' 'lat'    'latitude' 
     644!!    z    'depth'   'deptht' 'height'      'level' 
     645!!         'lev'     'plev'   'sigma_level' 'layer' 
     646!!    t    'time'    'tstep'  'timesteps' 
     647!! 
    637648!!-------------------------------------------------------------------- 
    638649!- 
     
    921932!- 
    922933! Define "Conventions" global attribute 
    923   i_rc = NF90_PUT_ATT(f_e,NF90_GLOBAL,'Conventions',"CF-1.0") 
     934  i_rc = NF90_PUT_ATT(f_e,NF90_GLOBAL,'Conventions',"CF-1.1") 
    924935!- 
    925936! Add the DOMAIN attributes if needed 
     
    11111122 &                      nw_di(k_1,f_i),levid) 
    11121123    i_rc = NF90_PUT_ATT(f_e,levid,"axis","Z") 
    1113     i_rc = NF90_PUT_ATT(f_e,levid,'standard_name','level') 
     1124    i_rc = NF90_PUT_ATT(f_e,levid,'standard_name','model_level_number') 
    11141125    i_rc = NF90_PUT_ATT(f_e,levid,'units','sigma_level') 
    11151126    i_rc = NF90_PUT_ATT(f_e,levid,'long_name','Sigma Levels') 
     
    48794890  INTEGER :: kv,k,n_r,l_d,n_d,i_rc,dimnb 
    48804891  CHARACTER(LEN=1)  :: c_ax 
     4892  CHARACTER(LEN=9)  :: c_sn 
    48814893  CHARACTER(LEN=15),DIMENSION(10) :: c_r 
    48824894  CHARACTER(LEN=40) :: c_t1,c_t2 
     
    48994911      CASE('x') 
    49004912        l_d = 2 
     4913        c_sn = 'longitude' 
    49014914      CASE('y') 
    49024915        l_d = 2 
     4916        c_sn = 'latitude' 
    49034917      CASE('z') 
    49044918        l_d = 1 
     4919        c_sn = 'model_level_number' 
    49054920      CASE('t') 
    49064921        l_d = 1 
     4922        c_sn = 'time' 
    49074923      END SELECT 
    49084924!--- 
    4909 !-- Rule 1 : we look for a correct "axis" attribute 
    4910 !--- 
    4911     IF (i_v < 0) THEN 
    4912       L_R1: DO kv=1,nw_nv(f_i) 
    4913         i_rc = NF90_GET_ATT(nw_id(f_i),kv,'axis',c_t1) 
    4914         IF (i_rc == NF90_NOERR) THEN 
    4915           CALL strlowercase (c_t1) 
    4916           IF (TRIM(c_t1) == c_ax) THEN 
    4917             i_rc = NF90_INQUIRE_VARIABLE(nw_id(f_i),kv,ndims=n_d) 
    4918             IF (n_d <= l_d) THEN 
    4919               i_v = kv; nbd = n_d; 
    4920               EXIT L_R1 
    4921             ENDIF 
    4922           ENDIF 
    4923         ENDIF 
    4924       ENDDO L_R1 
    4925     ENDIF 
    4926 !--- 
    4927 !-- Rule 2 : we look for a specific name 
    4928 !--- 
    4929     IF (i_v < 0) THEN 
    4930       SELECT CASE (c_ax) 
    4931       CASE('x') 
    4932         n_r = 3 
    4933         c_r(1)='nav_lon'; c_r(2)='lon'; c_r(3)='longitude'; 
    4934       CASE('y') 
    4935         n_r = 3 
    4936         c_r(1)='nav_lat'; c_r(2)='lat'; c_r(3)='latitude'; 
    4937       CASE('z') 
    4938         n_r = 8 
    4939         c_r(1)='depth'; c_r(2)='deptht'; c_r(3)='height'; 
    4940         c_r(4)='level'; c_r(5)='lev'; c_r(6)='plev'; 
    4941         c_r(7)='sigma_level'; c_r(8)='layer'; 
    4942       CASE('t') 
    4943         n_r = 3 
    4944         c_r(1)='time'; c_r(2)='tstep'; c_r(3)='timesteps'; 
    4945       END SELECT 
    4946 !----- 
    4947       L_R2: DO kv=1,nw_nv(f_i) 
    4948         i_rc = NF90_INQUIRE_VARIABLE & 
    4949  &               (nw_id(f_i),kv,name=c_t1,ndims=n_d) 
    4950         IF (i_rc == NF90_NOERR) THEN 
    4951           CALL strlowercase (c_t1) 
    4952           IF (n_d <= l_d) THEN 
    4953             DO k=1,n_r 
    4954               IF (TRIM(c_t1) == TRIM(c_r(k))) THEN 
    4955                 i_v = kv; nbd = n_d; 
    4956                 EXIT L_R2 
    4957               ENDIF 
    4958             ENDDO 
    4959           ENDIF 
    4960         ENDIF 
    4961       ENDDO L_R2 
    4962     ENDIF 
    4963 !--- 
    4964 !-- Rule 3 : we look for a variable with one dimension 
    4965 !--          and which has the same name as its dimension 
     4925!-- Rule 1 : we look for a variable with one dimension 
     4926!--          and which has the same name as its dimension (NUG) 
    49664927!--- 
    49674928    IF (i_v < 0) THEN 
     
    49854946      IF (i_rc == NF90_NOERR) THEN 
    49864947        CALL strlowercase (c_t1) 
    4987         L_R3: DO kv=1,nw_nv(f_i) 
     4948        L_R1: DO kv=1,nw_nv(f_i) 
    49884949          i_rc = NF90_INQUIRE_VARIABLE & 
    49894950 &                 (nw_id(f_i),kv,name=c_t2,ndims=n_d) 
     
    49924953            IF (TRIM(c_t1) == TRIM(c_t2)) THEN 
    49934954              i_v = kv; nbd = n_d; 
     4955              EXIT L_R1 
     4956            ENDIF 
     4957          ENDIF 
     4958        ENDDO L_R1 
     4959      ENDIF 
     4960    ENDIF 
     4961!--- 
     4962!-- Rule 2 : we look for a correct "axis" attribute (CF) 
     4963!--- 
     4964    IF (i_v < 0) THEN 
     4965      L_R2: DO kv=1,nw_nv(f_i) 
     4966        i_rc = NF90_GET_ATT(nw_id(f_i),kv,'axis',c_t1) 
     4967        IF (i_rc == NF90_NOERR) THEN 
     4968          CALL strlowercase (c_t1) 
     4969          IF (TRIM(c_t1) == c_ax) THEN 
     4970            i_rc = NF90_INQUIRE_VARIABLE(nw_id(f_i),kv,ndims=n_d) 
     4971            IF (n_d <= l_d) THEN 
     4972              i_v = kv; nbd = n_d; 
     4973              EXIT L_R2 
     4974            ENDIF 
     4975          ENDIF 
     4976        ENDIF 
     4977      ENDDO L_R2 
     4978    ENDIF 
     4979!--- 
     4980!-- Rule 3 : we look for a correct "standard_name" attribute (CF) 
     4981!--- 
     4982    IF (i_v < 0) THEN 
     4983      L_R3: DO kv=1,nw_nv(f_i) 
     4984        i_rc = NF90_GET_ATT(nw_id(f_i),kv,'standard_name',c_t1) 
     4985        IF (i_rc == NF90_NOERR) THEN 
     4986          CALL strlowercase (c_t1) 
     4987          IF (TRIM(c_t1) == TRIM(c_sn)) THEN 
     4988            i_rc = NF90_INQUIRE_VARIABLE(nw_id(f_i),kv,ndims=n_d) 
     4989            IF (n_d <= l_d) THEN 
     4990              i_v = kv; nbd = n_d; 
    49944991              EXIT L_R3 
    49954992            ENDIF 
    49964993          ENDIF 
    4997         ENDDO L_R3 
    4998       ENDIF 
     4994        ENDIF 
     4995      ENDDO L_R3 
     4996    ENDIF 
     4997!--- 
     4998!-- Rule 4 : we look for a specific name (IOIPSL) 
     4999!--- 
     5000    IF (i_v < 0) THEN 
     5001      SELECT CASE (c_ax) 
     5002      CASE('x') 
     5003        n_r = 3 
     5004        c_r(1)='nav_lon'; c_r(2)='lon'; c_r(3)='longitude'; 
     5005      CASE('y') 
     5006        n_r = 3 
     5007        c_r(1)='nav_lat'; c_r(2)='lat'; c_r(3)='latitude'; 
     5008      CASE('z') 
     5009        n_r = 8 
     5010        c_r(1)='depth'; c_r(2)='deptht'; c_r(3)='height'; 
     5011        c_r(4)='level'; c_r(5)='lev'; c_r(6)='plev'; 
     5012        c_r(7)='sigma_level'; c_r(8)='layer'; 
     5013      CASE('t') 
     5014        n_r = 3 
     5015        c_r(1)='time'; c_r(2)='tstep'; c_r(3)='timesteps'; 
     5016      END SELECT 
     5017!----- 
     5018      L_R4: DO kv=1,nw_nv(f_i) 
     5019        i_rc = NF90_INQUIRE_VARIABLE & 
     5020 &               (nw_id(f_i),kv,name=c_t1,ndims=n_d) 
     5021        IF (i_rc == NF90_NOERR) THEN 
     5022          CALL strlowercase (c_t1) 
     5023          IF (n_d <= l_d) THEN 
     5024            DO k=1,n_r 
     5025              IF (TRIM(c_t1) == TRIM(c_r(k))) THEN 
     5026                i_v = kv; nbd = n_d; 
     5027                EXIT L_R4 
     5028              ENDIF 
     5029            ENDDO 
     5030          ENDIF 
     5031        ENDIF 
     5032      ENDDO L_R4 
    49995033    ENDIF 
    50005034!--- 
Note: See TracChangeset for help on using the changeset viewer.