Ignore:
Timestamp:
Apr 6, 2009 6:36:10 AM (15 years ago)
Author:
raasch
Message:

further dvr updates

File:
1 edited

Legend:

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

    r274 r284  
    9393    CHARACTER (LEN=6) ::  output_variable
    9494    INTEGER ::  c_mode, c_size_x, c_size_y, c_size_z, dvrp_nop, dvrp_not,     &
    95                 gradient_normals, i, ip, j, jp, k, l, m, n, nn, section_mode, &
    96                 tv, vn
     95                gradient_normals, i, ip, j, jp, k, l, m, n, n_isosurfave,    &
     96                n_slicer, nn, section_mode, vn
    9797    INTEGER, DIMENSION(:), ALLOCATABLE ::  p_c, p_t
    9898
     
    111111!
    112112!-- Loop over all output modes choosed
    113     m           = 1
    114     tv          = 0  ! threshold counter
    115     islice_dvrp = 0  ! slice plane counter
     113    m            = 1
     114    n_isosurface = 0  ! isosurface counter (for threshold values and color)
     115    n_slicer     = 0  ! slice plane counter (for range of values)
    116116    DO WHILE ( mode_dvrp(m) /= ' ' )
    117117!
     
    131131          READ ( mode_dvrp(m), '(10X,I2)' )  vn
    132132          output_variable = do3d(0,vn)
    133           tv = tv + 1
     133          n_isosurface = n_isosurface + 1
    134134       ELSEIF ( mode_dvrp(m)(1:6) == 'slicer' )  THEN
    135135          READ ( mode_dvrp(m), '(6X,I2)' )  vn
     
    475475
    476476!
    477 !--          Definition of characteristics of isosurface material
    478 !--          Preliminary settings for w and pt!
    479              IF ( output_variable == 'w' )  THEN
    480                 IF ( tv == 1 )  THEN
    481                    tmp_r = 0.8;  tmp_g = 0.1;  tmp_b = 0.1;  tmp_t = 0.0
    482                    CALL DVRP_MATERIAL_RGB( m-1, 1, tmp_r, tmp_g, tmp_b, tmp_t )
    483                 ELSE
    484                    tmp_r = 0.1;  tmp_g = 0.1;  tmp_b = 0.8;  tmp_t = 0.0
    485                    CALL DVRP_MATERIAL_RGB( m-1, 1, tmp_r, tmp_g, tmp_b, tmp_t )
    486                 ENDIF
    487              ELSEIF ( output_variable == 'pt' )  THEN
    488                 tmp_r = 0.8;  tmp_g = 0.1;  tmp_b = 0.1;  tmp_t = 0.0
    489                 CALL DVRP_MATERIAL_RGB( m-1, 1, tmp_r, tmp_g, tmp_b, tmp_t )
    490              ELSE
    491                 tmp_r = 0.9;  tmp_g = 0.9;  tmp_b = 0.9;  tmp_t = 0.0
    492                 CALL DVRP_MATERIAL_RGB( m-1, 1, tmp_r, tmp_g, tmp_b, tmp_t )
    493              ENDIF
    494              WRITE(9,*) '#8.1'
    495              CALL local_flush( 9 )
     477!--          Definition of isosurface color
     478             tmp_r = isosurface_color(1,n_isosurface)
     479             tmp_g = isosurface_color(2,n_isosurface)
     480             tmp_b = isosurface_color(3,n_isosurface)
     481             tmp_t = 0.0
     482             CALL DVRP_MATERIAL_RGB( m-1, 1, tmp_r, tmp_g, tmp_b, tmp_t )
    496483
    497484!
     
    525512
    526513             IF ( dvrp_overlap )  THEN
    527                 tmp_th = threshold(tv)
     514                tmp_th = threshold(n_isosurface)
    528515             ELSE
    529516                tmp_th = 1.0   ! nothing is plotted because array values are 0
     
    559546             CALL DVRP_MATERIAL_RGB( m-1, 1, tmp_r, tmp_g, tmp_b, tmp_t )
    560547
    561              islice_dvrp = islice_dvrp + 1
    562 !             CALL DVRP_COLORFUNCTION( m-1, DVRP_CM_HLS, 25,                    &
    563 !                                      slicer_range_limits_dvrp(:,islice_dvrp), &
     548             n_slicer = n_slicer + 1
     549
     550!
     551!--           Using dolorfunction has not been properly tested
     552!             islice_dvrp = n_slicer
     553!             CALL DVRP_COLORFUNCTION( m-1, DVRP_CM_HLS, 25,                 &
     554!                                      slicer_range_limits_dvrp(:,n_slicer), &
    564555!                                      color_dvrp )
    565556
     557!
     558!--          Set interval of values defining the colortable
     559             CALL set_slicer_attributes_dvrp( n_slicer )
     560
     561!
     562!--          Create user-defined colortable
    566563             CALL user_dvrp_coltab( 'slicer', output_variable )
    567564
Note: See TracChangeset for help on using the changeset viewer.