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

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

Location:
LMDZ6/branches/Amaury_dev/libf/dynphy_lonlat/phylmd
Files:
6 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/Amaury_dev/libf/dynphy_lonlat/phylmd/callphysiq_mod.F90

    r5116 r5117  
    6969
    7070  !$OMP MASTER
    71   if (ok_dyn_xios) THEN
     71  IF (ok_dyn_xios) THEN
    7272     CALL xios_get_current_context(dyn3d_ctx_handle)
    73   endif
     73  ENDIF
    7474  !$OMP END MASTER
    7575
     
    9999! switching back to LMDZDYN context
    100100!$OMP MASTER
    101   if (ok_dyn_xios) THEN
     101  IF (ok_dyn_xios) THEN
    102102     CALL xios_set_current_context(dyn3d_ctx_handle)
    103   endif
     103  ENDIF
    104104!$OMP END MASTER
    105105
  • LMDZ6/branches/Amaury_dev/libf/dynphy_lonlat/phylmd/ce0l.F90

    r5116 r5117  
    7373
    7474#ifdef CPP_PARA
    75   integer ierr
     75  INTEGER ierr
    7676#else
    7777! for iniphysiq in serial mode
  • LMDZ6/branches/Amaury_dev/libf/dynphy_lonlat/phylmd/etat0dyn_netcdf.F90

    r5116 r5117  
    3939  USE comvert_mod, ONLY: ap, bp, preff, pressure_exner
    4040  USE temps_mod, ONLY: annee_ref, day_ref, itau_dyn, itau_phy, start_time
    41   USE strings_mod, ONLY: strLower
     41  USE lmdz_strings, ONLY: strLower
    4242
    4343  IMPLICIT NONE
     
    7878    USE lmdz_filtreg
    7979    USE lmdz_cppkeys_wrapper, ONLY: CPPKEY_INCA
     80    USE lmdz_q_sat, ONLY: q_sat
    8081    IMPLICIT NONE
    8182    !-------------------------------------------------------------------------------
  • LMDZ6/branches/Amaury_dev/libf/dynphy_lonlat/phylmd/etat0phys_netcdf.F90

    r5116 r5117  
    539539  do j=2,jmp1-1
    540540     PRINT*,'avant if ',cos(rlatu(j)),coslat0
    541      if (cos(rlatu(j))<coslat0) THEN
     541     IF (cos(rlatu(j))<coslat0) THEN
    542542         ! nb de pts affectes par le filtrage de part et d'autre du pt
    543543         ifiltre=(coslat0/cos(rlatu(j))-1.)/2.
     
    548548         wwf(ifiltre+1)=(coslat0/cos(rlatu(j))-1.)/2.-ifiltre
    549549         do i=1,imp1-1
    550             if (masque(i,j)>0.9) THEN
     550            IF (masque(i,j)>0.9) THEN
    551551               ssz=phis(i,j)
    552552               do ifi=1,ifiltre+1
    553553                  ii=i+ifi
    554                   if (ii>imp1-1) ii=ii-imp1+1
     554                  IF (ii>imp1-1) ii=ii-imp1+1
    555555                  ssz=ssz+wwf(ifi)*phis(ii,j)
    556556                  ii=i-ifi
    557                   if (ii<1) ii=ii+imp1-1
     557                  IF (ii<1) ii=ii+imp1-1
    558558                  ssz=ssz+wwf(ifi)*phis(ii,j)
    559559               enddo
  • LMDZ6/branches/Amaury_dev/libf/dynphy_lonlat/phylmd/limit_netcdf.f90

    r5116 r5117  
    378378      REAL :: chmin, chmax, timeday, al
    379379      INTEGER ierr, idx
    380       integer n_extrap ! number of extrapolated points
    381       logical skip
     380      INTEGER n_extrap ! number of extrapolated points
     381      LOGICAL skip
    382382
    383383      !------------------------------------------------------------------------------
     
    599599            CALL pchfe_95(timeyear, champtime(i, j, :), yder, skip, &
    600600                    arth(0.5, real(ndays_in) / ndays, ndays), champan(i, j, :), ierr)
    601             if (ierr < 0) CALL abort_physic("get_2Dfield", "", 1)
     601            IF (ierr < 0) CALL abort_physic("get_2Dfield", "", 1)
    602602            n_extrap = n_extrap + ierr
    603603          END DO
  • LMDZ6/branches/Amaury_dev/libf/dynphy_lonlat/phylmd/test_disvert_m.F90

    r5116 r5117  
    1313    ! the surface pressure, which sample possible values on Earth.
    1414
    15     use exner_hyb_m, ONLY: exner_hyb
    16     use lmdz_vertical_layers, ONLY: ap,bp,preff
    17     use comconst_mod, ONLY: kappa, cpp
     15    USE exner_hyb_m, ONLY: exner_hyb
     16    USE lmdz_vertical_layers, ONLY: ap,bp,preff
     17    USE comconst_mod, ONLY: kappa, cpp
    1818    USE lmdz_abort_physic, ONLY: abort_physic
    1919
     
    2222
    2323    ! Local:
    24     integer l, i
    25     integer, parameter:: ngrid = 7
    26     real p(ngrid, llm + 1) ! pressure at half-level, in Pa
    27     real pks(ngrid) ! exner function at the surface, in J K-1 kg-1
    28     real pk(ngrid, llm) ! exner function at full level, in J K-1 kg-1
    29     real ps(ngrid) ! surface pressure, in Pa
    30     real p_lay(ngrid, llm) ! pressure at full level, in Pa
    31     real delta_ps ! in Pa
     24    INTEGER l, i
     25    INTEGER, parameter:: ngrid = 7
     26    REAL p(ngrid, llm + 1) ! pressure at half-level, in Pa
     27    REAL pks(ngrid) ! exner function at the surface, in J K-1 kg-1
     28    REAL pk(ngrid, llm) ! exner function at full level, in J K-1 kg-1
     29    REAL ps(ngrid) ! surface pressure, in Pa
     30    REAL p_lay(ngrid, llm) ! pressure at full level, in Pa
     31    REAL delta_ps ! in Pa
    3232
    3333    !---------------------
     
    4242
    4343    ! Are pressure values in the right order?
    44     if (any(p(:, :llm) <= p_lay .or. p_lay <= p(:, 2:))) THEN
     44    IF (any(p(:, :llm) <= p_lay .OR. p_lay <= p(:, 2:))) THEN
    4545       ! List details and stop:
    4646       do l = 1, llm
    4747          do i = 1, ngrid
    48              if (p(i, l) <= p_lay(i, l)) THEN
     48             IF (p(i, l) <= p_lay(i, l)) THEN
    4949                print 1000, "ps = ", ps(i) / 100., "hPa, p(level ",  l, &
    5050                     ") = ", p(i, l) / 100., " hPa <= p(layer ", l, ") = ", &
    5151                     p_lay(i, l) / 100., " hPa"
    5252             end if
    53              if (p_lay(i, l) <= p(i, l + 1)) THEN
     53             IF (p_lay(i, l) <= p(i, l + 1)) THEN
    5454                print 1000, "ps = ", ps(i) / 100., "hPa, p(layer ", l, ") = ", &
    5555                     p_lay(i, l) / 100., " hPa <= p(level ", l + 1, ") = ", &
Note: See TracChangeset for help on using the changeset viewer.