Ignore:
Timestamp:
May 4, 2009, 5:24:19 PM (15 years ago)
Author:
lguez
Message:

-- Added "NetCDF95" interface in "bibio".
-- NetCDF95 uses the module "typesizes", which is part of NetCDF, so we
exclude dependency on "typesizes" in "bld.cfg".
-- Added "assert_eq" and "assert" procedures, which are in the public
part of Numerical Recipes.
-- Added some interpolation and regridding utilities in "bibio".
-- Added the ability to read an ozone climatology from a NetCDF file.
-- Commented out unused variables and code in "etat0_netcdf".
-- Updated calls to NetCDF in "etat0_netcdf": from Fortran 77
interface to Fortran 90 interface.
-- Removed useless "deallocate" at the end of "etat0_netcdf".
-- Corrected some declarations not conforming to Fortran standard, such
as "integer*4", or obsolescent such as "character*4".
-- Replaced some calls to not-standard function "float" by calls to
"real".
-- On Brodie at IDRIS, the NetCDF library compiled with OpenMP should
be used. Changed path in "arch-SX8_BRODIE.path".
-- Added warning for incompatibility of debugging options and OpenMP
parallelization in "makelmdz_fcm".

Location:
LMDZ4/branches/LMDZ4-dev/libf/dyn3d
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3d/etat0_netcdf.F

    r1151 r1154  
    1414      USE phys_state_var_mod
    1515      USE filtreg_mod
     16      use regr_lat_time_climoz_m, only: regr_lat_time_climoz
    1617#endif
    1718!#endif of #ifdef CPP_EARTH
     19      use netcdf, only: nf90_open, NF90_NOWRITE, nf90_close
    1820      !
    1921      IMPLICIT NONE
    2022      !
    21 #include "netcdf.inc"
    2223#include "dimensions.h"
    2324#include "paramet.h"
     
    4950      REAL :: vvent(iip1, jjm, llm)
    5051      REAL :: t3d(iip1, jjp1, llm), tpot(iip1, jjp1, llm)
    51       REAL, ALLOCATABLE, DIMENSION(:,:,:,:) :: q3d
    5252      REAL :: qsat(iip1, jjp1, llm)
     53      REAL,ALLOCATABLE :: q3d(:, :, :,:)
    5354      REAL :: tsol(klon), qsol(klon), sn(klon)
    54       REAL :: tsolsrf(klon,nbsrf), qsolsrf(klon,nbsrf),snsrf(klon,nbsrf)
     55!!      REAL :: tsolsrf(klon,nbsrf)
     56      real qsolsrf(klon,nbsrf),snsrf(klon,nbsrf)
    5557      REAL :: albe(klon,nbsrf), evap(klon,nbsrf)
    5658      REAL :: alblw(klon,nbsrf)
     
    7274      !
    7375
    74       CHARACTER*80 :: varname
     76      CHARACTER(len=80) :: varname
    7577      !
    7678      INTEGER :: i,j, ig, l, ji,ii1,ii2
     
    102104      REAL :: w(ip1jmp1,llm)
    103105      REAL ::phystep
    104       REAL :: rugsrel(iip1*jjp1)
     106CC      REAL :: rugsrel(iip1*jjp1)
    105107      REAL :: fder(klon)
    106       real zrel(iip1*jjp1),chmin,chmax
    107 
    108       CHARACTER*80 :: visu_file
     108!!      real zrel(iip1*jjp1),chmin,chmax
     109
     110!!      CHARACTER(len=80) :: visu_file
    109111      INTEGER :: visuid
    110112
     
    140142      REAL      :: solarlong0
    141143      real :: seuil_inversion
     144      logical  read_climoz ! read ozone climatology
    142145
    143146      !
     
    163166!      CALL defrun_new(99,.TRUE.,clesphy0)
    164167      CALL conf_gcm( 99, .TRUE. , clesphy0 )
    165       call conf_phys(ok_journe, ok_mensuel, ok_instan,                  &
    166      &                 ok_hf, ok_LES,                                   &
     168      call conf_phys(  ok_journe, ok_mensuel, ok_instan, ok_hf, ok_LES, &
    167169     &                 solarlong0,seuil_inversion,                      &
    168170     &                 fact_cldcon, facttemps,ok_newmicro,iflag_radia,  &
     
    174176     &                 iflag_thermals,nsplit_thermals,tau_thermals,     &
    175177     &                 iflag_thermals_ed,iflag_thermals_optflux,        &
    176      &                 iflag_coupl,iflag_clos,iflag_wake )
     178     &                 iflag_coupl,iflag_clos,iflag_wake, read_climoz )
     179
    177180      dtvr   = daysec/FLOAT(day_step)
    178181      print*,'dtvr',dtvr
    179182
    180 
    181 
    182183      CALL iniconst()
    183184      CALL inigeom()
    184185
    185186! Initialisation pour traceurs
    186       CALL infotrac_init
    187       ALLOCATE(q3d(iip1,jjp1,llm,nqtot))
    188 
     187      call infotrac_init
     188      ALLOCATE(q3d(iip1, jjp1, llm, nqtot))
    189189
    190190      CALL inifilr()
     
    246246
    247247      write(*,*)'Essai de lecture masque ocean'
    248       iret = nf_open("o2a.nc", NF_NOWRITE, nid_o2a)
     248      iret = nf90_open("o2a.nc", NF90_NOWRITE, nid_o2a)
    249249      if (iret .ne. 0) then
    250250        write(*,*)'ATTENTION!! pas de fichier o2a.nc trouve'
     
    265265      else
    266266        couple = .true.
    267         iret = nf_close(nid_o2a)
     267        iret = nf90_close(nid_o2a)
    268268        call flininfo("o2a.nc", iml_omask, jml_omask, llm_tmp, ttm_tmp
    269269     $    , nid_o2a)
     
    402402     .                           maxval(qsat(:,:,:))
    403403      !
    404       WRITE(*,*) 'QSAT :', qsat(10,20,:)
     404CC      WRITE(*,*) 'QSAT :', qsat(10,20,:)
    405405      !
    406406      varname = 'q'
     
    413413      q3d(:,:,:,1) = qd(:,:,:)
    414414      !
     415
     416      if (read_climoz) call regr_lat_time_climoz ! ozone climatology
     417
    415418      varname = 'tsol'
    416419      ! This line needs to be replaced by a call to restget to get the values in the restart file
     
    477480     .     jjm, rlonu, rlatv , interbar )
    478481c
    479       rugsrel(:) = 0.0
    480       IF(ok_orodr)  THEN
    481         DO i = 1, iip1* jjp1
    482          rugsrel(i) = MAX( 1.e-05, zstd(i)* zsig(i) /2. )
    483         ENDDO
    484       ENDIF
     482cc      rugsrel(:) = 0.0
     483cc      IF(ok_orodr)  THEN
     484cc        DO i = 1, iip1* jjp1
     485cc         rugsrel(i) = MAX( 1.e-05, zstd(i)* zsig(i) /2. )
     486cc        ENDDO
     487cc      ENDIF
    485488
    486489
     
    716719      q_ancien = 0.
    717720      agesno = 0.
     721c
    718722      frugs(1:klon,is_oce) = rugmer(1:klon)
    719723      frugs(1:klon,is_ter) = MAX(1.0e-05, zstd(1:klon)*zsig(1:klon)/2.0)
     
    752756
    753757C     Sortie Visu pour les champs dynamiques
    754       if (1.eq.0 ) then
    755       print*,'sortie visu'
    756       time_step = 1.
    757       t_ops = 2.
    758       t_wrt = 2.
    759       itau = 2.
    760       visu_file='Etat0_visu.nc'
    761       CALL initdynav(visu_file,dayref,anneeref,time_step,
    762      .              t_ops, t_wrt, visuid)
    763       CALL writedynav(visuid, itau,vvent ,
    764      .                uvent,tpot,pk,phi,q3d,masse,psol,phis)
    765       else
     758cc      if (1.eq.0 ) then
     759cc      print*,'sortie visu'
     760cc      time_step = 1.
     761cc      t_ops = 2.
     762cc      t_wrt = 2.
     763cc      itau = 2.
     764cc      visu_file='Etat0_visu.nc'
     765cc      CALL initdynav(visu_file,dayref,anneeref,time_step,
     766cc     .              t_ops, t_wrt, visuid)
     767cc      CALL writedynav(visuid, itau,vvent ,
     768cc     .                uvent,tpot,pk,phi,q3d,masse,psol,phis)
     769cc      else
    766770         print*,'CCCCCCCCCCCCCCCCCC REACTIVER SORTIE VISU DANS ETAT0'
    767       endif
     771cc      endif
    768772      print*,'entree histclo'
    769773      CALL histclo
    770 
    771       DEALLOCATE(q3d)
    772774
    773775#endif
     
    776778      !
    777779      END SUBROUTINE etat0_netcdf
    778 
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3d/temps.h

    r792 r1154  
    1515
    1616      INTEGER   itaufin
    17       INTEGER*4 itau_dyn, itau_phy
    18       INTEGER*4 day_ini, day_end, annee_ref, day_ref
     17      INTEGER(kind=4) itau_dyn, itau_phy
     18      INTEGER(kind=4) day_ini, day_end, annee_ref, day_ref
    1919      REAL      dt
    2020
Note: See TracChangeset for help on using the changeset viewer.