Ignore:
Timestamp:
04/14/16 23:12:41 (8 years ago)
Author:
dubos
Message:

New : positive advection option for theta

File:
1 edited

Legend:

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

    r369 r377  
    11961196! Test 3-1 
    11971197!========== 
    1198 SUBROUTINE test3_gravity_wave (lon,lat,p,z,zcoords,u,v,w,t,phis,ps,rho,q) 
     1198SUBROUTINE test3_gravity_wave (X,lon,lat,p,z,zcoords,u,v,w,t,phis,ps,rho,q) 
    11991199 
    12001200IMPLICIT NONE 
     
    12041204 
    12051205        real(rstd), intent(in)  :: lon, &       ! Longitude (radians) 
    1206                                    lat          ! Latitude (radians) 
     1206                                   lat, &       ! Latitude (radians) 
     1207                                   X            ! Reduced Earth reduction factor (DCMIP value = 125) 
    12071208 
    12081209        real(rstd), intent(inout) :: p, &       ! Pressure  (Pa) 
     
    12271228!     test case parameters 
    12281229!-----------------------------------------------------------------------  
    1229         real(rstd), parameter ::        X       = 125.d0,               &       ! Reduced Earth reduction factor 
     1230        real(rstd), parameter ::        & 
    12301231                                Om      = 0.d0,                 &       ! Rotation Rate of Earth 
    1231                                 as      = a/X,                  &       ! New Radius of small Earth      
    12321232                                u0      = 20.d0,                &       ! Reference Velocity  
    12331233!                               u0      = 0.d0,                 &       ! FIXME : no zonal wind for NH tests 
     
    12431243                                N2      = N*N,                  &       ! Brunt-Vaisala frequency Squared 
    12441244                                bigG    = (g*g)/(N2*cp)                 ! Constant 
    1245                              
     1245 
     1246      real(rstd) :: as                                                  ! New Radius of small Earth      
     1247 
    12461248      real(rstd) :: height                                                      ! Model level height 
    12471249      real(rstd) :: sin_tmp, cos_tmp                                    ! Calculation of great circle distance 
     
    12511253      real(rstd) :: theta_pert                                          ! Pot-temp perturbation 
    12521254 
     1255      as = a/X 
     1256 
    12531257!----------------------------------------------------------------------- 
    12541258!    THE VELOCITIES 
Note: See TracChangeset for help on using the changeset viewer.