[Dart-dev] [3871] DART/trunk: Clean up some of the tracing code, make it more consistent between

nancy at ucar.edu nancy at ucar.edu
Mon May 11 16:31:12 MDT 2009


An HTML attachment was scrubbed...
URL: http://mailman.ucar.edu/pipermail/dart-dev/attachments/20090511/5f5776c6/attachment-0001.html 
-------------- next part --------------
Modified: DART/trunk/assim_tools/assim_tools_mod.f90
===================================================================
--- DART/trunk/assim_tools/assim_tools_mod.f90	2009-05-11 22:28:58 UTC (rev 3870)
+++ DART/trunk/assim_tools/assim_tools_mod.f90	2009-05-11 22:31:11 UTC (rev 3871)
@@ -55,11 +55,14 @@
 implicit none
 private
 
-public :: filter_assim
+public :: filter_assim, set_assim_tools_trace
 
 ! Indicates if module initialization subroutine has been called yet
-logical                :: module_initialized = .false.
+logical :: module_initialized = .false.
+integer :: print_timestamps    = 0
+integer :: print_trace_details = 0
 
+
 ! True if random sequence needs to be initialized
 logical                :: first_inc_ran_call = .true.
 type (random_seq_type) :: inc_ran_seq
@@ -667,8 +670,9 @@
 call get_close_obs_destroy(gc_obs)
 
 ! Assure user we have done something
-write(errstring, '(A,I8,A)') 'Processed', obs_ens_handle%num_vars, ' total observations'
-call error_handler(E_MSG,'filter_assim',errstring)
+write(errstring, '(A,I8,A)') &
+   'Processed', obs_ens_handle%num_vars, ' total observations'
+if (print_trace_details >= 0) call error_handler(E_MSG,'filter_assim:',errstring)
 
 ! diagnostics for stats on saving calls by remembering obs at the same location.
 ! change .true. to .false. in the line below to remove the output completely.
@@ -2058,8 +2062,29 @@
 
 !------------------------------------------------------------------------
 
+subroutine set_assim_tools_trace(execution_level, timestamp_level)
+ integer, intent(in) :: execution_level
+ integer, intent(in) :: timestamp_level
 
+! set module local vars from the calling code to indicate how much
+! output we should generate from this code.  execution level is
+! intended to make it easier to figure out where in the code a crash
+! is happening; timestamp level is intended to help with gross levels
+! of overall performance profiling.  eventually, a level of 1 will
+! print out only basic info; level 2 will be more detailed.
+! (right now, only > 0 prints anything and it doesn't matter how
+! large the value is.)
 
+
+print_trace_details = execution_level
+print_timestamps    = timestamp_level
+
+end subroutine set_assim_tools_trace
+
+!--------------------------------------------------------------------
+
+
+
 !========================================================================
 ! end module assim_tools_mod
 !========================================================================

Modified: DART/trunk/filter/filter.f90
===================================================================
--- DART/trunk/filter/filter.f90	2009-05-11 22:28:58 UTC (rev 3870)
+++ DART/trunk/filter/filter.f90	2009-05-11 22:31:11 UTC (rev 3871)
@@ -33,7 +33,7 @@
 use assim_model_mod,      only : static_init_assim_model, get_model_size,                    &
                                  netcdf_file_type, init_diag_output, finalize_diag_output,   & 
                                  aoutput_diagnostics, ens_mean_for_model
-use assim_tools_mod,      only : filter_assim
+use assim_tools_mod,      only : filter_assim, set_assim_tools_trace
 use obs_model_mod,        only : move_ahead, advance_state, set_obs_model_trace
 use ensemble_manager_mod, only : init_ensemble_manager, end_ensemble_manager,                &
                                  ensemble_type, get_copy, get_my_num_copies, put_copy,       &
@@ -70,6 +70,8 @@
 character(len=129)      :: msgstring
 type(obs_type)          :: observation
 
+integer                 :: trace_level, timestamp_level
+
 ! Defining whether diagnostics are for prior or posterior
 integer, parameter :: PRIOR_DIAG = 0, POSTERIOR_DIAG = 2
 
@@ -103,6 +105,7 @@
 logical  :: output_forward_op_errors = .false.
 logical  :: output_timestamps = .false.
 logical  :: trace_execution   = .false.
+logical  :: silence           = .false.
 
 character(len = 129) :: obs_sequence_in_name  = "obs_seq.out",    &
                         obs_sequence_out_name = "obs_seq.final",  &
@@ -141,7 +144,8 @@
    inf_flavor, inf_initial_from_restart, inf_sd_initial_from_restart,               &
    inf_output_restart, inf_deterministic, inf_in_file_name, inf_damping,            &
    inf_out_file_name, inf_diag_file_name, inf_initial, inf_sd_initial,              &
-   inf_lower_bound, inf_upper_bound, inf_sd_lower_bound, output_inflation
+   inf_lower_bound, inf_upper_bound, inf_sd_lower_bound, output_inflation,          &
+   silence
 
 
 !----------------------------------------------------------------
@@ -196,7 +200,7 @@
 if (do_nml_file()) write(nmlfileunit, nml=filter_nml)
 if (do_nml_term()) write(     *     , nml=filter_nml)
 
-call set_trace(trace_execution, output_timestamps)
+call set_trace(trace_execution, output_timestamps, silence)
 
 call trace_message('Filter start')
 
@@ -356,11 +360,11 @@
    call trace_message('Top of main advance time loop')
 
    time_step_number = time_step_number + 1
-   write(msgstring , '(A,I5)') 'Main assimilation loop, starting iteration', time_step_number
-   call error_handler(E_MSG,'', ' ')
-   call error_handler(E_MSG,'filter:', msgstring)
+   write(msgstring , '(A,I5)') &
+      'Main assimilation loop, starting iteration', time_step_number
+   call trace_message(' ', ' ', -1)
+   call trace_message(msgstring, 'filter: ', -1)
 
-
    ! Check the time before doing the first model advance.  Not all tasks
    ! might have a time, so only check on PE0 if running multitask.
    ! This will get broadcast (along with the post-advance time) to all
@@ -389,7 +393,7 @@
    ! PAR For now, can only broadcast real arrays
    call filter_sync_keys_time(key_bounds, num_obs_in_set, curr_ens_time, next_ens_time)
    if(key_bounds(1) < 0) then 
-      call error_handler(E_MSG,'filter:', 'No more obs to assimilate, exiting main loop')
+      call trace_message('No more obs to assimilate, exiting main loop', 'filter:', -1)
       !call trace_message('No more obs to assimilate, exiting main loop')
       exit AdvanceTime
    endif
@@ -404,7 +408,7 @@
          call trace_message('After  advancing smoother')
       endif
 
-      call error_handler(E_MSG,'filter:', 'Ready to run model to advance data time')
+      call trace_message('Ready to run model to advance data time', 'filter:', -1)
       call print_ens_time(ens_handle, ' filter trace: Ensemble data time before advance')
       call trace_message('Before advance_state called to run model')
       call timestamp_message('Before model advance', sync=.true.)
@@ -418,7 +422,7 @@
       call trace_message('After  advance_state called to run model')
       call print_ens_time(ens_handle, ' filter trace: Ensemble data time after  advance')
    else
-      call error_handler(E_MSG,'filter:', 'Model does not need to run; data already at required time')
+      call trace_message('Model does not need to run; data already at required time', 'filter:', -1)
    endif
 
    call trace_message('Before setup for next group of observations')
@@ -523,7 +527,7 @@
    call all_vars_to_all_copies(obs_ens_handle)
 
    write(msgstring, '(A,I8,A)') 'Ready to assimilate up to', size(keys), ' observations'
-   call error_handler(E_MSG,'filter:', msgstring)
+   call trace_message(msgstring, 'filter:', -1)
    !call error_handler(E_MSG,'filter:', 'Ready to assimilate observations')
 
    call trace_message('Before observation assimilation')
@@ -544,7 +548,7 @@
    ! in the future
    if(ds) then
       write(msgstring, '(A,I8,A)') 'Ready to reassimilate up to', size(keys), ' observations in the smoother'
-      call error_handler(E_MSG,'filter:', msgstring)
+      call trace_message(msgstring, 'filter:', -1)
 
       call trace_message('Before smoother assimilation')
       call timestamp_message('Before smoother assimilation')
@@ -686,7 +690,7 @@
    call trace_message('Bottom of main advance time loop')
 end do AdvanceTime
 
-call error_handler(E_MSG,'filter:', 'End of main filter assimilation loop, starting cleanup')
+call trace_message('End of main filter assimilation loop, starting cleanup', 'filter:', -1)
 
 call trace_message('Before finalizing diagnostics files')
 ! properly dispose of the diagnostics files
@@ -1429,47 +1433,63 @@
 
 !-------------------------------------------------------------------------
 
-subroutine trace_message(msg)
+subroutine set_trace(trace_execution, output_timestamps, silence)
 
-character(len=*), intent(in) :: msg
-
-! Write message to stdout and log file.
-
-if (.not. trace_execution) return
-
-if (do_output()) &
-   call error_handler(E_MSG,'filter trace:',trim(msg))
-
-end subroutine trace_message
-
-!-------------------------------------------------------------------------
-
-subroutine set_trace(trace_execution, output_timestamps)
-
 logical, intent(in) :: trace_execution
 logical, intent(in) :: output_timestamps
+logical, intent(in) :: silence
 
 ! Set whether other modules trace execution with messages
 ! and whether they output timestamps to trace overall performance
 
-integer :: trace_level, timestamp_level
-
-if (.not. trace_execution .and. .not. output_timestamps) return
-
-trace_level = 0
+! defaults
+trace_level     = 0
 timestamp_level = 0
 
-if (trace_execution) trace_level = 1
+! selectively turn stuff back on
+if (trace_execution)   trace_level     = 1
 if (output_timestamps) timestamp_level = 1
 
+! turn as much off as possible
+if (silence) then
+   trace_level     = -1
+   timestamp_level = -1
+endif
+
 call set_smoother_trace(trace_level, timestamp_level)
 call set_obs_model_trace(trace_level, timestamp_level)
-! call set_assim_tools_trace(trace_level, timestamp_level)
+call set_assim_tools_trace(trace_level, timestamp_level)
 
 end subroutine set_trace
 
 !-------------------------------------------------------------------------
 
+subroutine trace_message(msg, label, threshold)
+
+character(len=*), intent(in)           :: msg
+character(len=*), intent(in), optional :: label
+integer,          intent(in), optional :: threshold
+
+! Write message to stdout and log file.
+integer :: t
+
+t = 0
+if (present(threshold)) t = threshold
+
+if (trace_level <= t) return
+
+if (.not. do_output()) return
+
+if (present(label)) then
+   call error_handler(E_MSG,trim(label),trim(msg))
+else
+   call error_handler(E_MSG,'filter trace:',trim(msg))
+endif
+
+end subroutine trace_message
+
+!-------------------------------------------------------------------------
+
 subroutine timestamp_message(msg, sync)
 
 character(len=*), intent(in) :: msg
@@ -1478,7 +1498,7 @@
 ! Write current time and message to stdout and log file. 
 ! if sync is present and true, sync mpi jobs before printing time.
 
-if (.not. output_timestamps) return
+if (timestamp_level <= 0) return
 
 if (present(sync)) then
   if (sync) call task_sync()
@@ -1498,7 +1518,7 @@
 ! Write message to stdout and log file.
 type(time_type) :: mtime
 
-if (.not. trace_execution) return
+if (trace_level <= 0) return
 
 if (do_output()) then
    if (get_my_num_copies(ens_handle) < 1) return
@@ -1522,7 +1542,7 @@
 type(obs_def_type) :: obs_def
 type(time_type) :: mtime
 
-if (.not. trace_execution) return
+if (trace_level <= 0) return
 
 if (do_output()) then
    call init_obs(obs, 0, 0)

Modified: DART/trunk/obs_model/obs_model_mod.f90
===================================================================
--- DART/trunk/obs_model/obs_model_mod.f90	2009-05-11 22:28:58 UTC (rev 3870)
+++ DART/trunk/obs_model/obs_model_mod.f90	2009-05-11 22:31:11 UTC (rev 3871)
@@ -14,7 +14,7 @@
 use types_mod,            only : r8
 use utilities_mod,        only : register_module, error_handler,     &
                                  E_ERR, E_MSG, E_WARN,               &
-                                 get_unit, file_exist
+                                 get_unit, file_exist, do_output
 use assim_model_mod,      only : aget_closest_state_time_to, get_model_time_step, &
                                  open_restart_write, open_restart_read,           &
                                  awrite_state_restart, close_restart, adv_1step,  &
@@ -600,8 +600,8 @@
 ! large the value is.)
  
 
-if (execution_level >= 0) print_trace_details = execution_level
-if (timestamp_level >= 0) print_timestamps    = timestamp_level
+print_trace_details = execution_level
+print_timestamps    = timestamp_level
 
 end subroutine set_obs_model_trace
 

Modified: DART/trunk/perfect_model_obs/perfect_model_obs.f90
===================================================================
--- DART/trunk/perfect_model_obs/perfect_model_obs.f90	2009-05-11 22:28:58 UTC (rev 3870)
+++ DART/trunk/perfect_model_obs/perfect_model_obs.f90	2009-05-11 22:31:11 UTC (rev 3871)
@@ -16,19 +16,20 @@
 use        types_mod,     only : r8, metadatalength
 use    utilities_mod,     only : initialize_utilities, register_module, error_handler, &
                                  find_namelist_in_file, check_namelist_read,           &
-                                 E_ERR, E_MSG, E_DBG, nmlfileunit, timestamp, &
-                                 do_nml_file, do_nml_term
-use time_manager_mod,     only : time_type, get_time, set_time, operator(/=)
+                                 E_ERR, E_MSG, E_DBG, nmlfileunit, timestamp,          &
+                                 do_nml_file, do_nml_term, logfileunit
+use time_manager_mod,     only : time_type, get_time, set_time, operator(/=), print_time
 use obs_sequence_mod,     only : read_obs_seq, obs_type, obs_sequence_type,                 &
                                  get_obs_from_key, set_copy_meta_data, get_obs_def,         &
                                  get_time_range_keys, set_obs_values, set_qc, set_obs,      &
                                  write_obs_seq, get_num_obs, init_obs, assignment(=),       &
                                  static_init_obs_sequence, get_num_qc, read_obs_seq_header, &
                                  set_qc_meta_data, get_expected_obs, delete_seq_head,       &
-                                 delete_seq_tail
+                                 delete_seq_tail, set_obs_def, destroy_obs
 
-use      obs_def_mod,     only : obs_def_type, get_obs_def_error_variance 
-use    obs_model_mod,     only : move_ahead, advance_state
+use      obs_def_mod,     only : obs_def_type, get_obs_def_error_variance, &
+                                 set_obs_def_error_variance, get_obs_def_time
+use    obs_model_mod,     only : move_ahead, advance_state, set_obs_model_trace
 use  assim_model_mod,     only : static_init_assim_model, get_model_size,                    &
                                  aget_initial_condition, netcdf_file_type, init_diag_output, &
                                  aoutput_diagnostics, finalize_diag_output
@@ -37,8 +38,9 @@
                                  task_count, task_sync
 
 use   random_seq_mod,     only : random_seq_type, init_random_seq, random_gaussian
-use ensemble_manager_mod, only : init_ensemble_manager, write_ensemble_restart, &
-                                 end_ensemble_manager, ensemble_type, read_ensemble_restart
+use ensemble_manager_mod, only : init_ensemble_manager, write_ensemble_restart,              &
+                                 end_ensemble_manager, ensemble_type, read_ensemble_restart, &
+                                 get_my_num_copies, get_ensemble_time
 
 implicit none
 
@@ -50,6 +52,7 @@
 
 ! Module storage for message output
 character(len=129) :: msgstring
+integer            :: trace_level, timestamp_level
 
 !-----------------------------------------------------------------------------
 ! Namelist with default values
@@ -57,6 +60,9 @@
 logical  :: start_from_restart = .false.
 logical  :: output_restart     = .false.
 integer  :: async              = 0
+logical  :: trace_execution    = .false.
+logical  :: output_timestamps  = .false.
+logical  :: silence            = .false.
 ! if init_time_days and seconds are negative initial time is 0, 0
 ! for no restart or comes from restart if restart exists
 integer  :: init_time_days     = 0
@@ -83,8 +89,9 @@
                                  last_obs_days,  last_obs_seconds, output_interval, &
                                  restart_in_file_name, restart_out_file_name,       &
                                  obs_seq_in_file_name, obs_seq_out_file_name,       &
-                                 adv_ens_command, tasks_per_model_advance,          &       
-                                 obs_window_days, obs_window_seconds
+                                 adv_ens_command, tasks_per_model_advance,          & 
+                                 obs_window_days, obs_window_seconds, silence,      &
+                                 trace_execution, output_timestamps
 
 !------------------------------------------------------------------------------
 
@@ -113,7 +120,7 @@
 integer                 :: ierr, io, istatus, num_obs_in_set
 integer                 :: model_size, key_bounds(2), num_qc, last_key_used
 
-real(r8)                :: true_obs(1), obs_value(1), qc(1)
+real(r8)                :: true_obs(1), obs_value(1), qc(1), errvar
 
 character(len=129)      :: copy_meta_data(2), qc_meta_data, obs_seq_read_format
 character(len=metadatalength) :: state_meta(1)
@@ -141,6 +148,9 @@
 endif
 call task_sync()
 
+! set the level of output
+call set_trace(trace_execution, output_timestamps, silence)
+
 ! Find out how many data copies are in the obs_sequence 
 call read_obs_seq_header(obs_seq_in_file_name, cnum_copies, cnum_qc, cnum_obs, cnum_max, &
    obs_seq_file_id, obs_seq_read_format, pre_I_format, close_the_file = .true.)
@@ -229,8 +239,8 @@
    time_step_number = time_step_number + 1
 
    write(msgstring , '(A,I5)') 'Main evaluation loop, starting iteration', time_step_number
-   call error_handler(E_MSG,'', ' ')
-   call error_handler(E_MSG,'perfect_model_obs:', msgstring)
+   if (.not.silence) call error_handler(E_MSG,'', ' ')
+   if (.not.silence) call error_handler(E_MSG,'perfect_model_obs:', msgstring)
 
    ! Get the model to a good time to use a next set of observations
    call move_ahead(ens_handle, 1, seq, last_key_used, window_time, &
@@ -241,11 +251,11 @@
    endif
  
    if (curr_ens_time /= next_ens_time) then
-      call error_handler(E_MSG,'perfect_model_obs:', 'Ready to run model to advance data time')
+      if (.not.silence) call error_handler(E_MSG,'perfect_model_obs:', 'Ready to run model to advance data time')
       call advance_state(ens_handle, 1, next_ens_time, async, &
          adv_ens_command, tasks_per_model_advance)
    else
-      call error_handler(E_MSG,'perfect_model_obs:', 'Model does not need to run; data already at required time')
+      if (.not.silence) call error_handler(E_MSG,'perfect_model_obs:', 'Model does not need to run; data already at required time')
    endif
 
    ! Allocate storage for observation keys for this part of sequence
@@ -259,7 +269,7 @@
       call aoutput_diagnostics(StateUnit, ens_handle%time(1), ens_handle%vars(:, 1), 1)
 
    write(msgstring, '(A,I8,A)') 'Ready to evaluate up to', size(keys), ' observations'
-   call error_handler(E_MSG,'perfect_model_obs:', msgstring)
+   if (.not.silence) call error_handler(E_MSG,'perfect_model_obs:', msgstring)
 
    ! How many observations in this set
    write(msgstring, *) 'num_obs_in_set is ', num_obs_in_set
@@ -280,8 +290,17 @@
       call get_obs_def(obs, obs_def)
 
       if(istatus == 0 .and. (assimilate_this_ob .or. evaluate_this_ob)) then
-         obs_value(1) = random_gaussian(random_seq, true_obs(1), &
-            sqrt(get_obs_def_error_variance(obs_def)))
+         ! DEBUG: try this out to see if it's useful.  if the incoming error
+         ! variance is negative, add no noise to the values, but do switch the
+         ! sign on the error so the file is useful in subsequent runs.
+         errvar = get_obs_def_error_variance(obs_def)
+         if (errvar > 0.0_r8) then
+            obs_value(1) = random_gaussian(random_seq, true_obs(1), errvar)
+         else
+            obs_value(1) = true_obs(1)
+            call set_obs_def_error_variance(obs_def, -errvar)
+            call set_obs_def(obs, obs_def)
+         endif
 
          ! Set qc to 0 if none existed before
          if(cnum_qc == 0) then
@@ -388,6 +407,124 @@
 
 end subroutine perfect_read_restart
 
-!---------------------------------------------------------------------
- 
+!-------------------------------------------------------------------------
+
+subroutine set_trace(trace_execution, output_timestamps, silence)
+
+logical, intent(in) :: trace_execution
+logical, intent(in) :: output_timestamps
+logical, intent(in) :: silence
+
+! Set whether other modules trace execution with messages
+! and whether they output timestamps to trace overall performance
+
+! defaults
+trace_level     = 0
+timestamp_level = 0
+
+! selectively turn stuff back on
+if (trace_execution)   trace_level     = 1
+if (output_timestamps) timestamp_level = 1
+
+! turn as much off as possible
+if (silence) then
+   trace_level     = -1
+   timestamp_level = -1
+endif
+
+call set_obs_model_trace(trace_level, timestamp_level)
+
+end subroutine set_trace
+
+!-------------------------------------------------------------------------
+
+subroutine trace_message(msg, label, threshold)
+
+character(len=*), intent(in)           :: msg
+character(len=*), intent(in), optional :: label
+integer,          intent(in), optional :: threshold
+
+! Write message to stdout and log file.
+integer :: t
+
+t = 0
+if (present(threshold)) t = threshold
+
+if (trace_level <= t) return
+
+if (present(label)) then
+   call error_handler(E_MSG,trim(label),trim(msg))
+else
+   call error_handler(E_MSG,'p_m_o trace:',trim(msg))
+endif
+
+end subroutine trace_message
+
+!-------------------------------------------------------------------------
+
+subroutine timestamp_message(msg, sync)
+
+character(len=*), intent(in) :: msg
+logical, intent(in), optional :: sync
+
+! Write current time and message to stdout and log file. 
+! if sync is present and true, sync mpi jobs before printing time.
+
+if (timestamp_level <= 0) return
+
+if (present(sync)) then
+  if (sync) call task_sync()
+endif
+
+call timestamp(trim(msg), pos='debug')
+
+end subroutine timestamp_message
+
+!-------------------------------------------------------------------------
+
+subroutine print_ens_time(ens_handle, msg)
+
+type(ensemble_type), intent(in) :: ens_handle
+character(len=*), intent(in) :: msg
+
+! Write message to stdout and log file.
+type(time_type) :: mtime
+
+if (trace_level <= 0) return
+
+if (get_my_num_copies(ens_handle) < 1) return
+
+call get_ensemble_time(ens_handle, 1, mtime)
+call print_time(mtime, msg, logfileunit)
+call print_time(mtime, msg)
+
+end subroutine print_ens_time
+
+!-------------------------------------------------------------------------
+
+subroutine print_obs_time(seq, key, msg)
+
+type(obs_sequence_type), intent(in) :: seq
+integer, intent(in) :: key
+character(len=*), intent(in), optional :: msg
+
+! Write time of an observation to stdout and log file.
+type(obs_type) :: obs
+type(obs_def_type) :: obs_def
+type(time_type) :: mtime
+
+if (trace_level <= 0) return
+
+call init_obs(obs, 0, 0)
+call get_obs_from_key(seq, key, obs)
+call get_obs_def(obs, obs_def)
+mtime = get_obs_def_time(obs_def)
+call print_time(mtime, msg, logfileunit)
+call print_time(mtime, msg)
+call destroy_obs(obs)
+
+end subroutine print_obs_time
+
+!-------------------------------------------------------------------------
+
 end program perfect_model_obs

Modified: DART/trunk/smoother/smoother_mod.f90
===================================================================
--- DART/trunk/smoother/smoother_mod.f90	2009-05-11 22:28:58 UTC (rev 3870)
+++ DART/trunk/smoother/smoother_mod.f90	2009-05-11 22:31:11 UTC (rev 3871)
@@ -396,8 +396,14 @@
    !                                ' data, cycle index', smoother_index
    !call error_handler(E_MSG,'smoother_assim',errstring)
 
-   write(errstring, '(A,I4,A)') 'starting assimilate pass for lag', i, ' data'
-   call error_handler(E_MSG,'smoother_assim',errstring)
+   write(errstring, '(A,I4,A)') 'Starting reassimilate pass for lag', i, ' data'
+   if (print_trace_details >= 0) call error_handler(E_MSG,'smoother_assim:',errstring)
+   if (print_trace_details >= 1) then
+      call print_time(lag_handle(smoother_index)%time(1), &
+         ' smoother_assim: Time of lagged data is: ', logfileunit)
+      call print_time(lag_handle(smoother_index)%time(1), &
+         ' smoother_assim: Time of lagged data is: ')
+   endif
 
    ! NEED A LAG INFLATE TYPE THAT DOES NO INFLATION FOR NOW
    call filter_assim(lag_handle(smoother_index), obs_ens_handle, &
@@ -615,8 +621,8 @@
 ! large the value is.)
  
 
-if (execution_level >= 0) print_trace_details = execution_level
-if (timestamp_level >= 0) print_timestamps    = timestamp_level
+print_trace_details = execution_level
+print_timestamps    = timestamp_level
 
 end subroutine set_smoother_trace
 


More information about the Dart-dev mailing list