Ignore:
Timestamp:
May 2, 2013, 10:33:18 AM (12 years ago)
Author:
slebonnois
Message:

SL: optimisation pour le parallèle suite à tests Venus / petite correction appels routines secondaires dans Venus et Titan

Location:
trunk/LMDZ.COMMON/libf/dyn3dpar
Files:
1 deleted
3 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.COMMON/libf/dyn3dpar/advtrac_p.F90

    r270 r953  
    111111  !$OMP END DO NOWAIT
    112112
    113   !   selection de la masse instantannee des mailles avant le transport.
     113  !   selection de la masse instantanee des mailles avant le transport.
    114114  IF(iadvtr.EQ.0) THEN
    115115
     
    206206     !$OMP BARRIER
    207207
    208      ! ... Flux de masse diaganostiques traceurs
     208     ! ... Flux de masse diagnostiques traceurs
    209209     ijb=ij_begin
    210210     ije=ij_end
     
    266266
    267267
    268      GOTO 1234     
     268!!! ATTENTION !!!! TOUT CE QUI EST ENTRE ICI ET 1234 EST OBSOLETE !!!!!!!
     269     GOTO 1234
     270!!! ATTENTION !!!!
     271
    269272     !-----------------------------------------------------------
    270273     !     Appel des sous programmes d'advection
     
    443446     end DO
    444447
     448!!! ATTENTION !!!!
    4454491234 CONTINUE
     450!!! ATTENTION !!!! LE CODE REPREND ICI !!!!!!!!
     451
    446452     !$OMP BARRIER
    447453
     
    461467        CALL qminimum_p( q, 2, finmasse )
    462468
     469     endif ! of if (planet_type=="earth")
     470
    463471        !------------------------------------------------------------------
    464472        !   on reinitialise a zero les flux de masse cumules
     
    471479        call VTb(VThallo)
    472480        !$OMP END MASTER
     481
    473482
    474483        do j=1,nqtot
     
    492501 !$OMP BARRIER 
    493502        iadvtr=0
    494      endif ! of if (planet_type=="earth")
    495503  ENDIF ! if iadvtr.EQ.iapp_tracvl
    496504
  • trunk/LMDZ.COMMON/libf/dyn3dpar/cpdet.F

    r847 r953  
    9393c======================================================================
    9494
    95       SUBROUTINE t2tpot_p(ip1jmp1,llm, yt, yteta, ypk)
     95      SUBROUTINE t2tpot_p(nlon,nlev, yt, yteta, ypk)
    9696! Parallel version of t2tpot
    9797      USE parallel
     
    102102#include "comconst.h"
    103103
    104       integer,intent(in) :: ip1jmp1,llm
    105       real,intent(in) :: yt(ip1jmp1,llm)
    106       real,intent(out) :: yteta(ip1jmp1,llm)
    107       real,intent(in) :: ypk(ip1jmp1,llm)
     104      integer,intent(in) :: nlon,nlev
     105      real,intent(in) :: yt(nlon,nlev)
     106      real,intent(out) :: yteta(nlon,nlev)
     107      real,intent(in) :: ypk(nlon,nlev)
    108108! local variable:
    109       integer :: ij,l,ijb,ije
     109      integer :: l
    110110     
    111       !ijb=ij_begin
    112       !ije=ij_end
    113       ijb=1
    114       ije=ip1jmp1
    115      
    116111      if (planet_type.eq."venus") then
    117 !$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
    118         do l=1,llm
    119           yteta(ijb:ije,l)=yt(ijb:ije,l)**nu_venus                      &
     112        do l=1,nlev
     113          yteta(:,l)=yt(:,l)**nu_venus                                  &
    120114     &                     -nu_venus*t0_venus**nu_venus*                &
    121      &                          log(ypk(ijb:ije,l)/cpp)
    122           yteta(ijb:ije,l)=yteta(ijb:ije,l)**(1./nu_venus)
     115     &                          log(ypk(:,l)/cpp)
     116          yteta(:,l)=yteta(:,l)**(1./nu_venus)
    123117        enddo
    124 !$OMP END DO
    125118      else
    126 !$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
    127         do l=1,llm
    128           yteta(ijb:ije,l)=yt(ijb:ije,l)*cpp/ypk(ijb:ije,l)
     119        do l=1,nlev
     120          yteta(:,l)=yt(:,l)*cpp/ypk(:,l)
    129121        enddo
    130 !$OMP END DO
    131122      endif ! of if (planet_type.eq."venus")
    132123
     
    167158c======================================================================
    168159c======================================================================
    169       SUBROUTINE tpot2t_p(ip1jmp1,llm,yteta,yt,ypk)
     160      SUBROUTINE tpot2t_p(nlon,nlev,yteta,yt,ypk)
    170161! Parallel version of tpot2t
    171162      USE parallel
     
    175166#include "comconst.h"
    176167
    177       integer,intent(in) :: ip1jmp1,llm
    178       real,intent(out) :: yt(ip1jmp1,llm)
    179       real,intent(in) :: yteta(ip1jmp1,llm)
    180       real,intent(in) :: ypk(ip1jmp1,llm)
     168      integer,intent(in) :: nlon,nlev
     169      real,intent(out) :: yt(nlon,nlev)
     170      real,intent(in) :: yteta(nlon,nlev)
     171      real,intent(in) :: ypk(nlon,nlev)
    181172
    182173! local variable:
    183       integer :: ij,l,ijb,ije
    184 
    185       !ijb=ij_begin
    186       !ije=ij_end
    187       ijb=1
    188       ije=ip1jmp1
     174      integer :: l
    189175
    190176      if (planet_type.eq."venus") then
    191 !$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
    192         do l=1,llm
    193           yt(ijb:ije,l)=yteta(ijb:ije,l)**nu_venus                      &
     177        do l=1,nlev
     178          yt(:,l)=yteta(:,l)**nu_venus                                  &
    194179     &                  +nu_venus*t0_venus**nu_venus*                   &
    195      &                       log(ypk(ijb:ije,l)/cpp)
    196           yt(ijb:ije,l)=yt(ijb:ije,l)**(1./nu_venus)
     180     &                       log(ypk(:,l)/cpp)
     181          yt(:,l)=yt(:,l)**(1./nu_venus)
    197182        enddo
    198 !$OMP END DO
    199183      else
    200 !$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
    201         do l=1,llm
    202           yt(ijb:ije,l)=yteta(ijb:ije,l)*ypk(ijb:ije,l)/cpp
     184        do l=1,nlev
     185          yt(:,l)=yteta(:,l)*ypk(:,l)/cpp
    203186        enddo
    204 !$OMP END DO
    205187      endif ! of if (planet_type.eq."venus")
    206188      END
  • trunk/LMDZ.COMMON/libf/dyn3dpar/leapfrog_p.F

    r847 r953  
    271271        dqfi(:,:,:) =0.
    272272        dpfi(:)     =0.
    273       dq(:,:,:)=0.
     273        dq(:,:,:)   =0.
    274274
    275275      CALL pression ( ip1jmp1, ap, bp, ps, p       )
     
    549549c   --------------------------------
    550550! ADAPTATION GCM POUR CP(T)
    551       call tpot2t_p(ip1jmp1,llm,teta,temp,pk)
    552551      ijb=ij_begin
    553552      ije=ij_end
     553      call tpot2t_p(ije-ijb+1,llm,teta(ijb:ije,:),temp(ijb:ije,:),
     554     &                            pk(ijb:ije,:))
    554555!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
    555556      do l=1,llm
     
    682683cc$OMP PARALLEL DEFAULT(SHARED)
    683684c
    684          CALL caladvtrac_p(q,pbaru,pbarv,
    685      *        p, masse, dq, teta,
    686      .        flxw,pk, iapptrac)
     685         CALL advtrac_p( pbaru,pbarv,
     686     *             p,  masse,q,iapptrac, teta,
     687     .             flxw, pk)
    687688
    688689C        Stokage du flux de masse pour traceurs OFF-LINE
     
    12181219c   dissipation
    12191220! ADAPTATION GCM POUR CP(T)
    1220         call tpot2t_p(ip1jmp1,llm,teta,temp,pk)
     1221            ijb=ij_begin
     1222            ije=ij_end
     1223        call tpot2t_p(ije-ijb+1,llm,teta(ijb:ije,:),temp(ijb:ije,:),
     1224     &                            pk(ijb:ije,:))
    12211225
    12221226!        CALL FTRACE_REGION_BEGIN("dissip")
     
    12751279              enddo
    12761280            enddo
    1277 c$OMP END DO
    1278             call t2tpot_p(ip1jmp1,llm,temp,ztetaec,pk)
     1281c$OMP END DO
     1282        call t2tpot_p(ije-ijb+1,llm,temp(ijb:ije,:),ztetaec(ijb:ije,:),
     1283     &                            pk(ijb:ije,:))
    12791284c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)           
    12801285            do l=1,llm
     
    15851590
    15861591! ADAPTATION GCM POUR CP(T)
    1587       call tpot2t_p(ip1jmp1,llm,teta,temp,pk)
    15881592      ijb=ij_begin
    15891593      ije=ij_end
     1594      call tpot2t_p(ije-ijb+1,llm,teta(ijb:ije,:),temp(ijb:ije,:),
     1595     &                            pk(ijb:ije,:))
    15901596!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
    15911597      do l=1,llm
     
    18091815
    18101816! ADAPTATION GCM POUR CP(T)
    1811                 call tpot2t_p(ip1jmp1,llm,teta,temp,pk)
    18121817                ijb=ij_begin
    18131818                ije=ij_end
     1819           call tpot2t_p(ije-ijb+1,llm,teta(ijb:ije,:),temp(ijb:ije,:),
     1820     &                            pk(ijb:ije,:))
    18141821!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
    18151822                do l=1,llm     
Note: See TracChangeset for help on using the changeset viewer.