SUBROUTINE user_parin !------------------------------------------------------------------------------! ! Actual revisions: ! ----------------- ! Former file user_interface.f90 split into one file per subroutine ! ! Former revisions: ! ----------------- ! $Id: user_parin.f90 211 2008-11-11 04:46:24Z raasch $ ! ! Description: ! ------------ ! Interface to read user-defined namelist-parameters. !------------------------------------------------------------------------------! USE control_parameters USE pegrid USE statistics USE user IMPLICIT NONE CHARACTER (LEN=80) :: zeile INTEGER :: i, j, max_pr_user_tmp NAMELIST /userpar/ data_output_pr_user, data_output_user, region ! !-- Position the namelist-file at the beginning (it was already opened in !-- parin), search for user-defined namelist-group ("userpar", but any other !-- name can be choosed) and position the file at this line. REWIND ( 11 ) zeile = ' ' DO WHILE ( INDEX( zeile, '&userpar' ) == 0 ) READ ( 11, '(A)', END=100 ) zeile ENDDO BACKSPACE ( 11 ) ! !-- Read user-defined namelist READ ( 11, userpar ) user_defined_namelist_found = .TRUE. ! !-- Determine the number of user-defined profiles and append them to the !-- standard data output (data_output_pr) max_pr_user_tmp = 0 IF ( data_output_pr_user(1) /= ' ' ) THEN i = 1 DO WHILE ( data_output_pr(i) /= ' ' .AND. i <= 100 ) i = i + 1 ENDDO j = 1 DO WHILE ( data_output_pr_user(j) /= ' ' .AND. j <= 100 ) data_output_pr(i) = data_output_pr_user(j) max_pr_user_tmp = max_pr_user_tmp + 1 i = i + 1 j = j + 1 ENDDO ENDIF ! !-- In case of a restart run, the number of user-defined profiles on the !-- restart file (already stored in max_pr_user) has to match the one given !-- for the current run IF ( TRIM( initializing_actions ) == 'read_restart_data' ) THEN IF ( max_pr_user /= max_pr_user_tmp ) THEN PRINT*, '+++ user_parin: the number of user-defined profiles given in' PRINT*, ' data_output_pr (', max_pr_user_tmp, ' doe', & 's not match the one' PRINT*, ' found in the restart file (', max_pr_user, & ')' CALL local_stop ENDIF ELSE max_pr_user = max_pr_user_tmp ENDIF 100 RETURN END SUBROUTINE user_parin