Ignore:
Timestamp:
10/11/14 23:27:39 (10 years ago)
Author:
dubos
Message:

time_style cleanup

File:
1 edited

Legend:

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

    r266 r278  
    4848   
    4949  SUBROUTINE init_time 
    50   USE earth_const 
    51   USE getin_mod 
    52   USE mpipara 
    53   IMPLICIT NONE 
    54   REAL(rstd) :: run_length 
    55  
    56  
    57    time_style='dcmip' 
    58    CALL getin('time_style',time_style) 
    59  
    60    IF (TRIM(time_style)=='dcmip')  Then 
     50    USE earth_const 
     51    USE getin_mod 
     52    USE mpipara 
     53    IMPLICIT NONE 
     54    REAL(rstd) :: run_length 
     55     
    6156    dt=90. 
    6257    CALL getin('dt',dt) 
    63  
     58    write_period=0 
     59    CALL getin('write_period',write_period) 
    6460    itaumax=100 
    65     CALL getin('itaumax',itaumax) 
    66  
     61    CALL getin('itaumax',itaumax)     
    6762    run_length=dt*itaumax 
    6863    CALL getin('run_length',run_length) 
    6964    itaumax=run_length/dt 
    70     dt=dt/scale_factor 
    71  
    72     write_period=0 
    73     CALL getin('write_period',write_period) 
    74     write_period=write_period/scale_factor 
     65     
     66    time_style='dcmip' 
     67    CALL getin('time_style',time_style) 
     68    SELECT CASE(TRIM(time_style)) 
     69    CASE('none') ! do nothing 
     70    CASE('dcmip') ! rescale time step for small-planet experiments 
     71       dt=dt/scale_factor        
     72       write_period=write_period/scale_factor 
     73       IF (is_mpi_root) PRINT *, 'Output frequency (scaled) set to ',write_period 
     74    CASE DEFAULT 
     75       IF (is_mpi_root) PRINT*,"Bad selector for variable time_style >",TRIM(time_style),"> options are <none>, <dcmip>" 
     76       STOP 
     77    END SELECT 
     78     
    7579    itau_out=FLOOR(.5+write_period/dt) 
    76     IF (is_mpi_root) PRINT *, 'Output frequency (scaled) set to ',write_period, ' : itau_out = ',itau_out 
    77     ENDIF  
     80    IF (is_mpi_root) PRINT *, 'Output frequency itau_out = ',itau_out 
    7881 
    7982    itau_adv=1 
    8083    CALL getin('itau_adv',itau_adv) 
    81  
     84     
    8285    itau_dissip=1 
    8386    CALL getin('itau_dissip',itau_dissip) 
    84  
     87     
    8588    itau_physics=1 
    8689    CALL getin('itau_physics',itau_physics) 
    87  
     90     
    8891    IF (is_mpi_root)  THEN 
    8992       PRINT *, 'itaumax=',itaumax 
Note: See TracChangeset for help on using the changeset viewer.