Ignore:
Timestamp:
08/06/15 10:48:45 (9 years ago)
Author:
dubos
Message:

OpenMP fixes for DCMIP

File:
1 edited

Legend:

Unmodified
Added
Removed
  • codes/icosagcm/trunk/src/etat0_dcmip2.f90

    r344 r353  
    11MODULE etat0_dcmip2_mod 
    2  
    32! test cases DCMIP 2012, category 2 : Orographic gravity waves 
    4  
    53  USE icosa 
     4  IMPLICIT NONE 
    65  PRIVATE 
    76 
     
    3332  SUBROUTINE compute_etat0(ngrid,lon,lat, phis, ps, Temp, ulon, ulat) 
    3433    USE disvert_mod 
    35     IMPLICIT NONE 
     34    USE omp_para 
    3635    INTEGER, INTENT(IN)    :: ngrid 
    3736    REAL(rstd),INTENT(IN)  :: lon(ngrid) 
     
    4645 
    4746    ! Hexagons : ps,phis,temp 
    48     DO l=1,llm 
     47    DO l=ll_begin,ll_end 
    4948       ! The surface pressure is not set yet so we provide the hybrid coefficients 
    5049       hyam = .5*(ap(l)+ap(l+1))/preff 
Note: See TracChangeset for help on using the changeset viewer.