source: codes/icosagcm/trunk/src/guided_mod.f90 @ 25

Last change on this file since 25 was 25, checked in by dubos, 12 years ago

Minor changes :
caldyn_sw.f90, advect_tracer.f90
icosa_mod.f90 : added parameters for NCAR test cases needing global scope
guided_mod.f90 : CALL to guided_ncar now takes tt=it*dt instead of it as input

Significant changes :
timeloop_gcm.f90 : re-activated CALL to advection scheme
disvert_ncar.f90,
etat0_ncar.f90
guided_ncar_mod.f90 : simplification, introduced several getin(...), update due to recent changes in advection test cases (deformational flow, Hadley cell)
run_adv.def : new keys, reorganized for legibility

Tests :
icosa_gcm.exe tested with ncar_adv_shape=const and ncar_adv_wind=solid,deform,hadley.
q1=1 maintained to machine accuracy. Surface pressure slightly oscillates as expected.

FIXME : Tests by Sarvesh with revision 24 show incorrect advection of cosine bell by solid-body rotation. Not fixed.

File size: 1.2 KB
Line 
1MODULE guided_mod
2
3  CHARACTER(LEN=255),SAVE :: guided_type
4
5CONTAINS
6
7
8  SUBROUTINE init_guided(dt)
9  USE icosa
10  USE guided_ncar_mod, ONLY : init_guided_ncar => init_guided
11  IMPLICIT NONE
12    REAL(rstd),INTENT(IN) :: dt
13   
14    guided_type='none'
15    CALL getin("guided_type",guided_type)
16   
17    SELECT CASE(TRIM(guided_type))
18      CASE ('none')
19     
20      CASE ('ncar')
21        CALL init_guided_ncar
22       
23      CASE DEFAULT
24       
25         PRINT*,"Bad selector for varaible guided_type >",TRIM(guided_type),"> option are <none>, <ncar>"
26         STOP
27    END SELECT
28   
29  END SUBROUTINE init_guided
30
31 
32  SUBROUTINE guided(tt, f_ps, f_theta_rhodz, f_u, f_q)
33  USE icosa
34  USE guided_ncar_mod, ONLY : guided_ncar => guided
35  IMPLICIT NONE
36    REAL(rstd), INTENT(IN):: tt
37    TYPE(t_field),POINTER :: f_ps(:)
38    TYPE(t_field),POINTER :: f_phis(:)
39    TYPE(t_field),POINTER :: f_theta_rhodz(:)
40    TYPE(t_field),POINTER :: f_u(:) 
41    TYPE(t_field),POINTER :: f_q(:) 
42
43    SELECT CASE(TRIM(guided_type))
44      CASE ('none')
45     
46      CASE ('ncar')
47        CALL guided_ncar(tt, f_ps, f_theta_rhodz, f_u, f_q)
48    END SELECT
49 
50  END SUBROUTINE guided
51 
52END MODULE guided_mod
53 
Note: See TracBrowser for help on using the repository browser.