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/dyn3d
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/Amaury_dev/libf/dyn3d/dynetat0.F90

    r5088 r5091  
    1919  USE temps_mod, ONLY: annee_ref, day_ini, day_ref, itau_dyn, start_time
    2020  USE ener_mod, ONLY: etot0,ptot0,ztot0,stot0,ang0
     21  USE lmdz_cppkeys_wrapper, ONLY: CPPKEY_INCA
    2122
    2223  IMPLICIT NONE
     
    140141    ix = strIdx(newHNO3, var); IF(ix /= 0) oldVar = oldHNO3(ix)                          !--- REPROBUS HNO3 exceptions
    141142#endif
    142 #ifdef INCA
    143     IF(var == 'O3') oldVar = 'OX'                                                        !--- DEAL WITH INCA OZONE EXCEPTION
    144 #endif
     143    IF (CPPKEY_INCA) THEN
     144      IF(var == 'O3') oldVar = 'OX'                                                        !--- DEAL WITH INCA OZONE EXCEPTION
     145    END IF
    145146    !--------------------------------------------------------------------------------------------------------------------------
    146147    IF(NF90_INQ_VARID(fID, var, vID) == NF90_NoErr .AND. .NOT.lSkip) THEN                !=== REGULAR CASE: AVAILABLE VARIABLE
  • LMDZ6/branches/Amaury_dev/libf/dyn3d/integrd.F

    r5082 r5091  
    182182c$$$      IF( iadv(1).NE.3.AND.iadv(2).NE.3 )    THEN
    183183c$$$c
    184 c$$$       IF( forward. OR . leapf )  THEN
     184c$$$       IF( forward .OR. leapf )  THEN
    185185c$$$        DO iq = 1,2
    186186c$$$        DO  l = 1,llm
  • LMDZ6/branches/Amaury_dev/libf/dyn3d/leapfrog.F

    r5090 r5091  
    344344     &           'leapfrog 686: avant caladvtrac')
    345345
    346       IF( forward. OR . leapf )  THEN
     346      IF( forward .OR. leapf )  THEN
    347347! Ehouarn: NB: fields sent to advtrac are those at the beginning of the time step
    348348         CALL caladvtrac(q,pbaru,pbarv,
     
    363363         ENDIF ! of IF (offline)
    364364c
    365       ENDIF ! of IF( forward. OR . leapf )
     365      ENDIF ! of IF( forward .OR. leapf )
    366366
    367367
     
    390390          IF( itau==itaufin.AND..NOT.forward ) lafin = .TRUE.
    391391       ELSE
    392           IF( itau+1. EQ. itaufin )              lafin = .TRUE.
     392          IF( itau+1 == itaufin )              lafin = .TRUE.
    393393       ENDIF
    394394c
     
    634634c       ........................................................
    635635
    636             IF(forward. OR. leapf) THEN
     636            IF(forward .OR. leapf) THEN
    637637              itau= itau + 1
    638638c              iday= day_ini+itau/day_step
     
    645645
    646646
    647             IF( itau. EQ. itaufinp1 ) then 
     647            IF( itau == itaufinp1 ) then
    648648              if (flag_verif) then
    649649                write(79,*) 'ucov',ucov
     
    746746            IF( MOD(itau,iperiod)==0 )    THEN
    747747                    GO TO 1
    748             ELSE IF ( MOD(itau-1,iperiod). EQ. 0 ) THEN
     748            ELSE IF ( MOD(itau-1,iperiod) == 0 ) THEN
    749749
    750750                   IF( forward )  THEN
     
    791791
    792792               forward =  .FALSE.
    793                IF( itau. EQ. itaufinp1 ) then 
     793               IF( itau == itaufinp1 ) then
    794794                 abort_message = 'Simulation finished'
    795795                 call abort_gcm(modname,abort_message,0)
     
    801801              call check_isotopes_seq(q,ip1jmp1,'leapfrog 1698')
    802802
    803               IF(MOD(itau,iperiod).EQ.0 .OR. itau.EQ.itaufin) THEN
    804                IF(itau.EQ.itaufin) THEN
     803              IF(MOD(itau,iperiod)==0 .OR. itau==itaufin) THEN
     804               IF(itau==itaufin) THEN
    805805                  iav=1
    806806               ELSE
     
    826826              ENDIF ! of IF(MOD(itau,iperiod).EQ.0 .OR. itau.EQ.itaufin)
    827827
    828               IF(MOD(itau,iecri         ).EQ.0) THEN
     828              IF(MOD(itau,iecri         )==0) THEN
    829829c              IF(MOD(itau,iecri*day_step).EQ.0) THEN
    830830                CALL geopot(ip1jmp1,teta,pk,pks,phis,phi)
     
    848848              ENDIF ! of IF(MOD(itau,iecri         ).EQ.0)
    849849
    850               IF(itau.EQ.itaufin) THEN
     850              IF(itau==itaufin) THEN
    851851!                if (planet_type.eq."earth") then
    852852                  CALL dynredem1("restart.nc",start_time,
Note: See TracChangeset for help on using the changeset viewer.