Changeset 183


Ignore:
Timestamp:
12/16/13 00:48:24 (11 years ago)
Author:
dubos
Message:

moved Boussniesq calculation of pressure into compute_caldyn_horiz

File:
1 edited

Legend:

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

    r182 r183  
    221221          pk = f_pk(ind) 
    222222          geopot = f_geopot(ind)   
    223           CALL compute_geopot(ps,mass,theta,u, pk,geopot) 
     223          CALL compute_geopot(ps,mass,theta, pk,geopot) 
    224224          hflux=f_hflux(ind) 
    225225          convm = f_dmass(ind) 
     
    249249          pk = f_pk(ind) 
    250250          geopot = f_geopot(ind)   
    251           CALL compute_geopot(ps,mass,theta,u, pk,geopot) 
     251          CALL compute_geopot(ps,mass,theta, pk,geopot) 
    252252          hflux=f_hflux(ind) 
    253253          convm = f_dmass(ind) 
     
    405405  END SUBROUTINE compute_pvort 
    406406   
    407   SUBROUTINE compute_geopot(ps,rhodz,theta,u, pk,geopot)  
     407  SUBROUTINE compute_geopot(ps,rhodz,theta, pk,geopot)  
    408408  USE icosa 
    409409  USE disvert_mod 
     
    415415    REAL(rstd),INTENT(IN)    :: rhodz(iim*jjm,llm) 
    416416    REAL(rstd),INTENT(IN)    :: theta(iim*jjm,llm)    ! potential temperature 
    417     REAL(rstd),INTENT(IN)    :: u(3*iim*jjm,llm)      ! prognostic velocity 
    418417    REAL(rstd),INTENT(INOUT) :: pk(iim*jjm,llm)       ! Exner function 
    419418    REAL(rstd),INTENT(INOUT) :: geopot(iim*jjm,llm+1) ! geopotential 
    420419     
    421     REAL(rstd) :: urel(3*iim*jjm,llm)  ! relative velocity 
    422     REAL(rstd) :: cor_NT(iim*jjm,llm)  ! NT coriolis force u.(du/dPhi) 
    423420    INTEGER :: i,j,ij,l 
    424421    REAL(rstd) :: p_ik, exner_ik 
     
    448445       ! Notice that the computation below should work also when caldyn_eta=eta_mass           
    449446 
    450        IF(boussinesq) THEN  
    451           ! use theta*rhodz in hydrostatic balance 
    452           ! uppermost layer 
    453           !DIR$ SIMD 
    454           DO ij=ij_begin_ext,ij_end_ext          
    455              pk(ij,llm) = ptop + (.5*g)*theta(ij,llm)*rhodz(ij,llm) 
    456           END DO 
    457           ! other layers 
    458           DO l = llm-1, 1, -1 
    459              !$OMP DO SCHEDULE(STATIC)  
    460              !DIR$ SIMD 
    461              DO ij=ij_begin_ext,ij_end_ext          
    462                 pk(ij,l) = pk(ij,l+1) + (.5*g)*(theta(ij,l)*rhodz(ij,l)+theta(ij,l+1)*rhodz(ij,l+1)) 
    463              END DO 
    464           END DO 
    465           ! surface pressure (for diagnostics) 
    466           DO ij=ij_begin_ext,ij_end_ext          
    467              ps(ij) = pk(ij,1) + (.5*g)*theta(ij,1)*rhodz(ij,1) 
    468           END DO 
    469           ! now pk contains the Lagrange multiplier (pressure) 
    470  
     447       IF(boussinesq) THEN ! compute only geopotential : pressure pk will be computed in compute_caldyn_horiz 
    471448          ! specific volume 1 = dphi/g/rhodz 
    472449          DO l = 1,llm 
     
    477454             ENDDO 
    478455          ENDDO 
    479        ELSE ! non-Boussinesq 
     456       ELSE ! non-Boussinesq, compute geopotential and Exner pressure 
    480457          ! uppermost layer 
    481458          !DIR$ SIMD 
     
    496473          END DO 
    497474 
    498  
    499475          ! specific volume v = kappa*theta*pi/p = dphi/g/rhodz 
    500476          DO l = 1,llm 
     
    523499  USE omp_para 
    524500  IMPLICIT NONE 
    525     REAL(rstd),INTENT(IN)  :: u(iim*3*jjm,llm) 
     501    REAL(rstd),INTENT(IN)  :: u(iim*3*jjm,llm)    ! prognostic "velocity" 
    526502    REAL(rstd),INTENT(IN)  :: rhodz(iim*jjm,llm) 
    527503    REAL(rstd),INTENT(IN)  :: qu(iim*3*jjm,llm) 
     
    535511    REAL(rstd),INTENT(OUT) :: du(iim*3*jjm,llm) 
    536512 
     513    REAL(rstd) :: cor_NT(iim*jjm,llm)  ! NT coriolis force u.(du/dPhi) 
    537514    REAL(rstd) :: urel(3*iim*jjm,llm)  ! relative velocity 
    538515    REAL(rstd) :: Ftheta(3*iim*jjm,llm) ! theta flux 
     
    686663!!! Compute bernouilli term = Kinetic Energy + geopotential 
    687664    IF(boussinesq) THEN 
     665       ! first use hydrostatic balance with theta*rhodz to find pk (Lagrange multiplier=pressure)  
     666       ! uppermost layer 
     667       !DIR$ SIMD 
     668       DO ij=ij_begin_ext,ij_end_ext          
     669          pk(ij,llm) = ptop + (.5*g)*theta(ij,llm)*rhodz(ij,llm) 
     670       END DO 
     671       ! other layers 
     672       DO l = llm-1, 1, -1 
     673          !$OMP DO SCHEDULE(STATIC)  
     674          !DIR$ SIMD 
     675          DO ij=ij_begin_ext,ij_end_ext          
     676             pk(ij,l) = pk(ij,l+1) + (.5*g)*(theta(ij,l)*rhodz(ij,l)+theta(ij,l+1)*rhodz(ij,l+1)) 
     677          END DO 
     678       END DO 
     679       ! surface pressure (for diagnostics) FIXME 
     680       ! DO ij=ij_begin_ext,ij_end_ext          
     681       !   ps(ij) = pk(ij,1) + (.5*g)*theta(ij,1)*rhodz(ij,1) 
     682       ! END DO 
     683       ! now pk contains the Lagrange multiplier (pressure) 
    688684 
    689685       DO l=ll_begin,ll_end 
    690686!DIR$ SIMD 
    691687          DO ij=ij_begin,ij_end          
    692                 ! until this point pk contains the Lagrange multiplier (pressure) 
    693688                berni(ij,l) = pk(ij,l) & 
    694689                     + 1/(4*Ai(ij))*(le(ij+u_right)*de(ij+u_right)*u(ij+u_right,l)**2 +    & 
     
    703698       ENDDO 
    704699 
    705     ELSE 
     700    ELSE ! compressible 
    706701 
    707702       DO l=ll_begin,ll_end 
Note: See TracChangeset for help on using the changeset viewer.