Changeset 558


Ignore:
Timestamp:
09/21/17 18:18:47 (7 years ago)
Author:
dubos
Message:

devel : Fix OpenMP for NH

Location:
codes/icosagcm/devel/src/dynamics
Files:
4 edited

Legend:

Unmodified
Added
Removed
  • codes/icosagcm/devel/src/dynamics/caldyn_gcm.F90

    r557 r558  
    2222    REAL(rstd),POINTER :: planetvel(:) 
    2323 
    24     #ifdef CPP_DYSL 
     24#ifdef CPP_DYSL 
    2525       IF(is_master) PRINT *,'CPP_DYSL : Using macro-generated compute kernels' 
    26     #endif 
     26#endif 
    2727 
    2828    hydrostatic=.TRUE. 
     
    122122    CALL allocate_field(f_qv,field_z,type_real,llm)  
    123123    CALL allocate_field(f_pk,    field_t,type_real,llm,  name='pk') 
    124     CALL allocate_field(f_wwuu,  field_u,type_real,llm+1,name='wwuu') 
     124    CALL allocate_field(f_wwuu,  field_u,type_real,llm+1,name='wwuu')     
    125125    CALL allocate_field(f_planetvel,  field_u,type_real, name='planetvel') ! planetary velocity at r=a 
    126  
     126    IF(.NOT.hydrostatic) THEN 
     127       CALL allocate_field(f_Fel,      field_u,type_real,llm+1,name='F_el') 
     128       CALL allocate_field(f_gradPhi2, field_t,type_real,llm+1,name='gradPhi2') 
     129       CALL allocate_field(f_wil,      field_t,type_real,llm+1,name='w_il') 
     130       CALL allocate_field(f_Wetadot,  field_t,type_real,llm,name='W_etadot') 
     131    END IF 
    127132  END SUBROUTINE allocate_caldyn 
    128133 
  • codes/icosagcm/devel/src/dynamics/caldyn_hevi.f90

    r531 r558  
    5959    REAL(rstd),POINTER  :: convm(:,:)  
    6060    REAL(rstd),POINTER  :: wwuu(:,:) 
    61          
     61    REAL(rstd),POINTER  :: F_el(:,:), gradPhi2(:,:), w_il(:,:) , W_etadot(:,:), pres(:,:), m_il(:,:) 
    6262    INTEGER :: ind 
    6363    LOGICAL,SAVE :: first=.TRUE. 
     
    118118          dW = f_dW_fast(ind) 
    119119          dPhi = f_dPhi_fast(ind) 
    120           CALL compute_caldyn_solver(tau,mass,theta,pk,geopot,W,dPhi,dW,du) ! computes d(Phi,W,du)_fast and updates Phi,W 
     120          ! reuse buffers 
     121          m_il = f_wil(ind) 
     122          pres = f_gradPhi2(ind) 
     123          CALL compute_caldyn_solver(tau,mass,theta,pk,geopot,W, m_il,pres, dPhi,dW,du) ! computes d(Phi,W,du)_fast and updates Phi,W 
    121124       END IF 
    122125       u=f_u(ind) 
     
    161164          geopot = f_geopot(ind) 
    162165          dPhi = f_dPhi_slow(ind) 
    163           CALL compute_caldyn_slow_NH(u,mass,geopot,W, hflux,du,dPhi,dW) 
     166          F_el = f_Fel(ind) 
     167          gradPhi2 = f_gradPhi2(ind) 
     168          w_il = f_wil(ind) 
     169          CALL compute_caldyn_slow_NH(u,mass,geopot,W, F_el,gradPhi2,w_il, hflux,du,dPhi,dW) 
    164170       END IF 
    165171       CALL compute_caldyn_Coriolis(hflux,theta,qu, convm,dtheta_rhodz,du) 
     
    168174          wwuu=f_wwuu(ind) 
    169175          dps=f_dps(ind) 
     176          W_etadot=f_Wetadot(ind) 
    170177          CALL compute_caldyn_vert(u,theta,mass,convm, wflux,wwuu, dps, dtheta_rhodz, du) 
    171178          IF(.NOT.hydrostatic) THEN 
    172              CALL compute_caldyn_vert_NH(mass,geopot,W,wflux, du,dPhi,dW) 
     179             CALL compute_caldyn_vert_NH(mass,geopot,W,wflux, W_etadot, du,dPhi,dW) 
    173180          END IF 
    174181       END IF 
  • codes/icosagcm/devel/src/dynamics/caldyn_kernels_base.F90

    r538 r558  
    1414 
    1515  ! temporary shared variables for caldyn 
    16   TYPE(t_field),POINTER,PUBLIC :: f_pk(:),f_wwuu(:),f_planetvel(:) 
     16  TYPE(t_field),POINTER,PUBLIC :: f_pk(:),f_wwuu(:),f_planetvel(:), & 
     17                                  f_Fel(:), f_gradPhi2(:), f_wil(:), f_Wetadot(:) 
    1718 
    1819  INTEGER, PUBLIC :: caldyn_conserv 
     
    295296  END SUBROUTINE compute_caldyn_vert 
    296297 
    297   SUBROUTINE compute_caldyn_vert_NH(mass,geopot,W,wflux, du,dPhi,dW) 
     298  SUBROUTINE compute_caldyn_vert_NH(mass,geopot,W,wflux, W_etadot, du,dPhi,dW) 
    298299    REAL(rstd),INTENT(IN) :: mass(iim*jjm,llm) 
    299300    REAL(rstd),INTENT(IN) :: geopot(iim*jjm,llm+1) 
     
    303304    REAL(rstd),INTENT(INOUT) :: dPhi(iim*jjm,llm+1) 
    304305    REAL(rstd),INTENT(INOUT) :: dW(iim*jjm,llm+1) 
     306    REAL(rstd) :: W_etadot(iim*jjm,llm) ! vertical flux of vertical momentum 
    305307    ! local arrays 
    306308    REAL(rstd) :: eta_dot(iim*jjm, llm) ! eta_dot in full layers 
    307309    REAL(rstd) :: wcov(iim*jjm,llm) ! covariant vertical momentum in full layers 
    308     REAL(rstd) :: W_etadot(iim*jjm,llm) ! vertical flux of vertical momentum 
    309310    ! indices and temporary values 
    310311    INTEGER    :: ij, l 
     
    314315 
    315316#ifdef CPP_DYSL 
    316 !#if 0 
     317!$OMP BARRIER 
    317318#include "../kernels/caldyn_vert_NH.k90" 
     319!$OMP BARRIER 
    318320#else 
    319321#define ETA_DOT(ij) eta_dot(ij,1) 
  • codes/icosagcm/devel/src/dynamics/caldyn_kernels_hevi.F90

    r539 r558  
    125125 
    126126#ifdef CPP_DYSL 
    127 !#if 0 
    128127#include "../kernels/compute_NH_geopot.k90" 
    129128#else 
    130  
    131129!    FIXME : vertical OpenMP parallelism will not work 
    132130    
     
    266264  END SUBROUTINE compute_NH_geopot 
    267265 
    268   SUBROUTINE compute_caldyn_solver(tau,rhodz,theta,pk, geopot,W, dPhi,dW,du) 
     266  SUBROUTINE compute_caldyn_solver(tau,rhodz,theta,pk, geopot,W, m_il,pres, dPhi,dW,du) 
    269267    REAL(rstd),INTENT(IN) :: tau ! "solve" Phi-tau*dPhi/dt = Phi_rhs 
    270268    REAL(rstd),INTENT(IN)    :: rhodz(iim*jjm,llm) 
     
    273271    REAL(rstd),INTENT(INOUT) :: geopot(iim*jjm,llm+1) 
    274272    REAL(rstd),INTENT(INOUT) :: W(iim*jjm,llm+1) ! OUT if tau>0 
     273    REAL(rstd),INTENT(OUT)   :: m_il(iim*jjm,llm+1)        ! rhodz averaged to interfaces 
     274    REAL(rstd),INTENT(OUT)   :: pres(iim*jjm,llm)          ! pressure 
    275275    REAL(rstd),INTENT(OUT)   :: dW(iim*jjm,llm+1) 
    276276    REAL(rstd),INTENT(OUT)   :: dPhi(iim*jjm,llm+1) 
    277277    REAL(rstd),INTENT(OUT)   :: du(3*iim*jjm,llm) 
    278278 
    279     REAL(rstd) :: m_il(iim*jjm,llm+1)        ! rhodz averaged to interfaces 
    280     REAL(rstd) :: pres(iim*jjm,llm)          ! pressure 
    281     REAL(rstd) :: berni(iim*jjm,llm)             ! (W/m_il)^2 
     279    REAL(rstd) :: berni(iim*jjm,llm)         ! (W/m_il)^2 
    282280    REAL(rstd) :: gamma, rho_ij, T_ij, X_ij, Y_ij, vreff, Rd, Cvd 
    283281    INTEGER    :: ij, l 
     
    288286 
    289287#ifdef CPP_DYSL 
    290 !#if 0 
     288!$OMP BARRIER 
    291289#include "../kernels/caldyn_solver.k90" 
     290!$OMP BARRIER 
    292291#else 
    293292#define BERNI(ij) berni(ij,1) 
     
    517516 
    518517#ifdef CPP_DYSL 
    519 !#if 0 
    520518#include "../kernels/coriolis.k90" 
    521519#else 
     
    675673 
    676674#ifdef CPP_DYSL 
    677 !#if 0 
    678675#define BERNI(ij,l) berni(ij,l) 
    679676#include "../kernels/caldyn_slow_hydro.k90" 
     
    733730  END SUBROUTINE compute_caldyn_slow_hydro 
    734731 
    735   SUBROUTINE compute_caldyn_slow_NH(u,rhodz,Phi,W, hflux,du,dPhi,dW) 
     732  SUBROUTINE compute_caldyn_slow_NH(u,rhodz,Phi,W, F_el,gradPhi2,w_il, hflux,du,dPhi,dW) 
    736733    REAL(rstd),INTENT(IN)  :: u(3*iim*jjm,llm)    ! prognostic "velocity" 
    737734    REAL(rstd),INTENT(IN)  :: rhodz(iim*jjm,llm)  ! rho*dz 
     
    744741    REAL(rstd),INTENT(OUT) :: dPhi(iim*jjm,llm+1) 
    745742 
    746     REAL(rstd) :: w_il(3*iim*jjm,llm+1) ! Wil/mil 
     743    REAL(rstd) :: w_il(iim*jjm,llm+1) ! Wil/mil 
    747744    REAL(rstd) :: F_el(3*iim*jjm,llm+1) ! NH mass flux 
    748     REAL(rstd) :: GradPhi2(3*iim*jjm,llm+1) ! grad_Phi**2 
     745    REAL(rstd) :: gradPhi2(iim*jjm,llm+1) ! grad_Phi**2 
    749746    REAL(rstd) :: DePhil(3*iim*jjm,llm+1) ! grad(Phi) 
    750747     
     
    765762 
    766763#ifdef CPP_DYSL 
     764!$OMP BARRIER 
    767765#include "../kernels/caldyn_slow_NH.k90" 
     766!$OMP BARRIER 
    768767#else 
    769768    DO l=ll_begin, ll_endp1 ! compute on l levels (interfaces) 
Note: See TracChangeset for help on using the changeset viewer.