LCOV - code coverage report
Current view: top level - binary/private - pgbinary_grid.f90 (source / functions) Coverage Total Hit
Test: coverage.info Lines: 0.0 % 154 0
Test Date: 2025-10-14 06:41:40 Functions: 0.0 % 10 0

            Line data    Source code
       1              : ! ***********************************************************************
       2              : !
       3              : !   Copyright (C) 2014-2022  The MESA Team, Bill Paxton & Matthias Fabry
       4              : !
       5              : !   This program is free software: you can redistribute it and/or modify
       6              : !   it under the terms of the GNU Lesser General Public License
       7              : !   as published by the Free Software Foundation,
       8              : !   either version 3 of the License, or (at your option) any later version.
       9              : !
      10              : !   This program is distributed in the hope that it will be useful,
      11              : !   but WITHOUT ANY WARRANTY; without even the implied warranty of
      12              : !   MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.
      13              : !   See the GNU Lesser General Public License for more details.
      14              : !
      15              : !   You should have received a copy of the GNU Lesser General Public License
      16              : !   along with this program. If not, see <https://www.gnu.org/licenses/>.
      17              : !
      18              : ! ***********************************************************************
      19              : 
      20              : module pgbinary_grid
      21              : 
      22              :    use binary_def
      23              :    use const_def, only: dp
      24              :    use pgbinary_support
      25              : 
      26              :    implicit none
      27              : 
      28              : 
      29              : contains
      30              : 
      31              : 
      32            0 :    subroutine grid1_plot(id, device_id, ierr)
      33              :       integer, intent(in) :: id, device_id
      34              :       integer, intent(out) :: ierr
      35              :       type (binary_info), pointer :: b
      36              :       ierr = 0
      37            0 :       call get_binary_ptr(id, b, ierr)
      38            0 :       if (ierr /= 0) return
      39              :       call Grid_plot(b, id, device_id, &
      40              :          b% pg% Grid1_xleft, b% pg% Grid1_xright, &
      41              :          b% pg% Grid1_ybot, b% pg% Grid1_ytop, .false., b% pg% Grid1_title, &
      42              :          b% pg% Grid1_txt_scale_factor, &
      43              :          b% pg% Grid1_num_cols, &
      44              :          b% pg% Grid1_num_rows, &
      45              :          b% pg% Grid1_num_plots, &
      46              :          b% pg% Grid1_plot_name, &
      47              :          b% pg% Grid1_plot_row, &
      48              :          b% pg% Grid1_plot_rowspan, &
      49              :          b% pg% Grid1_plot_col, &
      50              :          b% pg% Grid1_plot_colspan, &
      51              :          b% pg% Grid1_plot_pad_left, &
      52              :          b% pg% Grid1_plot_pad_right, &
      53              :          b% pg% Grid1_plot_pad_top, &
      54              :          b% pg% Grid1_plot_pad_bot, &
      55            0 :          ierr)
      56              :    end subroutine grid1_plot
      57              : 
      58              : 
      59            0 :    subroutine grid2_plot(id, device_id, ierr)
      60              :       integer, intent(in) :: id, device_id
      61              :       integer, intent(out) :: ierr
      62              :       type (binary_info), pointer :: b
      63              :       ierr = 0
      64            0 :       call get_binary_ptr(id, b, ierr)
      65            0 :       if (ierr /= 0) return
      66              :       call Grid_plot(b, id, device_id, &
      67              :          b% pg% Grid2_xleft, b% pg% Grid2_xright, &
      68              :          b% pg% Grid2_ybot, b% pg% Grid2_ytop, .false., b% pg% Grid2_title, &
      69              :          b% pg% Grid2_txt_scale_factor, &
      70              :          b% pg% Grid2_num_cols, &
      71              :          b% pg% Grid2_num_rows, &
      72              :          b% pg% Grid2_num_plots, &
      73              :          b% pg% Grid2_plot_name, &
      74              :          b% pg% Grid2_plot_row, &
      75              :          b% pg% Grid2_plot_rowspan, &
      76              :          b% pg% Grid2_plot_col, &
      77              :          b% pg% Grid2_plot_colspan, &
      78              :          b% pg% Grid2_plot_pad_left, &
      79              :          b% pg% Grid2_plot_pad_right, &
      80              :          b% pg% Grid2_plot_pad_top, &
      81              :          b% pg% Grid2_plot_pad_bot, &
      82            0 :          ierr)
      83              :    end subroutine grid2_plot
      84              : 
      85              : 
      86            0 :    subroutine grid3_plot(id, device_id, ierr)
      87              :       integer, intent(in) :: id, device_id
      88              :       integer, intent(out) :: ierr
      89              :       type (binary_info), pointer :: b
      90              :       ierr = 0
      91            0 :       call get_binary_ptr(id, b, ierr)
      92            0 :       if (ierr /= 0) return
      93              :       call Grid_plot(b, id, device_id, &
      94              :          b% pg% Grid3_xleft, b% pg% Grid3_xright, &
      95              :          b% pg% Grid3_ybot, b% pg% Grid3_ytop, .false., b% pg% Grid3_title, &
      96              :          b% pg% Grid3_txt_scale_factor, &
      97              :          b% pg% Grid3_num_cols, &
      98              :          b% pg% Grid3_num_rows, &
      99              :          b% pg% Grid3_num_plots, &
     100              :          b% pg% Grid3_plot_name, &
     101              :          b% pg% Grid3_plot_row, &
     102              :          b% pg% Grid3_plot_rowspan, &
     103              :          b% pg% Grid3_plot_col, &
     104              :          b% pg% Grid3_plot_colspan, &
     105              :          b% pg% Grid3_plot_pad_left, &
     106              :          b% pg% Grid3_plot_pad_right, &
     107              :          b% pg% Grid3_plot_pad_top, &
     108              :          b% pg% Grid3_plot_pad_bot, &
     109            0 :          ierr)
     110              :    end subroutine grid3_plot
     111              : 
     112              : 
     113            0 :    subroutine grid4_plot(id, device_id, ierr)
     114              :       integer, intent(in) :: id, device_id
     115              :       integer, intent(out) :: ierr
     116              :       type (binary_info), pointer :: b
     117              :       ierr = 0
     118            0 :       call get_binary_ptr(id, b, ierr)
     119            0 :       if (ierr /= 0) return
     120              :       call Grid_plot(b, id, device_id, &
     121              :          b% pg% Grid4_xleft, b% pg% Grid4_xright, &
     122              :          b% pg% Grid4_ybot, b% pg% Grid4_ytop, .false., b% pg% Grid4_title, &
     123              :          b% pg% Grid4_txt_scale_factor, &
     124              :          b% pg% Grid4_num_cols, &
     125              :          b% pg% Grid4_num_rows, &
     126              :          b% pg% Grid4_num_plots, &
     127              :          b% pg% Grid4_plot_name, &
     128              :          b% pg% Grid4_plot_row, &
     129              :          b% pg% Grid4_plot_rowspan, &
     130              :          b% pg% Grid4_plot_col, &
     131              :          b% pg% Grid4_plot_colspan, &
     132              :          b% pg% Grid4_plot_pad_left, &
     133              :          b% pg% Grid4_plot_pad_right, &
     134              :          b% pg% Grid4_plot_pad_top, &
     135              :          b% pg% Grid4_plot_pad_bot, &
     136            0 :          ierr)
     137              :    end subroutine grid4_plot
     138              : 
     139              : 
     140            0 :    subroutine grid5_plot(id, device_id, ierr)
     141              :       integer, intent(in) :: id, device_id
     142              :       integer, intent(out) :: ierr
     143              :       type (binary_info), pointer :: b
     144              :       ierr = 0
     145            0 :       call get_binary_ptr(id, b, ierr)
     146            0 :       if (ierr /= 0) return
     147              :       call Grid_plot(b, id, device_id, &
     148              :          b% pg% Grid5_xleft, b% pg% Grid5_xright, &
     149              :          b% pg% Grid5_ybot, b% pg% Grid5_ytop, .false., b% pg% Grid5_title, &
     150              :          b% pg% Grid5_txt_scale_factor, &
     151              :          b% pg% Grid5_num_cols, &
     152              :          b% pg% Grid5_num_rows, &
     153              :          b% pg% Grid5_num_plots, &
     154              :          b% pg% Grid5_plot_name, &
     155              :          b% pg% Grid5_plot_row, &
     156              :          b% pg% Grid5_plot_rowspan, &
     157              :          b% pg% Grid5_plot_col, &
     158              :          b% pg% Grid5_plot_colspan, &
     159              :          b% pg% Grid5_plot_pad_left, &
     160              :          b% pg% Grid5_plot_pad_right, &
     161              :          b% pg% Grid5_plot_pad_top, &
     162              :          b% pg% Grid5_plot_pad_bot, &
     163            0 :          ierr)
     164              :    end subroutine grid5_plot
     165              : 
     166              : 
     167            0 :    subroutine grid6_plot(id, device_id, ierr)
     168              :       integer, intent(in) :: id, device_id
     169              :       integer, intent(out) :: ierr
     170              :       type (binary_info), pointer :: b
     171              :       ierr = 0
     172            0 :       call get_binary_ptr(id, b, ierr)
     173            0 :       if (ierr /= 0) return
     174              :       call Grid_plot(b, id, device_id, &
     175              :          b% pg% Grid6_xleft, b% pg% Grid6_xright, &
     176              :          b% pg% Grid6_ybot, b% pg% Grid6_ytop, .false., b% pg% Grid6_title, &
     177              :          b% pg% Grid6_txt_scale_factor, &
     178              :          b% pg% Grid6_num_cols, &
     179              :          b% pg% Grid6_num_rows, &
     180              :          b% pg% Grid6_num_plots, &
     181              :          b% pg% Grid6_plot_name, &
     182              :          b% pg% Grid6_plot_row, &
     183              :          b% pg% Grid6_plot_rowspan, &
     184              :          b% pg% Grid6_plot_col, &
     185              :          b% pg% Grid6_plot_colspan, &
     186              :          b% pg% Grid6_plot_pad_left, &
     187              :          b% pg% Grid6_plot_pad_right, &
     188              :          b% pg% Grid6_plot_pad_top, &
     189              :          b% pg% Grid6_plot_pad_bot, &
     190            0 :          ierr)
     191              :    end subroutine grid6_plot
     192              : 
     193              : 
     194            0 :    subroutine grid7_plot(id, device_id, ierr)
     195              :       integer, intent(in) :: id, device_id
     196              :       integer, intent(out) :: ierr
     197              :       type (binary_info), pointer :: b
     198              :       ierr = 0
     199            0 :       call get_binary_ptr(id, b, ierr)
     200            0 :       if (ierr /= 0) return
     201              :       call Grid_plot(b, id, device_id, &
     202              :          b% pg% Grid7_xleft, b% pg% Grid7_xright, &
     203              :          b% pg% Grid7_ybot, b% pg% Grid7_ytop, .false., b% pg% Grid7_title, &
     204              :          b% pg% Grid7_txt_scale_factor, &
     205              :          b% pg% Grid7_num_cols, &
     206              :          b% pg% Grid7_num_rows, &
     207              :          b% pg% Grid7_num_plots, &
     208              :          b% pg% Grid7_plot_name, &
     209              :          b% pg% Grid7_plot_row, &
     210              :          b% pg% Grid7_plot_rowspan, &
     211              :          b% pg% Grid7_plot_col, &
     212              :          b% pg% Grid7_plot_colspan, &
     213              :          b% pg% Grid7_plot_pad_left, &
     214              :          b% pg% Grid7_plot_pad_right, &
     215              :          b% pg% Grid7_plot_pad_top, &
     216              :          b% pg% Grid7_plot_pad_bot, &
     217            0 :          ierr)
     218              :    end subroutine grid7_plot
     219              : 
     220              : 
     221            0 :    subroutine grid8_plot(id, device_id, ierr)
     222              :       integer, intent(in) :: id, device_id
     223              :       integer, intent(out) :: ierr
     224              :       type (binary_info), pointer :: b
     225              :       ierr = 0
     226            0 :       call get_binary_ptr(id, b, ierr)
     227            0 :       if (ierr /= 0) return
     228              :       call Grid_plot(b, id, device_id, &
     229              :          b% pg% Grid8_xleft, b% pg% Grid8_xright, &
     230              :          b% pg% Grid8_ybot, b% pg% Grid8_ytop, .false., b% pg% Grid8_title, &
     231              :          b% pg% Grid8_txt_scale_factor, &
     232              :          b% pg% Grid8_num_cols, &
     233              :          b% pg% Grid8_num_rows, &
     234              :          b% pg% Grid8_num_plots, &
     235              :          b% pg% Grid8_plot_name, &
     236              :          b% pg% Grid8_plot_row, &
     237              :          b% pg% Grid8_plot_rowspan, &
     238              :          b% pg% Grid8_plot_col, &
     239              :          b% pg% Grid8_plot_colspan, &
     240              :          b% pg% Grid8_plot_pad_left, &
     241              :          b% pg% Grid8_plot_pad_right, &
     242              :          b% pg% Grid8_plot_pad_top, &
     243              :          b% pg% Grid8_plot_pad_bot, &
     244            0 :          ierr)
     245              :    end subroutine grid8_plot
     246              : 
     247              : 
     248            0 :    subroutine grid9_plot(id, device_id, ierr)
     249              :       integer, intent(in) :: id, device_id
     250              :       integer, intent(out) :: ierr
     251              :       type (binary_info), pointer :: b
     252              :       ierr = 0
     253            0 :       call get_binary_ptr(id, b, ierr)
     254            0 :       if (ierr /= 0) return
     255              :       call Grid_plot(b, id, device_id, &
     256              :          b% pg% Grid9_xleft, b% pg% Grid9_xright, &
     257              :          b% pg% Grid9_ybot, b% pg% Grid9_ytop, .false., b% pg% Grid9_title, &
     258              :          b% pg% Grid9_txt_scale_factor, &
     259              :          b% pg% Grid9_num_cols, &
     260              :          b% pg% Grid9_num_rows, &
     261              :          b% pg% Grid9_num_plots, &
     262              :          b% pg% Grid9_plot_name, &
     263              :          b% pg% Grid9_plot_row, &
     264              :          b% pg% Grid9_plot_rowspan, &
     265              :          b% pg% Grid9_plot_col, &
     266              :          b% pg% Grid9_plot_colspan, &
     267              :          b% pg% Grid9_plot_pad_left, &
     268              :          b% pg% Grid9_plot_pad_right, &
     269              :          b% pg% Grid9_plot_pad_top, &
     270              :          b% pg% Grid9_plot_pad_bot, &
     271            0 :          ierr)
     272              :    end subroutine grid9_plot
     273              : 
     274              : 
     275            0 :    subroutine Grid_plot(b, id, device_id, &
     276              :       Grid_xleft, Grid_xright, &
     277              :       Grid_ybot, Grid_ytop, subplot, Grid_title, &
     278            0 :       Grid_txt_scale_factor, &
     279              :       Grid_num_cols, &
     280              :       Grid_num_rows, &
     281              :       Grid_num_plots, &
     282            0 :       Grid_plot_name, &
     283            0 :       Grid_plot_row, &
     284            0 :       Grid_plot_rowspan, &
     285            0 :       Grid_plot_col, &
     286            0 :       Grid_plot_colspan, &
     287            0 :       Grid_plot_pad_left, &
     288            0 :       Grid_plot_pad_right, &
     289            0 :       Grid_plot_pad_top, &
     290            0 :       Grid_plot_pad_bot, &
     291              :       ierr)
     292              : 
     293              :       use utils_lib, only : StrLowCase
     294              :       use pgbinary_summary_history, only : do_summary_history_plot
     295              :       use pgbinary_summary, only : &
     296              :          do_Text_Summary1_plot, do_Text_Summary2_plot, do_Text_Summary3_plot, &
     297              :          do_Text_Summary4_plot, do_Text_Summary5_plot, do_Text_Summary6_plot, &
     298              :          do_Text_Summary7_plot, do_Text_Summary8_plot, do_Text_Summary9_plot
     299              :       use pgbinary_history_panels, only : &
     300              :          do_History_Panels1_plot, do_History_Panels2_plot, do_History_Panels3_plot, &
     301              :          do_History_Panels4_plot, do_History_Panels5_plot, do_History_Panels6_plot, &
     302              :          do_History_Panels7_plot, do_History_Panels8_plot, do_History_Panels9_plot
     303              :       use pgbinary_hist_track, only : &
     304              :          do_History_Track1_plot, do_History_Track2_plot, do_History_Track3_plot, &
     305              :          do_History_Track4_plot, do_History_Track5_plot, do_History_Track6_plot, &
     306              :          do_History_Track7_plot, do_History_Track8_plot, do_History_Track9_plot
     307              :       use pgbinary_star, only : do_Star1_plot, do_Star2_plot
     308              :       use pgbinary_orbit, only : do_orbit_plot
     309              : 
     310              :       type (binary_info), pointer :: b
     311              :       logical, intent(in) :: subplot
     312              :       integer, intent(in) :: id, device_id, &
     313              :          Grid_num_cols, &
     314              :          Grid_num_rows, &
     315              :          Grid_num_plots, &
     316              :          Grid_plot_row(:), &
     317              :          Grid_plot_rowspan(:), &
     318              :          Grid_plot_col(:), &
     319              :          Grid_plot_colspan(:)
     320              :       real, intent(in) :: &
     321              :          Grid_xleft, Grid_xright, &
     322              :          Grid_ybot, Grid_ytop, &
     323              :          Grid_txt_scale_factor(:), &
     324              :          Grid_plot_pad_left(:), &
     325              :          Grid_plot_pad_right(:), &
     326              :          Grid_plot_pad_top(:), &
     327              :          Grid_plot_pad_bot(:)
     328              :       character (len = *) :: Grid_title, Grid_plot_name(:)
     329              :       integer, intent(out) :: ierr
     330              : 
     331              :       integer :: i, j, plot_id
     332              :       logical :: found_it
     333            0 :       real :: xleft, xright, ybot, ytop
     334            0 :       real :: row_height, col_width
     335              :       type (pgbinary_win_file_data), pointer :: p
     336              :       logical, parameter :: grid_subplot = .true.
     337              : 
     338              :       include 'formats'
     339              : 
     340            0 :       ierr = 0
     341              :       if (Grid_num_plots <= 0 .or. &
     342            0 :          Grid_num_cols <= 0 .or. Grid_num_rows <= 0) return
     343              : 
     344            0 :       col_width = (Grid_xright - Grid_xleft) / Grid_num_cols
     345            0 :       row_height = (Grid_ytop - Grid_ybot) / Grid_num_rows
     346              : 
     347            0 :       if (col_width <= 0d0 .or. row_height <= 0d0) then
     348            0 :          ierr = -1
     349            0 :          write(*, 1) 'Grid: col_width', col_width
     350            0 :          write(*, 1) 'row_height', row_height
     351            0 :          write(*, 1) 'Grid_xleft', Grid_xleft
     352            0 :          write(*, 1) 'Grid_xright', Grid_xright
     353            0 :          write(*, 1) 'Grid_ybot', Grid_ybot
     354            0 :          write(*, 1) 'Grid_ytop', Grid_ytop
     355            0 :          write(*, 2) 'Grid_num_cols', Grid_num_cols
     356            0 :          write(*, 2) 'Grid_num_rows', Grid_num_rows
     357            0 :          return
     358              :       end if
     359              : 
     360            0 :       call pgslct(device_id)
     361            0 :       call pgbbuf()
     362            0 :       call pgeras()
     363              : 
     364            0 :       call pgsave
     365            0 :       call pgsvp(Grid_xleft, Grid_xright, Grid_ybot, Grid_ytop)
     366            0 :       if (.not. subplot) then
     367            0 :          call show_model_number_pgbinary(b)
     368            0 :          call show_age_pgbinary(b)
     369              :       end if
     370            0 :       call show_grid_title_pgbinary(b, Grid_title)
     371            0 :       call pgunsa
     372              : 
     373            0 :       do i = 1, Grid_num_plots
     374              : 
     375            0 :          if (len_trim(Grid_plot_name(i))==0) exit
     376              : 
     377            0 :          xleft = Grid_xleft + col_width * (Grid_plot_col(i) - 1)
     378            0 :          xright = xleft + col_width * Grid_plot_colspan(i)
     379              : 
     380            0 :          ytop = Grid_ytop - row_height * (Grid_plot_row(i) - 1)
     381            0 :          ybot = ytop - row_height * Grid_plot_rowspan(i)
     382              : 
     383            0 :          xleft = xleft + Grid_plot_pad_left(i)
     384            0 :          xright = xright - Grid_plot_pad_right(i)
     385            0 :          ybot = ybot + Grid_plot_pad_bot(i)
     386            0 :          ytop = ytop - Grid_plot_pad_top(i)
     387              : 
     388            0 :          if (xright <= xleft .or. ytop <= ybot) then
     389            0 :             write(*, 2) 'Bad pgbinary grid spec', i
     390            0 :             write(*, *) 'xright <= xleft', xright <= xleft
     391            0 :             write(*, *) 'ytop <= ybot', ytop <= ybot
     392            0 :             write(*, 2) 'xleft', i, xleft
     393            0 :             write(*, 2) 'xright', i, xright
     394            0 :             write(*, 2) 'ybot', i, ybot
     395            0 :             write(*, 2) 'ytop', i, ytop
     396            0 :             write(*, 2) 'Grid_plot_pad_left(i)', i, Grid_plot_pad_left(i)
     397            0 :             write(*, 2) 'Grid_plot_pad_right(i)', i, Grid_plot_pad_right(i)
     398            0 :             write(*, 2) 'Grid_plot_pad_top(i)', i, Grid_plot_pad_top(i)
     399            0 :             write(*, 2) 'Grid_plot_pad_bot(i)', i, Grid_plot_pad_bot(i)
     400            0 :             write(*, 2) 'col_width', i, col_width
     401            0 :             write(*, 2) 'row_height', i, row_height
     402            0 :             exit
     403              :          end if
     404              : 
     405            0 :          call pgsave
     406              : 
     407            0 :          select case(StrLowCase(Grid_plot_name(i)))
     408              :          case ('summary_history')
     409              :             call do_summary_history_plot(&
     410              :                b, id, device_id, xleft, xright, ybot, ytop, grid_subplot, b% pg% Summary_History_title, &
     411            0 :                Grid_txt_scale_factor(i) * b% pg% Summary_History_txt_scale, ierr)
     412              :          case ('history_panels1')
     413              :             call do_History_Panels1_plot(&
     414              :                b, id, device_id, xleft, xright, ybot, ytop, grid_subplot, b% pg% history_Panels1_title, &
     415            0 :                Grid_txt_scale_factor(i) * b% pg% history_Panels1_txt_scale, ierr)
     416              :          case ('history_panels2')
     417              :             call do_History_Panels2_plot(&
     418              :                b, id, device_id, xleft, xright, ybot, ytop, grid_subplot, b% pg% history_Panels2_title, &
     419            0 :                Grid_txt_scale_factor(i) * b% pg% history_Panels2_txt_scale, ierr)
     420              :          case ('history_panels3')
     421              :             call do_History_Panels3_plot(&
     422              :                b, id, device_id, xleft, xright, ybot, ytop, grid_subplot, b% pg% history_Panels3_title, &
     423            0 :                Grid_txt_scale_factor(i) * b% pg% history_Panels3_txt_scale, ierr)
     424              :          case ('history_panels4')
     425              :             call do_History_Panels4_plot(&
     426              :                b, id, device_id, xleft, xright, ybot, ytop, grid_subplot, b% pg% history_Panels4_title, &
     427            0 :                Grid_txt_scale_factor(i) * b% pg% history_Panels4_txt_scale, ierr)
     428              :          case ('history_panels5')
     429              :             call do_History_Panels5_plot(&
     430              :                b, id, device_id, xleft, xright, ybot, ytop, grid_subplot, b% pg% history_Panels5_title, &
     431            0 :                Grid_txt_scale_factor(i) * b% pg% history_Panels5_txt_scale, ierr)
     432              :          case ('history_panels6')
     433              :             call do_History_Panels6_plot(&
     434              :                b, id, device_id, xleft, xright, ybot, ytop, grid_subplot, b% pg% history_Panels6_title, &
     435            0 :                Grid_txt_scale_factor(i) * b% pg% history_Panels6_txt_scale, ierr)
     436              :          case ('history_panels7')
     437              :             call do_History_Panels7_plot(&
     438              :                b, id, device_id, xleft, xright, ybot, ytop, grid_subplot, b% pg% history_Panels7_title, &
     439            0 :                Grid_txt_scale_factor(i) * b% pg% history_Panels7_txt_scale, ierr)
     440              :          case ('history_panels8')
     441              :             call do_History_Panels8_plot(&
     442              :                b, id, device_id, xleft, xright, ybot, ytop, grid_subplot, b% pg% history_Panels8_title, &
     443            0 :                Grid_txt_scale_factor(i) * b% pg% history_Panels8_txt_scale, ierr)
     444              :          case ('history_panels9')
     445              :             call do_History_Panels9_plot(&
     446              :                b, id, device_id, xleft, xright, ybot, ytop, grid_subplot, b% pg% history_Panels9_title, &
     447            0 :                Grid_txt_scale_factor(i) * b% pg% history_Panels9_txt_scale, ierr)
     448              :          case ('history_track1')
     449              :             call do_History_Track1_plot(&
     450              :                b, id, device_id, xleft, xright, ybot, ytop, grid_subplot, b% pg% history_Track1_title, &
     451            0 :                Grid_txt_scale_factor(i) * b% pg% history_Track1_txt_scale, ierr)
     452              :          case ('history_track2')
     453              :             call do_History_Track2_plot(&
     454              :                b, id, device_id, xleft, xright, ybot, ytop, grid_subplot, b% pg% history_Track2_title, &
     455            0 :                Grid_txt_scale_factor(i) * b% pg% history_Track2_txt_scale, ierr)
     456              :          case ('history_track3')
     457              :             call do_History_Track3_plot(&
     458              :                b, id, device_id, xleft, xright, ybot, ytop, grid_subplot, b% pg% history_Track3_title, &
     459            0 :                Grid_txt_scale_factor(i) * b% pg% history_Track3_txt_scale, ierr)
     460              :          case ('history_track4')
     461              :             call do_History_Track4_plot(&
     462              :                b, id, device_id, xleft, xright, ybot, ytop, grid_subplot, b% pg% history_Track4_title, &
     463            0 :                Grid_txt_scale_factor(i) * b% pg% history_Track4_txt_scale, ierr)
     464              :          case ('history_track5')
     465              :             call do_History_Track5_plot(&
     466              :                b, id, device_id, xleft, xright, ybot, ytop, grid_subplot, b% pg% history_Track5_title, &
     467            0 :                Grid_txt_scale_factor(i) * b% pg% history_Track5_txt_scale, ierr)
     468              :          case ('history_track6')
     469              :             call do_History_Track6_plot(&
     470              :                b, id, device_id, xleft, xright, ybot, ytop, grid_subplot, b% pg% history_Track6_title, &
     471            0 :                Grid_txt_scale_factor(i) * b% pg% history_Track6_txt_scale, ierr)
     472              :          case ('history_track7')
     473              :             call do_History_Track7_plot(&
     474              :                b, id, device_id, xleft, xright, ybot, ytop, grid_subplot, b% pg% history_Track7_title, &
     475            0 :                Grid_txt_scale_factor(i) * b% pg% history_Track7_txt_scale, ierr)
     476              :          case ('history_track8')
     477              :             call do_History_Track8_plot(&
     478              :                b, id, device_id, xleft, xright, ybot, ytop, grid_subplot, b% pg% history_Track8_title, &
     479            0 :                Grid_txt_scale_factor(i) * b% pg% history_Track8_txt_scale, ierr)
     480              :          case ('history_track9')
     481              :             call do_History_Track9_plot(&
     482              :                b, id, device_id, xleft, xright, ybot, ytop, grid_subplot, b% pg% history_Track9_title, &
     483            0 :                Grid_txt_scale_factor(i) * b% pg% history_Track9_txt_scale, ierr)
     484              :          case ('text_summary1')
     485              :             call do_Text_Summary1_plot(&
     486              :                b, id, device_id, xleft, xright, ybot, ytop, grid_subplot, b% pg% text_Summary1_title, &
     487            0 :                Grid_txt_scale_factor(i) * b% pg% text_Summary1_txt_scale, ierr)
     488              :          case ('text_summary2')
     489              :             call do_Text_Summary2_plot(&
     490              :                b, id, device_id, xleft, xright, ybot, ytop, grid_subplot, b% pg% text_Summary2_title, &
     491            0 :                Grid_txt_scale_factor(i) * b% pg% text_Summary2_txt_scale, ierr)
     492              :          case ('text_summary3')
     493              :             call do_Text_Summary3_plot(&
     494              :                b, id, device_id, xleft, xright, ybot, ytop, grid_subplot, b% pg% text_Summary3_title, &
     495            0 :                Grid_txt_scale_factor(i) * b% pg% text_Summary3_txt_scale, ierr)
     496              :          case ('text_summary4')
     497              :             call do_Text_Summary4_plot(&
     498              :                b, id, device_id, xleft, xright, ybot, ytop, grid_subplot, b% pg% text_Summary4_title, &
     499            0 :                Grid_txt_scale_factor(i) * b% pg% text_Summary4_txt_scale, ierr)
     500              :          case ('text_summary5')
     501              :             call do_Text_Summary5_plot(&
     502              :                b, id, device_id, xleft, xright, ybot, ytop, grid_subplot, b% pg% text_Summary5_title, &
     503            0 :                Grid_txt_scale_factor(i) * b% pg% text_Summary5_txt_scale, ierr)
     504              :          case ('text_summary6')
     505              :             call do_Text_Summary6_plot(&
     506              :                b, id, device_id, xleft, xright, ybot, ytop, grid_subplot, b% pg% text_Summary6_title, &
     507            0 :                Grid_txt_scale_factor(i) * b% pg% text_Summary6_txt_scale, ierr)
     508              :          case ('text_summary7')
     509              :             call do_Text_Summary7_plot(&
     510              :                b, id, device_id, xleft, xright, ybot, ytop, grid_subplot, b% pg% text_Summary7_title, &
     511            0 :                Grid_txt_scale_factor(i) * b% pg% text_Summary7_txt_scale, ierr)
     512              :          case ('text_summary8')
     513              :             call do_Text_Summary8_plot(&
     514              :                b, id, device_id, xleft, xright, ybot, ytop, grid_subplot, b% pg% text_Summary8_title, &
     515            0 :                Grid_txt_scale_factor(i) * b% pg% text_Summary8_txt_scale, ierr)
     516              :          case ('text_summary9')
     517              :             call do_Text_Summary9_plot(&
     518              :                b, id, device_id, xleft, xright, ybot, ytop, grid_subplot, b% pg% text_Summary9_title, &
     519            0 :                Grid_txt_scale_factor(i) * b% pg% text_Summary9_txt_scale, ierr)
     520              :          case ('star1')
     521              :             call do_Star1_plot(&
     522              :                b, id, device_id, xleft, xright, ybot, ytop, grid_subplot, b% pg% Star1_Title, &
     523            0 :                Grid_txt_scale_factor(i) * b% pg% Star1_txt_scale_factor, b% pg% Star1_plot_name, ierr)
     524              :          case ('star2')
     525              :             call do_Star2_plot(&
     526              :                b, id, device_id, xleft, xright, ybot, ytop, grid_subplot, b% pg% Star2_Title, &
     527            0 :                Grid_txt_scale_factor(i) * b% pg% Star2_txt_scale_factor, b% pg% Star2_plot_name, ierr)
     528              :          case ('orbit')
     529              :             call do_orbit_plot(&
     530              :                b, id, device_id, xleft, xright, ybot, ytop, grid_subplot, b% pg% Orbit_title, &
     531            0 :                Grid_txt_scale_factor(i) * b% pg% Orbit_txt_scale_factor, ierr)
     532              :          case default
     533              :             ! check for "other" plot
     534            0 :             found_it = .false.
     535            0 :             do j = 1, max_num_Other_plots
     536            0 :                plot_id = i_Other + j - 1
     537            0 :                p => b% pg% pgbinary_win_file_ptr(plot_id)
     538            0 :                if (p% okay_to_call_do_plot_in_binary_grid .and. &
     539            0 :                   StrLowCase(p% name) == StrLowCase(Grid_plot_name(i))) then
     540              :                   call p% do_plot_in_binary_grid(&
     541              :                      id, device_id, xleft, xright, ybot, ytop, &
     542            0 :                      Grid_txt_scale_factor(i), ierr)
     543            0 :                   found_it = .true.
     544            0 :                   exit
     545              :                end if
     546              :             end do
     547              : 
     548            0 :             if (.not. found_it) then
     549              : 
     550            0 :                write(*, *) 'FAILED TO RECOGNIZE NAME FOR GRID PLOT: ' // trim(Grid_plot_name(i))
     551              :                write(*, '(a)') &
     552            0 :                   'here are the valid names:', &
     553            0 :                   'Summary_History', &
     554            0 :                   'Text_Summary1..9', &
     555            0 :                   'History_Panels1..9', &
     556            0 :                   'History_Tracks1..9', &
     557            0 :                   'Star1,2'
     558            0 :                write(*, *)
     559              : 
     560              :             end if
     561              : 
     562              :          end select
     563              : 
     564            0 :          call pgunsa
     565              : 
     566            0 :          if (ierr /= 0) exit
     567              : 
     568              :       end do
     569              : 
     570            0 :       call pgebuf()
     571              : 
     572            0 :    end subroutine Grid_plot
     573              : 
     574              : 
     575              : end module pgbinary_grid
     576              : 
        

Generated by: LCOV version 2.0-1