Ignore:
Timestamp:
Jul 20, 2024, 11:17:09 PM (2 months ago)
Author:
abarral
Message:

Move lmdz_netcdf_format.F90 -> lmdz_cppkeys_wrapper.F90 to handle other CPP keys
Replace all (except wrapper) use of CPP_PHYS by fortran logical
Refactor makelmdz_fcm (put blocks into functions, use modern bash)

Location:
LMDZ6/branches/Amaury_dev/libf/dyn3dmem
Files:
4 edited

Legend:

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

    r5088 r5091  
    2020  USE temps_mod, ONLY: annee_ref, day_ini, day_ref, itau_dyn, start_time
    2121  USE ener_mod, ONLY: etot0,ptot0,ztot0,stot0,ang0
     22  USE lmdz_cppkeys_wrapper, ONLY: CPPKEY_INCA
    2223
    2324  IMPLICIT NONE
     
    165166    ix = strIdx(newHNO3, var); IF(ix /= 0) oldVar = oldHNO3(ix)                          !--- REPROBUS HNO3 exceptions
    166167#endif
    167 #ifdef INCA
    168     IF(var == 'O3') oldVar = 'OX'                                                        !--- DEAL WITH INCA OZONE EXCEPTION
    169 #endif
     168    IF (CPPKEY_INCA) THEN
     169      IF(var == 'O3') oldVar = 'OX'                                                        !--- DEAL WITH INCA OZONE EXCEPTION
     170    END IF
    170171    !--------------------------------------------------------------------------------------------------------------------------
    171172    IF(NF90_INQ_VARID(fID, var, vID) == NF90_NoErr .AND. .NOT.lSkip) THEN                !=== REGULAR CASE: AVAILABLE VARIABLE
  • LMDZ6/branches/Amaury_dev/libf/dyn3dmem/filtreg_p.F

    r5082 r5091  
    361361
    362362            IF (jdfil<=jffil) THEN
    363                IF( ifiltre. EQ. -2 )   THEN
     363               IF( ifiltre == -2 )   THEN
    364364                  CALL Filtre_inv_fft(champ_fft,nlat,jdfil,jffil,nbniv)
    365365               ELSE IF ( griscal )     THEN
  • LMDZ6/branches/Amaury_dev/libf/dyn3dmem/leapfrog_loc.F

    r5082 r5091  
    4646     &                      xios_set_current_context,
    4747     &                      using_xios
     48       USE lmdz_cppkeys_wrapper, ONLY: CPPKEY_INCA
    4849       
    4950      IMPLICIT NONE
     
    313314c   -----
    314315
    315       jD_cur = jD_ref + day_ini - day_ref +                             &
     316      jD_cur = jD_ref + day_ini - day_ref +
    316317     &          (itau+1)/day_step
    317       jH_cur = jH_ref + start_time +                                    &
     318      jH_cur = jH_ref + start_time +
    318319     &         mod(itau+1,day_step)/float(day_step)
    319320      if (jH_cur > 1.0 ) then
     
    494495      if (Adjust) then
    495496        AdjustCount=AdjustCount+1
    496 !        if (iapptrac==iapp_tracvl .and. (forward. OR . leapf)
     497!        if (iapptrac==iapp_tracvl .and. (forward .OR. leapf)
    497498!     &         .and. itau/iphysiq>2 .and. Adjustcount>30) then
    498499        if (Adjustcount>1) then
     
    714715     &           'leapfrog 686: avant caladvtrac')
    715716     
    716       IF( forward. OR . leapf )  THEN
     717      IF( forward .OR. leapf )  THEN
    717718! Ehouarn: NB: fields sent to advtrac are those at the beginning of the time step
    718719        !write(*,*) 'leapfrog 679: avant CALL caladvtrac_loc'
     
    736737! Ehouarn: Storage of mass flux for off-line tracers... not implemented...
    737738
    738       ENDIF ! of IF( forward. OR . leapf )
     739      ENDIF ! of IF( forward .OR. leapf )
    739740
    740741
     
    808809          IF( itau==itaufin.AND..NOT.forward ) lafin = .TRUE.
    809810       ELSE
    810           IF( itau+1. EQ. itaufin )              lafin = .TRUE.
     811          IF( itau+1 == itaufin )              lafin = .TRUE.
    811812       ENDIF
    812813
     
    15191520         endif
    15201521
    1521 #ifdef INCA
     1522         IF (CPPKEY_INCA) THEN
    15221523         IF (ANY(type_trac == ['inca','inco'])) THEN
    15231524            CALL finalize_inca
     
    15291530!$OMP END MASTER
    15301531         ENDIF
    1531 #endif
     1532         END IF
    15321533#ifdef REPROBUS
    15331534         if (type_trac == 'repr') CALL finalize_reprobus
     
    15481549c       ........................................................
    15491550
    1550             IF(forward. OR. leapf) THEN
     1551            IF(forward .OR. leapf) THEN
    15511552              itau= itau + 1
    15521553!              iday= day_ini+itau/day_step
     
    15591560
    15601561
    1561             IF( itau. EQ. itaufinp1 ) then
     1562            IF( itau == itaufinp1 ) then
    15621563
    15631564              if (flag_verif) then
     
    15761577c$OMP END MASTER
    15771578
    1578 #ifdef INCA
     1579              IF (CPPKEY_INCA) THEN
    15791580              IF (ANY(type_trac == ['inca','inco'])) THEN
    15801581                 CALL finalize_inca
     
    15861587!$OMP END MASTER
    15871588              ENDIF
    1588 #endif
     1589              END IF
    15891590#ifdef REPROBUS
    15901591              if (type_trac == 'repr') CALL finalize_reprobus
     
    16971698            IF( MOD(itau,iperiod)==0 )    THEN
    16981699                    GO TO 1
    1699             ELSE IF ( MOD(itau-1,iperiod). EQ. 0 ) THEN
     1700            ELSE IF ( MOD(itau-1,iperiod) == 0 ) THEN
    17001701
    17011702                   IF( forward )  THEN
     
    17441745
    17451746               forward =  .FALSE.
    1746                IF( itau. EQ. itaufinp1 ) then 
     1747               IF( itau == itaufinp1 ) then
    17471748c$OMP MASTER
    17481749                 call fin_getparam
    17491750c$OMP END MASTER
    17501751
    1751 #ifdef INCA
     1752                 IF (CPPKEY_INCA) THEN
    17521753                 IF (ANY(type_trac == ['inca','inco'])) THEN
    17531754                    CALL finalize_inca
     
    17601761                 ENDIF
    17611762
    1762 #endif
     1763                 END IF
    17631764#ifdef REPROBUS
    17641765                 if (type_trac == 'repr') CALL finalize_reprobus
     
    17791780              call check_isotopes(q,ijb_u,ije_u,'leapfrog 1698')
    17801781
    1781               IF(MOD(itau,iperiod).EQ.0 .OR. itau.EQ.itaufin) THEN
    1782                IF(itau.EQ.itaufin) THEN
     1782              IF(MOD(itau,iperiod)==0 .OR. itau==itaufin) THEN
     1783               IF(itau==itaufin) THEN
    17831784                  iav=1
    17841785               ELSE
     
    18091810
    18101811
    1811                IF(MOD(itau,iecri         ).EQ.0) THEN
     1812               IF(MOD(itau,iecri         )==0) THEN
    18121813
    18131814c$OMP BARRIER
     
    18371838             
    18381839
    1839               IF(itau.EQ.itaufin) THEN
     1840              IF(itau==itaufin) THEN
    18401841!                if (planet_type.eq."earth") then
    18411842                   CALL dynredem1_loc("restart.nc",0.0,
     
    18631864c$OMP END MASTER
    18641865
    1865 #ifdef INCA
     1866      IF (CPPKEY_INCA) THEN
    18661867      IF (ANY(type_trac == ['inca','inco'])) THEN
    18671868         CALL finalize_inca
     
    18731874!$OMP END MASTER
    18741875      ENDIF
    1875 
    1876 #endif
     1876      END IF
    18771877#ifdef REPROBUS
    18781878      if (type_trac == 'repr') CALL finalize_reprobus
  • LMDZ6/branches/Amaury_dev/libf/dyn3dmem/mod_filtreg_p.F

    r5082 r5091  
    369369
    370370            IF (jdfil<=jffil) THEN
    371                IF( ifiltre. EQ. -2 )   THEN
     371               IF( ifiltre == -2 )   THEN
    372372                CALL Filtre_inv_fft(champ_fft,jjb,jje,jdfil,jffil,nbniv)
    373373               ELSE IF ( griscal )     THEN
Note: See TracChangeset for help on using the changeset viewer.