Ignore:
Timestamp:
07/16/12 10:24:35 (12 years ago)
Author:
ymipsl
Message:

Merge advection scheme from sarvesh in standard version

YM

File:
1 edited

Legend:

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

    r15 r17  
    33  USE transfert_mod 
    44  USE etat0_mod 
    5    
    6   INTEGER,PARAMETER :: euler=1, leapfrog=2, leapfrog_matsuno=3, adam_bashforth=4 
    75   
    86CONTAINS 
     
    1816  USE dissip_gcm_mod 
    1917  USE ioipsl 
    20   USE caldyn_gcm_mod 
     18  USE caldyn_mod 
    2119  USE theta2theta_rhodz_mod 
    2220  USE etat0_mod 
     21  USE guided_mod 
     22  USE advect_tracer_mod 
     23   
    2324  IMPLICIT NONE 
    2425  TYPE(t_field),POINTER :: f_phis(:) 
    2526  TYPE(t_field),POINTER :: f_theta(:) 
     27  TYPE(t_field),POINTER :: f_q(:) 
    2628  TYPE(t_field),POINTER :: f_dtheta(:) 
    2729  TYPE(t_field),POINTER :: f_ps(:),f_psm1(:), f_psm2(:) 
     
    3335 
    3436  REAL(rstd),POINTER :: phis(:) 
     37  REAL(rstd),POINTER :: q(:,:,:) 
    3538  REAL(rstd),POINTER :: ps(:) ,psm1(:), psm2(:) 
    3639  REAL(rstd),POINTER :: u(:,:) , um1(:,:), um2(:,:) 
     
    4245  INTEGER :: ind 
    4346  INTEGER :: it,i,j,n 
    44   INTEGER :: scheme 
     47  CHARACTER(len=255) :: scheme 
    4548  INTEGER :: matsuno_period 
    4649  INTEGER :: itaumax 
    47    
     50  INTEGER :: write_period   
     51  INTEGER :: itau_out 
    4852 
    4953  dt=90. 
     
    5256  itaumax=100 
    5357  CALL getin('itaumax',itaumax) 
    54    
    55   scheme=leapfrog_matsuno 
     58 
     59  write_period=0 
     60  CALL getin('write_period',write_period) 
     61  itau_out=INT(write_period/dt) 
     62   
     63  scheme='adam_bashforth' 
    5664  CALL getin('scheme',scheme) 
    5765   
    5866  matsuno_period=5 
    5967  CALL getin('matsuno_period',matsuno_period) 
    60   IF (scheme==leapfrog) matsuno_period=itaumax+1 
     68  IF (TRIM(scheme)=='leapfrog') matsuno_period=itaumax+1 
    6169 
    6270  CALL allocate_field(f_phis,field_t,type_real) 
     
    7987  CALL allocate_field(f_dtheta,field_t,type_real,llm) 
    8088 
     89  CALL allocate_field(f_q,field_t,type_real,llm,nqtot) 
     90 
    8191  CALL allocate_field(f_theta_rhodz,field_t,type_real,llm) 
    8292  CALL allocate_field(f_theta_rhodzm1,field_t,type_real,llm) 
     
    8898  CALL init_dissip(dt) 
    8999  CALL init_caldyn(dt) 
    90    
    91 !  CALL etat0_academic(f_ps,f_phis,f_theta_rhodz,f_u) 
    92   CALL etat0_jablonowsky06(f_ps,f_phis,f_theta_rhodz,f_u) 
    93 !  CALL test_etat0_jablonowsky06 
     100  CALL init_guided(dt) 
     101  CALL init_advect_tracer(dt) 
     102   
     103  CALL etat0(f_ps,f_phis,f_theta_rhodz,f_u, f_q) 
    94104   
    95105  DO it=0,itaumax 
    96106    PRINT *,"It No :",It 
    97107 
     108    CALL guided(it,f_ps,f_theta_rhodz,f_u,f_q) 
    98109    CALL caldyn(it,f_phis,f_ps,f_theta_rhodz,f_u, f_dps, f_dtheta_rhodz, f_du) 
    99  
    100     IF (scheme==Euler) THEN 
    101       CALL  euler_scheme 
    102     ELSE IF (scheme==leapfrog) THEN 
    103       CALL leapfrog_scheme 
    104     ELSE IF (scheme==leapfrog_matsuno) THEN 
    105       CALL  leapfrog_matsuno_scheme 
    106     ELSE IF (scheme==adam_bashforth) THEN 
    107       CALL dissip(f_u,f_du,f_ps,f_theta_rhodz,f_dtheta_rhodz) 
    108       CALL adam_bashforth_scheme 
     110    CALL advect_tracer(f_ps,f_u,f_q) 
     111     
     112    SELECT CASE (TRIM(scheme)) 
     113      CASE('euler') 
     114        CALL  euler_scheme 
     115 
     116      CASE ('leapfrog') 
     117        CALL leapfrog_scheme 
     118 
     119      CASE ('leapfrog_matsuno') 
     120        CALL  leapfrog_matsuno_scheme 
     121 
     122      CASE ('adam_bashforth') 
     123        CALL dissip(f_u,f_du,f_ps,f_theta_rhodz,f_dtheta_rhodz) 
     124        CALL adam_bashforth_scheme 
     125 
     126      CASE default 
     127        PRINT*,'Bad selector for variable scheme : <', TRIM(scheme),"> options are <euler>, <leapfrog>, <leapfrog_matsuno>, <adam_bashforth>"  
     128        STOP 
     129         
     130    END SELECT 
     131 
     132     
     133    IF ( itau_out>0 .AND. MOD(it,itau_out)==0) THEN 
     134      CALL writefield("q",f_q) 
     135      CALL writefield("ps",f_ps) 
    109136    ENDIF 
    110137 
Note: See TracChangeset for help on using the changeset viewer.