Ignore:
Timestamp:
06/25/14 15:00:24 (10 years ago)
Author:
dubos
Message:

Fixed DCMIP5 physics/etat0

File:
1 edited

Legend:

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

    r186 r192  
    77  SUBROUTINE etat0(f_ps,f_mass,f_phis,f_theta_rhodz,f_u, f_q) 
    88    USE icosa 
     9    USE mpipara, ONLY : is_mpi_root 
    910    USE disvert_mod 
    1011    USE etat0_williamson_mod, ONLY : etat0_williamson_new 
     
    6162       CALL etat0_dcmip3(f_ps,f_phis,f_theta_rhodz,f_u, f_q) 
    6263     CASE ('dcmip4') 
     64        IF(nqtot<2) THEN 
     65           IF (is_mpi_root)  THEN 
     66              PRINT *, "nqtot must be at least 2 for test case DCMIP4" 
     67           END IF 
     68           STOP 
     69        END IF 
    6370       CALL etat0_dcmip4(f_ps,f_phis,f_theta_rhodz,f_u, f_q) 
    6471     CASE ('dcmip5') 
Note: See TracChangeset for help on using the changeset viewer.