ReadDataFileUnit Subroutine

private subroutine ReadDataFileUnit(network, fileunit, time, aggr_time, aggr_type, tresh)

read data from file unit. Data spanned on multiple time steps can be aggregated computing average, cumulated, maximum or minimum. Aggregated value is considered as missing if number of actual available observations is less than a given percentage (tresh)

Arguments

Type IntentOptional Attributes Name
type(ObservationalNetwork), intent(inout) :: network
integer(kind=short), intent(in) :: fileunit
type(DateTime), intent(in), optional :: time
integer(kind=short), intent(in), optional :: aggr_time
character(len=*), intent(in), optional :: aggr_type
real(kind=float), intent(in), optional :: tresh

Variables

Type Visibility Attributes Name Initial
integer(kind=short), public :: err_io
character(len=300), public :: filename
integer(kind=short), public :: i
integer(kind=short), public :: j
integer(kind=short), public :: nstep
integer(kind=short), public :: step
character(len=10), public :: string
type(ObservationalNetwork), public :: tempNetwork
character(len=5), public :: type
real(kind=float), public :: valid
integer(kind=short), public, POINTER :: validObs(:)

Source Code

SUBROUTINE ReadDataFileUnit &
!
(network, fileunit, time, aggr_time, aggr_type, tresh)

IMPLICIT NONE

! Arguments with intent (in):
INTEGER (KIND = short), INTENT(IN) :: fileunit

! Arguments with intent(inout):
TYPE (ObservationalNetwork), INTENT(INOUT) :: network

!Optional arguments:
TYPE (DateTime), OPTIONAL, INTENT(IN) :: time
INTEGER (KIND = short), OPTIONAL, INTENT(IN) :: aggr_time ![s]
CHARACTER (LEN = *), OPTIONAL, INTENT(IN) :: aggr_type !sum, ave, min, max
REAL (KIND = float), OPTIONAL, INTENT(IN) :: tresh ![0-1]

!local declarations:
CHARACTER (LEN = 10)   :: string
INTEGER (KIND = short) :: err_io
INTEGER (KIND = short) :: nstep
INTEGER (KIND = short) :: i, j
INTEGER (KIND = short) :: step
REAL (KIND = float)    :: valid
TYPE (ObservationalNetwork) :: tempNetwork
INTEGER (KIND = short), POINTER :: validObs(:)
CHARACTER (LEN = 300) :: filename
CHARACTER (LEN = 5) :: type

!----------------------------end of declarations-------------------------------

!Check optional arguments
IF( PRESENT(aggr_time) .AND. .not.PRESENT(aggr_type) ) THEN
    CALL Catch ('error', 'ObservationalNetworks', &
       'undefined aggregation type in routine ReadData')
END IF

!sync file to first data to read
!firstly scan for searching keyword "data"
IF ( .NOT. network % syncData) THEN
    string = ''
    DO WHILE ( .NOT. (string(1:4) == 'data'))
	    READ(fileunit,'(a)', iostat = err_io) string
	    IF (err_io /= 0) THEN
	       CALL Catch ('error', 'ObservationalNetworks', &
           'keyword data not found' )     
        END IF
        string = StringToLower (string)
    END DO
	READ(fileunit,*) !skip line
    
    !search for first data
    IF (PRESENT (time) ) THEN
        
        !scan file to search for time
        network % time = timeDefault
        DO WHILE (.not. (network % time >= time) )
            READ (fileunit,*,iostat = err_io) timeString
            
            network % time = timeString
            
        
            IF (err_io < 0) THEN !end of file reached

                INQUIRE (fileunit, NAME=filename)
			    timeString = time
	            CALL Catch ('error', 'ObservationalNetworks', &
                'time ' // timeString // ' not present in file: ', &
                argument = TRIM (filename) ) 
            END IF
        END DO    
        network % syncData = .TRUE.
        
    ELSE !sync file to first available data and return
        network % syncData = .TRUE.
        RETURN
    END IF
    
    !back to the preceding record.
    BACKSPACE (fileunit)
    IF ( network % time > time ) THEN ! back again
        BACKSPACE (fileunit)
    END IF
    
ELSE
   CALL Catch ('info', 'ObservationalNetworks', &
               ' network already synchronized to data section in file: ' , &
               argument = TRIM(network % path) ) 
END IF



IF( PRESENT(aggr_time) .AND. PRESENT(aggr_type) )THEN
        type = aggr_type
        type = StringToLower (type)
		IF((type /= 'ave').AND.(type /= 'sum').AND.&
		  (type /= 'min').AND.(type /= 'max'))THEN
		   CALL Catch ('error', 'ObservationalNetworks', &
            'wrong aggregation type in routine ReadData')
        END IF
        
        !initialize nstep
		IF( MOD(aggr_time,network % timeIncrement) == 0) THEN
			nstep = INT( aggr_time / network % timeIncrement )
		ELSE
		    CALL Catch ('error', 'ObservationalNetworks', &
            'wrong aggregation time in routine ReadData')
		END IF
END IF


!set threshold for missing data definition. Default value = 1 (100%)
IF (PRESENT(tresh)) THEN
	valid = tresh
ELSE
	valid = 1.
END IF

!set all observations value to missing data
DO i = 1, network % countObs
	network % obs (i) % value = network % nodata
END DO

!read data
IF( PRESENT(aggr_time) ) THEN
	CALL CopyNetwork (network, tempNetwork)
	ALLOCATE ( validObs(network % countObs) )
	validObs = nstep 
	DO step = 1, nstep
		READ(fileunit,*,iostat=err_io) timeString, &
		                (tempNetwork % obs(i) % value, i=1,tempNetwork % countObs)
		IF (err_io /= 0) THEN
	       CALL Catch ('error', 'ObservationalNetworks', &
           'error while reading data' )     
        END IF                
		network % time = timeString
		
		DO i = 1, tempNetwork % countObs
			IF (tempNetwork % obs (i) % value /= tempNetwork % nodata) THEN
				SELECT CASE (type(1:LEN_TRIM(type)))
					CASE ('ave','sum')
						IF (network % obs(i) % value == network % nodata) THEN
						    network % obs(i) % value = 0.
						END IF
						network % obs(i) % value = network % obs(i) % value + &
						                           tempNetwork % obs(i) % value
					CASE ('min')
						IF ((network % obs(i) % value == network % nodata) .OR. &
						   (network%obs(i)%value>tempNetwork%obs(i)%value))&
						    network%obs(i)%value=tempNetwork%obs(i)%value
					CASE ('max')
						IF ((network % obs(i) % value == network % nodata) .OR. &
						   (network % obs(i) % value < tempNetwork % obs(i) % value))&
						    network % obs(i) % value = tempNetwork % obs(i) % value
				END SELECT
			ELSE
				validObs(i) = validObs(i) - 1
			END IF
		END DO
	END DO
	
	SELECT CASE (type)
		CASE ('ave')
			DO i = 1, network % countObs
				IF((network % obs (i)% value /= network % nodata) .AND. &
				    (validObs(i) >= INT(valid*nstep)))     THEN
					network % obs(i) % value = network % obs(i) % value / validObs(i)
				ELSE
					network % obs(i) % value = network % nodata
				END IF
			END DO
		CASE ('sum')
			DO i = 1, network % countObs
				IF(.NOT.((network % obs(i) % value /= network % nodata) .AND. &
				    (validObs(i) >= INT(valid*nstep))))         THEN
					network % obs(i) % value = network % nodata
				END IF
			END DO
		CASE ('min','max')
			DO i = 1, network % countObs
				IF(.NOT.((network % obs(i) % value /= network % nodata) .AND. &
				         (validObs(i) >= INT (valid*nstep)))) THEN
					network % obs(i) % value = network % nodata
				END IF
			END DO
	END SELECT
	DEALLOCATE (tempNetwork % obs)
	DEALLOCATE (validObs)
ELSE
	READ(fileunit,*,iostat=err_io) timeString,(network % obs(j) % value,j = 1, network % countObs)
	IF (err_io /= 0) THEN
	   CALL Catch ('error', 'ObservationalNetworks', &
       'error reading  observation')     
    END IF
	
	network % time = timeString
	
END IF

RETURN
END SUBROUTINE ReadDataFileUnit