Changeset 920


Ignore:
Timestamp:
06/19/19 00:40:30 (5 years ago)
Author:
dubos
Message:

devel : separate module for compute_geopot

Location:
codes/icosagcm/devel/src/dynamics
Files:
1 added
3 edited

Legend:

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

    r909 r920  
    236236       f_geopot, f_hflux, f_wflux, f_dps, f_dmass, f_dtheta_rhodz, f_du) 
    237237    USE observable_mod 
     238    USE compute_geopot_mod, ONLY : compute_geopot => compute_geopot_manual 
    238239    USE disvert_mod, ONLY : caldyn_eta, eta_mass 
    239240    USE trace 
  • codes/icosagcm/devel/src/dynamics/caldyn_hevi.f90

    r917 r920  
    66  USE caldyn_kernels_base_mod 
    77  USE compute_theta_mod, ONLY : compute_theta => compute_theta_manual 
     8  USE compute_geopot_mod, ONLY : compute_geopot => compute_geopot_manual 
    89  USE compute_caldyn_kv_mod, ONLY : compute_caldyn_kv 
    910  USE compute_caldyn_Coriolis_mod, ONLY : compute_caldyn_Coriolis 
  • codes/icosagcm/devel/src/dynamics/caldyn_kernels_base.F90

    r836 r920  
    1010  SAVE 
    1111 
    12   PUBLIC :: compute_geopot, compute_caldyn_vert, compute_caldyn_vert_nh 
     12  PUBLIC :: compute_caldyn_vert, compute_caldyn_vert_nh 
    1313 
    1414CONTAINS 
    1515 
    16   !**************************** Geopotential ***************************** 
    17  
    18   SUBROUTINE compute_geopot(rhodz,theta, ps,pk,geopot)  
    19     REAL(rstd),INTENT(IN)    :: rhodz(iim*jjm,llm) 
    20     REAL(rstd),INTENT(IN)    :: theta(iim*jjm,llm,nqdyn) ! active scalars : theta/entropy, moisture, ... 
    21     REAL(rstd),INTENT(INOUT) :: ps(iim*jjm) 
    22     REAL(rstd),INTENT(OUT)   :: pk(iim*jjm,llm)       ! Exner function (compressible) /Lagrange multiplier (Boussinesq) 
    23     REAL(rstd),INTENT(INOUT) :: geopot(iim*jjm,llm+1) ! geopotential 
    24  
    25     INTEGER :: i,j,ij,l 
    26     REAL(rstd) :: p_ik, exner_ik, Cp_ik, temp_ik, qv, chi, Rmix, gv 
    27     INTEGER    :: ij_omp_begin_ext, ij_omp_end_ext 
    28  
    29     CALL trace_start("compute_geopot") 
    30  
    31 !$OMP BARRIER 
    32  
    33     CALL distrib_level(ij_begin_ext,ij_end_ext, ij_omp_begin_ext,ij_omp_end_ext) 
    34  
    35     IF(dysl_geopot) THEN 
    36 #include "../kernels_hex/compute_geopot.k90" 
    37     ELSE 
    38     ! Pressure is computed first top-down (temporarily stored in pk) 
    39     ! Then Exner pressure and geopotential are computed bottom-up 
    40     ! Works also when caldyn_eta=eta_mass           
    41  
    42     IF(boussinesq) THEN ! compute geopotential and pk=Lagrange multiplier 
    43        ! specific volume 1 = dphi/g/rhodz 
    44        !         IF (is_omp_level_master) THEN ! no openMP on vertical due to dependency 
    45        DO l = 1,llm 
    46           !DIR$ SIMD 
    47           DO ij=ij_omp_begin_ext,ij_omp_end_ext          
    48              geopot(ij,l+1) = geopot(ij,l) + g*rhodz(ij,l) 
    49           ENDDO 
    50        ENDDO 
    51        ! use hydrostatic balance with theta*rhodz to find pk (Lagrange multiplier=pressure)  
    52        ! uppermost layer 
    53        !DIR$ SIMD 
    54        DO ij=ij_begin_ext,ij_end_ext          
    55           pk(ij,llm) = ptop + (.5*g)*theta(ij,llm,1)*rhodz(ij,llm) 
    56        END DO 
    57        ! other layers 
    58        DO l = llm-1, 1, -1 
    59           !          !$OMP DO SCHEDULE(STATIC)  
    60           !DIR$ SIMD 
    61           DO ij=ij_begin_ext,ij_end_ext          
    62              pk(ij,l) = pk(ij,l+1) + (.5*g)*(theta(ij,l,1)*rhodz(ij,l)+theta(ij,l+1,1)*rhodz(ij,l+1)) 
    63           END DO 
    64        END DO 
    65        ! now pk contains the Lagrange multiplier (pressure) 
    66     ELSE ! non-Boussinesq, compute pressure, Exner pressure or temperature, then geopotential 
    67        ! uppermost layer 
    68         
    69        SELECT CASE(caldyn_thermo) 
    70           CASE(thermo_theta, thermo_entropy) 
    71              !DIR$ SIMD 
    72              DO ij=ij_omp_begin_ext,ij_omp_end_ext 
    73                 pk(ij,llm) = ptop + (.5*g)*rhodz(ij,llm) 
    74              END DO 
    75              ! other layers 
    76              DO l = llm-1, 1, -1 
    77                 !DIR$ SIMD 
    78                 DO ij=ij_omp_begin_ext,ij_omp_end_ext          
    79                    pk(ij,l) = pk(ij,l+1) + (.5*g)*(rhodz(ij,l)+rhodz(ij,l+1)) 
    80                 END DO 
    81              END DO 
    82              ! surface pressure (for diagnostics) 
    83              IF(caldyn_eta==eta_lag) THEN 
    84                 DO ij=ij_omp_begin_ext,ij_omp_end_ext          
    85                    ps(ij) = pk(ij,1) + (.5*g)*rhodz(ij,1) 
    86                 END DO 
    87              END IF 
    88           CASE(thermo_moist) ! theta(ij,l,2) = qv = mv/md 
    89              !DIR$ SIMD 
    90              DO ij=ij_omp_begin_ext,ij_omp_end_ext 
    91                 pk(ij,llm) = ptop + (.5*g)*rhodz(ij,llm)*(1.+theta(ij,l,2)) 
    92              END DO 
    93              ! other layers 
    94              DO l = llm-1, 1, -1 
    95                 !DIR$ SIMD 
    96                 DO ij=ij_omp_begin_ext,ij_omp_end_ext          
    97                    pk(ij,l) = pk(ij,l+1) + (.5*g)*(          & 
    98                         rhodz(ij,l)  *(1.+theta(ij,l,2)) +   & 
    99                         rhodz(ij,l+1)*(1.+theta(ij,l+1,2)) ) 
    100                 END DO 
    101              END DO 
    102              ! surface pressure (for diagnostics) 
    103              IF(caldyn_eta==eta_lag) THEN 
    104                 DO ij=ij_omp_begin_ext,ij_omp_end_ext          
    105                    ps(ij) = pk(ij,1) + (.5*g)*rhodz(ij,1)*(1.+theta(ij,l,2)) 
    106                 END DO 
    107              END IF 
    108           END SELECT 
    109  
    110        DO l = 1,llm 
    111           SELECT CASE(caldyn_thermo) 
    112           CASE(thermo_theta) 
    113              !DIR$ SIMD 
    114              DO ij=ij_omp_begin_ext,ij_omp_end_ext 
    115                 p_ik = pk(ij,l) 
    116                 exner_ik = cpp * (p_ik/preff) ** kappa 
    117                 pk(ij,l) = exner_ik 
    118                 ! specific volume v = kappa*theta*pi/p = dphi/g/rhodz 
    119                 geopot(ij,l+1) = geopot(ij,l) + (g*kappa)*rhodz(ij,l)*theta(ij,l,1)*exner_ik/p_ik 
    120              ENDDO 
    121           CASE(thermo_entropy) ! theta is in fact entropy = cpp*log(theta/Treff) = cpp*log(T/Treff) - Rd*log(p/preff) 
    122              !DIR$ SIMD 
    123              DO ij=ij_omp_begin_ext,ij_omp_end_ext 
    124                 p_ik = pk(ij,l) 
    125                 temp_ik = Treff*exp((theta(ij,l,1) + Rd*log(p_ik/preff))/cpp) 
    126                 pk(ij,l) = temp_ik 
    127                 ! specific volume v = Rd*T/p = dphi/g/rhodz 
    128                 geopot(ij,l+1) = geopot(ij,l) + (g*Rd)*rhodz(ij,l)*temp_ik/p_ik 
    129              ENDDO 
    130           CASE(thermo_moist) ! theta is moist pseudo-entropy per dry air mass 
    131              DO ij=ij_omp_begin_ext,ij_omp_end_ext 
    132                 p_ik = pk(ij,l) 
    133                 qv = theta(ij,l,2) ! water vaper mixing ratio = mv/md 
    134                 Rmix = Rd+qv*Rv 
    135                 chi = ( theta(ij,l,1) + Rmix*log(p_ik/preff) ) / (cpp + qv*cppv) ! log(T/Treff) 
    136                 temp_ik = Treff*exp(chi) 
    137                 pk(ij,l) = temp_ik 
    138                 ! specific volume v = R*T/p = dphi/g/rhodz 
    139                 ! R = (Rd + qv.Rv)/(1+qv) 
    140                 geopot(ij,l+1) = geopot(ij,l) + g*Rmix*rhodz(ij,l)*temp_ik/(p_ik*(1+qv)) 
    141              ENDDO 
    142           CASE DEFAULT 
    143              STOP 
    144           END SELECT 
    145        ENDDO 
    146     END IF 
    147  
    148     END IF ! dysl 
    149  
    150     !ym flush geopot 
    151     !$OMP BARRIER 
    152  
    153     CALL trace_end("compute_geopot") 
    154  
    155   END SUBROUTINE compute_geopot 
    15616 
    15717  SUBROUTINE compute_caldyn_vert(u,theta,rhodz,convm, wflux,wwuu, dps,dtheta_rhodz,du) 
     
    16020    REAL(rstd),INTENT(IN)  :: rhodz(iim*jjm,llm) 
    16121    REAL(rstd),INTENT(INOUT)  :: convm(iim*jjm,llm)  ! mass flux convergence 
    162  
    16322    REAL(rstd),INTENT(INOUT) :: wflux(iim*jjm,llm+1) ! vertical mass flux (kg/m2/s) 
    16423    REAL(rstd),INTENT(INOUT) :: wwuu(iim*3*jjm,llm+1) 
     
    341200 
    342201  END SUBROUTINE compute_caldyn_vert_NH 
     202 
    343203END MODULE caldyn_kernels_base_mod 
Note: See TracChangeset for help on using the changeset viewer.