Ignore:
Timestamp:
02/04/13 15:15:35 (11 years ago)
Author:
dubos
Message:

Changed timeloop design for multistage schemes

File:
1 edited

Legend:

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

    r128 r129  
    8080  END SUBROUTINE allocate_caldyn 
    8181    
    82   SUBROUTINE caldyn(it,f_phis, f_ps, f_theta_rhodz, f_u, f_q, f_dps, f_dtheta_rhodz, f_du) 
     82  SUBROUTINE caldyn(write_out,f_phis, f_ps, f_theta_rhodz, f_u, f_q, f_dps, f_dtheta_rhodz, f_du) 
    8383    USE icosa 
    8484    USE vorticity_mod 
     
    8686    USE theta2theta_rhodz_mod 
    8787    IMPLICIT NONE 
    88     INTEGER,INTENT(IN)    :: it 
     88    LOGICAL,INTENT(IN)    :: write_out 
    8989    TYPE(t_field),POINTER :: f_phis(:) 
    9090    TYPE(t_field),POINTER :: f_ps(:) 
     
    168168    END SELECT 
    169169 
    170     IF (mod(it,itau_out)==0 ) THEN 
     170    IF (write_out) THEN 
    171171       PRINT *,'CALL write_output_fields' 
    172172       CALL write_output_fields(f_ps, f_phis, f_dps, f_u, f_theta_rhodz, f_q, & 
Note: See TracChangeset for help on using the changeset viewer.