Ignore:
Timestamp:
Jul 22, 2016, 8:44:47 AM (8 years ago)
Author:
Ehouarn Millour
Message:

Cleanup in the dynamics: get rid of comconst.h, make it a module comconst_mod.
EM

File:
1 edited

Legend:

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

    r2286 r2597  
    3131     &    ok_iso_verif
    3232      USE vlspltgen_mod
     33      USE comconst_mod, ONLY: cpp
    3334      IMPLICIT NONE
    3435
    3536c
    36 #include "dimensions.h"
    37 #include "paramet.h"
    38 #include "logic.h"
    39 #include "comvert.h"
    40 #include "comconst.h"
     37      include "dimensions.h"
     38      include "paramet.h"
     39      include "logic.h"
     40      include "comvert.h"
    4141
    4242c
     
    100100
    101101       
    102         ijb=ij_begin-iip1
    103         ije=ij_end+iip1
    104         if (pole_nord) ijb=ij_begin
    105         if (pole_sud) ije=ij_end
    106        
     102        ijb=ij_begin-iip1
     103        ije=ij_end+iip1
     104        if (pole_nord) ijb=ij_begin
     105        if (pole_sud) ije=ij_end
     106       
    107107c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
    108         DO l = 1, llm
     108        DO l = 1, llm
    109109         DO ij = ijb, ije
    110110          tempe(ij) = teta(ij,l) * pk(ij,l) /cpp
     
    208208#endif
    209209        if(iadv(iq) == 0) then
    210        
    211           cycle
    212        
    213         else if (iadv(iq)==10) then
     210       
     211          cycle
     212       
     213        else if (iadv(iq)==10) then
    214214
    215215#ifdef _ADV_HALO       
    216216! CRisi: on ajoute les nombres de fils et tableaux des fils
    217217! On suppose qu'on ne peut advecter les fils que par le schéma 10. 
    218           call vlx_loc(zq,pente_max,zm,mu,
    219      &               ij_begin,ij_begin+2*iip1-1,iq)
     218          call vlx_loc(zq,pente_max,zm,mu,
     219     &                     ij_begin,ij_begin+2*iip1-1,iq)
    220220          call vlx_loc(zq,pente_max,zm,mu,
    221221     &               ij_end-2*iip1+1,ij_end,iq)
    222222#else
    223           call vlx_loc(zq,pente_max,zm,mu,
    224      &               ij_begin,ij_end,iq)
     223          call vlx_loc(zq,pente_max,zm,mu,
     224     &                     ij_begin,ij_end,iq)
    225225#endif
    226226
     
    240240          call VTe(VTHallo)
    241241c$OMP END MASTER
    242         else if (iadv(iq)==14) then
     242        else if (iadv(iq)==14) then
    243243
    244244#ifdef _ADV_HALO           
     
    268268c$OMP END MASTER
    269269        else
    270        
    271           stop 'vlspltgen_p : schema non parallelise'
     270       
     271          stop 'vlspltgen_p : schema non parallelise'
    272272     
    273273        endif
     
    301301
    302302        if(iadv(iq) == 0) then
    303        
    304           cycle
    305        
    306         else if (iadv(iq)==10) then
     303       
     304          cycle
     305       
     306        else if (iadv(iq)==10) then
    307307
    308308#ifdef _ADV_HALLO
     
    310310     &                 ij_begin+2*iip1,ij_end-2*iip1,iq)
    311311#endif       
    312         else if (iadv(iq)==14) then
     312        else if (iadv(iq)==14) then
    313313#ifdef _ADV_HALLO
    314314          call vlxqs_loc(zq,pente_max,zm,mu,
     
    316316#endif   
    317317        else
    318        
    319           stop 'vlspltgen_p : schema non parallelise'
     318       
     319          stop 'vlspltgen_p : schema non parallelise'
    320320     
    321321        endif
     
    358358
    359359        if(iadv(iq) == 0) then
    360        
    361           cycle
    362        
    363         else if (iadv(iq)==10) then
     360       
     361          cycle
     362       
     363        else if (iadv(iq)==10) then
    364364       
    365365          call vly_loc(zq,pente_max,zm,mv,iq)
    366366 
    367         else if (iadv(iq)==14) then
     367        else if (iadv(iq)==14) then
    368368     
    369369          call vlyqs_loc(zq,pente_max,zm,mv,
     
    371371 
    372372        else
    373        
    374           stop 'vlspltgen_p : schema non parallelise'
     373       
     374          stop 'vlspltgen_p : schema non parallelise'
    375375     
    376376        endif
     
    389389#endif
    390390        if(iadv(iq) == 0) then
    391          
    392           cycle
    393        
    394         else if (iadv(iq)==10 .or. iadv(iq)==14 ) then
     391         
     392          cycle
     393       
     394        else if (iadv(iq)==10 .or. iadv(iq)==14 ) then
    395395
    396396c$OMP BARRIER       
     
    420420c$OMP MASTER
    421421          call VTe(VTHallo)
    422 c$OMP END MASTER       
     422c$OMP END MASTER       
    423423c$OMP BARRIER
    424424        else
    425        
    426           stop 'vlspltgen_p : schema non parallelise'
     425       
     426          stop 'vlspltgen_p : schema non parallelise'
    427427     
    428428        endif
     
    439439c$OMP MASTER
    440440      call VTe(VTHallo)
    441 c$OMP END MASTER       
     441c$OMP END MASTER       
    442442
    443443
     
    451451
    452452        if(iadv(iq) == 0) then
    453          
    454           cycle
    455        
    456         else if (iadv(iq)==10 .or. iadv(iq)==14 ) then
     453         
     454          cycle
     455       
     456        else if (iadv(iq)==10 .or. iadv(iq)==14 ) then
    457457c$OMP BARRIER       
    458458
     
    464464c$OMP BARRIER       
    465465        else
    466        
    467           stop 'vlspltgen_p : schema non parallelise'
     466       
     467          stop 'vlspltgen_p : schema non parallelise'
    468468     
    469469        endif
     
    501501#endif
    502502        if(iadv(iq) == 0) then
    503        
    504           cycle
    505        
    506         else if (iadv(iq)==10) then
     503       
     504          cycle
     505       
     506        else if (iadv(iq)==10) then
    507507       
    508508          call vly_loc(zq,pente_max,zm,mv,iq)
    509509 
    510         else if (iadv(iq)==14) then
     510        else if (iadv(iq)==14) then
    511511     
    512512          call vlyqs_loc(zq,pente_max,zm,mv,
     
    514514 
    515515        else
    516        
    517           stop 'vlspltgen_p : schema non parallelise'
     516       
     517          stop 'vlspltgen_p : schema non parallelise'
    518518     
    519519        endif
     
    532532#endif
    533533        if(iadv(iq) == 0) then
    534          
    535           cycle
    536        
    537         else if (iadv(iq)==10) then
     534         
     535          cycle
     536       
     537        else if (iadv(iq)==10) then
    538538       
    539539          call vlx_loc(zq,pente_max,zm,mu,
    540540     &               ij_begin,ij_end,iq)
    541541 
    542         else if (iadv(iq)==14) then
     542        else if (iadv(iq)==14) then
    543543     
    544544          call vlxqs_loc(zq,pente_max,zm,mu,
     
    546546 
    547547        else
    548        
     548       
    549549          stop 'vlspltgen_p : schema non parallelise'
    550550     
     
    574574           DO ij=ijb,ije
    575575c             print *,'zq-->',ij,l,iq,zq(ij,l,iq)
    576 c            print *,'q-->',ij,l,iq,q(ij,l,iq)
    577              q(ij,l,iq)=zq(ij,l,iq)
     576c             print *,'q-->',ij,l,iq,q(ij,l,iq)
     577             q(ij,l,iq)=zq(ij,l,iq)
    578578           ENDDO
    579579        ENDDO
Note: See TracChangeset for help on using the changeset viewer.