source: palm/trunk/SOURCE/user_dvrp_coltab.f90 @ 258

Last change on this file since 258 was 258, checked in by heinze, 15 years ago

Output of messages replaced by message handling routine.

  • Property svn:keywords set to Id
File size: 1.0 KB
RevLine 
[211]1 SUBROUTINE user_dvrp_coltab( mode, variable )
2
3!------------------------------------------------------------------------------!
[258]4! Current revisions:
[211]5! -----------------
[258]6! Output of messages replaced by message handling routine.
[211]7!
[258]8!
[211]9! Former revisions:
10! -----------------
11! $Id: user_dvrp_coltab.f90 258 2009-03-13 12:36:03Z heinze $
12!
[226]13! 211 2008-11-11 04:46:24Z raasch
14! Former file user_interface.f90 split into one file per subroutine
15!
[211]16! Description:
17! ------------
18! Definition of the colour table to be used by the dvrp software.
19!------------------------------------------------------------------------------!
[258]20   
21    USE control_parameters
[211]22    USE dvrp_variables
23    USE pegrid
24    USE user
25
26    IMPLICIT NONE
27
28    CHARACTER (LEN=*) ::  mode
29    CHARACTER (LEN=*) ::  variable
30
31
32!
33!-- Here the user-defined actions follow
34    SELECT CASE ( mode )
35
36       CASE ( 'particles' )
37
38       CASE ( 'slicer' )
39
40       CASE DEFAULT
[258]41          message_string = 'unknown mode "' // mode // '"'
42          CALL message( 'user_dvrp_coltab', 'UI0004', 1, 2, 0, 6, 0 )
[211]43
[258]44
[211]45    END SELECT
46
47 END SUBROUTINE user_dvrp_coltab
48
Note: See TracBrowser for help on using the repository browser.