Ignore:
Timestamp:
06/27/13 18:37:27 (11 years ago)
Author:
dubos
Message:

Lagrangian vertical coordinate tested with test4.1 - 60 MPI procs

File:
1 edited

Legend:

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

    r159 r162  
    3232   
    3333  SUBROUTINE caldyn(write_out,f_phis, f_ps, f_mass, f_theta_rhodz, f_u, f_q, & 
    34        f_hflux, f_wflux, f_dps, f_dtheta_rhodz, f_du) 
     34       f_hflux, f_wflux, f_dps, f_dmass, f_dtheta_rhodz, f_du) 
    3535  USE icosa 
    3636  USE caldyn_gcm_mod, ONLY : caldyn_gcm=>caldyn 
     
    4747  TYPE(t_field),POINTER :: f_wflux(:) 
    4848  TYPE(t_field),POINTER :: f_dps(:) 
     49  TYPE(t_field),POINTER :: f_dmass(:) 
    4950  TYPE(t_field),POINTER :: f_dtheta_rhodz(:) 
    5051  TYPE(t_field),POINTER :: f_du(:) 
     
    5354      CASE('gcm') 
    5455        CALL caldyn_gcm(write_out,f_phis, f_ps, f_mass, f_theta_rhodz, f_u, f_q, & 
    55              f_hflux, f_wflux, f_dps, f_dtheta_rhodz, f_du) 
     56             f_hflux, f_wflux, f_dps, f_dmass, f_dtheta_rhodz, f_du) 
    5657      CASE('adv') 
    5758        CALL caldyn_adv(write_out,f_phis, f_ps, f_theta_rhodz, f_u, f_q, & 
Note: See TracChangeset for help on using the changeset viewer.