Changeset 373 for codes/icosagcm


Ignore:
Timestamp:
04/08/16 09:34:17 (8 years ago)
Author:
dubos
Message:

Mass-based NH

Location:
codes/icosagcm/trunk/src
Files:
2 edited

Legend:

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

    r369 r373  
    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)_fast and updates Phi,W 
     120          CALL compute_caldyn_solver(tau,mass,theta,pk,geopot,W,dPhi,dW,du) ! computes d(Phi,W,du)_fast and updates Phi,W 
    121121       END IF 
    122122       u=f_u(ind) 
    123        CALL compute_caldyn_fast(tau,u,mass,theta,pk,geopot,du) ! computes du_fast and updates du 
     123       CALL compute_caldyn_fast(tau,u,mass,theta,pk,geopot,du) ! computes du_fast and updates u 
    124124    ENDDO 
    125125     
     
    167167          wwuu=f_wwuu(ind) 
    168168          dps=f_dps(ind) 
    169           IF(hydrostatic) THEN 
    170              CALL compute_caldyn_vert(u,theta,mass,convm, wflux,wwuu, dps, dtheta_rhodz, du) 
    171           ELSE 
    172              PRINT *, 'NH dynamics limited to Lagrangian vertical coordinate so far !'  
    173              STOP 
     169          CALL compute_caldyn_vert(u,theta,mass,convm, wflux,wwuu, dps, dtheta_rhodz, du) 
     170          IF(.NOT.hydrostatic) THEN 
     171             CALL compute_caldyn_vert_NH(mass,geopot,W,wflux, du,dPhi,dW) 
    174172          END IF 
    175173       END IF 
  • codes/icosagcm/trunk/src/caldyn_kernels_base.f90

    r366 r373  
    22  USE icosa 
    33  USE transfert_mod 
     4  USE disvert_mod 
     5  USE omp_para 
     6  USE trace 
    47  IMPLICIT NONE 
    58  PRIVATE 
     
    2023  TYPE(t_message),PUBLIC :: req_ps, req_mass, req_theta_rhodz, req_u, req_qu, req_geopot, req_w 
    2124 
    22   PUBLIC :: compute_geopot, compute_caldyn_vert 
     25  PUBLIC :: compute_geopot, compute_caldyn_vert, compute_caldyn_vert_nh 
    2326 
    2427CONTAINS 
     
    2730 
    2831  SUBROUTINE compute_geopot(ps,rhodz,theta, pk,geopot)  
    29     USE icosa 
    30     USE disvert_mod 
    31     USE exner_mod 
    32     USE trace 
    33     USE omp_para 
    34     IMPLICIT NONE 
    3532    REAL(rstd),INTENT(INOUT) :: ps(iim*jjm) 
    3633    REAL(rstd),INTENT(IN)    :: rhodz(iim*jjm,llm) 
     
    134131 
    135132  SUBROUTINE compute_caldyn_vert(u,theta,rhodz,convm, wflux,wwuu, dps,dtheta_rhodz,du) 
    136     USE icosa 
    137     USE disvert_mod 
    138     USE exner_mod 
    139     USE trace 
    140     USE omp_para 
    141     IMPLICIT NONE 
    142133    REAL(rstd),INTENT(IN)  :: u(iim*3*jjm,llm) 
    143134    REAL(rstd),INTENT(IN)  :: theta(iim*jjm,llm) 
     
    264255  END SUBROUTINE compute_caldyn_vert 
    265256 
     257  SUBROUTINE compute_caldyn_vert_NH(mass,geopot,W,wflux, du,dPhi,dW) 
     258    REAL(rstd),INTENT(IN) :: mass(iim*jjm,llm) 
     259    REAL(rstd),INTENT(IN) :: geopot(iim*jjm,llm+1) 
     260    REAL(rstd),INTENT(IN) :: W(iim*jjm,llm+1) 
     261    REAL(rstd),INTENT(IN) :: wflux(iim*jjm,llm+1) 
     262    REAL(rstd),INTENT(INOUT) :: du(iim*3*jjm,llm) 
     263    REAL(rstd),INTENT(INOUT) :: dPhi(iim*jjm,llm+1) 
     264    REAL(rstd),INTENT(INOUT) :: dW(iim*jjm,llm+1) 
     265    ! local arrays 
     266    REAL(rstd) :: eta_dot(iim*jjm) ! eta_dot in full layers 
     267    REAL(rstd) :: wcov(iim*jjm) ! covariant vertical momentum in full layers 
     268    REAL(rstd) :: W_etadot(iim*jjm,llm) ! vertical flux of vertical momentum 
     269    ! indices and temporary values 
     270    INTEGER    :: ij, l 
     271    REAL(rstd) :: wflux_ij, w_ij 
     272 
     273    CALL trace_start("compute_caldyn_vert_nh") 
     274 
     275    DO l=ll_begin,ll_end 
     276       ! compute the local arrays 
     277       !DIR$ SIMD 
     278       DO ij=ij_begin_ext,ij_end_ext 
     279          wflux_ij = .5*(wflux(ij,l)+wflux(ij,l+1)) 
     280          w_ij = .5*(W(ij,l)+W(ij,l+1))/mass(ij,l) 
     281          W_etadot(ij,l) = wflux_ij*w_ij 
     282          eta_dot(ij) = wflux_ij / mass(ij,l) 
     283          wcov(ij) = w_ij*(geopot(ij,l+1)-geopot(ij,l)) 
     284       ENDDO 
     285       ! add NH term to du 
     286      !DIR$ SIMD 
     287      DO ij=ij_begin,ij_end 
     288          du(ij+u_right,l) = du(ij+u_right,l) & 
     289               - .5*(wcov(ij+t_right)+wcov(ij)) & 
     290               *ne_right*(eta_dot(ij+t_right)-eta_dot(ij)) 
     291          du(ij+u_lup,l) = du(ij+u_lup,l) & 
     292               - .5*(wcov(ij+t_lup)+wcov(ij)) & 
     293               *ne_lup*(eta_dot(ij+t_lup)-eta_dot(ij)) 
     294          du(ij+u_ldown,l) = du(ij+u_ldown,l) & 
     295               - .5*(wcov(ij+t_ldown)+wcov(ij)) & 
     296               *ne_ldown*(eta_dot(ij+t_ldown)-eta_dot(ij)) 
     297       END DO 
     298    ENDDO 
     299    ! add NH terms to dW, dPhi 
     300    ! FIXME : TODO top and bottom 
     301    DO l=ll_beginp1,ll_end ! inner interfaces only 
     302       !DIR$ SIMD 
     303       DO ij=ij_begin,ij_end 
     304          dW(ij,l) = dW(ij,l) + W_etadot(ij,l-1) - W_etadot(ij,l) 
     305          dPhi(ij,l) = dPhi(ij,l) - wflux(ij,l) & 
     306               * (geopot(ij,l+1)-geopot(ij,l-1))/(mass(ij,l-1)+mass(ij,l)) 
     307       END DO 
     308    END DO 
     309    CALL trace_end("compute_caldyn_vert_nh") 
     310 
     311  END SUBROUTINE compute_caldyn_vert_NH 
    266312END MODULE caldyn_kernels_base_mod 
Note: See TracChangeset for help on using the changeset viewer.