Ignore:
Timestamp:
Oct 22, 2012 1:43:42 PM (12 years ago)
Author:
raasch
Message:

code has been put under the GNU General Public License (v3)

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/data_output_dvrp.f90

    r829 r1036  
    1  MODULE dvrp_color
    2 
    3     USE dvrp_variables
    4 
    5     IMPLICIT NONE
    6 
    7  CONTAINS
    8 
    9     SUBROUTINE color_dvrp( value, color )
    10 
    11        REAL, INTENT(IN)  ::  value
    12        REAL, INTENT(OUT) ::  color(4)
    13 
    14        REAL              ::  scale
    15 
    16        scale = ( value - slicer_range_limits_dvrp(1,islice_dvrp) ) / &
    17                ( slicer_range_limits_dvrp(2,islice_dvrp) -           &
    18                  slicer_range_limits_dvrp(1,islice_dvrp) )
    19 
    20        scale = MODULO( 180.0 + 180.0 * scale, 360.0 )
    21 
    22        color = (/ scale, 0.5, 1.0, 0.0 /)
    23 
    24     END SUBROUTINE color_dvrp
    25 
    26  END MODULE dvrp_color
    27 
    28 
    29  RECURSIVE SUBROUTINE data_output_dvrp
    30 
    31 !------------------------------------------------------------------------------!
     1!--------------------------------------------------------------------------------!
     2! This file is part of PALM.
     3!
     4! PALM is free software: you can redistribute it and/or modify it under the terms
     5! of the GNU General Public License as published by the Free Software Foundation,
     6! either version 3 of the License, or (at your option) any later version.
     7!
     8! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
     9! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
     10! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
     11!
     12! You should have received a copy of the GNU General Public License along with
     13! PALM. If not, see <http://www.gnu.org/licenses/>.
     14!
     15! Copyright 1997-2012  Leibniz University Hannover
     16!--------------------------------------------------------------------------------!
     17!
    3218! Current revisions:
    3319! -----------------
     
    7763! Plot of isosurface, particles and slicers with dvrp-software
    7864!------------------------------------------------------------------------------!
     65
     66 MODULE dvrp_color
     67
     68    USE dvrp_variables
     69
     70    IMPLICIT NONE
     71
     72 CONTAINS
     73
     74    SUBROUTINE color_dvrp( value, color )
     75
     76       REAL, INTENT(IN)  ::  value
     77       REAL, INTENT(OUT) ::  color(4)
     78
     79       REAL              ::  scale
     80
     81       scale = ( value - slicer_range_limits_dvrp(1,islice_dvrp) ) / &
     82               ( slicer_range_limits_dvrp(2,islice_dvrp) -           &
     83                 slicer_range_limits_dvrp(1,islice_dvrp) )
     84
     85       scale = MODULO( 180.0 + 180.0 * scale, 360.0 )
     86
     87       color = (/ scale, 0.5, 1.0, 0.0 /)
     88
     89    END SUBROUTINE color_dvrp
     90
     91 END MODULE dvrp_color
     92
     93
     94 RECURSIVE SUBROUTINE data_output_dvrp
     95
    7996#if defined( __dvrp_graphics )
    8097
Note: See TracChangeset for help on using the changeset viewer.