Ignore:
Timestamp:
Mar 30, 2009, 4:46:54 PM (15 years ago)
Author:
Ehouarn Millour
Message:

Premiere vaque de modifications pour l'unification des dynamiques (planetes-Terre) et un peu de netoyage ...

  • modified 'makegcm' and 'makegcm_fcm' to remove 'CPP_PHYS' key and add 'CPP_EARTH' preprocessing key instead
  • updated 'diagedyn.F' (in dyn3d and dyn3dpar) to use 'CPP_EARTH' key
  • added 'ioipsl_getincom.F90' and 'ioipsl_stringop.F90' to 'dyn3d' and 'dyn3dpar' for future possibility of running without IOIPSL library
  • modified conf_gcm.F ( in d'yn3d' and 'dyn3dpar') to read in flag 'planet_type' (default=='earth') (flag added in 'control.h')
  • modified 'gcm.F' (in 'dyn3d' and 'dyn3dpar') so that flags so that 'read_start' and 'iflag_phys' (known from conf_gcm.F) are used
  • added flag 'output_grads_dyn' (read by conf_gcm.F, stored in 'control.h') to write grads outputs from 'leapfrog.F' and 'leapfrog_p.F'
  • removed 'comdiss.h' from 'dyn3d' and 'dyn3dpar' (it is not used)
  • removed variable 'lstardis' from 'comdissip.h' (it is also in

'comdissnew.h'), in dyn3d as well as in dyn3dpar

  • adapted 'dyn3d/iniacademic.F' to not use 'inicons0.F' but 'iniconst.F'
  • updated 'dyn3d/etat0_netcdf.F' to not use 'inicons0' but 'iniconst' (added prerequisite pa=50000 instruction) and added #ifdef CPP_EARTH keys
  • removed 'inicons0.F' and 'disvert0.F' (not used any more)
File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3d/leapfrog.F

    r1114 r1140  
    77
    88cIM : pour sortir les param. du modele dans un fis. netcdf 110106
    9       USE IOIPSL
     9#ifdef CPP_IOIPSL
     10      use IOIPSL
     11#endif
    1012      USE infotrac
    1113
     
    161163
    162164      character*80 dynhist_file, dynhistave_file
    163       character*20 modname
     165      character(len=20) :: modname
    164166      character*80 abort_message
    165167
     
    217219        call guide(itau,ucov,vcov,teta,q,masse,ps)
    218220      else
    219         IF(prt_level>9)WRITE(*,*)'attention on ne guide pas les ',
    220      .    '6 dernieres heures'
     221        IF(prt_level>9)WRITE(lunout,*)'leapfrog: attention on ne ',
     222     .    'guide pas les 6 dernieres heures'
    221223      endif
    222224#endif
     
    227229c     ENDIF
    228230c
     231
     232! Save fields obtained at previous time step as '...m1'
    229233      CALL SCOPY( ijmllm ,vcov , 1, vcovm1 , 1 )
    230234      CALL SCOPY( ijp1llm,ucov , 1, ucovm1 , 1 )
     
    242246      CALL filtreg ( finvmaold ,jjp1, llm, -2,2, .TRUE., 1 )
    243247
    244       call minmax(ijp1llm,q(:,:,3),zqmin,zqmax)
     248! Ehouarn: what is this for? zqmin & zqmax are not used anyway ...
     249!      call minmax(ijp1llm,q(:,:,3),zqmin,zqmax)
    245250
    246251   2  CONTINUE
     
    302307
    303308
    304          ENDIF
    305 c
    306       ENDIF
     309         ENDIF ! of IF (offline)
     310c
     311      ENDIF ! of IF( forward. OR . leapf )
    307312
    308313
     
    350355c   -----------------------------------------------------
    351356
    352 #ifdef CPP_PHYS
    353357c+jld
    354358
    355359c  Diagnostique de conservation de l'énergie : initialisation
    356       IF (ip_ebil_dyn.ge.1 ) THEN
     360         IF (ip_ebil_dyn.ge.1 ) THEN
    357361          ztit='bil dyn'
    358           CALL diagedyn(ztit,2,1,1,dtphys
    359      e  , ucov    , vcov , ps, p ,pk , teta , q(:,:,1), q(:,:,2))
    360       ENDIF
     362! Ehouarn: be careful, diagedyn is Earth-specific (includes ../phylmd/..)!
     363           IF (planet_type.eq."earth") THEN
     364            CALL diagedyn(ztit,2,1,1,dtphys
     365     &    , ucov    , vcov , ps, p ,pk , teta , q(:,:,1), q(:,:,2))
     366           ENDIF
     367         ENDIF ! of IF (ip_ebil_dyn.ge.1 )
    361368c-jld
     369#ifdef CPP_IOIPSL
    362370cIM : pour sortir les param. du modele dans un fis. netcdf 110106
    363       IF (first) THEN
    364        first=.false.
     371         IF (first) THEN
     372          first=.false.
    365373#include "ini_paramLMDZ_dyn.h"
    366       ENDIF
     374         ENDIF
    367375c
    368376#include "write_paramLMDZ_dyn.h"
    369377c
    370 
    371         CALL calfis( lafin ,rdayvrai,time  ,
     378#endif
     379! #endif of #ifdef CPP_IOIPSL
     380         CALL calfis( lafin ,rdayvrai,time  ,
    372381     $               ucov,vcov,teta,q,masse,ps,p,pk,phis,phi ,
    373382     $               du,dv,dteta,dq,
     
    375384     $               clesphy0, dufi,dvfi,dtetafi,dqfi,dpfi  )
    376385
    377        IF (ok_strato) THEN
    378          CALL top_bound( vcov,ucov,teta, dufi,dvfi,dtetafi)
    379        ENDIF
     386         IF (ok_strato) THEN
     387           CALL top_bound( vcov,ucov,teta, dufi,dvfi,dtetafi)
     388         ENDIF
    380389       
    381390c      ajout des tendances physiques:
     
    386395c
    387396c  Diagnostique de conservation de l'énergie : difference
    388       IF (ip_ebil_dyn.ge.1 ) THEN
     397         IF (ip_ebil_dyn.ge.1 ) THEN
    389398          ztit='bil phys'
    390           CALL diagedyn(ztit,2,1,1,dtphys
    391      e  , ucov    , vcov , ps, p ,pk , teta , q(:,:,1), q(:,:,2))
    392       ENDIF
    393 #endif
     399          IF (planet_type.eq."earth") THEN
     400           CALL diagedyn(ztit,2,1,1,dtphys
     401     &     , ucov    , vcov , ps, p ,pk , teta , q(:,:,1), q(:,:,2))
     402          ENDIF
     403         ENDIF ! of IF (ip_ebil_dyn.ge.1 )
     404
    394405       ENDIF ! of IF( apphys )
    395406
    396       IF(iflag_phys.EQ.2) THEN ! "Newtonian physics" case
     407      IF(iflag_phys.EQ.2) THEN ! "Newtonian" case
    397408c   Calcul academique de la physique = Rappel Newtonien + friction
    398409c   --------------------------------------------------------------
     
    472483
    473484
    474       END IF
     485      END IF ! of IF(apdiss)
    475486
    476487c ajout debug
     
    545556c           IF( MOD(itau,iecri*day_step).EQ.0) THEN
    546557
    547                nbetat = nbetatdem
    548        CALL geopot  ( ip1jmp1, teta  , pk , pks,  phis  , phi        )
    549         unat=0.
    550         do l=1,llm
    551            unat(iip2:ip1jm,l)=ucov(iip2:ip1jm,l)/cu(iip2:ip1jm)
    552            vnat(:,l)=vcov(:,l)/cv(:)
    553         enddo
    554 #ifdef CPP_IOIPSL
    555 c        CALL writehist(histid,histvid,itau,vcov,
    556 c     s                       ucov,teta,phi,q,masse,ps,phis)
    557 #else
     558              nbetat = nbetatdem
     559              CALL geopot(ip1jmp1,teta,pk,pks,phis,phi)
     560              unat=0.
     561              do l=1,llm
     562                unat(iip2:ip1jm,l)=ucov(iip2:ip1jm,l)/cu(iip2:ip1jm)
     563                vnat(:,l)=vcov(:,l)/cv(:)
     564              enddo
     565#ifdef CPP_IOIPSL
     566c             CALL writehist(histid,histvid,itau,vcov,
     567c     &                      ucov,teta,phi,q,masse,ps,phis)
     568#endif
     569! For some Grads outputs of fields
     570             if (output_grads_dyn) then
    558571#include "write_grads_dyn.h"
    559 #endif
    560 
    561 
    562             ENDIF
     572             endif
     573
     574            ENDIF ! of IF(MOD(itau,iecri).EQ.0)
    563575
    564576            IF(itau.EQ.itaufin) THEN
    565577
    566578
    567 #ifdef CPP_IOIPSL
    568        CALL dynredem1("restart.nc",0.0,
    569      ,                     vcov,ucov,teta,q,masse,ps)
    570 #endif
     579              if (planet_type.eq."earth") then
     580#ifdef CPP_EARTH
     581! Write an Earth-format restart file
     582                CALL dynredem1("restart.nc",0.0,
     583     &                         vcov,ucov,teta,q,masse,ps)
     584#endif
     585              endif ! of if (planet_type.eq."earth")
    571586
    572587              CLOSE(99)
    573             ENDIF
     588            ENDIF ! of IF (itau.EQ.itaufin)
    574589
    575590c-----------------------------------------------------------------------
     
    593608                        leapf =  .TRUE.
    594609                        dt  =  2.*dtvr
    595                         GO TO 2
    596                    END IF
     610                        GO TO 2 
     611                   END IF ! of IF (forward)
    597612            ELSE
    598613
     
    602617                 dt  = 2.*dtvr
    603618                 GO TO 2
    604             END IF
    605 
    606       ELSE
     619            END IF ! of IF (MOD(itau,iperiod).EQ.0)
     620                   !    ELSEIF (MOD(itau-1,iperiod).EQ.0)
     621
     622      ELSE ! of IF (.not.purmats)
    607623
    608624c       ........................................................
     
    627643               GO TO 2
    628644
    629             ELSE
    630 
    631             IF(MOD(itau,iperiod).EQ.0 .OR. itau.EQ.itaufin) THEN
     645            ELSE ! of IF(forward)
     646
     647              IF(MOD(itau,iperiod).EQ.0 .OR. itau.EQ.itaufin) THEN
    632648               IF(itau.EQ.itaufin) THEN
    633649                  iav=1
     
    636652               ENDIF
    637653#ifdef CPP_IOIPSL
    638               CALL writedynav(histaveid, itau,vcov ,
     654               CALL writedynav(histaveid, itau,vcov ,
    639655     ,                          ucov,teta,pk,phi,q,masse,ps,phis)
    640656               call bilan_dyn (2,dtvr*iperiod,dtvr*day_step*periodav,
     
    642658#endif
    643659
    644             ENDIF
    645 
    646                IF(MOD(itau,iecri         ).EQ.0) THEN
     660              ENDIF ! of IF(MOD(itau,iperiod).EQ.0 .OR. itau.EQ.itaufin)
     661
     662              IF(MOD(itau,iecri         ).EQ.0) THEN
    647663c              IF(MOD(itau,iecri*day_step).EQ.0) THEN
    648                   nbetat = nbetatdem
    649        CALL geopot  ( ip1jmp1, teta  , pk , pks,  phis  , phi       )
    650         unat=0.
    651         do l=1,llm
    652            unat(iip2:ip1jm,l)=ucov(iip2:ip1jm,l)/cu(iip2:ip1jm)
    653            vnat(:,l)=vcov(:,l)/cv(:)
    654         enddo
    655 #ifdef CPP_IOIPSL
    656 c       CALL writehist( histid, histvid, itau,vcov ,
    657 c    ,                           ucov,teta,phi,q,masse,ps,phis)
    658 #else
     664                nbetat = nbetatdem
     665                CALL geopot(ip1jmp1,teta,pk,pks,phis,phi)
     666                unat=0.
     667                do l=1,llm
     668                  unat(iip2:ip1jm,l)=ucov(iip2:ip1jm,l)/cu(iip2:ip1jm)
     669                  vnat(:,l)=vcov(:,l)/cv(:)
     670                enddo
     671#ifdef CPP_IOIPSL
     672c               CALL writehist( histid, histvid, itau,vcov ,
     673c    &                           ucov,teta,phi,q,masse,ps,phis)
     674#endif
     675! For some Grads outputs
     676                if (output_grads_dyn) then
    659677#include "write_grads_dyn.h"
    660 #endif
    661 
    662 
    663                ENDIF
    664 
    665 #ifdef CPP_IOIPSL
    666                  IF(itau.EQ.itaufin)
    667      . CALL dynredem1("restart.nc",0.0,
    668      .                     vcov,ucov,teta,q,masse,ps)
    669 #endif
    670 
    671                  forward = .TRUE.
    672                  GO TO  1
    673 
    674             ENDIF
    675 
    676       END IF
     678                endif
     679
     680              ENDIF ! of IF(MOD(itau,iecri         ).EQ.0)
     681
     682              IF(itau.EQ.itaufin) THEN
     683                if (planet_type.eq."earth") then
     684#ifdef CPP_EARTH
     685                  CALL dynredem1("restart.nc",0.0,
     686     &                           vcov,ucov,teta,q,masse,ps)
     687#endif
     688                endif ! of if (planet_type.eq."earth")
     689              ENDIF ! of IF(itau.EQ.itaufin)
     690
     691              forward = .TRUE.
     692              GO TO  1
     693
     694            ENDIF ! of IF (forward)
     695
     696      END IF ! of IF(.not.purmats)
    677697
    678698      STOP
Note: See TracChangeset for help on using the changeset viewer.