Ignore:
Timestamp:
Dec 10, 2009, 10:02:56 AM (15 years ago)
Author:
Laurent Fairhead
Message:

Merged LMDZ4-dev branch changes r1241:1278 into the trunk
Running trunk and LMDZ4-dev in LMDZOR configuration on local
machine (sequential) and SX8 (4-proc) yields identical results
(restart and restartphy are identical binarily)
Log history from r1241 to r1278 is available by switching to
source:LMDZ4/branches/LMDZ4-dev-20091210

Location:
LMDZ4/trunk
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ4/trunk

  • LMDZ4/trunk/libf/dyn3d/etat0_netcdf.F

    r1146 r1279  
    1414      USE phys_state_var_mod
    1515      USE filtreg_mod
     16      use regr_lat_time_climoz_m, only: regr_lat_time_climoz
     17      use conf_phys_m, only: conf_phys
    1618#endif
    1719!#endif of #ifdef CPP_EARTH
     20      use netcdf, only: nf90_open, NF90_NOWRITE, nf90_close
    1821      !
    1922      IMPLICIT NONE
    2023      !
    21 #include "netcdf.inc"
    2224#include "dimensions.h"
    2325#include "paramet.h"
     
    4951      REAL :: vvent(iip1, jjm, llm)
    5052      REAL :: t3d(iip1, jjp1, llm), tpot(iip1, jjp1, llm)
    51       REAL, ALLOCATABLE, DIMENSION(:,:,:,:) :: q3d
    5253      REAL :: qsat(iip1, jjp1, llm)
     54      REAL,ALLOCATABLE :: q3d(:, :, :,:)
    5355      REAL :: tsol(klon), qsol(klon), sn(klon)
    54       REAL :: tsolsrf(klon,nbsrf), qsolsrf(klon,nbsrf),snsrf(klon,nbsrf)
     56!!      REAL :: tsolsrf(klon,nbsrf)
     57      real qsolsrf(klon,nbsrf),snsrf(klon,nbsrf)
    5558      REAL :: albe(klon,nbsrf), evap(klon,nbsrf)
    5659      REAL :: alblw(klon,nbsrf)
     
    7275      !
    7376
    74       CHARACTER*80 :: varname
     77      CHARACTER(len=80) :: varname
    7578      !
    7679      INTEGER :: i,j, ig, l, ji,ii1,ii2
     
    102105      REAL :: w(ip1jmp1,llm)
    103106      REAL ::phystep
    104       REAL :: rugsrel(iip1*jjp1)
     107CC      REAL :: rugsrel(iip1*jjp1)
    105108      REAL :: fder(klon)
    106       real zrel(iip1*jjp1),chmin,chmax
    107 
    108       CHARACTER*80 :: visu_file
     109!!      real zrel(iip1*jjp1),chmin,chmax
     110
     111!!      CHARACTER(len=80) :: visu_file
    109112      INTEGER :: visuid
    110113
     
    126129      logical              :: ok_journe, ok_mensuel, ok_instan, ok_hf
    127130      logical              :: ok_LES
    128       LOGICAL              :: ok_ade, ok_aie, aerosol_couple
     131      LOGICAL              :: ok_ade, ok_aie, aerosol_couple, new_aod
     132      INTEGER              :: flag_aerosol
    129133      REAL                 :: bl95_b0, bl95_b1
    130134      real                 :: fact_cldcon, facttemps,ratqsbas,ratqshaut
     135      real                 :: tau_ratqs
    131136      integer              :: iflag_cldcon
    132137      integer              :: iflag_ratqs
     
    140145      real :: seuil_inversion
    141146
     147      integer  read_climoz ! read ozone climatology
     148C     Allowed values are 0, 1 and 2
     149C     0: do not read an ozone climatology
     150C     1: read a single ozone climatology that will be used day and night
     151C     2: read two ozone climatologies, the average day and night
     152C     climatology and the daylight climatology
     153
    142154      !
    143155      !   Constantes
     
    162174!      CALL defrun_new(99,.TRUE.,clesphy0)
    163175      CALL conf_gcm( 99, .TRUE. , clesphy0 )
    164       call conf_phys(ok_journe, ok_mensuel, ok_instan,                  &
    165      &                 ok_hf, ok_LES,                                   &
     176      call conf_phys(  ok_journe, ok_mensuel, ok_instan, ok_hf, ok_LES, &
    166177     &                 solarlong0,seuil_inversion,                      &
    167178     &                 fact_cldcon, facttemps,ok_newmicro,iflag_radia,  &
    168179     &                 iflag_cldcon,                                    &
    169      &                 iflag_ratqs,ratqsbas,ratqshaut,                  &
     180     &                 iflag_ratqs,ratqsbas,ratqshaut,tau_ratqs,        &
    170181     &                 ok_ade, ok_aie, aerosol_couple,                  &
     182     &                 flag_aerosol, new_aod,                           &
    171183     &                 bl95_b0, bl95_b1,                                &
    172184     &                 iflag_thermals,nsplit_thermals,tau_thermals,     &
    173185     &                 iflag_thermals_ed,iflag_thermals_optflux,        &
    174      &                 iflag_coupl,iflag_clos,iflag_wake )
     186     &                 iflag_coupl,iflag_clos,iflag_wake, read_climoz )
     187
     188! co2_ppm0 : initial value of atmospheric CO2 from .def file (co2_ppm value)
     189      co2_ppm0 = co2_ppm
     190
    175191      dtvr   = daysec/FLOAT(day_step)
    176192      print*,'dtvr',dtvr
    177193
    178 
    179 
    180194      CALL iniconst()
    181195      CALL inigeom()
    182196
    183197! Initialisation pour traceurs
    184       CALL infotrac_init
    185       ALLOCATE(q3d(iip1,jjp1,llm,nqtot))
    186 
     198      call infotrac_init
     199      ALLOCATE(q3d(iip1, jjp1, llm, nqtot))
    187200
    188201      CALL inifilr()
    189       CALL phys_state_var_init()
     202      CALL phys_state_var_init(read_climoz)
    190203      !
    191204      latfi(1) = ASIN(1.0)
     
    244257
    245258      write(*,*)'Essai de lecture masque ocean'
    246       iret = nf_open("o2a.nc", NF_NOWRITE, nid_o2a)
     259      iret = nf90_open("o2a.nc", NF90_NOWRITE, nid_o2a)
    247260      if (iret .ne. 0) then
    248261        write(*,*)'ATTENTION!! pas de fichier o2a.nc trouve'
     
    263276      else
    264277        couple = .true.
    265         iret = nf_close(nid_o2a)
     278        iret = nf90_close(nid_o2a)
    266279        call flininfo("o2a.nc", iml_omask, jml_omask, llm_tmp, ttm_tmp
    267280     $    , nid_o2a)
     
    400413     .                           maxval(qsat(:,:,:))
    401414      !
    402       WRITE(*,*) 'QSAT :', qsat(10,20,:)
     415CC      WRITE(*,*) 'QSAT :', qsat(10,20,:)
    403416      !
    404417      varname = 'q'
     
    411424      q3d(:,:,:,1) = qd(:,:,:)
    412425      !
     426
     427!     Ozone climatology:
     428      if (read_climoz >= 1) call regr_lat_time_climoz(read_climoz)
     429
    413430      varname = 'tsol'
    414431      ! This line needs to be replaced by a call to restget to get the values in the restart file
     
    475492     .     jjm, rlonu, rlatv , interbar )
    476493c
    477       rugsrel(:) = 0.0
    478       IF(ok_orodr)  THEN
    479         DO i = 1, iip1* jjp1
    480          rugsrel(i) = MAX( 1.e-05, zstd(i)* zsig(i) /2. )
    481         ENDDO
    482       ENDIF
     494cc      rugsrel(:) = 0.0
     495cc      IF(ok_orodr)  THEN
     496cc        DO i = 1, iip1* jjp1
     497cc         rugsrel(i) = MAX( 1.e-05, zstd(i)* zsig(i) /2. )
     498cc        ENDDO
     499cc      ENDIF
    483500
    484501
     
    650667      itau_phy = 0
    651668      iday = dayref +itau/day_step
    652       time = FLOAT(itau-(iday-dayref)*day_step)/day_step
     669      time = real(itau-(iday-dayref)*day_step)/day_step
    653670c     
    654671      IF(time.GT.1)  THEN
     
    714731      q_ancien = 0.
    715732      agesno = 0.
     733c
    716734      frugs(1:klon,is_oce) = rugmer(1:klon)
    717735      frugs(1:klon,is_ter) = MAX(1.0e-05, zstd(1:klon)*zsig(1:klon)/2.0)
     
    750768
    751769C     Sortie Visu pour les champs dynamiques
    752       if (1.eq.0 ) then
    753       print*,'sortie visu'
    754       time_step = 1.
    755       t_ops = 2.
    756       t_wrt = 2.
    757       itau = 2.
    758       visu_file='Etat0_visu.nc'
    759       CALL initdynav(visu_file,dayref,anneeref,time_step,
    760      .              t_ops, t_wrt, visuid)
    761       CALL writedynav(visuid, itau,vvent ,
    762      .                uvent,tpot,pk,phi,q3d,masse,psol,phis)
    763       else
     770cc      if (1.eq.0 ) then
     771cc      print*,'sortie visu'
     772cc      time_step = 1.
     773cc      t_ops = 2.
     774cc      t_wrt = 2.
     775cc      itau = 2.
     776cc      visu_file='Etat0_visu.nc'
     777cc      CALL initdynav(visu_file,dayref,anneeref,time_step,
     778cc     .              t_ops, t_wrt, visuid)
     779cc      CALL writedynav(visuid, itau,vvent ,
     780cc     .                uvent,tpot,pk,phi,q3d,masse,psol,phis)
     781cc      else
    764782         print*,'CCCCCCCCCCCCCCCCCC REACTIVER SORTIE VISU DANS ETAT0'
    765       endif
     783cc      endif
    766784      print*,'entree histclo'
    767785      CALL histclo
    768 
    769       DEALLOCATE(q3d)
    770786
    771787#endif
     
    774790      !
    775791      END SUBROUTINE etat0_netcdf
    776 
Note: See TracChangeset for help on using the changeset viewer.