54   '$Id: ODPS_TauCoeff.f90 2210 2008-07-01 19:30:54Z paul.vandelst@noaa.gov $'    61   TYPE(odps_taucoeff_type), 
SAVE, 
ALLOCATABLE, 
TARGET :: 
tc(:)
   169                           File_Path        , &  ! Optional input      
   170                           Quiet            , &  ! Optional input      
   171                           Process_ID       , &  ! Optional input      
   172                           Output_Process_ID, &  ! Optional input      
   174                         result( error_status )                        
   176     CHARACTER(*), 
DIMENSION(:), 
OPTIONAL, 
INTENT(IN) :: sensor_id
   177     CHARACTER(*),               
OPTIONAL, 
INTENT(IN) :: file_path
   178     INTEGER,                    
OPTIONAL, 
INTENT(IN) :: quiet
   179     INTEGER,                    
OPTIONAL, 
INTENT(IN) :: process_id
   180     INTEGER,                    
OPTIONAL, 
INTENT(IN) :: output_process_id
   181     CHARACTER(*),               
OPTIONAL, 
INTENT(IN) :: message_log
   183     INTEGER :: error_status
   185     CHARACTER(*), 
PARAMETER :: routine_name = 
'Load_TauCoeff'   187     CHARACTER(256) :: message
   188     CHARACTER(256) :: process_id_tag
   189     CHARACTER(256) :: taucoeff_file
   190     INTEGER :: allocate_status
   191     INTEGER :: n, n_sensors
   197     IF ( 
PRESENT(process_id) ) 
THEN   198       WRITE( process_id_tag, 
'(";  MPI Process ID: ",i0)' ) process_id
   204     IF ( 
PRESENT(sensor_id) ) 
THEN   206       n_sensors = 
SIZE(sensor_id)
   213     ALLOCATE(
tc(n_sensors), stat=allocate_status)
   214     IF( allocate_status /= 0 )
THEN   215       WRITE(message,
'("TauCoeff structure array allocation failed. STAT=",i0)') allocate_status
   218                             trim(message)//trim(process_id_tag), & 
   220                             message_log = message_log )
   227       IF ( 
PRESENT(sensor_id) ) 
THEN   228           taucoeff_file = trim(adjustl(sensor_id(n)))//
'.TauCoeff.bin'   231         taucoeff_file = 
'TauCoeff.bin'   235       IF ( 
PRESENT(file_path) ) 
THEN   236         taucoeff_file = trim(adjustl(file_path))//trim(taucoeff_file)
   239       error_status = read_taucoeff_binary( trim(taucoeff_file)             , &  
   242                                            process_id       =process_id       , &
   243                                            output_process_id=output_process_id, &
   244                                            message_log      =message_log        )
   245       IF ( error_status /= 
success ) 
THEN   246         WRITE(message,
'("Error reading TauCoeff file #",i0,", ",a)') &
   247                       n, trim(taucoeff_file)
   249                               trim(message)//trim(process_id_tag), &
   251                               message_log=message_log )
   311                            result( error_status )                   
   313     INTEGER,      
OPTIONAL, 
INTENT(IN)  :: process_id
   314     CHARACTER(*), 
OPTIONAL, 
INTENT(IN)  :: message_log
   316     INTEGER :: error_status
   318     CHARACTER(*), 
PARAMETER :: routine_name = 
'CRTM_Destroy_TauCoeff'   320     CHARACTER(256) :: message
   321     CHARACTER(256) :: process_id_tag
   322     INTEGER :: n, destroy_status, allocate_status
   328     IF ( 
PRESENT( process_id ) ) 
THEN   329       WRITE( process_id_tag, 
'(";  MPI Process ID: ",i0)' ) process_id
   336       destroy_status = odps_destroy_taucoeff( 
tc(n), &
   337                                               message_log=message_log )
   338       IF ( destroy_status /= 
success ) 
THEN   340         WRITE(message,
'("Error destroying TauCoeff structure array element #",i0)') n
   342                               trim(message)//trim(process_id_tag), &
   344                               message_log=message_log )
   350     DEALLOCATE(
tc, stat=allocate_status)
   351     IF( allocate_status /= 0 )
THEN   352       WRITE(message,
'("RTTOV TC structure deallocation failed. STAT=",i0)') allocate_status
   355                             trim(message)//trim(process_id_tag), &
   357                             message_log=message_log)
 integer, parameter, public failure
integer, parameter, public warning
integer function, public destroy_odps(ODPS, No_Clear, RCS_Id, Message_Log)
character(*), parameter, private module_rcs_id
integer function, public read_odps_binary(Filename, ODPS, Quiet, Process_ID, Output_Process_ID, RCS_Id, Message_Log)
recursive subroutine, public display_message(Routine_Name, Message, Error_State, Message_Log)
integer function, public destroy_taucoeff(Process_ID, Message_Log)
type(odps_taucoeff_type), dimension(:), allocatable, target, save, public tc
integer function, public load_taucoeff(Sensor_ID, File_Path, Quiet, Process_ID, Output_Process_ID, Message_Log)
integer, parameter, public success