Ignore:
Timestamp:
05/28/16 00:32:21 (8 years ago)
Author:
dubos
Message:

Infrastructure for multiple dynamical tracers - tested with JW06 and moist baroclinic wave

File:
1 edited

Legend:

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

    r377 r387  
    4141       STOP 
    4242    END IF 
     43 
     44    nqdyn = 1 ! one dynamical tracer = theta for the moment 
    4345 
    4446    def='ARK2.3' 
     
    8789    CALL allocate_field(f_mass,field_t,type_real,llm,name='mass') 
    8890    CALL allocate_field(f_rhodz,field_t,type_real,llm,name='rhodz') 
    89     CALL allocate_field(f_theta_rhodz,field_t,type_real,llm,name='theta_rhodz') 
     91    CALL allocate_field(f_theta_rhodz,field_t,type_real,llm,nqdyn,name='theta_rhodz') 
    9092    CALL allocate_field(f_u,field_u,type_real,llm,name='u') 
    9193    CALL allocate_field(f_geopot,field_t,type_real,llm+1,name='geopot') 
     
    103105       CALL allocate_field(f_dps,field_t,type_real,name='dps') 
    104106       CALL allocate_field(f_dmass,field_t,type_real,llm, name='dmass') 
    105        CALL allocate_field(f_dtheta_rhodz,field_t,type_real,llm,name='dtheta_rhodz') 
     107       CALL allocate_field(f_dtheta_rhodz,field_t,type_real,llm,nqdyn,name='dtheta_rhodz') 
    106108       CALL allocate_field(f_du,field_u,type_real,llm,name='du') 
    107109       ! Model state at previous time step (RK/MLF) 
    108110       CALL allocate_field(f_psm1,field_t,type_real,name='psm1') 
    109111       CALL allocate_field(f_massm1,field_t,type_real,llm, name='massm1') 
    110        CALL allocate_field(f_theta_rhodzm1,field_t,type_real,llm,name='theta_rhodzm1') 
     112       CALL allocate_field(f_theta_rhodzm1,field_t,type_real,llm,nqdyn,name='theta_rhodzm1') 
    111113       CALL allocate_field(f_um1,field_u,type_real,llm,name='um1') 
    112114    CASE(hevi) 
     
    114116       CALL allocate_fields(nb_stage,f_dps_slow, field_t,type_real,name='dps_slow') 
    115117       CALL allocate_fields(nb_stage,f_dmass_slow, field_t,type_real,llm, name='dmass_slow') 
    116        CALL allocate_fields(nb_stage,f_dtheta_rhodz_slow, field_t,type_real,llm,name='dtheta_rhodz_fast') 
     118       CALL allocate_fields(nb_stage,f_dtheta_rhodz_slow, field_t,type_real,llm,nqdyn,name='dtheta_rhodz_fast') 
    117119       CALL allocate_fields(nb_stage,f_du_slow, field_u,type_real,llm,name='du_slow') 
    118120       CALL allocate_fields(nb_stage,f_du_fast, field_u,type_real,llm,name='du_fast') 
     
    131133       CALL allocate_field(f_psm2,field_t,type_real) 
    132134       CALL allocate_field(f_massm2,field_t,type_real,llm) 
    133        CALL allocate_field(f_theta_rhodzm2,field_t,type_real,llm) 
     135       CALL allocate_field(f_theta_rhodzm2,field_t,type_real,llm,nqdyn) 
    134136       CALL allocate_field(f_um2,field_u,type_real,llm) 
    135137    END SELECT 
     
    208210    fluxt_zero=.TRUE. 
    209211 
    210     IF(positive_theta) CALL copy_theta_to_q1(f_theta_rhodz,f_rhodz,f_q) 
     212    IF(positive_theta) CALL copy_theta_to_q(f_theta_rhodz,f_rhodz,f_q) 
    211213 
    212214    !$OMP MASTER 
     
    303305             END DO 
    304306          ENDIF 
    305           IF(positive_theta) CALL copy_q1_to_theta(f_theta_rhodz,f_rhodz,f_q) 
     307          IF(positive_theta) CALL copy_q_to_theta(f_theta_rhodz,f_rhodz,f_q) 
    306308       END IF 
    307309        
     
    360362  END SUBROUTINE print_iteration 
    361363 
    362   SUBROUTINE copy_theta_to_q1(f_theta_rhodz,f_rhodz,f_q) 
     364  SUBROUTINE copy_theta_to_q(f_theta_rhodz,f_rhodz,f_q) 
    363365    TYPE(t_field),POINTER :: f_theta_rhodz(:),f_rhodz(:), f_q(:) 
    364     REAL(rstd), POINTER :: theta_rhodz(:,:), rhodz(:,:), q(:,:,:) 
    365     INTEGER :: ind 
     366    REAL(rstd), POINTER :: theta_rhodz(:,:,:), rhodz(:,:), q(:,:,:) 
     367    INTEGER :: ind, iq 
    366368    DO ind=1, ndomain 
    367369       IF (.NOT. assigned_domain(ind)) CYCLE 
     
    371373       rhodz=f_rhodz(ind) 
    372374       q=f_q(ind) 
    373        q(:,:,1)  = theta_rhodz(:,:)/rhodz(:,:) 
     375       DO iq=1, nqdyn 
     376          q(:,:,iq)  = theta_rhodz(:,:,iq)/rhodz(:,:) 
     377       END DO 
    374378    END DO 
    375   END SUBROUTINE copy_theta_to_q1 
    376  
    377   SUBROUTINE copy_q1_to_theta(f_theta_rhodz,f_rhodz,f_q) 
     379  END SUBROUTINE copy_theta_to_q 
     380 
     381  SUBROUTINE copy_q_to_theta(f_theta_rhodz,f_rhodz,f_q) 
    378382    TYPE(t_field),POINTER :: f_theta_rhodz(:),f_rhodz(:), f_q(:) 
    379     REAL(rstd), POINTER :: theta_rhodz(:,:), rhodz(:,:), q(:,:,:) 
    380     INTEGER :: ind 
     383    REAL(rstd), POINTER :: theta_rhodz(:,:,:), rhodz(:,:), q(:,:,:) 
     384    INTEGER :: ind, iq 
    381385    DO ind=1, ndomain 
    382386       IF (.NOT. assigned_domain(ind)) CYCLE 
     
    386390       rhodz=f_rhodz(ind) 
    387391       q=f_q(ind) 
    388        theta_rhodz(:,:) = rhodz(:,:)*q(:,:,1) 
     392       DO iq=1,nqdyn 
     393          theta_rhodz(:,:,iq) = rhodz(:,:)*q(:,:,iq) 
     394       END DO 
    389395    END DO 
    390   END SUBROUTINE copy_q1_to_theta 
     396  END SUBROUTINE copy_q_to_theta 
    391397 
    392398END MODULE timeloop_gcm_mod 
Note: See TracChangeset for help on using the changeset viewer.