MODULE user_actions_mod !------------------------------------------------------------------------------! ! Current revisions: ! ----------------- ! ! ! Former revisions: ! ----------------- ! $Id: user_actions.f90 392 2009-09-24 10:39:14Z maronga $ ! ! 258 2009-03-13 12:36:03Z heinze ! Output of messages replaced by message handling routine. ! ! 211 2008-11-11 04:46:24Z raasch ! Former file user_interface.f90 split into one file per subroutine ! ! Description: ! ------------ ! Execution of user-defined actions before or after single timesteps !------------------------------------------------------------------------------! PRIVATE PUBLIC user_actions INTERFACE user_actions MODULE PROCEDURE user_actions MODULE PROCEDURE user_actions_ij END INTERFACE user_actions CONTAINS !------------------------------------------------------------------------------! ! Call for all grid points !------------------------------------------------------------------------------! SUBROUTINE user_actions( location ) USE control_parameters USE cpulog USE indices USE interfaces USE pegrid USE user USE arrays_3d IMPLICIT NONE CHARACTER (LEN=*) :: location INTEGER :: i, j, k CALL cpu_log( log_point(24), 'user_actions', 'start' ) ! !-- Here the user-defined actions follow !-- No calls for single grid points are allowed at locations before and !-- after the timestep, since these calls are not within an i,j-loop SELECT CASE ( location ) CASE ( 'before_timestep' ) ! !-- Enter actions to be done before every timestep here CASE ( 'after_integration' ) ! !-- Enter actions to be done after every time integration (before !-- data output) !-- Sample for user-defined output: ! DO i = nxl-1, nxr+1 ! DO j = nys-1, nyn+1 ! DO k = nzb, nzt+1 ! u2(k,j,i) = u(k,j,i)**2 ! ENDDO ! ENDDO ! ENDDO ! DO i = nxl-1, nxr ! DO j = nys-1, nyn ! DO k = nzb, nzt+1 ! ustvst(k,j,i) = & ! ( 0.5 * ( u(k,j,i) + u(k,j,i+1) ) - hom(k,1,1,0) ) * & ! ( 0.5 * ( v(k,j,i) + v(k,j+1,i) ) - hom(k,1,2,0) ) ! ENDDO ! ENDDO ! ENDDO CASE ( 'after_timestep' ) ! !-- Enter actions to be done after every timestep here CASE ( 'u-tendency' ) ! !-- Enter actions to be done in the u-tendency term here CASE ( 'v-tendency' ) CASE ( 'w-tendency' ) CASE ( 'pt-tendency' ) CASE ( 'sa-tendency' ) CASE ( 'e-tendency' ) CASE ( 'q-tendency' ) CASE DEFAULT message_string = 'unknown location "' // location // '"' CALL message( 'user_actions', 'UI0001', 1, 2, 0, 6, 0 ) END SELECT CALL cpu_log( log_point(24), 'user_actions', 'stop' ) END SUBROUTINE user_actions !------------------------------------------------------------------------------! ! Call for grid point i,j !------------------------------------------------------------------------------! SUBROUTINE user_actions_ij( i, j, location ) USE control_parameters USE pegrid USE user IMPLICIT NONE CHARACTER (LEN=*) :: location INTEGER :: i, idum, j ! !-- Here the user-defined actions follow SELECT CASE ( location ) CASE ( 'u-tendency' ) ! !-- Enter actions to be done in the u-tendency term here CASE ( 'v-tendency' ) CASE ( 'w-tendency' ) CASE ( 'pt-tendency' ) CASE ( 'sa-tendency' ) CASE ( 'e-tendency' ) CASE ( 'q-tendency' ) CASE ( 'before_timestep', 'after_integration', 'after_timestep' ) message_string = 'location "' // location // '" is not ' // & 'allowed to be called with parameters "i" and "j"' CALL message( 'user_actions', 'UI0002', 1, 2, 0, 6, 0 ) CASE DEFAULT message_string = 'unknown location "' // location // '"' CALL message( 'user_actions', 'UI0001', 1, 2, 0, 6, 0 ) END SELECT END SUBROUTINE user_actions_ij END MODULE user_actions_mod