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/dyn3dpar
Files:
2 edited

Legend:

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

    r1151 r1154  
    99      USE ioipsl
    1010      USE dimphy
     11      USE infotrac
    1112      USE fonte_neige_mod
    1213      USE pbl_surface_mod
    1314      USE phys_state_var_mod
    1415      USE filtreg_mod
    15       USE infotrac
     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"
     
    4344      ! local variables:
    4445      REAL :: latfi(klon), lonfi(klon)
    45       REAL :: orog(iip1,jjp1), rugo(iip1,jjp1),
    46      . psol(iip1, jjp1), phis(iip1, jjp1)
     46      REAL :: orog(iip1,jjp1), rugo(iip1,jjp1)
     47      REAL :: psol(iip1, jjp1), phis(iip1, jjp1)
    4748      REAL :: p3d(iip1, jjp1, llm+1)
    4849      REAL :: uvent(iip1, jjp1, llm)
     
    5253      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
    77       INTEGER :: nq
    7879      REAL :: xpi
    7980      !
     
    103104      REAL :: w(ip1jmp1,llm)
    104105      REAL ::phystep
    105       REAL :: rugsrel(iip1*jjp1)
     106CC      REAL :: rugsrel(iip1*jjp1)
    106107      REAL :: fder(klon)
    107       real zrel(iip1*jjp1),chmin,chmax
    108 
    109       CHARACTER*80 :: visu_file
     108!!      real zrel(iip1*jjp1),chmin,chmax
     109
     110!!      CHARACTER(len=80) :: visu_file
    110111      INTEGER :: visuid
    111112
     
    141142      REAL      :: solarlong0
    142143      real :: seuil_inversion
     144      logical  read_climoz ! read ozone climatology
    143145
    144146      !
     
    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 )
    177179
    178180      dtvr   = daysec/FLOAT(day_step)
     
    181183      CALL iniconst()
    182184      CALL inigeom()
    183       !
     185
    184186      CALL inifilr()
    185 C init pour traceurs
     187! Initialisation pour traceurs
    186188      call infotrac_init
    187       ALLOCATE(q3d(iip1, jjp1, llm,nqtot))
    188 !      CALL phys_state_var_init()
     189      ALLOCATE(q3d(iip1, jjp1, llm, nqtot))
     190!     CALL phys_state_var_init()
    189191      !
    190192      latfi(1) = ASIN(1.0)
     
    243245
    244246      write(*,*)'Essai de lecture masque ocean'
    245       iret = nf_open("o2a.nc", NF_NOWRITE, nid_o2a)
     247      iret = nf90_open("o2a.nc", NF90_NOWRITE, nid_o2a)
    246248      if (iret .ne. 0) then
    247249        write(*,*)'ATTENTION!! pas de fichier o2a.nc trouve'
     
    262264      else
    263265        couple = .true.
    264         iret = nf_close(nid_o2a)
     266        iret = nf90_close(nid_o2a)
    265267        call flininfo("o2a.nc", iml_omask, jml_omask, llm_tmp, ttm_tmp
    266268     $    , nid_o2a)
     
    399401     .                           maxval(qsat(:,:,:))
    400402      !
    401       WRITE(*,*) 'QSAT :', qsat(10,20,:)
     403CC      WRITE(*,*) 'QSAT :', qsat(10,20,:)
    402404      !
    403405      varname = 'q'
     
    410412      q3d(:,:,:,1) = qd(:,:,:)
    411413      !
     414
     415      if (read_climoz) call regr_lat_time_climoz ! ozone climatology
     416
    412417      varname = 'tsol'
    413418      ! This line needs to be replaced by a call to restget to get the values in the restart file
     
    474479     .     jjm, rlonu, rlatv , interbar )
    475480c
    476       rugsrel(:) = 0.0
    477       IF(ok_orodr)  THEN
    478         DO i = 1, iip1* jjp1
    479          rugsrel(i) = MAX( 1.e-05, zstd(i)* zsig(i) /2. )
    480         ENDDO
    481       ENDIF
     481cc      rugsrel(:) = 0.0
     482cc      IF(ok_orodr)  THEN
     483cc        DO i = 1, iip1* jjp1
     484cc         rugsrel(i) = MAX( 1.e-05, zstd(i)* zsig(i) /2. )
     485cc        ENDDO
     486cc      ENDIF
    482487
    483488
     
    750755
    751756C     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
     757cc      if (1.eq.0 ) then
     758cc      print*,'sortie visu'
     759cc      time_step = 1.
     760cc      t_ops = 2.
     761cc      t_wrt = 2.
     762cc      itau = 2.
     763cc      visu_file='Etat0_visu.nc'
     764cc      CALL initdynav(visu_file,dayref,anneeref,time_step,
     765cc     .              t_ops, t_wrt, visuid)
     766cc      CALL writedynav(visuid, itau,vvent ,
     767cc     .                uvent,tpot,pk,phi,q3d,masse,psol,phis)
     768cc      else
    764769         print*,'CCCCCCCCCCCCCCCCCC REACTIVER SORTIE VISU DANS ETAT0'
    765       endif
     770cc      endif
    766771      print*,'entree histclo'
    767772      CALL histclo
     
    772777      !
    773778      END SUBROUTINE etat0_netcdf
    774 
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3dpar/temps.h

    r985 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!$OMP THREADPRIVATE(/temps/)
Note: See TracChangeset for help on using the changeset viewer.