Ignore:
Timestamp:
May 9, 2022, 12:35:40 PM (2 years ago)
Author:
dcugnet
Message:
  • Some variables are renamed or replaced by direct equivalents:
    • iso_indnum -> tracers(:)%iso_iName
    • niso_possibles -> niso
    • iqiso -> iqIsoPha ; index_trac -> itZonIso
    • ok_iso_verif -> isoCheck
    • ntraceurs_zone -> nzone ; ntraciso -> ntiso
    • qperemin -> min_qparent ; masseqmin -> min_qmass ; ratiomin -> min_ratio
  • Some renamed variables are only aliased with the older name (using USE <module>, ONLY: <oldName> => <newName>) in routines where they are repeated many times.
  • Few hard-coded indexes are now computed (examples: ilic, iso, ivap, irneb, iq_vap, iq_liq, iso_H2O, iso_HDO, iso_HTO, iso_O17, iso_O18).
  • The IF(isoCheck) test is now embedded in the check_isotopes_seq and check_isotopes_loc routines (lighter calling).
File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/dyn3d/leapfrog.F

    r4120 r4143  
    1111      use IOIPSL
    1212#endif
    13       USE infotrac, ONLY: nqtot,ok_iso_verif
     13      USE infotrac, ONLY: nqtot, isoCheck
    1414      USE guide_mod, ONLY : guide_main
    1515      USE write_field, ONLY: writefield
     
    2626      USE temps_mod, ONLY: jD_ref,jH_ref,itaufin,day_ini,day_ref,
    2727     &                        start_time,dt
     28      USE strings_mod, ONLY: msg
    2829
    2930      IMPLICIT NONE
     
    237238      jH_cur = jH_cur - int(jH_cur)
    238239
    239         if (ok_iso_verif) then
    240            call check_isotopes_seq(q,ip1jmp1,'leapfrog 321')
    241         endif !if (ok_iso_verif) then
     240      call check_isotopes_seq(q,ip1jmp1,'leapfrog 321')
    242241
    243242#ifdef CPP_IOIPSL
     
    271270!      CALL filtreg ( finvmaold ,jjp1, llm, -2,2, .TRUE., 1 )
    272271
    273         if (ok_iso_verif) then
    274            call check_isotopes_seq(q,ip1jmp1,'leapfrog 400')
    275         endif !if (ok_iso_verif) then
     272      call check_isotopes_seq(q,ip1jmp1,'leapfrog 400')
    276273
    277274   2  CONTINUE ! Matsuno backward or leapfrog step begins here
     
    324321
    325322
    326         if (ok_iso_verif) then
    327            call check_isotopes_seq(q,ip1jmp1,'leapfrog 589')
    328         endif !if (ok_iso_verif) then
     323      call check_isotopes_seq(q,ip1jmp1,'leapfrog 589')
    329324
    330325c-----------------------------------------------------------------------
     
    345340c   -------------------------------------------------------------
    346341
    347         if (ok_iso_verif) then
    348            call check_isotopes_seq(q,ip1jmp1,
     342      call check_isotopes_seq(q,ip1jmp1,
    349343     &           'leapfrog 686: avant caladvtrac')
    350         endif !if (ok_iso_verif) then
    351344
    352345      IF( forward. OR . leapf )  THEN
     
    376369c   ----------------------------------
    377370
    378         if (ok_iso_verif) then
    379            write(*,*) 'leapfrog 720'
    380            call check_isotopes_seq(q,ip1jmp1,'leapfrog 756')
    381         endif !if (ok_iso_verif) then
     371       CALL msg('720', modname, isoCheck)
     372       call check_isotopes_seq(q,ip1jmp1,'leapfrog 756')
    382373       
    383374       CALL integrd ( nqtot,vcovm1,ucovm1,tetam1,psm1,massem1 ,
     
    385376!     $              finvmaold                                    )
    386377
    387        if (ok_iso_verif) then
    388           write(*,*) 'leapfrog 724'
    389            call check_isotopes_seq(q,ip1jmp1,'leapfrog 762')
    390         endif !if (ok_iso_verif) then
     378       CALL msg('724', modname, isoCheck)
     379       call check_isotopes_seq(q,ip1jmp1,'leapfrog 762')
    391380
    392381c .P.Le Van (26/04/94  ajout de  finvpold dans l'appel d'integrd)
     
    552541        CALL massdair(p,masse)
    553542
    554         if (ok_iso_verif) then
    555            call check_isotopes_seq(q,ip1jmp1,'leapfrog 1196')
    556         endif !if (ok_iso_verif) then
     543        call check_isotopes_seq(q,ip1jmp1,'leapfrog 1196')
    557544
    558545c-----------------------------------------------------------------------
     
    639626c   preparation du pas d'integration suivant  ......
    640627
    641         if (ok_iso_verif) then
    642            call check_isotopes_seq(q,ip1jmp1,'leapfrog 1509')
    643         endif !if (ok_iso_verif) then
     628      call check_isotopes_seq(q,ip1jmp1,'leapfrog 1509')
    644629
    645630      IF ( .NOT.purmats ) THEN
     
    703688            ENDIF ! of IF((MOD(itau,iperiod).EQ.0).OR.(itau.EQ.itaufin))
    704689
    705         if (ok_iso_verif) then
    706            call check_isotopes_seq(q,ip1jmp1,'leapfrog 1584')
    707         endif !if (ok_iso_verif) then
     690            call check_isotopes_seq(q,ip1jmp1,'leapfrog 1584')
    708691
    709692c-----------------------------------------------------------------------
     
    790773      ELSE ! of IF (.not.purmats)
    791774
    792         if (ok_iso_verif) then
    793            call check_isotopes_seq(q,ip1jmp1,'leapfrog 1664')
    794         endif !if (ok_iso_verif) then
     775            call check_isotopes_seq(q,ip1jmp1,'leapfrog 1664')
    795776
    796777c       ........................................................
     
    817798            ELSE ! of IF(forward) i.e. backward step
    818799 
    819         if (ok_iso_verif) then
    820            call check_isotopes_seq(q,ip1jmp1,'leapfrog 1698')
    821         endif !if (ok_iso_verif) then 
     800              call check_isotopes_seq(q,ip1jmp1,'leapfrog 1698')
    822801
    823802              IF(MOD(itau,iperiod).EQ.0 .OR. itau.EQ.itaufin) THEN
Note: See TracChangeset for help on using the changeset viewer.