Ignore:
Timestamp:
Jul 1, 2010, 11:02:53 AM (14 years ago)
Author:
Laurent Fairhead
Message:

Merged LMDZ4V5.0-dev branch changes r1292:r1399 to trunk.

Validation:
Validation consisted in compiling the HEAD revision of the trunk,
LMDZ4V5.0-dev branch and the merged sources and running different
configurations on local and SX8 machines comparing results.

Local machine: bench configuration, 32x24x11, gfortran

  • IPSLCM5A configuration (comparison between trunk and merged sources):
    • numerical convergence on dynamical fields over 3 days
    • start files are equivalent (except for RN and PB fields)
    • daily history files equivalent
  • MH07 configuration, new physics package (comparison between LMDZ4V5.0-dev branch and merged sources):
    • numerical convergence on dynamical fields over 3 days
    • start files are equivalent (except for RN and PB fields)
    • daily history files equivalent

SX8 machine (brodie), 96x95x39 on 4 processors:

  • IPSLCM5A configuration:
    • start files are equivalent (except for RN and PB fields)
    • monthly history files equivalent
  • MH07 configuration:
    • start files are equivalent (except for RN and PB fields)
    • monthly history files equivalent

Changes to the makegcm and create_make_gcm scripts to take into account
main programs in F90 files


Fusion de la branche LMDZ4V5.0-dev (r1292:r1399) au tronc principal

Validation:
La validation a consisté à compiler la HEAD de le trunk et de la banche
LMDZ4V5.0-dev et les sources fusionnées et de faire tourner le modéle selon
différentes configurations en local et sur SX8 et de comparer les résultats

En local: 32x24x11, config bench/gfortran

  • pour une config IPSLCM5A (comparaison tronc/fusion):
    • convergence numérique sur les champs dynamiques après 3 jours
    • restart et restartphy égaux (à part sur RN et Pb)
    • fichiers histoire égaux
  • pour une config nlle physique (MH07) (comparaison LMDZ4v5.0-dev/fusion):
    • convergence numérique sur les champs dynamiques après 3 jours
    • restart et restartphy égaux
    • fichiers histoire équivalents

Sur brodie, 96x95x39 sur 4 proc:

  • pour une config IPSLCM5A:
    • restart et restartphy égaux (à part sur RN et PB)
    • pas de différence dans les fichiers histmth.nc
  • pour une config MH07
    • restart et restartphy égaux (à part sur RN et PB)
    • pas de différence dans les fichiers histmth.nc

Changement sur makegcm et create_make-gcm pour pouvoir prendre en compte des
programmes principaux en *F90

Location:
LMDZ4/trunk
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ4/trunk

  • LMDZ4/trunk/libf/dyn3dpar/leapfrog_p.F

    r1286 r1403  
    2020       USE guide_p_mod, ONLY : guide_main
    2121       USE getparam
     22       USE control_mod
    2223
    2324      IMPLICIT NONE
     
    6263#include "logic.h"
    6364#include "temps.h"
    64 #include "control.h"
    6565#include "ener.h"
    6666#include "description.h"
    6767#include "serre.h"
    68 #include "com_io_dyn.h"
     68!#include "com_io_dyn.h"
    6969#include "iniprint.h"
    7070#include "academic.h"
     
    212212      itau = 0
    213213!      iday = day_ini+itau/day_step
    214 !      time = FLOAT(itau-(iday-day_ini)*day_step)/day_step+time_0
     214!      time = REAL(itau-(iday-day_ini)*day_step)/day_step+time_0
    215215!         IF(time.GT.1.) THEN
    216216!          time = time-1.
     
    352352c      idissip=1
    353353      IF( purmats ) THEN
     354      ! Purely Matsuno time stepping
    354355         IF( MOD(itau,iconser) .EQ.0.AND.  forward    ) conser = .TRUE.
    355356         IF( MOD(itau,idissip ).EQ.0.AND..NOT.forward ) apdiss = .TRUE.
     
    357358     s          .and. iflag_phys.EQ.1                 ) apphys = .TRUE.
    358359      ELSE
     360      ! Leapfrog/Matsuno time stepping
    359361         IF( MOD(itau   ,iconser) .EQ. 0              ) conser = .TRUE.
    360362         IF( MOD(itau+1,idissip)  .EQ. 0              ) apdiss = .TRUE.
     
    362364      END IF
    363365
     366! Ehouarn: for Shallow Water case (ie: 1 vertical layer),
     367!          supress dissipation step
     368      if (llm.eq.1) then
     369        apdiss=.false.
     370      endif
     371
    364372cym    ---> Pour le moment     
    365373cym      apphys = .FALSE.
    366374      statcl = .FALSE.
    367       conser = .FALSE.
     375      conser = .FALSE. ! ie: no output of control variables to stdout in //
    368376     
    369377      if (firstCaldyn) then
     
    677685         call suspend_timer(timer_caldyn)
    678686
     687        if (prt_level >= 10) then
    679688         write(lunout,*)
    680689     &   'leapfrog_p: Entree dans la physique : Iteration No ',true_itau
     690        endif
    681691c$OMP END MASTER
    682692
     
    964974       ijb=ij_begin
    965975       ije=ij_end
    966        teta(ijb:ije,:)=teta(ijb:ije,:)
    967      s  -iphysiq*dtvr*(teta(ijb:ije,:)-tetarappel(ijb:ije,:))/taurappel
     976!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
     977       do l=1,llm
     978       teta(ijb:ije,l)=teta(ijb:ije,l)
     979     &  -iphysiq*dtvr*(teta(ijb:ije,l)-tetarappel(ijb:ije,l))/taurappel
     980       enddo
     981!$OMP END DO
    968982
    969983       call Register_Hallo(ucov,ip1jmp1,llm,0,1,1,0,Request_Physic)
     
    972986c$OMP BARRIER
    973987       call WaitRequest(Request_Physic)     
    974 
     988c$OMP BARRIER
     989!$OMP MASTER
    975990       call friction_p(ucov,vcov,iphysiq*dtvr)
     991!$OMP END MASTER
     992!$OMP BARRIER
    976993      ENDIF ! of IF(iflag_phys.EQ.2)
    977994
     
    10891106            enddo
    10901107c$OMP END DO NOWAIT           
    1091        endif
     1108       endif ! of if (dissip_conservative)
    10921109
    10931110       ijb=ij_begin
     
    11981215c$OMP END MASTER
    11991216c$OMP BARRIER
    1200       END IF
     1217      END IF ! of IF(apdiss)
    12011218
    12021219cc$OMP END PARALLEL
     
    12801297              itau= itau + 1
    12811298!              iday= day_ini+itau/day_step
    1282 !              time= FLOAT(itau-(iday-day_ini)*day_step)/day_step+time_0
     1299!              time= REAL(itau-(iday-day_ini)*day_step)/day_step+time_0
    12831300!                IF(time.GT.1.) THEN
    12841301!                  time = time-1.
     
    13371354              ENDIF !ok_dynzon
    13381355#endif
    1339             ENDIF
     1356               IF (ok_dyn_ave) THEN
     1357!$OMP MASTER
     1358#ifdef CPP_IOIPSL
     1359! Ehouarn: Gather fields and make master send to output
     1360                call Gather_Field(vcov,ip1jm,llm,0)
     1361                call Gather_Field(ucov,ip1jmp1,llm,0)
     1362                call Gather_Field(teta,ip1jmp1,llm,0)
     1363                call Gather_Field(pk,ip1jmp1,llm,0)
     1364                call Gather_Field(phi,ip1jmp1,llm,0)
     1365                do iq=1,nqtot
     1366                  call Gather_Field(q(1,1,iq),ip1jmp1,llm,0)
     1367                enddo
     1368                call Gather_Field(masse,ip1jmp1,llm,0)
     1369                call Gather_Field(ps,ip1jmp1,1,0)
     1370                call Gather_Field(phis,ip1jmp1,1,0)
     1371                if (mpi_rank==0) then
     1372                 CALL writedynav(itau,vcov,
     1373     &                 ucov,teta,pk,phi,q,masse,ps,phis)
     1374                endif
     1375#endif
     1376!$OMP END MASTER
     1377               ENDIF ! of IF (ok_dyn_ave)
     1378            ENDIF ! of IF((MOD(itau,iperiod).EQ.0).OR.(itau.EQ.itaufin))
    13401379
    13411380c-----------------------------------------------------------------------
     
    13431382c   ------------------------------
    13441383
    1345 c      IF( MOD(itau,iecri         ).EQ.0) THEN
    1346 
    1347             IF( MOD(itau,iecri*day_step).EQ.0) THEN
     1384            IF( MOD(itau,iecri).EQ.0) THEN
     1385             ! Ehouarn: output only during LF or Backward Matsuno
     1386             if (leapf.or.(.not.leapf.and.(.not.forward))) then
    13481387c$OMP BARRIER
    13491388c$OMP MASTER
     
    13791418       
    13801419#ifdef CPP_IOIPSL
    1381  
     1420              if (ok_dyn_ins) then
     1421! Ehouarn: Gather fields and make master write to output
     1422                call Gather_Field(vcov,ip1jm,llm,0)
     1423                call Gather_Field(ucov,ip1jmp1,llm,0)
     1424                call Gather_Field(teta,ip1jmp1,llm,0)
     1425                call Gather_Field(phi,ip1jmp1,llm,0)
     1426                do iq=1,nqtot
     1427                  call Gather_Field(q(1,1,iq),ip1jmp1,llm,0)
     1428                enddo
     1429                call Gather_Field(masse,ip1jmp1,llm,0)
     1430                call Gather_Field(ps,ip1jmp1,1,0)
     1431                call Gather_Field(phis,ip1jmp1,1,0)
     1432                if (mpi_rank==0) then
     1433                 CALL writehist(itau,vcov,ucov,teta,phi,q,masse,ps,phis)
     1434                endif
    13821435!              CALL writehist_p(histid,histvid, itau,vcov,
    13831436!     &                         ucov,teta,phi,q,masse,ps,phis)
    1384 
     1437! or use writefield_p
     1438!      call WriteField_p('ucov',reshape(ucov,(/iip1,jmp1,llm/)))
     1439!      call WriteField_p('vcov',reshape(vcov,(/iip1,jjm,llm/)))
     1440!      call WriteField_p('teta',reshape(teta,(/iip1,jmp1,llm/)))
     1441!      call WriteField_p('ps',reshape(ps,(/iip1,jmp1/)))
     1442              endif ! of if (ok_dyn_ins)
    13851443#endif
    13861444! For some Grads outputs of fields
     
    13991457              endif ! of if (output_grads_dyn)
    14001458c$OMP END MASTER
     1459             endif ! of if (leapf.or.(.not.leapf.and.(.not.forward)))
    14011460            ENDIF ! of IF(MOD(itau,iecri).EQ.0)
    14021461
     
    14581517             itau =  itau + 1
    14591518!             iday = day_ini+itau/day_step
    1460 !             time = FLOAT(itau-(iday-day_ini)*day_step)/day_step+time_0
     1519!             time = REAL(itau-(iday-day_ini)*day_step)/day_step+time_0
    14611520!
    14621521!                  IF(time.GT.1.) THEN
     
    14771536               GO TO 2
    14781537
    1479             ELSE ! of IF(forward)
     1538            ELSE ! of IF(forward) i.e. backward step
    14801539
    14811540              IF(MOD(itau,iperiod).EQ.0 .OR. itau.EQ.itaufin) THEN
     
    14881547               IF (ok_dynzon) THEN
    14891548c$OMP BARRIER
    1490 
    14911549               call Register_Hallo(vcov,ip1jm,llm,1,0,0,1,TestRequest)
    14921550               call SendRequest(TestRequest)
    14931551c$OMP BARRIER
    14941552               call WaitRequest(TestRequest)
    1495 
    14961553c$OMP BARRIER
    14971554c$OMP MASTER
     
    15031560               END IF !ok_dynzon
    15041561#endif
     1562               IF (ok_dyn_ave) THEN
     1563!$OMP MASTER
     1564#ifdef CPP_IOIPSL
     1565! Ehouarn: Gather fields and make master send to output
     1566                call Gather_Field(vcov,ip1jm,llm,0)
     1567                call Gather_Field(ucov,ip1jmp1,llm,0)
     1568                call Gather_Field(teta,ip1jmp1,llm,0)
     1569                call Gather_Field(pk,ip1jmp1,llm,0)
     1570                call Gather_Field(phi,ip1jmp1,llm,0)
     1571                do iq=1,nqtot
     1572                  call Gather_Field(q(1,1,iq),ip1jmp1,llm,0)
     1573                enddo
     1574                call Gather_Field(masse,ip1jmp1,llm,0)
     1575                call Gather_Field(ps,ip1jmp1,1,0)
     1576                call Gather_Field(phis,ip1jmp1,1,0)
     1577                if (mpi_rank==0) then
     1578                 CALL writedynav(itau,vcov,
     1579     &                 ucov,teta,pk,phi,q,masse,ps,phis)
     1580                endif
     1581#endif
     1582!$OMP END MASTER
     1583               ENDIF ! of IF (ok_dyn_ave)
     1584
    15051585              ENDIF ! of IF(MOD(itau,iperiod).EQ.0 .OR. itau.EQ.itaufin)
    15061586
    15071587
    1508 c               IF(MOD(itau,iecri         ).EQ.0) THEN
    1509               IF(MOD(itau,iecri*day_step).EQ.0) THEN
     1588               IF(MOD(itau,iecri         ).EQ.0) THEN
     1589c              IF(MOD(itau,iecri*day_step).EQ.0) THEN
    15101590c$OMP BARRIER
    15111591c$OMP MASTER
     
    15401620
    15411621#ifdef CPP_IOIPSL
    1542 
     1622              if (ok_dyn_ins) then
     1623! Ehouarn: Gather fields and make master send to output
     1624                call Gather_Field(vcov,ip1jm,llm,0)
     1625                call Gather_Field(ucov,ip1jmp1,llm,0)
     1626                call Gather_Field(teta,ip1jmp1,llm,0)
     1627                call Gather_Field(phi,ip1jmp1,llm,0)
     1628                do iq=1,nqtot
     1629                  call Gather_Field(q(1,1,iq),ip1jmp1,llm,0)
     1630                enddo
     1631                call Gather_Field(masse,ip1jmp1,llm,0)
     1632                call Gather_Field(ps,ip1jmp1,1,0)
     1633                call Gather_Field(phis,ip1jmp1,1,0)
     1634                if (mpi_rank==0) then
     1635                 CALL writehist(itau,vcov,ucov,teta,phi,q,masse,ps,phis)
     1636                endif
    15431637!                CALL writehist_p(histid, histvid, itau,vcov ,
    15441638!     &                           ucov,teta,phi,q,masse,ps,phis)
     1639              endif ! of if (ok_dyn_ins)
    15451640#endif
    15461641! For some Grads output (but does it work?)
     
    15601655
    15611656c$OMP END MASTER
    1562               ENDIF ! of IF(MOD(itau,iecri*day_step).EQ.0)
     1657              ENDIF ! of IF(MOD(itau,iecri).EQ.0)
    15631658
    15641659              IF(itau.EQ.itaufin) THEN
Note: See TracChangeset for help on using the changeset viewer.