Ignore:
Timestamp:
Jun 25, 2014, 1:19:59 PM (11 years ago)
Author:
emillour
Message:

Common dynamics:
Some updates to keep up with LMDZ5 Earth model evolution (up to LMDZ5 rev 1955).
Main change is the introduction of a "dyn3d_common" directory
to store files common to dyn3d and dyn3dpar.
See file "DOC/chantiers/commit_importants.log" for detailed list
of changes. These changes do not change results on test cases.
EM

Location:
trunk/LMDZ.COMMON/libf/dyn3dpar
Files:
133 deleted
8 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.COMMON/libf/dyn3dpar/abort_gcm.F

    r1019 r1300  
    11!
    2 ! $Id: abort_gcm.F 1748 2013-04-24 14:18:40Z emillour $
     2! $Id: abort_gcm.F 1907 2013-11-26 13:10:46Z lguez $
    33!
    44c
     
    1313#endif
    1414      USE parallel_lmdz
     15
     16
     17
     18
    1519#include "iniprint.h"
    1620 
     
    3741c$OMP END MASTER
    3842#endif
     43
     44
     45
    3946c     call histclo(2)
    4047c     call histclo(3)
     
    5663      endif
    5764      END
     65
  • trunk/LMDZ.COMMON/libf/dyn3dpar/bilan_dyn_p.F

    r1019 r1300  
    11!
    2 ! $Id: bilan_dyn_p.F 1403 2010-07-01 09:02:53Z fairhead $
     2! $Id: bilan_dyn_p.F 1907 2013-11-26 13:10:46Z lguez $
    33!
    44      SUBROUTINE bilan_dyn_p (ntrac,dt_app,dt_cum,
     
    1616      USE mod_hallo
    1717      use misc_mod
    18       use write_field
     18      use write_field_p
    1919      IMPLICIT NONE
    2020
     
    5757c   =======
    5858
    59       integer icum,ncum
    60       logical first
    61       real zz,zqy,zfactv(jjm,llm)
    62 
    63       integer nQ
    64       parameter (nQ=7)
     59      integer,save :: icum,ncum
     60!$OMP THREADPRIVATE(icum,ncum)
     61      logical,SAVE :: first=.true.
     62!$OMP THREADPRIVATE(first)
     63
     64      real zz,zqy
     65      real,save :: zfactv(jjm,llm)
     66
     67      integer,parameter :: nQ=7
    6568
    6669
    6770cym      character*6 nom(nQ)
    6871cym      character*6 unites(nQ)
    69       character*6,save :: nom(nQ)
    70       character*6,save :: unites(nQ)
    71 
    72       character*10 file
     72      character(len=6),save :: nom(nQ)
     73      character(len=6),save :: unites(nQ)
     74
     75      character(len=10) file
    7376      integer ifile
    7477      parameter (ifile=4)
    7578
    76       integer itemp,igeop,iecin,iang,iu,iovap,iun
    77       integer i_sortie
    78 
    79       save first,icum,ncum
    80       save itemp,igeop,iecin,iang,iu,iovap,iun
    81       save i_sortie
    82 
    83       real time
    84       integer itau
    85       save time,itau
    86       data time,itau/0.,0/
    87 
    88       data first/.true./
    89       data itemp,igeop,iecin,iang,iu,iovap,iun/1,2,3,4,5,6,7/
    90       data i_sortie/1/
     79      integer,PARAMETER :: itemp=1,igeop=2,iecin=3,iang=4,iu=5
     80      INTEGER,PARAMETER :: iovap=6,iun=7
     81      integer,PARAMETER :: i_sortie=1
     82
     83      real,SAVE :: time=0.
     84      integer,SAVE :: itau=0.
     85!$OMP THREADPRIVATE(time,itau)
    9186
    9287      real ww
    9388
    9489c   variables dynamiques intermédiaires
    95       REAL vcont(iip1,jjm,llm),ucont(iip1,jjp1,llm)
    96       REAL ang(iip1,jjp1,llm),unat(iip1,jjp1,llm)
    97       REAL massebx(iip1,jjp1,llm),masseby(iip1,jjm,llm)
    98       REAL vorpot(iip1,jjm,llm)
    99       REAL w(iip1,jjp1,llm),ecin(iip1,jjp1,llm),convm(iip1,jjp1,llm)
    100       REAL bern(iip1,jjp1,llm)
     90      REAL,save :: vcont(iip1,jjm,llm),ucont(iip1,jjp1,llm)
     91      REAL,save :: ang(iip1,jjp1,llm),unat(iip1,jjp1,llm)
     92      REAL,save :: massebx(iip1,jjp1,llm),masseby(iip1,jjm,llm)
     93      REAL,save :: vorpot(iip1,jjm,llm)
     94      REAL,save :: w(iip1,jjp1,llm),ecin(iip1,jjp1,llm)
     95      REAL,save ::convm(iip1,jjp1,llm)
     96      REAL,save :: bern(iip1,jjp1,llm)
    10197
    10298c   champ contenant les scalaires advectés.
    103       real Q(iip1,jjp1,llm,nQ)
     99      real,save :: Q(iip1,jjp1,llm,nQ)
    104100   
    105101c   champs cumulés
    106       real ps_cum(iip1,jjp1)
    107       real masse_cum(iip1,jjp1,llm)
    108       real flux_u_cum(iip1,jjp1,llm)
    109       real flux_v_cum(iip1,jjm,llm)
    110       real Q_cum(iip1,jjp1,llm,nQ)
    111       real flux_uQ_cum(iip1,jjp1,llm,nQ)
    112       real flux_vQ_cum(iip1,jjm,llm,nQ)
    113       real flux_wQ_cum(iip1,jjp1,llm,nQ)
    114       real dQ(iip1,jjp1,llm,nQ)
    115 
    116       save ps_cum,masse_cum,flux_u_cum,flux_v_cum
    117       save Q_cum,flux_uQ_cum,flux_vQ_cum
     102      real,save :: ps_cum(iip1,jjp1)
     103      real,save :: masse_cum(iip1,jjp1,llm)
     104      real,save :: flux_u_cum(iip1,jjp1,llm)
     105      real,save :: flux_v_cum(iip1,jjm,llm)
     106      real,save :: Q_cum(iip1,jjp1,llm,nQ)
     107      real,save :: flux_uQ_cum(iip1,jjp1,llm,nQ)
     108      real,save :: flux_vQ_cum(iip1,jjm,llm,nQ)
     109      real,save :: flux_wQ_cum(iip1,jjp1,llm,nQ)
     110      real,save :: dQ(iip1,jjp1,llm,nQ)
     111
    118112
    119113c   champs de tansport en moyenne zonale
     
    128122      character*10,save :: zunites(ntr,nQ)
    129123
    130       integer iave,itot,immc,itrs,istn
    131       data iave,itot,immc,itrs,istn/1,2,3,4,5/
     124      INTEGER,PARAMETER :: iave=1,itot=2,immc=3,itrs=4,istn=5
     125
    132126      character*3 ctrs(ntr)
    133127      data ctrs/'  ','TOT','MMC','TRS','STN'/
    134128
    135       real zvQ(jjm,llm,ntr,nQ),zvQtmp(jjm,llm)
    136       real zavQ(jjm,ntr,nQ),psiQ(jjm,llm+1,nQ)
    137       real zmasse(jjm,llm),zamasse(jjm)
    138 
    139       real zv(jjm,llm),psi(jjm,llm+1)
     129      real,save :: zvQ(jjm,llm,ntr,nQ),zvQtmp(jjm,llm)
     130      real,save :: zavQ(jjm,ntr,nQ),psiQ(jjm,llm+1,nQ)
     131      real,save :: zmasse(jjm,llm),zamasse(jjm)
     132
     133      real,save :: zv(jjm,llm),psi(jjm,llm+1)
    140134
    141135      integer i,j,l,iQ
     
    151145      save fileid
    152146
    153       integer ndex3d(jjm*llm)
     147      integer,save :: ndex3d(jjm*llm)
    154148
    155149C   Variables locales
     
    162156      integer zan, dayref
    163157C
    164       real rlong(jjm),rlatg(jjm)
     158      real,save :: rlong(jjm),rlatg(jjm)
    165159      integer :: jjb,jje,jjn,ijb,ije
    166       type(Request) :: Req
     160      type(Request),SAVE :: Req
     161!$OMP THREADPRIVATE(Req)
    167162
    168163! definition du domaine d'ecriture pour le rebuild
     
    182177c   Initialisation
    183178c=====================================================================
    184       ndex3d=0
    185179      if (adjust) return
    186180     
     
    190184      if (first) then
    191185
     186        ndex3d=0
    192187
    193188        icum=0
     
    202197           WRITE(lunout,*)'dt_cum=',dt_cum
    203198           stop
     199        else
     200          write(lunout,*) "bilan_dyn_p: ncum=",ncum
    204201        endif
    205202
    206         if (i_sortie.eq.1) then
    207          file='dynzon'
    208          if (mpi_rank==0) then
    209          call inigrads(ifile,1
    210      s  ,0.,180./pi,0.,0.,jjm,rlatv,-90.,90.,180./pi
    211      s  ,llm,presnivs,1.
    212      s  ,dt_cum,file,'dyn_zon ')
    213          endif
    214         endif
    215 
     203!        if (i_sortie.eq.1) then
     204!        file='dynzon'
     205!         if (mpi_rank==0) then
     206!        call inigrads(ifile,1
     207!     s  ,0.,180./pi,0.,0.,jjm,rlatv,-90.,90.,180./pi
     208!     s  ,llm,presnivs,1.
     209!     s  ,dt_cum,file,'dyn_zon ')
     210!         endif
     211!        endif
     212
     213!$OMP MASTER
    216214        nom(itemp)='T'
    217215        nom(igeop)='gz'
     
    339337               CALL histend(fileid)
    340338
    341 
     339!$OMP END MASTER
     340!$OMP BARRIER
    342341      endif
    343342
     
    351350   
    352351c   énergie cinétique
    353       ucont(:,jjb:jje,:)=0
     352!      ucont(:,jjb:jje,:)=0
    354353
    355354      call Register_Hallo(ucov,ip1jmp1,llm,1,1,1,1,Req)
    356355      call Register_Hallo(vcov,ip1jm,llm,1,1,1,1,Req)
    357356      call SendRequest(Req)
     357c$OMP BARRIER
    358358      call WaitRequest(Req)
     359c$OMP BARRIER
    359360
    360361      CALL covcont_p(llm,ucov,vcov,ucont,vcont)
     
    362363
    363364c   moment cinétique
     365!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
    364366      do l=1,llm
    365367         ang(:,jjb:jje,l)=ucov(:,jjb:jje,l)+constang(:,jjb:jje)
    366368         unat(:,jjb:jje,l)=ucont(:,jjb:jje,l)*cu(:,jjb:jje)
    367369      enddo
    368 
    369       Q(:,jjb:jje,:,itemp)=teta(:,jjb:jje,:)*pk(:,jjb:jje,:)/cpp
    370       Q(:,jjb:jje,:,igeop)=phi(:,jjb:jje,:)
    371       Q(:,jjb:jje,:,iecin)=ecin(:,jjb:jje,:)
    372       Q(:,jjb:jje,:,iang)=ang(:,jjb:jje,:)
    373       Q(:,jjb:jje,:,iu)=unat(:,jjb:jje,:)
    374       Q(:,jjb:jje,:,iovap)=trac(:,jjb:jje,:,1)
    375       Q(:,jjb:jje,:,iun)=1.
    376 
     370!$OMP END DO
     371
     372!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
     373      DO l=1,llm
     374        Q(:,jjb:jje,l,itemp)=teta(:,jjb:jje,l)*pk(:,jjb:jje,l)/cpp
     375        Q(:,jjb:jje,l,igeop)=phi(:,jjb:jje,l)
     376        Q(:,jjb:jje,l,iecin)=ecin(:,jjb:jje,l)
     377        Q(:,jjb:jje,l,iang)=ang(:,jjb:jje,l)
     378        Q(:,jjb:jje,l,iu)=unat(:,jjb:jje,l)
     379        Q(:,jjb:jje,l,iovap)=trac(:,jjb:jje,l,1)
     380        Q(:,jjb:jje,l,iun)=1.
     381      ENDDO
     382!$OMP END DO NOWAIT
    377383
    378384c=====================================================================
     
    384390         jje=jj_end
    385391
     392!$OMP MASTER
    386393         ps_cum(:,jjb:jje)=0.
    387          masse_cum(:,jjb:jje,:)=0.
    388          flux_u_cum(:,jjb:jje,:)=0.
    389          Q_cum(:,jjb:jje,:,:)=0.
    390          flux_uQ_cum(:,jjb:jje,:,:)=0.
    391          if (pole_sud) jje=jj_end-1
    392          flux_v_cum(:,jjb:jje,:)=0.
    393          flux_vQ_cum(:,jjb:jje,:,:)=0.
     394!$OMP END MASTER
     395!$OMP BARRIER
     396
     397!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
     398        DO l=1,llm
     399          masse_cum(:,jjb:jje,l)=0.
     400          flux_u_cum(:,jjb:jje,l)=0.
     401          Q_cum(:,jjb:jje,l,:)=0.
     402          flux_uQ_cum(:,jjb:jje,l,:)=0.
     403          if (pole_sud) jje=jj_end-1
     404          flux_v_cum(:,jjb:jje,l)=0.
     405          flux_vQ_cum(:,jjb:jje,l,:)=0.
     406        ENDDO
     407!$OMP END DO NOWAIT
    394408      endif
    395409
     
    402416      jje=jj_end
    403417
     418!$OMP MASTER
    404419      ps_cum(:,jjb:jje)=ps_cum(:,jjb:jje)+ps(:,jjb:jje)
    405       masse_cum(:,jjb:jje,:)=masse_cum(:,jjb:jje,:)+masse(:,jjb:jje,:)
    406       flux_u_cum(:,jjb:jje,:)=flux_u_cum(:,jjb:jje,:)
    407      .                       +flux_u(:,jjb:jje,:)
     420!$OMP END MASTER
     421!$OMP BARRIER
     422
     423!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
     424      DO l=1,llm
     425        masse_cum(:,jjb:jje,l)=masse_cum(:,jjb:jje,l)+masse(:,jjb:jje,l)
     426        flux_u_cum(:,jjb:jje,l)=flux_u_cum(:,jjb:jje,l)
     427     .                         +flux_u(:,jjb:jje,l)
     428      ENDDO
     429!$OMP END DO NOWAIT
     430     
    408431      if (pole_sud) jje=jj_end-1
    409       flux_v_cum(:,jjb:jje,:)=flux_v_cum(:,jjb:jje,:)
    410      .                         +flux_v(:,jjb:jje,:)
    411 
    412       jjb=jj_begin
    413       jje=jj_end
    414 
    415       do iQ=1,nQ
    416         Q_cum(:,jjb:jje,:,iQ)=Q_cum(:,jjb:jje,:,iQ)
    417      .                       +Q(:,jjb:jje,:,iQ)*masse(:,jjb:jje,:)
     432
     433!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
     434      DO l=1,llm
     435       flux_v_cum(:,jjb:jje,l)=flux_v_cum(:,jjb:jje,l)
     436     .                          +flux_v(:,jjb:jje,l)
     437      ENDDO
     438!$OMP END DO NOWAIT
     439     
     440      jjb=jj_begin
     441      jje=jj_end
     442
     443      do iQ=1,nQ
     444!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
     445        DO l=1,llm
     446          Q_cum(:,jjb:jje,l,iQ)=Q_cum(:,jjb:jje,l,iQ)
     447     .                       +Q(:,jjb:jje,l,iQ)*masse(:,jjb:jje,l)
     448        ENDDO
     449!$OMP END DO NOWAIT
    418450      enddo
    419451
     
    425457c   -----------------
    426458      do iQ=1,nQ
     459!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
    427460         do l=1,llm
    428461            do j=jjb,jje
     
    434467            enddo
    435468         enddo
     469!$OMP END DO NOWAIT
    436470      enddo
    437471
     
    442476      enddo
    443477      call SendRequest(Req)
     478!$OMP BARRIER     
    444479      call WaitRequest(Req)
    445      
     480!$OMP BARRIER
     481
    446482      jjb=jj_begin
    447483      jje=jj_end
     
    449485     
    450486      do iQ=1,nQ
     487!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
    451488         do l=1,llm
    452489            do j=jjb,jje
     
    457494            enddo
    458495         enddo
     496!$OMP END DO NOWAIT
    459497      enddo
    460498
     
    467505      call Register_Hallo(flux_vQ_cum,ip1jm,llm,2,2,2,2,Req)
    468506      call SendRequest(Req)
     507!$OMP BARRIER     
    469508      call WaitRequest(Req)
     509c$OMP BARRIER
    470510
    471511      call  convflu_p(flux_uQ_cum,flux_vQ_cum,llm*nQ,dQ)
     
    475515      call Register_Hallo(flux_v_cum,ip1jm,llm,2,2,2,2,Req)
    476516      call SendRequest(Req)
     517!$OMP BARRIER     
    477518      call WaitRequest(Req)
     519c$OMP BARRIER
    478520
    479521      call convmas_p(flux_u_cum,flux_v_cum,convm)
    480522      CALL vitvert_p(convm,w)
    481 
    482       jjb=jj_begin
    483       jje=jj_end
    484 
    485       do iQ=1,nQ
    486          do l=1,llm-1
    487             do j=jjb,jje
    488                do i=1,iip1
    489                   ww=-0.5*w(i,j,l+1)*(Q(i,j,l,iQ)+Q(i,j,l+1,iQ))
    490                   dQ(i,j,l  ,iQ)=dQ(i,j,l  ,iQ)-ww
    491                   dQ(i,j,l+1,iQ)=dQ(i,j,l+1,iQ)+ww
    492                enddo
    493             enddo
    494          enddo
     523!$OMP BARRIER     
     524
     525      jjb=jj_begin
     526      jje=jj_end
     527
     528      do iQ=1,nQ
     529!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
     530         do l=1,llm
     531            IF (l<llm) THEN
     532              do j=jjb,jje
     533                 do i=1,iip1
     534                    ww=-0.5*w(i,j,l+1)*(Q(i,j,l,iQ)+Q(i,j,l+1,iQ))
     535                    dQ(i,j,l  ,iQ)=dQ(i,j,l  ,iQ)-ww
     536                    dQ(i,j,l+1,iQ)=dQ(i,j,l+1,iQ)+ww
     537                 enddo
     538              enddo
     539            ENDIF
     540            IF (l>2) THEN
     541              do j=jjb,jje
     542                do i=1,iip1
     543                  ww=-0.5*w(i,j,l)*(Q(i,j,l-1,iQ)+Q(i,j,l,iQ))
     544                  dQ(i,j,l,iQ)=dQ(i,j,l,iQ)+ww
     545                enddo
     546              enddo
     547            ENDIF
     548         enddo
     549!$OMP ENDDO NOWAIT
    495550      enddo
    496551      IF (prt_level > 5)
     
    505560     . WRITE(lunout,*)'Pas d ecriture'
    506561
     562      jjb=jj_begin
     563      jje=jj_end
     564
    507565c   Normalisation
    508566      do iQ=1,nQ
    509          Q_cum(:,jjb:jje,:,iQ)=Q_cum(:,jjb:jje,:,iQ)
    510      .                        /masse_cum(:,jjb:jje,:)
    511       enddo
     567!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
     568        do l=1,llm
     569          Q_cum(:,jjb:jje,l,iQ)=Q_cum(:,jjb:jje,l,iQ)
     570     .                          /masse_cum(:,jjb:jje,l)
     571        enddo
     572!$OMP ENDDO NOWAIT
     573      enddo
     574
    512575      zz=1./REAL(ncum)
    513576
    514       jjb=jj_begin
    515       jje=jj_end
    516 
     577!$OMP MASTER
    517578      ps_cum(:,jjb:jje)=ps_cum(:,jjb:jje)*zz
    518       masse_cum(:,jjb:jje,:)=masse_cum(:,jjb:jje,:)*zz
    519       flux_u_cum(:,jjb:jje,:)=flux_u_cum(:,jjb:jje,:)*zz
    520       flux_uQ_cum(:,jjb:jje,:,:)=flux_uQ_cum(:,jjb:jje,:,:)*zz
    521       dQ(:,jjb:jje,:,:)=dQ(:,jjb:jje,:,:)*zz
     579!$OMP END MASTER
     580
     581!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
     582      DO l=1,llm
     583        masse_cum(:,jjb:jje,l)=masse_cum(:,jjb:jje,l)*zz
     584        flux_u_cum(:,jjb:jje,l)=flux_u_cum(:,jjb:jje,l)*zz
     585        flux_uQ_cum(:,jjb:jje,l,:)=flux_uQ_cum(:,jjb:jje,l,:)*zz
     586        dQ(:,jjb:jje,l,:)=dQ(:,jjb:jje,l,:)*zz
     587      ENDDO
     588!$OMP ENDDO NOWAIT
     589         
    522590     
    523591      IF (pole_sud) jje=jj_end-1
    524       flux_v_cum(:,jjb:jje,:)=flux_v_cum(:,jjb:jje,:)*zz
    525       flux_vQ_cum(:,jjb:jje,:,:)=flux_vQ_cum(:,jjb:jje,:,:)*zz
     592!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
     593      DO l=1,llm
     594        flux_v_cum(:,jjb:jje,l)=flux_v_cum(:,jjb:jje,l)*zz
     595        flux_vQ_cum(:,jjb:jje,l,:)=flux_vQ_cum(:,jjb:jje,l,:)*zz
     596      ENDDO
     597!$OMP ENDDO
    526598
    527599      jjb=jj_begin
     
    532604c   division de dQ par la masse pour revenir aux bonnes grandeurs
    533605      do iQ=1,nQ
    534          dQ(:,jjb:jje,:,iQ)=dQ(:,jjb:jje,:,iQ)/masse_cum(:,jjb:jje,:)
     606!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
     607        DO l=1,llm
     608           dQ(:,jjb:jje,l,iQ)=dQ(:,jjb:jje,l,iQ)/masse_cum(:,jjb:jje,l)
     609        ENDDO
     610!$OMP ENDDO NOWAIT
    535611      enddo
    536612 
     
    545621      if (pole_sud) jje=jj_end-1
    546622
    547       zv(jjb:jje,:)=0.
    548       zmasse(jjb:jje,:)=0.
     623!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
     624        DO l=1,llm
     625          zv(jjb:jje,l)=0.
     626          zmasse(jjb:jje,l)=0.
     627        ENDDO
     628!$OMP ENDDO NOWAIT
    549629
    550630      call Register_Hallo(masse_cum,ip1jmp1,llm,1,1,1,1,Req)
     
    554634
    555635      call SendRequest(Req)
     636!$OMP BARRIER
    556637      call WaitRequest(Req)
     638c$OMP BARRIER
    557639
    558640      call massbar_p(masse_cum,massebx,masseby)
     
    562644      if (pole_sud) jje=jj_end-1
    563645     
     646!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
    564647      do l=1,llm
    565648         do j=jjb,jje
     
    571654         enddo
    572655      enddo
     656!$OMP ENDDO
    573657
    574658c     print*,'3OK'
     
    609693      psiQ=0.
    610694      do iQ=1,nQ
    611          zvQtmp=0.
     695!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
    612696         do l=1,llm
     697            zvQtmp(:,l)=0.
    613698            do j=jjb,jje
    614699c              print*,'j,l,iQ=',j,l,iQ
     
    633718            enddo
    634719         enddo
     720!$OMP ENDDO NOWAIT
    635721c   fonction de courant meridienne pour la quantite Q
     722!$OMP BARRIER
     723!$OMP MASTER
    636724         do l=llm,1,-1
    637725            do j=jjb,jje
     
    639727            enddo
    640728         enddo
    641       enddo
     729!$OMP END MASTER
     730!$OMP BARRIER
     731      enddo ! of do iQ=1,nQ
    642732
    643733c   fonction de courant pour la circulation meridienne moyenne
     734!$OMP BARRIER
     735!$OMP MASTER
    644736      psi(jjb:jje,:)=0.
    645737      do l=llm,1,-1
     
    649741         enddo
    650742      enddo
     743!$OMP END MASTER
     744!$OMP BARRIER
    651745
    652746c     print*,'4OK'
    653747c   sorties proprement dites
     748!$OMP MASTER     
    654749      if (i_sortie.eq.1) then
    655750      jjb=jj_begin
     
    669764     s                  ,jjn*llm,ndex3d)
    670765      enddo
    671 
    672766      call histwrite(fileid,'masse',itau,zmasse(jjb:jje,1:llm)
    673767     s   ,jjn*llm,ndex3d)
     
    703797         enddo
    704798      enddo
    705 
     799!$OMP END MASTER
     800!$OMP BARRIER
    706801c     on doit pouvoir tracer systematiquement la fonction de courant.
    707802
     
    712807c/////////////////////////////////////////////////////////////////////
    713808c=====================================================================
    714 
    715809      return
    716810      end
     811
  • trunk/LMDZ.COMMON/libf/dyn3dpar/conf_gcm.F

    r1189 r1300  
    1515      use mod_filtre_fft, ONLY : use_filtre_fft
    1616      use mod_hallo, ONLY : use_mpi_alloc
    17       use parallel_lmdz, ONLY : omp_chunk
    1817      USE control_mod
    1918      USE infotrac, ONLY : type_trac
     
    587586      use_mpi_alloc=.FALSE.
    588587      CALL getin('use_mpi_alloc',use_mpi_alloc)
    589 
    590 !Config  Key  = omp_chunk
    591 !Config  Desc = taille des blocs openmp
    592 !Config  Def  = 1
    593 !Config  Help = defini la taille des packets d'iteration openmp
    594 !Config         distribuee a chaque tache lors de l'entree dans une
    595 !Config         boucle parallelisee
    596  
    597       omp_chunk=1
    598       CALL getin('omp_chunk',omp_chunk)
    599588
    600589!Config key = ok_strato
     
    10161005      write(lunout,*)' use_filtre_fft = ', use_filtre_fft
    10171006      write(lunout,*)' use_mpi_alloc = ', use_mpi_alloc
    1018       write(lunout,*)' omp_chunk = ', omp_chunk
    10191007      write(lunout,*)' ok_strato = ', ok_strato
    10201008      write(lunout,*)' ok_gradsfile = ', ok_gradsfile
  • trunk/LMDZ.COMMON/libf/dyn3dpar/gcm.F

    r1107 r1300  
    1010#endif
    1111
    12 
    13 #ifdef CPP_XIOS
    14     ! ug Pour les sorties XIOS
    15         USE wxios
    16 #endif
    1712
    1813      USE mod_const_mpi, ONLY: init_const_mpi
     
    193188c   Initialisation partie parallele
    194189c------------------------------------
     190
    195191      CALL init_const_mpi
    196 
    197192      call init_parallel
    198193      call ini_getparam("out.def")
     
    225220!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    226221
    227 #ifdef CPP_XIOS
    228         CALL wxios_init("LMDZ")
    229 #endif
    230222
    231223c
     
    362354          start_time = starttime
    363355        ELSE
    364           WRITE(lunout,*)'Je m''arrete'
    365           CALL abort
     356          call abort_gcm("gcm", "'Je m''arrete'", 1)
    366357        ENDIF
    367358      ENDIF
  • trunk/LMDZ.COMMON/libf/dyn3dpar/guide_p_mod.F90

    r1019 r1300  
    9191    CALL getpar('guide_teta',.false.,guide_teta,'guidage de T par Teta')
    9292
    93     CALL getpar('guide_add',.false.,guide_add,'forage constant?')
     93    CALL getpar('guide_add',.false.,guide_add,'for�age constant?')
    9494    CALL getpar('guide_zon',.false.,guide_zon,'guidage moy zonale')
    9595
     
    108108    CALL getpar('guide_BL',.true.,guide_BL,'guidage dans C.Lim')
    109109   
    110 ! Sauvegarde du forage
     110! Sauvegarde du for�age
    111111    CALL getpar('guide_sav',.false.,guide_sav,'sauvegarde guidage')
    112112    CALL getpar('iguide_sav',4,iguide_sav,'freq. sauvegarde guidage')
     
    155155    ncidpl=-99
    156156    if (guide_plevs.EQ.1) then
    157        if (ncidpl.eq.-99) rcod=nf90_open('apbp.nc',Nf90_NOWRITe, ncidpl)
     157       if (ncidpl.eq.-99) then
     158          rcod=nf90_open('apbp.nc',Nf90_NOWRITe, ncidpl)
     159          if (rcod.NE.NF_NOERR) THEN
     160             print *,'Guide: probleme -> pas de fichier apbp.nc'
     161             CALL abort_gcm(modname,abort_message,1)
     162          endif
     163       endif
    158164    elseif (guide_plevs.EQ.2) then
    159        if (ncidpl.EQ.-99) rcod=nf90_open('P.nc',Nf90_NOWRITe,ncidpl)
     165       if (ncidpl.EQ.-99) then
     166          rcod=nf90_open('P.nc',Nf90_NOWRITe,ncidpl)
     167          if (rcod.NE.NF_NOERR) THEN
     168             print *,'Guide: probleme -> pas de fichier P.nc'
     169             CALL abort_gcm(modname,abort_message,1)
     170          endif
     171       endif
    160172    elseif (guide_u) then
    161        if (ncidpl.eq.-99) rcod=nf90_open('u.nc',Nf90_NOWRITe,ncidpl)
     173       if (ncidpl.eq.-99) then
     174          rcod=nf90_open('u.nc',Nf90_NOWRITe,ncidpl)
     175          if (rcod.NE.NF_NOERR) THEN
     176             print *,'Guide: probleme -> pas de fichier u.nc'
     177             CALL abort_gcm(modname,abort_message,1)
     178          endif
     179       endif
    162180    elseif (guide_v) then
    163        if (ncidpl.eq.-99) rcod=nf90_open('v.nc',nf90_nowrite,ncidpl)
     181       if (ncidpl.eq.-99) then
     182          rcod=nf90_open('v.nc',nf90_nowrite,ncidpl)
     183          if (rcod.NE.NF_NOERR) THEN
     184             print *,'Guide: probleme -> pas de fichier v.nc'
     185             CALL abort_gcm(modname,abort_message,1)
     186          endif
     187       endif
    164188    elseif (guide_T) then
    165        if (ncidpl.eq.-99) rcod=nf90_open('T.nc',nf90_nowrite,ncidpl)
     189       if (ncidpl.eq.-99) then
     190          rcod=nf90_open('T.nc',nf90_nowrite,ncidpl)
     191          if (rcod.NE.NF_NOERR) THEN
     192             print *,'Guide: probleme -> pas de fichier T.nc'
     193             CALL abort_gcm(modname,abort_message,1)
     194          endif
     195       endif
    166196    elseif (guide_Q) then
    167        if (ncidpl.eq.-99) rcod=nf90_open('hur.nc',nf90_nowrite, ncidpl)
     197       if (ncidpl.eq.-99) then
     198          rcod=nf90_open('hur.nc',nf90_nowrite, ncidpl)
     199          if (rcod.NE.NF_NOERR) THEN
     200             print *,'Guide: probleme -> pas de fichier hur.nc'
     201             CALL abort_gcm(modname,abort_message,1)
     202          endif
     203       endif
    168204    endif
    169205    error=NF_INQ_DIMID(ncidpl,'LEVEL',rid)
     
    292328!=======================================================================
    293329  SUBROUTINE guide_main(itau,ucov,vcov,teta,q,masse,ps)
    294     use parallel_lmdz
     330    USE parallel_lmdz
    295331    USE control_mod
    296332   
     
    12311267    INTEGER               :: status,rcode
    12321268
     1269    CHARACTER (len = 80)   :: abort_message
     1270    CHARACTER (len = 20)   :: modname = 'guide_read'
    12331271! -----------------------------------------------------------------
    12341272! Premier appel: initialisation de la lecture des fichiers
     
    12411279             print *,'Lecture du guidage sur niveaux modele'
    12421280             rcode = nf90_open('apbp.nc', nf90_nowrite, ncidpl)
     1281             IF (rcode.NE.NF_NOERR) THEN
     1282              print *,'Guide: probleme -> pas de fichier apbp.nc'
     1283              CALL abort_gcm(modname,abort_message,1)
     1284             ENDIF
    12431285             rcode = nf90_inq_varid(ncidpl, 'AP', varidap)
     1286             IF (rcode.NE.NF_NOERR) THEN
     1287              print *,'Guide: probleme -> pas de variable AP, fichier apbp.nc'
     1288              CALL abort_gcm(modname,abort_message,1)
     1289             ENDIF
    12441290             rcode = nf90_inq_varid(ncidpl, 'BP', varidbp)
     1291             IF (rcode.NE.NF_NOERR) THEN
     1292              print *,'Guide: probleme -> pas de variable BP, fichier apbp.nc'
     1293              CALL abort_gcm(modname,abort_message,1)
     1294             ENDIF
    12451295             print*,'ncidpl,varidap',ncidpl,varidap
    12461296         endif
     
    12481298         if (guide_plevs.EQ.2) then
    12491299             rcode = nf90_open('P.nc', nf90_nowrite, ncidp)
     1300             IF (rcode.NE.NF_NOERR) THEN
     1301              print *,'Guide: probleme -> pas de fichier P.nc'
     1302              CALL abort_gcm(modname,abort_message,1)
     1303             ENDIF
    12501304             rcode = nf90_inq_varid(ncidp, 'PRES', varidp)
     1305             IF (rcode.NE.NF_NOERR) THEN
     1306              print *,'Guide: probleme -> pas de variable PRES, fichier P.nc'
     1307              CALL abort_gcm(modname,abort_message,1)
     1308             ENDIF
    12511309             print*,'ncidp,varidp',ncidp,varidp
    12521310             if (ncidpl.eq.-99) ncidpl=ncidp
     
    12551313         if (guide_u) then
    12561314             rcode = nf90_open('u.nc', nf90_nowrite, ncidu)
     1315             IF (rcode.NE.NF_NOERR) THEN
     1316              print *,'Guide: probleme -> pas de fichier u.nc'
     1317              CALL abort_gcm(modname,abort_message,1)
     1318             ENDIF
    12571319             rcode = nf90_inq_varid(ncidu, 'UWND', varidu)
     1320             IF (rcode.NE.NF_NOERR) THEN
     1321              print *,'Guide: probleme -> pas de variable UWND, fichier u.nc'
     1322              CALL abort_gcm(modname,abort_message,1)
     1323             ENDIF
    12581324             print*,'ncidu,varidu',ncidu,varidu
    12591325             if (ncidpl.eq.-99) ncidpl=ncidu
     
    12621328         if (guide_v) then
    12631329             rcode = nf90_open('v.nc', nf90_nowrite, ncidv)
     1330             IF (rcode.NE.NF_NOERR) THEN
     1331              print *,'Guide: probleme -> pas de fichier v.nc'
     1332              CALL abort_gcm(modname,abort_message,1)
     1333             ENDIF
    12641334             rcode = nf90_inq_varid(ncidv, 'VWND', varidv)
     1335             IF (rcode.NE.NF_NOERR) THEN
     1336              print *,'Guide: probleme -> pas de variable VWND, fichier v.nc'
     1337              CALL abort_gcm(modname,abort_message,1)
     1338             ENDIF
    12651339             print*,'ncidv,varidv',ncidv,varidv
    12661340             if (ncidpl.eq.-99) ncidpl=ncidv
     
    12691343         if (guide_T) then
    12701344             rcode = nf90_open('T.nc', nf90_nowrite, ncidt)
     1345             IF (rcode.NE.NF_NOERR) THEN
     1346              print *,'Guide: probleme -> pas de fichier T.nc'
     1347              CALL abort_gcm(modname,abort_message,1)
     1348             ENDIF
    12711349             rcode = nf90_inq_varid(ncidt, 'AIR', varidt)
     1350             IF (rcode.NE.NF_NOERR) THEN
     1351              print *,'Guide: probleme -> pas de variable AIR, fichier T.nc'
     1352              CALL abort_gcm(modname,abort_message,1)
     1353             ENDIF
    12721354             print*,'ncidT,varidT',ncidt,varidt
    12731355             if (ncidpl.eq.-99) ncidpl=ncidt
     
    12761358         if (guide_Q) then
    12771359             rcode = nf90_open('hur.nc', nf90_nowrite, ncidQ)
     1360             IF (rcode.NE.NF_NOERR) THEN
     1361              print *,'Guide: probleme -> pas de fichier hur.nc'
     1362              CALL abort_gcm(modname,abort_message,1)
     1363             ENDIF
    12781364             rcode = nf90_inq_varid(ncidQ, 'RH', varidQ)
     1365             IF (rcode.NE.NF_NOERR) THEN
     1366              print *,'Guide: probleme -> pas de variable RH, fichier hur.nc'
     1367              CALL abort_gcm(modname,abort_message,1)
     1368             ENDIF
    12791369             print*,'ncidQ,varidQ',ncidQ,varidQ
    12801370             if (ncidpl.eq.-99) ncidpl=ncidQ
     
    12831373         if ((guide_P).OR.(guide_plevs.EQ.1)) then
    12841374             rcode = nf90_open('ps.nc', nf90_nowrite, ncidps)
     1375             IF (rcode.NE.NF_NOERR) THEN
     1376              print *,'Guide: probleme -> pas de fichier ps.nc'
     1377              CALL abort_gcm(modname,abort_message,1)
     1378             ENDIF
    12851379             rcode = nf90_inq_varid(ncidps, 'SP', varidps)
     1380             IF (rcode.NE.NF_NOERR) THEN
     1381              print *,'Guide: probleme -> pas de variable SP, fichier ps.nc'
     1382              CALL abort_gcm(modname,abort_message,1)
     1383             ENDIF
    12861384             print*,'ncidps,varidps',ncidps,varidps
    12871385         endif
     
    14341532    INTEGER               :: i
    14351533
     1534    CHARACTER (len = 80)   :: abort_message
     1535    CHARACTER (len = 20)   :: modname = 'guide_read2D'
    14361536! -----------------------------------------------------------------
    14371537! Premier appel: initialisation de la lecture des fichiers
     
    14421542! Ap et Bp si niveaux de pression hybrides
    14431543         if (guide_plevs.EQ.1) then
    1444              print *,'Lecture du guidage sur niveaux modle'
     1544             print *,'Lecture du guidage sur niveaux mod�le'
    14451545             rcode = nf90_open('apbp.nc', nf90_nowrite, ncidpl)
     1546             IF (rcode.NE.NF_NOERR) THEN
     1547              print *,'Guide: probleme -> pas de fichier apbp.nc'
     1548              CALL abort_gcm(modname,abort_message,1)
     1549             ENDIF
    14461550             rcode = nf90_inq_varid(ncidpl, 'AP', varidap)
     1551             IF (rcode.NE.NF_NOERR) THEN
     1552              print *,'Guide: probleme -> pas de variable AP, fichier apbp.nc'
     1553              CALL abort_gcm(modname,abort_message,1)
     1554             ENDIF
    14471555             rcode = nf90_inq_varid(ncidpl, 'BP', varidbp)
     1556             IF (rcode.NE.NF_NOERR) THEN
     1557              print *,'Guide: probleme -> pas de variable BP, fichier apbp.nc'
     1558              CALL abort_gcm(modname,abort_message,1)
     1559             ENDIF
    14481560             print*,'ncidpl,varidap',ncidpl,varidap
    14491561         endif
     
    14511563         if (guide_plevs.EQ.2) then
    14521564             rcode = nf90_open('P.nc', nf90_nowrite, ncidp)
     1565             IF (rcode.NE.NF_NOERR) THEN
     1566              print *,'Guide: probleme -> pas de fichier P.nc'
     1567              CALL abort_gcm(modname,abort_message,1)
     1568             ENDIF
    14531569             rcode = nf90_inq_varid(ncidp, 'PRES', varidp)
     1570             IF (rcode.NE.NF_NOERR) THEN
     1571              print *,'Guide: probleme -> pas de variable PRES, fichier P.nc'
     1572              CALL abort_gcm(modname,abort_message,1)
     1573             ENDIF
    14541574             print*,'ncidp,varidp',ncidp,varidp
    14551575             if (ncidpl.eq.-99) ncidpl=ncidp
     
    14581578         if (guide_u) then
    14591579             rcode = nf90_open('u.nc', nf90_nowrite, ncidu)
     1580             IF (rcode.NE.NF_NOERR) THEN
     1581              print *,'Guide: probleme -> pas de fichier u.nc'
     1582              CALL abort_gcm(modname,abort_message,1)
     1583             ENDIF
    14601584             rcode = nf90_inq_varid(ncidu, 'UWND', varidu)
     1585             IF (rcode.NE.NF_NOERR) THEN
     1586              print *,'Guide: probleme -> pas de variable UWND, fichier u.nc'
     1587              CALL abort_gcm(modname,abort_message,1)
     1588             ENDIF
    14611589             print*,'ncidu,varidu',ncidu,varidu
    14621590             if (ncidpl.eq.-99) ncidpl=ncidu
     
    14651593         if (guide_v) then
    14661594             rcode = nf90_open('v.nc', nf90_nowrite, ncidv)
     1595             IF (rcode.NE.NF_NOERR) THEN
     1596              print *,'Guide: probleme -> pas de fichier v.nc'
     1597              CALL abort_gcm(modname,abort_message,1)
     1598             ENDIF
    14671599             rcode = nf90_inq_varid(ncidv, 'VWND', varidv)
     1600             IF (rcode.NE.NF_NOERR) THEN
     1601              print *,'Guide: probleme -> pas de variable VWND, fichier v.nc'
     1602              CALL abort_gcm(modname,abort_message,1)
     1603             ENDIF
    14681604             print*,'ncidv,varidv',ncidv,varidv
    14691605             if (ncidpl.eq.-99) ncidpl=ncidv
     
    14721608         if (guide_T) then
    14731609             rcode = nf90_open('T.nc', nf90_nowrite, ncidt)
     1610             IF (rcode.NE.NF_NOERR) THEN
     1611              print *,'Guide: probleme -> pas de fichier T.nc'
     1612              CALL abort_gcm(modname,abort_message,1)
     1613             ENDIF
    14741614             rcode = nf90_inq_varid(ncidt, 'AIR', varidt)
     1615             IF (rcode.NE.NF_NOERR) THEN
     1616              print *,'Guide: probleme -> pas de variable AIR, fichier T.nc'
     1617              CALL abort_gcm(modname,abort_message,1)
     1618             ENDIF
    14751619             print*,'ncidT,varidT',ncidt,varidt
    14761620             if (ncidpl.eq.-99) ncidpl=ncidt
     
    14791623         if (guide_Q) then
    14801624             rcode = nf90_open('hur.nc', nf90_nowrite, ncidQ)
     1625             IF (rcode.NE.NF_NOERR) THEN
     1626              print *,'Guide: probleme -> pas de fichier hur.nc'
     1627              CALL abort_gcm(modname,abort_message,1)
     1628             ENDIF
    14811629             rcode = nf90_inq_varid(ncidQ, 'RH', varidQ)
     1630             IF (rcode.NE.NF_NOERR) THEN
     1631              print *,'Guide: probleme -> pas de variable RH, fichier hur.nc'
     1632              CALL abort_gcm(modname,abort_message,1)
     1633             ENDIF
    14821634             print*,'ncidQ,varidQ',ncidQ,varidQ
    14831635             if (ncidpl.eq.-99) ncidpl=ncidQ
     
    14861638         if ((guide_P).OR.(guide_plevs.EQ.1)) then
    14871639             rcode = nf90_open('ps.nc', nf90_nowrite, ncidps)
     1640             IF (rcode.NE.NF_NOERR) THEN
     1641              print *,'Guide: probleme -> pas de fichier ps.nc'
     1642              CALL abort_gcm(modname,abort_message,1)
     1643             ENDIF
    14881644             rcode = nf90_inq_varid(ncidps, 'SP', varidps)
     1645             IF (rcode.NE.NF_NOERR) THEN
     1646              print *,'Guide: probleme -> pas de variable SP, fichier ps.nc'
     1647              CALL abort_gcm(modname,abort_message,1)
     1648             ENDIF
    14891649             print*,'ncidps,varidps',ncidps,varidps
    14901650         endif
     
    17101870#endif
    17111871! --------------------------------------------------------------------
    1712 ! Cr�ation des variables sauvegard�es
     1872! Cr�ation des variables sauvegard�es
    17131873! --------------------------------------------------------------------
    17141874        ierr = NF_REDEF(nid)
     
    18361996!===========================================================================
    18371997END MODULE guide_p_mod
     1998
  • trunk/LMDZ.COMMON/libf/dyn3dpar/leapfrog_p.F

    r1190 r1300  
    2929       use sponge_mod_p, only: callsponge,mode_sponge,sponge_p
    3030       use comuforc_h
    31 
    32 #ifdef CPP_XIOS
    33     ! ug Pour les sorties XIOS
    34         USE wxios
    35 #endif
    3631
    3732      IMPLICIT NONE
     
    15451540c$OMP BARRIER
    15461541        RETURN
    1547       ENDIF
     1542      ENDIF ! of IF (itau==itaumax)
    15481543     
    15491544      IF ( .NOT.purmats ) THEN
     
    15791574
    15801575c$OMP MASTER
    1581 
    1582 #ifdef CPP_XIOS
    1583     !Fermeture propre de XIOS
    1584       CALL wxios_close()
    1585 #endif
    15861576              call fin_getparam
    15871577              call finalize_parallel
     
    16041594#ifdef CPP_IOIPSL
    16051595             IF (ok_dynzon) THEN
    1606              call Register_Hallo(vcov,ip1jm,llm,1,0,0,1,TestRequest)
    1607              call SendRequest(TestRequest)
    1608 c$OMP BARRIER
    1609               call WaitRequest(TestRequest)
    1610 c$OMP BARRIER
    1611 c$OMP MASTER
    1612 !              CALL writedynav_p(histaveid, itau,vcov ,
    1613 !     ,                          ucov,teta,pk,phi,q,masse,ps,phis)
    1614 
    1615 c ATTENTION!!! bilan_dyn_p ne marche probablement pas avec OpenMP
    1616 !              CALL bilan_dyn_p(2,dtvr*iperiod,dtvr*day_step*periodav,
    1617 !     ,             ps,masse,pk,pbaru,pbarv,teta,phi,ucov,vcov,q)
     1596              CALL bilan_dyn_p(2,dtvr*iperiod,dtvr*day_step*periodav,
     1597     ,             ps,masse,pk,pbaru,pbarv,teta,phi,ucov,vcov,q)
    16181598c les traceurs ne sont pas sortis, trop lourd.
    16191599c Peut changer eventuellement si besoin.
    1620                  CALL bilan_dyn_p(dtvr*iperiod,dtvr*day_step*periodav,
    1621      &                 ps,masse,pk,pbaru,pbarv,teta,phi,ucov,vcov,
    1622      &                 du,dudis,dutop,dufi)
    1623 c$OMP END MASTER
     1600!                 CALL bilan_dyn_p(dtvr*iperiod,dtvr*day_step*periodav,
     1601!     &                 ps,masse,pk,pbaru,pbarv,teta,phi,ucov,vcov,
     1602!     &                 du,dudis,dutop,dufi)
    16241603              ENDIF !ok_dynzon
    16251604#endif
     
    18281807#ifdef CPP_IOIPSL
    18291808               IF (ok_dynzon) THEN
    1830 c$OMP BARRIER
    1831                call Register_Hallo(vcov,ip1jm,llm,1,0,0,1,TestRequest)
    1832                call SendRequest(TestRequest)
    1833 c$OMP BARRIER
    1834                call WaitRequest(TestRequest)
    1835 c$OMP BARRIER
    1836 c$OMP MASTER
    1837 !               CALL writedynav_p(histaveid, itau,vcov ,
    1838 !     ,                          ucov,teta,pk,phi,q,masse,ps,phis)
    1839 !               CALL bilan_dyn_p(2,dtvr*iperiod,dtvr*day_step*periodav,
    1840 !     ,           ps,masse,pk,pbaru,pbarv,teta,phi,ucov,vcov,q)
     1809               CALL bilan_dyn_p(2,dtvr*iperiod,dtvr*day_step*periodav,
     1810     ,           ps,masse,pk,pbaru,pbarv,teta,phi,ucov,vcov,q)
    18411811c les traceurs ne sont pas sortis, trop lourd.
    18421812c Peut changer eventuellement si besoin.
    1843                  CALL bilan_dyn_p(dtvr*iperiod,dtvr*day_step*periodav,
    1844      &                 ps,masse,pk,pbaru,pbarv,teta,phi,ucov,vcov,
    1845      &                 du,dudis,dutop,dufi)
    1846 
    1847 c$OMP END MASTER
     1813!                 CALL bilan_dyn_p(dtvr*iperiod,dtvr*day_step*periodav,
     1814!     &                 ps,masse,pk,pbaru,pbarv,teta,phi,ucov,vcov,
     1815!     &                 du,dudis,dutop,dufi)
    18481816               END IF !ok_dynzon
    18491817#endif
  • trunk/LMDZ.COMMON/libf/dyn3dpar/mod_const_mpi.F90

    r979 r1300  
    33!
    44MODULE mod_const_mpi
    5 
     5  IMPLICIT NONE
    66  INTEGER,SAVE :: COMM_LMDZ
    77  INTEGER,SAVE :: MPI_REAL_LMDZ
     
    1212  SUBROUTINE Init_const_mpi
    1313#ifdef CPP_IOIPSL
    14     USE IOIPSL
     14    USE IOIPSL, ONLY: getin
    1515#else
    1616! if not using IOIPSL, we still need to use (a local version of) getin
    17     USE ioipsl_getincom
     17    USE ioipsl_getincom, only: getin
    1818#endif
    1919
     
    2222    INCLUDE 'mpif.h'
    2323#endif
     24
    2425    INTEGER             :: ierr
    2526    INTEGER             :: comp_id
     
    5152 
    5253  SUBROUTINE Init_mpi
     54#ifdef CPP_XIOS
     55    USE wxios, only: wxios_init
     56#endif
    5357  IMPLICIT NONE
    5458#ifdef CPP_MPI
     
    7074      COMM_LMDZ=MPI_COMM_WORLD
    7175      MPI_REAL_LMDZ=MPI_REAL8
     76!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     77! Initialisation de XIOS
     78!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     79#ifdef CPP_XIOS
     80      CALL wxios_init("LMDZ", outcom=COMM_LMDZ)
     81#endif
    7282!$OMP END MASTER
     83#else
     84#ifdef CPP_XIOS
     85!$OMP MASTER
     86      CALL wxios_init("LMDZ")
     87!$OMP END MASTER
     88#endif
    7389#endif
    7490
     
    7692   
    7793END MODULE mod_const_mpi
     94
  • trunk/LMDZ.COMMON/libf/dyn3dpar/parallel_lmdz.F90

    r1019 r1300  
    44  module parallel_lmdz
    55  USE mod_const_mpi
     6#ifdef CPP_IOIPSL
     7      use IOIPSL, only: getin
     8#else
     9! if not using IOIPSL, we still need to use (a local version of) getin
     10      use ioipsl_getincom, only: getin
     11#endif   
    612   
    713    LOGICAL,SAVE :: using_mpi=.TRUE.
     
    155161        omp_size=OMP_GET_NUM_THREADS()
    156162!$OMP END MASTER
     163!$OMP BARRIER
    157164        omp_rank=OMP_GET_THREAD_NUM()   
     165
     166!Config  Key  = omp_chunk
     167!Config  Desc = taille des blocs openmp
     168!Config  Def  = 1
     169!Config  Help = defini la taille des packets d'it�ration openmp
     170!Config         distribue a chaque tache lors de l'entree dans une
     171!Config         boucle parallelisee
     172
     173!$OMP MASTER
     174      omp_chunk=(llm+1)/omp_size
     175      IF (MOD(llm+1,omp_size)/=0) omp_chunk=omp_chunk+1
     176      CALL getin('omp_chunk',omp_chunk)
     177!$OMP END MASTER
     178!$OMP BARRIER       
    158179#else   
    159180        omp_size=1
     
    199220   
    200221    subroutine Finalize_parallel
     222#ifdef CPP_XIOS
     223    ! ug Pour les sorties XIOS
     224        USE wxios
     225#endif
    201226#ifdef CPP_COUPLE
    202227    use mod_prism_proto
     
    234259#endif
    235260      else
     261#ifdef CPP_XIOS
     262    !Fermeture propre de XIOS
     263      CALL wxios_close()
     264#endif
    236265#ifdef CPP_MPI
    237266         IF (using_mpi) call MPI_FINALIZE(ierr)
Note: See TracChangeset for help on using the changeset viewer.