Ignore:
Timestamp:
Nov 28, 2014, 4:36:29 PM (10 years ago)
Author:
Laurent Fairhead
Message:

Merged trunk changes -r2070:2158 into testing branch. Compilation problems introduced by revision r2155 have been corrected by hand

Location:
LMDZ5/branches/testing
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/branches/testing

  • LMDZ5/branches/testing/libf/phylmd/limit_netcdf.F90

    r1910 r2160  
    2525  USE dimphy
    2626  USE ioipsl,             ONLY : ioget_year_len
    27   USE phys_state_var_mod, ONLY : pctsrf
     27  USE phys_state_var_mod, ONLY : pctsrf, rlon, rlat
    2828  USE netcdf,             ONLY : NF90_OPEN,    NF90_CREATE,  NF90_CLOSE,       &
    2929                   NF90_DEF_DIM, NF90_DEF_VAR, NF90_PUT_VAR, NF90_PUT_ATT,     &
     
    3131                   NF90_CLOBBER, NF90_ENDDEF,  NF90_UNLIMITED, NF90_FLOAT
    3232  USE inter_barxy_m, only: inter_barxy
     33  use netcdf95, only: nf95_def_var, nf95_put_att, nf95_put_var
    3334#endif
    3435  IMPLICIT NONE
     
    5455!--- INPUT NETCDF FILES NAMES --------------------------------------------------
    5556  CHARACTER(LEN=25) :: icefile, sstfile, dumstr
    56   CHARACTER(LEN=25), PARAMETER :: famipsst='amipbc_sst_1x1.nc        ',        &
    57                                   famipsic='amipbc_sic_1x1.nc        ',        &
    58                                   fcpldsst='cpl_atm_sst.nc           ',        &
    59                                   fcpldsic='cpl_atm_sic.nc           ',        &
    60                                   fhistsst='histmth_sst.nc           ',        &
    61                                   fhistsic='histmth_sic.nc           ',        &
    62                                   frugo   ='Rugos.nc                 ',        &
    63                                   falbe   ='Albedo.nc                '
     57  CHARACTER(LEN=25), PARAMETER :: famipsst ='amipbc_sst_1x1.nc        ',        &
     58                                  famipsic ='amipbc_sic_1x1.nc        ',        &
     59                                  fcpldsst ='cpl_atm_sst.nc           ',        &
     60                                  fcpldsic ='cpl_atm_sic.nc           ',        &
     61                                  fhistsst ='histmth_sst.nc           ',        &
     62                                  fhistsic ='histmth_sic.nc           ',        &
     63                                  frugo    ='Rugos.nc                 ',        &
     64                                  falbe    ='Albedo.nc                ',        &
     65                                  feraisstk='sstk.nc                  ',        &
     66                                  feraici  ='ci.nc                    '
    6467  CHARACTER(LEN=10) :: varname
    6568!--- OUTPUT VARIABLES FOR NETCDF FILE ------------------------------------------
     
    7578  INTEGER, DIMENSION(2) :: dims
    7679  INTEGER :: id_tim,  id_SST,  id_BILS, id_RUG, id_ALB
    77   INTEGER :: id_FOCE, id_FSIC, id_FTER, id_FLIC
     80  INTEGER :: id_FOCE, id_FSIC, id_FTER, id_FLIC, varid_longitude, varid_latitude
    7881  INTEGER :: NF90_FORMAT
    7982  INTEGER :: ndays                   !--- Depending on the output calendar
     
    118121     icefile=TRIM(fhistsic)
    119122     varname='pourc_sic'
     123  ELSE IF ( NF90_OPEN(TRIM(feraici),NF90_NOWRITE,nid)==NF90_NOERR ) THEN
     124     icefile=TRIM(feraici)
     125     varname='ci'
    120126  ELSE
    121127     WRITE(lunout,*) 'ERROR! No sea-ice input file was found.'
    122      WRITE(lunout,*) 'One of following files must be availible : ',trim(famipsic),', ',trim(fcpldsic),', ',trim(fhistsic)
     128     WRITE(lunout,*) 'One of following files must be availible : ',trim(famipsic),', ',trim(fcpldsic),', ',trim(fhistsic), trim(feraici)
    123129     CALL abort_gcm('limit_netcdf','No sea-ice file was found',1)
    124130  END IF
     
    179185     sstfile=TRIM(fhistsst)
    180186     varname='tsol_oce'
     187  ELSE IF ( NF90_OPEN(TRIM(feraisstk),NF90_NOWRITE,nid)==NF90_NOERR ) THEN
     188     sstfile=TRIM(feraisstk)
     189     varname='sstk'
    181190  ELSE
    182191     WRITE(lunout,*) 'ERROR! No sst input file was found.'
    183      WRITE(lunout,*) 'One of following files must be availible : ',trim(famipsst),trim(fcpldsst),trim(fhistsst)
     192     WRITE(lunout,*) 'One of following files must be availible : ',trim(famipsst),trim(fcpldsst),trim(fhistsst),trim(feraisstk)
    184193     CALL abort_gcm('limit_netcdf','No sst file was found',1)
    185194  END IF
     
    220229  ierr=NF90_DEF_VAR(nid,"ALB",  NF90_FORMAT,dims,id_ALB)
    221230  ierr=NF90_DEF_VAR(nid,"RUG",  NF90_FORMAT,dims,id_RUG)
     231  call nf95_def_var(nid, "longitude", NF90_FLOAT, ndim, varid_longitude)
     232  call nf95_def_var(nid, "latitude", NF90_FLOAT, ndim, varid_latitude)
    222233
    223234  !--- Attributes creation
     
    232243  ierr=NF90_PUT_ATT(nid,id_RUG, "title","Rugosite")
    233244
     245  call nf95_put_att(nid, varid_longitude, "standard_name", "longitude")
     246  call nf95_put_att(nid, varid_longitude, "units", "degrees_east")
     247
     248  call nf95_put_att(nid, varid_latitude, "standard_name", "latitude")
     249  call nf95_put_att(nid, varid_latitude, "units", "degrees_north")
     250
    234251  ierr=NF90_ENDDEF(nid)
    235252
     
    244261  ierr=NF90_PUT_VAR(nid,id_ALB ,phy_alb(:,:),(/1,1/),(/klon,ndays/))
    245262  ierr=NF90_PUT_VAR(nid,id_RUG ,phy_rug(:,:),(/1,1/),(/klon,ndays/))
     263  call nf95_put_var(nid, varid_longitude, rlon)
     264  call nf95_put_var(nid, varid_latitude, rlat)
    246265
    247266  ierr=NF90_CLOSE(nid)
Note: See TracChangeset for help on using the changeset viewer.