Ignore:
Timestamp:
Jul 24, 2024, 4:23:34 PM (4 months ago)
Author:
abarral
Message:

rename modules properly lmdz_*
move some unused files to obsolete/
(lint) uppercase fortran keywords

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/Amaury_dev/libf/dyn3dmem/iniacademic_loc.F90

    r5116 r5117  
    77  USE infotrac,    ONLY: nqtot, niso, iqIsoPha, tracers, getKey, isoName
    88  USE control_mod, ONLY: day_step,planet_type
    9   use exner_hyb_m, ONLY: exner_hyb
    10   use exner_milieu_m, ONLY: exner_milieu
     9  USE exner_hyb_m, ONLY: exner_hyb
     10  USE exner_milieu_m, ONLY: exner_milieu
    1111  USE parallel_lmdz, ONLY: ijb_u, ije_u, ijb_v, ije_v
    1212  USE IOIPSL, ONLY: getin
    13   USE Write_Field
     13  USE lmdz_write_field
    1414  USE comconst_mod, ONLY: cpp, kappa, g, daysec, dtvr, pi, im, jm
    1515  USE logic_mod, ONLY: iflag_phys, read_start
     
    1717  USE temps_mod, ONLY: annee_ref, day_ini, day_ref
    1818  USE ener_mod, ONLY: etot0,ptot0,ztot0,stot0,ang0
    19   USE readTracFiles_mod, ONLY: addPhase
    20   use netcdf, ONLY: nf90_nowrite,nf90_open,nf90_noerr,nf90_inq_varid,nf90_close, nf90_get_var
     19  USE lmdz_readTracFiles, ONLY: addPhase
     20  USE netcdf, ONLY: nf90_nowrite,nf90_open,nf90_noerr,nf90_inq_varid,nf90_close, nf90_get_var
     21  USE lmdz_ran1, ONLY: ran1
    2122
    2223  !   Author:    Frederic Hourdin      original: 15/01/93
     
    6061  REAL phi(ip1jmp1,llm)                  ! geopotentiel
    6162  REAL ddsin,zsig,tetapv,w_pv  ! variables auxiliaires
    62   real tetastrat ! potential temperature in the stratosphere, in K
    63   real tetajl(jjp1,llm)
     63  REAL tetastrat ! potential temperature in the stratosphere, in K
     64  REAL tetajl(jjp1,llm)
    6465  INTEGER i,j,l,lsup,ij, iq, iName, iPhase, iqParent
    6566
    6667  INTEGER :: nid_relief,varid,ierr
    67   real, dimension(iip1,jjp1) :: relief
    68 
     68  REAL, DIMENSION(iip1,jjp1) :: relief
    6969
    7070  REAL teta0,ttp,delt_y,delt_z,eps ! Constantes pour profil de T
     
    7474  REAL phi_pv,dphi_pv,gam_pv,tetanoise   ! Constantes pour polar vortex
    7575
    76   real zz,ran1
    77   integer idum
     76  REAL zz
     77  INTEGER idum
    7878
    7979  REAL zdtvr, tnat, alpha_ideal
     
    8484
    8585  ! Sanity check: verify that options selected by user are not incompatible
    86   if ((iflag_phys==1).and. .not. read_start) THEN
     86  IF ((iflag_phys==1).AND. .NOT. read_start) THEN
    8787    WRITE(lunout,*) trim(modname)," error: if read_start is set to ", &
    8888    " false then iflag_phys should not be 1"
     
    9090    " (iflag_phys >= 100)"
    9191    CALL abort_gcm(modname,"incompatible iflag_phys==1 and read_start==.FALSE.",1)
    92   endif
     92  ENDIF
    9393 
    9494  !-----------------------------------------------------------------------
     
    114114  ang0       = 0.
    115115
    116   if (llm == 1) THEN
     116  IF (llm == 1) THEN
    117117     ! specific initializations for the shallow water case
    118118     kappa=1
    119   endif
     119  ENDIF
    120120
    121121  CALL iniconst
     
    148148     relief=0.
    149149     ierr = nf90_open ('relief_in.nc', nf90_nowrite,nid_relief)
    150      if (ierr==nf90_noerr) THEN
     150     IF (ierr==nf90_noerr) THEN
    151151         ierr=nf90_inq_varid(nid_relief,'RELIEF',varid)
    152          if (ierr==nf90_noerr) THEN
     152         IF (ierr==nf90_noerr) THEN
    153153              ierr=nf90_get_var(nid_relief,varid,relief(1:iim,1:jjp1))
    154154              relief(iip1,:)=relief(1,:)
     
    173173
    174174     CALL pression ( ip1jmp1, ap, bp, ps_glo, p       )
    175      if (pressure_exner) THEN
     175     IF (pressure_exner) THEN
    176176       CALL exner_hyb( ip1jmp1, ps_glo, p, pks, pk )
    177177     else
     
    181181  ENDIF
    182182
    183   if (llm == 1) THEN
     183  IF (llm == 1) THEN
    184184     ! initialize fields for the shallow water case, if required
    185      if (.not.read_start) THEN
     185     IF (.NOT.read_start) THEN
    186186        phis(ijb_u:ije_u)=0.
    187187        q(ijb_u:ije_u,1:llm,1:nqtot)=0
    188188        CALL sw_case_williamson91_6_loc(vcov,ucov,teta,masse,ps)
    189189     endif
    190   endif
     190  ENDIF
    191191
    192192  academic_case: if (iflag_phys >= 2) THEN
     
    258258           tetajl(j,l)=teta0-delt_y*ddsin*ddsin+eps*ddsin &
    259259                -delt_z*(1.-ddsin*ddsin)*log(zsig)
    260            if (planet_type=="giant") THEN
     260           IF (planet_type=="giant") THEN
    261261             tetajl(j,l)=teta0+(delt_y*                   &
    262262                ((sin(rlatu(j)*3.14159*eps+0.0001))**2)   &
     
    295295
    296296        ! winds
    297         if (ok_geost) THEN
     297        IF (ok_geost) THEN
    298298           CALL ugeostr(phi,ucov_glo)
    299299        else
     
    303303
    304304        ! bulk initialization of tracers
    305         if (planet_type=="earth") THEN
     305        IF (planet_type=="earth") THEN
    306306           ! Earth: first two tracers will be water
    307307           do iq=1,nqtot
     
    313313              ! distill de Rayleigh très simplifiée
    314314              iName    = tracers(iq)%iso_iName
    315               if (niso <= 0 .OR. iName <= 0) CYCLE
     315              IF (niso <= 0 .OR. iName <= 0) CYCLE
    316316              iPhase   = tracers(iq)%iso_iPhase
    317317              iqParent = tracers(iq)%iqParent
    318318              IF(tracers(iq)%iso_iZone == 0) THEN
    319                  if (tnat1) THEN
     319                 IF (tnat1) THEN
    320320                         tnat=1.0
    321321                         alpha_ideal=1.0
     
    374374        deallocate(phis_glo)
    375375     ENDIF ! of IF (.NOT. read_start)
    376   endif academic_case
     376  ENDIF academic_case
    377377
    378378END SUBROUTINE iniacademic_loc
Note: See TracChangeset for help on using the changeset viewer.