Ignore:
Timestamp:
Aug 23, 2013, 2:20:58 PM (11 years ago)
Author:
yann meurdesoif
Message:

Solve performance problem comming from declarations of a derived type.

YM

Location:
LMDZ5/trunk/libf/dyn3dmem
Files:
12 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/dyn3dmem/advtrac_loc.F

    r1823 r1848  
    7979      DATA dum/.true./
    8080      integer ijb,ije,ijbu,ijbv,ijeu,ijev,j
    81       type(Request) :: testRequest
     81      type(Request),SAVE :: testRequest
     82!$OMP THREADPRIVATE(testRequest)
    8283
    8384c  test sur l'eventuelle creation de valeurs negatives de la masse
  • LMDZ5/trunk/libf/dyn3dmem/bilan_dyn_loc.F

    r1823 r1848  
    157157      real,SAVE,ALLOCATABLE :: rlong(:),rlatg(:)
    158158      integer :: jjb,jje,jjn,ijb,ije
    159       type(Request) :: Req
     159      type(Request),SAVE :: Req
     160!$OMP THREADPRIVATE(Req)
    160161
    161162! definition du domaine d'ecriture pour le rebuild
  • LMDZ5/trunk/libf/dyn3dmem/caladvtrac_loc.F

    r1823 r1848  
    5353      INTEGER ::  ijb,ije,ijbu,ijbv,ijeu,ijev,j
    5454      INTEGER :: ij,l
    55       TYPE(Request) :: Request_vanleer
    56 
     55      TYPE(Request),SAVE :: Request_vanleer
     56!$OMP THREADPRIVATE(Request_vanleer)
    5757
    5858           
  • LMDZ5/trunk/libf/dyn3dmem/call_calfis_mod.F90

    r1823 r1848  
    111111    REAL :: jD_cur, jH_cur
    112112    CHARACTER(LEN=15) :: ztit
    113     TYPE(Request) :: Request_physic
     113    TYPE(Request),SAVE :: Request_physic
     114!$OMP THREADPRIVATE(Request_physic )
    114115    INTEGER :: ijb,ije,l,j
    115116   
  • LMDZ5/trunk/libf/dyn3dmem/call_dissip_mod.F90

    r1823 r1848  
    9898    REAL  SSUM
    9999    LOGICAL,PARAMETER :: dissip_conservative=.TRUE.
    100     TYPE(Request) :: Request_dissip
    101    
     100    TYPE(Request),SAVE :: Request_dissip
     101!$OMP THREADPRIVATE(Request_dissip )   
    102102    INTEGER :: ij,l,ijb,ije
    103103 
  • LMDZ5/trunk/libf/dyn3dmem/divgrad2_loc.F

    r1823 r1848  
    3131      INTEGER  l,ij,iter,lh
    3232c    ...................................................................
    33       Type(Request) :: request_dissip
     33      Type(Request),SAVE :: request_dissip
     34!$OMP THREADPRIVATE(request_dissip)
    3435      INTEGER ijb,ije
    3536
  • LMDZ5/trunk/libf/dyn3dmem/gradiv2_loc.F

    r1823 r1848  
    3838      INTEGER l,ij,iter,ld
    3939      INTEGER :: ijb,ije,jjb,jje
    40       Type(Request)  :: request_dissip
    41      
     40      Type(Request),SAVE  :: request_dissip
     41!$OMP THREADPRIVATE(request_dissip)     
    4242c    ........................................................
    4343c
  • LMDZ5/trunk/libf/dyn3dmem/guide_loc_mod.F90

    r1823 r1848  
    894894 
    895895  INTEGER                            :: i,j,l,ij
    896   TYPE(Request) :: Req 
    897 
     896  TYPE(Request),SAVE :: Req 
     897!$OMP THREADPRIVATE(Req)
    898898    print *,'Guide: conversion variables guidage'
    899899! -----------------------------------------------------------------
  • LMDZ5/trunk/libf/dyn3dmem/leapfrog_loc.F

    r1823 r1848  
    449449      IF (ok_start_timer) THEN
    450450        CALL InitTime
    451 !        ok_start_timer=.FALSE.
    452         ok_start_timer=.TRUE.
     451        ok_start_timer=.FALSE.
    453452      ENDIF     
    454453c$OMP END MASTER     
     
    624623      True_itau=True_itau+1
    625624
    626 c$OMP MASTER     
    627       PRINT *,"---> itau=",itau,"  True_itau=",True_itau
    628 c$OMP END MASTER
    629 
    630625c$OMP MASTER
    631626      IF (prt_level>9) THEN
     
    10861081
    10871082      IF(iflag_phys.EQ.2) THEN ! "Newtonian" case
     1083c$OMP MASTER
     1084         if (FirstPhysic) then
     1085           ok_start_timer=.TRUE.
     1086           FirstPhysic=.false.
     1087         endif
     1088c$OMP END MASTER
     1089
     1090
    10881091c   Calcul academique de la physique = Rappel Newtonien + fritcion
    10891092c   --------------------------------------------------------------
     
    13881391c$OMP MASTER
    13891392            call allgather_timer_average
    1390 
     1393      call barrier
    13911394      if (mpi_rank==0) then
    13921395       
     
    14241427       
    14251428      endif 
    1426      
     1429      CALL barrier
    14271430      print *,'Taille du Buffer MPI (REAL*8)',MaxBufferSize
    14281431      print *,'Taille du Buffer MPI utilise (REAL*8)',MaxBufferSize_Used
  • LMDZ5/trunk/libf/dyn3dmem/nxgraro2_loc.F

    r1823 r1848  
    3434      REAL  signe, nugradrs
    3535      INTEGER l,ij,iter,lr
    36       Type(Request) :: Request_dissip
     36      Type(Request),SAVE :: Request_dissip
     37!$OMP THREADPRIVATE(Request_dissip)
    3738c    ........................................................
    3839c
  • LMDZ5/trunk/libf/dyn3dmem/vlspltgen_loc.F

    r1823 r1848  
    6767      LOGICAL, SAVE :: firstcall=.TRUE.
    6868!$OMP THREADPRIVATE(firstcall)
    69       type(request) :: MyRequest1
    70       type(request) :: MyRequest2
    71 
     69      type(request),SAVE :: MyRequest1
     70!$OMP THREADPRIVATE(MyRequest1)
     71      type(request),SAVE :: MyRequest2
     72!$OMP THREADPRIVATE(MyRequest2)
    7273c    fonction psat(T)
    7374
  • LMDZ5/trunk/libf/dyn3dmem/write_field_loc.F90

    r1823 r1848  
    4545    real, allocatable,SAVE :: New_Field(:,:,:)
    4646    integer,dimension(0:mpi_size-1) :: jj_nb_master
    47     type(Request) :: Request_write
     47    type(Request),SAVE :: Request_write
     48!$OMP THREADPRIVATE(Request_write)
    4849    integer :: ll,i
    4950   
     
    6162      New_Field(:,jj_begin:jj_end,i)=reshape(Field(ij_begin:ij_end,i),(/iip1,jj_nb/))
    6263    ENDDO
    63    
     64!$OMP BARRIER   
    6465    call Register_SwapField(new_field,new_field,ip1jmp1,ll,jj_Nb_master,Request_write)
    6566    call SendRequest(Request_write)
     
    109110    real, allocatable,SAVE :: New_Field(:,:,:)
    110111    integer,dimension(0:mpi_size-1) :: jj_nb_master
    111     type(Request) :: Request_write
     112    type(Request),SAVE :: Request_write
     113!$OMP THREADPRIVATE(Request_write)   
    112114    integer :: ll,i,jje,ije,jjn
    113115   
     
    136138      New_Field(:,jj_begin:jje,i)=reshape(Field(ij_begin:ije,i),(/iip1,jjn/))
    137139    ENDDO
    138    
     140!$OMP BARRIER   
    139141    call Register_SwapField(new_field,new_field,ip1jm,ll,jj_Nb_master,Request_write)
    140142    call SendRequest(Request_write)
Note: See TracChangeset for help on using the changeset viewer.