Ignore:
Timestamp:
06/25/13 09:32:16 (11 years ago)
Author:
dubos
Message:

Towards Lagrangian vertical coordinate (not there yet)

File:
1 edited

Legend:

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

    r157 r159  
    3131  END SUBROUTINE init_caldyn 
    3232   
    33   SUBROUTINE caldyn(write_out,f_phis, f_ps, f_theta_rhodz, f_u, f_q, & 
     33  SUBROUTINE caldyn(write_out,f_phis, f_ps, f_mass, f_theta_rhodz, f_u, f_q, & 
    3434       f_hflux, f_wflux, f_dps, f_dtheta_rhodz, f_du) 
    3535  USE icosa 
     
    4040  TYPE(t_field),POINTER :: f_phis(:) 
    4141  TYPE(t_field),POINTER :: f_ps(:) 
     42  TYPE(t_field),POINTER :: f_mass(:) 
    4243  TYPE(t_field),POINTER :: f_theta_rhodz(:) 
    4344  TYPE(t_field),POINTER :: f_u(:) 
     
    5152    SELECT CASE (TRIM(caldyn_type)) 
    5253      CASE('gcm') 
    53         CALL caldyn_gcm(write_out,f_phis, f_ps, f_theta_rhodz, f_u, f_q, & 
     54        CALL caldyn_gcm(write_out,f_phis, f_ps, f_mass, f_theta_rhodz, f_u, f_q, & 
    5455             f_hflux, f_wflux, f_dps, f_dtheta_rhodz, f_du) 
    5556      CASE('adv') 
Note: See TracChangeset for help on using the changeset viewer.