19 use base_utils,
only : tostr
20 use base_strings,
only : lowercase
45 integer :: food_items_encountered
47 integer :: food_items_ingested_total
49 integer :: food_items_not_ingested_total
51 integer :: n_food_items_stomach
53 integer :: n_food_items_midgut
55 real(srp) :: fish_appetite
57 real(srp) :: food_mass_total_stomach
59 real(srp) :: food_mass_total_midgut
62 real(srp) :: food_mass_absorb_total_midgut
65 real(srp) :: food_mass_absorb_cumulate
67 real(srp) :: food_mass_absorb_rate_instant
69 real(srp) :: oxygen_uptake_total
71 real(srp) :: baseline_smr
73 real(srp) :: active_amr
75 real(srp) :: branchial_ue_ze
77 real(srp) :: digestion_cost_sda
79 real(srp) :: mass_evacuated_cumulative
82 real(srp) :: energy_balance_total
85 real(srp) :: body_mass_dynamics
90 real(srp) :: current_activity
103 real(srp) :: total_mass_food_ingested
104 real(srp) :: total_mass_evacuated
119 integer,
optional,
intent(in) :: hours
120 integer(LONG) :: time_steps
122 if (
present(hours))
then
123 time_steps = hours *
hour
137 integer(LONG),
optional,
intent(in) :: time_steps
139 integer(LONG) :: time_steps_loc
141 if (
present(time_steps))
then
142 time_steps_loc = time_steps
183 class(
fish),
intent(in) :: this_fish
187 integer(LONG),
optional,
intent(in) :: time_step
189 real(srp),
optional,
intent(in) :: temperature
192 integer(LONG) :: time_step_loc
193 real(srp) :: temp_loc
195 if (
present(time_step))
then
196 time_step_loc = time_step
201 if (
present(temperature))
then
202 temp_loc = temperature
209 this_fish%food_items_midgut(1:this_fish%n_food_items_midgut) )
211 aout%fish_appetite = this_fish%appetite()
212 aout%food_mass_total_stomach = this_fish%st_food_mass()
213 aout%food_mass_total_midgut = this_fish%mg_food_mass()
214 aout%n_food_items_stomach = this_fish%n_food_items_stomach
215 aout%n_food_items_midgut = this_fish%n_food_items_midgut - &
216 this_fish%n_food_items_stomach
217 aout%food_mass_absorb_total_midgut = &
218 sum( foods_midgut%absorped, foods_midgut%absorped /= missing )
221 aout%food_mass_absorb_cumulate = &
225 aout%food_mass_absorb_rate_instant = this_fish%absorption_rate()
228 aout%oxygen_uptake_total = &
229 hour *
g2mg(this_fish%uptake_o2(temperature=temp_loc, &
231 g2kg(this_fish%mass())
234 aout%baseline_smr = &
235 this_fish%smr(temperature=temp_loc, is_per_hour=.true.) / &
236 g2kg(this_fish%mass())
240 this_fish%amr(temperature=temp_loc, &
241 is_per_hour=.true.,is_exclude_smr=.false.) /&
242 g2kg( this_fish%mass() )
245 aout%digestion_cost_sda = &
246 ( this_fish%smr(temperature=temp_loc, is_per_hour=.true.)&
249 /
g2kg(this_fish%mass())
253 aout%branchial_ue_ze = 24 *
hour * &
254 this_fish%ue_ze(temperature=temp_loc, is_oxygen=.false.) &
255 /
g2kg(this_fish%mass())
262 aout%branchial_ue_ze =
hour * &
263 g2mg(this_fish%ue_ze(temperature=temp_loc,is_oxygen=.true.))&
264 /
g2kg(this_fish%mass())
269 aout%mass_evacuated_cumulative = &
270 last(this_fish%history%total_mass_evacuated)
274 aout%energy_balance_total =
last(this_fish%history%energy_balance_curr)
277 aout%body_mass_dynamics =
last(this_fish%history%body_mass_current)
278 aout%current_activity = &
279 this_fish%activity_baseline() * this_fish%activity_appetite()
283 last(this_fish%history%total_mass_food_ingested)
285 last(this_fish%history%total_mass_evacuated)
294 is_given, is_eaten, time_step, add_eaten )
298 logical,
intent(in) :: is_given
302 logical,
intent(in) :: is_eaten
306 integer(LONG),
optional,
intent(in) :: time_step
308 integer,
optional,
intent(in) :: add_eaten
311 integer(LONG) :: time_step_loc
312 integer :: add_eaten_loc
314 if (
present(time_step))
then
315 time_step_loc = time_step
317 time_step_loc = global_time_step
320 if (
present(add_eaten))
then
321 add_eaten_loc = add_eaten
326 if ( time_step_loc == 1 )
then
332 if ( is_given .and. .not. is_eaten )
then
333 output_arrays(time_step_loc)%food_items_not_ingested_total = 1
335 output_arrays(time_step_loc)%food_items_not_ingested_total = 0
349 output_arrays(time_step_loc-1)%food_items_ingested_total + add_eaten_loc
358 if ( is_given .and. .not. is_eaten )
then
359 output_arrays(time_step_loc)%food_items_not_ingested_total = &
360 output_arrays(time_step_loc-1)%food_items_not_ingested_total &
363 output_arrays(time_step_loc)%food_items_not_ingested_total = &
379 character(len=*),
intent(in) :: file_name
381 logical,
optional,
intent(in) :: is_gui_dialog
383 logical,
optional,
intent(out) :: is_write_error
385 logical :: is_gui_dialog_loc
389 type(csv_file) :: handle_csv
392 character(len=:),
allocatable :: csv_record
397 character(len=LABEL_LEN),
dimension(*),
parameter :: &
398 columns = [ character(len=label_len) :: &
421 integer(LONG) :: step
423 if (
present(is_gui_dialog))
then
424 is_gui_dialog_loc = is_gui_dialog
426 is_gui_dialog_loc = .false.
429 handle_csv%name = file_name
431 call csv_open_write( handle_csv )
433 if ( .not. handle_csv%status )
then
435 if(
present(is_write_error)) is_write_error=.true.
443 csv_record = repeat(
" ",
size(columns) * len(columns(1)) )
446 call csv_record_append( csv_record, columns )
447 call csv_record_write ( csv_record, handle_csv )
455 csv_record = repeat(
" ", &
456 max( csv_guess_record_length(
size(columns)+2, 0.0_srp), label_len ) )
460 if ( is_day(step) )
then
461 call csv_record_append(csv_record,
"DAY")
463 call csv_record_append(csv_record,
"NIGHT")
465 call csv_record_append(csv_record, &
466 tostr(global_interval_food_pattern(step)))
467 call csv_record_append(csv_record, dat%food_items_encountered)
468 call csv_record_append(csv_record, dat%food_items_ingested_total)
469 call csv_record_append(csv_record, dat%food_items_not_ingested_total)
470 call csv_record_append(csv_record, dat%n_food_items_stomach)
471 call csv_record_append(csv_record, dat%n_food_items_midgut)
472 call csv_record_append(csv_record, dat%fish_appetite)
473 call csv_record_append(csv_record, dat%food_mass_total_stomach)
474 call csv_record_append(csv_record, dat%food_mass_total_midgut)
475 call csv_record_append(csv_record, dat%food_mass_absorb_cumulate )
476 call csv_record_append(csv_record, dat%food_mass_absorb_rate_instant)
477 call csv_record_append(csv_record, dat%oxygen_uptake_total)
478 call csv_record_append(csv_record, dat%baseline_smr)
479 call csv_record_append(csv_record, dat%active_amr)
480 call csv_record_append(csv_record, dat%digestion_cost_sda)
481 call csv_record_append(csv_record, dat%branchial_ue_ze)
482 call csv_record_append(csv_record, dat%energy_balance_total)
483 call csv_record_append(csv_record, dat%body_mass_dynamics)
484 call csv_record_append(csv_record, dat%current_activity)
485 call csv_record_append(csv_record, dat%mass_evacuated_cumulative)
489 call csv_record_write( csv_record, handle_csv )
490 if ( .not. handle_csv%status )
then
492 call csv_close( handle_csv )
493 if(
present(is_write_error)) is_write_error=.true.
499 call csv_close( handle_csv )
501 if(
present(is_write_error)) is_write_error=.false.
511 character(len=*),
intent(in) :: file_name
513 logical,
optional,
intent(in) :: is_gui_dialog
515 logical,
optional,
intent(out) :: is_write_error
517 logical :: is_gui_dialog_loc
519 integer :: i, rate_unit_loc, raw_scale_max, rate_scale_y
520 real(srp),
dimension(:),
allocatable :: rows_x, &
524 y_specific_growth_rate
528 type(csv_file) :: handle_csv
531 character(len=:),
allocatable :: csv_record
532 character(len=LABEL_LEN),
dimension(*),
parameter :: &
533 columns = [ character(len=label_len) ::
"INTERVAL_HOUR", &
539 if (
present(is_gui_dialog))
then
540 is_gui_dialog_loc = is_gui_dialog
542 is_gui_dialog_loc = .false.
545 handle_csv%name = file_name
547 call csv_open_write( handle_csv )
549 if ( .not. handle_csv%status )
then
551 if(
present(is_write_error)) is_write_error=.true.
559 csv_record = repeat(
" ",
size(columns) * len(columns(1)) )
562 call csv_record_append( csv_record, columns )
563 call csv_record_write ( csv_record, handle_csv )
567 rate_unit_loc = minute * global_rate_interval
570 allocate( rows_x(raw_scale_max/rate_unit_loc), &
571 y_rate_ingested(raw_scale_max/rate_unit_loc), &
572 y_absorption_rate(raw_scale_max/rate_unit_loc), &
573 y_growth_rate(raw_scale_max/rate_unit_loc), &
574 y_specific_growth_rate(raw_scale_max/rate_unit_loc) )
576 rows_x = real([( 1 + (i-1), i=1,raw_scale_max/rate_unit_loc )], srp)
577 y_rate_ingested = cum2rate(
output_arrays%food_items_ingested_total, &
579 y_absorption_rate = cum2rate(
output_arrays%food_mass_absorb_cumulate, &
581 y_growth_rate = blockrate(
output_arrays%body_mass_dynamics, rate_unit_loc)
582 y_growth_rate(1) = 0.0_srp
584 y_specific_growth_rate = &
585 sgr(
output_arrays%body_mass_dynamics,rate_unit_loc,rate_scale_y)
586 y_specific_growth_rate(1) = 0.0_srp
589 record_wrt:
do i=1, raw_scale_max / rate_unit_loc
593 csv_record = repeat(
" ", &
594 max( csv_guess_record_length(
size(columns)+2, 0.0_srp), label_len ) )
595 call csv_record_append( csv_record, rows_x(i)*rate_unit_loc/hour )
596 call csv_record_append( csv_record, y_rate_ingested(i)*rate_scale_y )
597 call csv_record_append( csv_record, y_absorption_rate(i)*rate_scale_y)
598 call csv_record_append( csv_record, y_growth_rate(i)*rate_scale_y )
599 call csv_record_append( csv_record, y_specific_growth_rate(i) )
606 csv_record = adjustl(csv_record)
609 call csv_record_write( csv_record, handle_csv )
610 if ( .not. handle_csv%status )
then
612 call csv_close( handle_csv )
613 if(
present(is_write_error)) is_write_error=.true.
619 call csv_close( handle_csv )
621 if(
present(is_write_error)) is_write_error=.false.
627 use csv_io,
only : csv_file
628 use,
intrinsic :: iso_fortran_env, only : error_unit
629 type(csv_file),
intent(inout) :: csv_handle
631 logical,
optional,
intent(in) :: is_gui_dialog
633 write(error_unit,
"(a)")
"ERROR: cannot open CSV file '" // &
634 trim(csv_handle%name) //
"' for writing."
639 use csv_io,
only : csv_matrix_write
641 character(len=*),
intent(in) :: csv_file
644 integer,
parameter,
dimension(*) :: plot_t = [(i,i=0,38000,10)]
645 real(srp),
dimension(size(plot_t)) :: data_y
647 data_y = st_food_item_mass(plot_t)
649 call csv_matrix_write ( reshape( &
650 [real(plot_t, srp), &
652 [
size(plot_t), 2]), &
654 [
"TIME ",
"FEED_VOLUME"] &
662 use csv_io,
only : csv_matrix_write
664 character(len=*),
intent(in) :: csv_file
669 real(srp),
parameter :: incr = 0.01
670 real(srp),
parameter,
dimension(*) :: plot_x = &
671 [( incr * (i-1), i=1, floor((1.0)/incr + 1) )]
672 real(srp),
dimension(size(plot_x)) :: data_y
674 data_y = appetite_func( plot_x, global_appetite_logist_a, &
675 global_appetite_logist_r )
677 call csv_matrix_write ( reshape( &
680 [
size(plot_x), 2]), &
682 [
"RELATIVE_VOL",
"APPETITE_FAC"] &
691 character(len=:),
allocatable :: txt_out
694 character(len=*),
parameter :: rfmt =
"(f10.4)", ifmt =
"(i10)"
696 real(srp) :: ratio_ingested, ratio_fcr
700 ratio_ingested = real(outdata%food_items_ingested_total,srp) / &
701 real(outdata%food_items_encountered,srp)
704 ratio_fcr = fcr(outdata%food_items_ingested_total*global_food_item_mass,&
705 outdata%body_mass_dynamics - &
709 "General model output statistics (" &
710 // svn_version_global //
")"// crlf // crlf // &
711 " - Simulation duration, hours : " // &
712 tostr(global_run_model_hours,ifmt,.false.) // crlf // &
713 " - Total N of food items ingested : " // &
714 tostr(outdata%food_items_ingested_total,ifmt,.false.) // crlf // &
715 " - The mass of food ingested (run), g: " // &
716 tostr( outdata%food_items_ingested_total* &
717 global_food_item_mass,rfmt,.false.)//crlf//&
718 " - Total mass of food ingested, g : " // &
719 tostr(
output_stats%total_mass_food_ingested,rfmt,.false.)//crlf//&
720 " - Total cumulative absorption,g : " // &
721 tostr(outdata%food_mass_absorb_cumulate,rfmt,.false.) //crlf// &
722 " - Total energy intake from food, kJ : " // &
724 tostr(feed_energy(outdata%food_mass_absorb_cumulate ) ,rfmt, &
726 " - Total maintenance (at SMR), mg O2*: " // &
727 tostr(smr(global_body_mass, global_temperature, .true. ) &
728 * global_run_model_hours, rfmt,.false. )//crlf// &
729 " - Total maintenance energy, kJ* : " // &
731 tostr( energy_o2(o2vol(mg2g(smr(global_body_mass, &
732 global_temperature, .true. ) ) ) ) &
733 * global_run_model_hours, rfmt,.false. )//crlf// &
734 " - Energy budget at the end, kJ : " // &
735 tostr(outdata%energy_balance_total,rfmt,.false.) //crlf// &
737 " - Body mass at the start, g : " // &
738 tostr(
output_arrays(1)%body_mass_dynamics ,rfmt,.false.) //crlf// &
739 " - Body mass at the end, g : " // &
740 tostr(outdata%body_mass_dynamics,rfmt,.false.) //crlf// &
741 " - Feed conversion ratio : " // &
742 tostr(ratio_fcr,rfmt,.false.) //crlf// &
743 " - Specific growth rate (overall),%/h: " // &
744 tostr( sgr( outdata%body_mass_dynamics, &
747 global_run_model_hours, 0,-1),rfmt,.false. )//crlf// &
750 " - Body mass equivalent of energy, g*: " // &
751 tostr( energy2mass(outdata%energy_balance_total),rfmt,.false.)//crlf//&
753 " - Total mass evacuated, g : " // &
754 tostr(
output_stats%total_mass_evacuated,rfmt,.false. ) // crlf//&
755 " - Total N of food items provided : " // &
756 tostr(outdata%food_items_encountered,ifmt,.false.) // crlf // &
757 " - Ingestion ratio ingested/provided : " // &
758 tostr(ratio_ingested,rfmt,.false.) // crlf
769 use csv_io,
only : csv_record_append
770 use base_utils,
only : timestamp_full
773 logical,
optional,
intent(in) :: show_header
774 character(len=:),
allocatable :: txt_out
775 character(len=:),
allocatable :: csv_record, header_record
776 real(srp) :: ratio_ingested, ratio_fcr
777 logical :: show_header_loc
778 character(len=LABEL_LEN),
dimension(:), &
779 allocatable :: col_time, col_par, col_out, columns
781 character(len=LABEL_LEN) :: timestamp_out
782 logical,
parameter :: qte = .false.
784 timestamp_out = timestamp_full()
786 col_time = [
character(len=45) ::
"TIMESTAMP " ]
788 col_par = [
character(len=LABEL_LEN) :: &
791 "run_model_hours ", &
795 "stomach_capacity ", &
796 "midgut_capacity ", &
797 "absorption_ratio ", &
798 "ingestion_delay ", &
802 "appetite_factor_a ", &
803 "appetite_factor_r ", &
804 "appetite_threshold_stom", &
805 "digestion_delay ", &
807 "appetite_energy_rate ", &
808 "appetite_energy_shift ", &
809 "midgut_michaelis_r_max ", &
810 "midgut_michaelis_k ", &
812 "food_input_rate ", &
813 "feed_start_offset ", &
815 [(
"transport_pattern_t_" // &
817 size(global_transport_pattern_t))],&
818 [(
"transport_pattern_r_" // &
820 size(global_transport_pattern_r))],&
821 [(
"smr_oxygen_temp_" // &
823 size(global_oxygen_grid_x_temp))], &
824 [(
"smr_oxygen_o2_" // &
826 size(global_oxygen_grid_y_o2std))] ]
829 col_out = [
character(len=LABEL_LEN) :: &
833 "TOTAL_MASS_INGESTED ", &
837 "BODY_MASS_START ", &
839 "FEED_CONVERSION_RATIO ", &
840 "N_FOOD_PROVIDED ", &
841 "INGESTION_RATIO ", &
844 if (global_output_stats_is_long)
then
845 columns = [col_time, col_par, col_out]
850 if (
present(show_header))
then
851 show_header_loc = show_header
853 show_header_loc = .false.
855 csv_record = repeat(
" ",
size(columns) * len(columns(1)) )
856 header_record = csv_record
860 ratio_ingested = real(outdata%food_items_ingested_total,srp) / &
861 real(outdata%food_items_encountered,srp)
864 ratio_fcr = fcr(outdata%food_items_ingested_total*global_food_item_mass,&
865 outdata%body_mass_dynamics - &
868 call csv_record_append(header_record, columns)
870 if (global_output_stats_is_long)
then
872 call csv_record_append(csv_record, timestamp_out )
874 call csv_record_append(csv_record, global_run_model_hours)
875 call csv_record_append(csv_record, global_hours_daytime_feeding)
876 call csv_record_append(csv_record, global_temperature)
877 call csv_record_append(csv_record, global_body_mass)
878 call csv_record_append(csv_record, global_stomach_mass)
879 call csv_record_append(csv_record, global_midgut_mass)
880 call csv_record_append(csv_record, global_absorption_ratio)
881 call csv_record_append(csv_record, global_ingestion_delay_min)
882 call csv_record_append(csv_record, global_water_uptake)
883 call csv_record_append(csv_record, global_water_uptake_a)
884 call csv_record_append(csv_record, global_water_uptake_r)
885 call csv_record_append(csv_record, global_appetite_logist_a)
886 call csv_record_append(csv_record, global_appetite_logist_r)
887 call csv_record_append(csv_record, global_appetite_stomach_threshold)
888 call csv_record_append(csv_record, global_digestion_delay_min)
889 call csv_record_append(csv_record, global_maximum_duration_midgut_min)
890 call csv_record_append(csv_record, global_energy_appetite_rate)
891 call csv_record_append(csv_record, global_energy_appetite_shift)
892 call csv_record_append(csv_record, global_mid_gut_mm_r_max)
893 call csv_record_append(csv_record, global_mid_gut_mm_k_m)
894 call csv_record_append(csv_record, global_food_item_mass)
895 call csv_record_append(csv_record, global_food_input_rate)
896 call csv_record_append(csv_record, global_run_model_feed_offset)
898 call csv_record_append(csv_record, global_transport_pattern_t)
899 call csv_record_append(csv_record, global_transport_pattern_r)
900 call csv_record_append(csv_record, global_oxygen_grid_x_temp)
901 call csv_record_append(csv_record, global_oxygen_grid_y_o2std)
905 call csv_record_append(csv_record, outdata%food_items_ingested_total)
906 call csv_record_append(csv_record, outdata%food_items_ingested_total* &
907 global_food_item_mass)
908 call csv_record_append(csv_record,
output_stats%total_mass_food_ingested)
909 call csv_record_append(csv_record, outdata%food_mass_absorb_cumulate)
910 call csv_record_append(csv_record, &
911 feed_energy(outdata%food_mass_absorb_cumulate))
912 call csv_record_append(csv_record, outdata%energy_balance_total)
913 call csv_record_append(csv_record,
output_arrays(1)%body_mass_dynamics)
914 call csv_record_append(csv_record, outdata%body_mass_dynamics)
915 call csv_record_append(csv_record, ratio_fcr)
916 call csv_record_append(csv_record, outdata%food_items_encountered)
917 call csv_record_append(csv_record, ratio_ingested)
918 call csv_record_append(csv_record,
output_stats%total_mass_evacuated)
922 if (show_header_loc)
then
923 txt_out = header_record // crlf // csv_record
936 use,
intrinsic :: iso_fortran_env, only : error_unit
937 use base_random,
only : random_seed_init
941 integer,
parameter :: max_col = min(50, max_food_items_index)
943 integer(LONG) :: total_steps
945 type(food_item) :: feed
947 type(fish) :: fish_agent
949 logical :: is_given_feed, is_eaten
955 character(len=*),
parameter :: detailed_csv_file =
"debug_data_steps.csv"
958 type(csv_file) :: detailed_csv_output_handle
959 integer :: detailed_csv_n_cols
965 logical,
parameter :: progbar_hide = .true.
973 real(srp) :: mass_stomach_prev_no_shrink, mass_midgut_prev_no_shrink, &
974 mass_stomach_next_no_shrink, mass_midgut_next_no_shrink
978 if (.NOT. is_debug)
call random_seed_init()
986 call feed%init( mass=global_food_item_mass )
988 call fish_agent%new( id_num = 1 )
989 if (global_stomach_midgut_mass_is_automatic)
then
990 call fish_agent%st_init(mass=salmon_stomach_capacity(global_body_mass))
991 call fish_agent%mg_init(mass=salmon_midgut_capacity(global_body_mass))
993 call fish_agent%st_init( mass=global_stomach_mass )
994 call fish_agent%mg_init( mass=global_midgut_mass )
997 debug_report_init:
if (is_debug .and. verbose)
then
998 write(*,
"(a,f9.3)")
"DEBUG_REPORT_INIT: Initialized body_mass:", &
1000 write(*,
"(a,f9.3)")
"DEBUG_REPORT_INIT: Initialized stomach_capacity:", &
1001 fish_agent%mass_stomach
1002 write(*,
"(a,f9.3)")
"DEBUG_REPORT_INIT: Initialized midgut_capacity:", &
1003 fish_agent%mass_midgut
1004 end if debug_report_init
1006 if ( is_logging_debug ) &
1008 detailed_csv_output_handle, &
1009 detailed_csv_n_cols )
1011 time_loop:
do global_time_step = 1, total_steps
1013 debug_warn_size:
if (is_debug)
then
1014 if (fish_agent%mass() < fish_agent%body_mass0/2.0_srp) &
1015 write(*,*)
"DEBUG_WARN_SIZE: Body mass is less than 1/2 of start mass"
1016 if (fish_agent%mass() < 10.0_srp) &
1017 write(*,*)
"DEBUG_WARN_SIZE: Body mass too small: ", fish_agent%mass()
1018 end if debug_warn_size
1022 call fish_agent%decide_eat( feed%schedule(is_provided=is_given_feed), &
1023 have_eaten=is_eaten )
1026 call fish_agent%st_step()
1027 call fish_agent%mg_step()
1028 call fish_agent%energy_update()
1029 call fish_agent%do_grow()
1035 grow_stomach_midgut:
if (global_stomach_midgut_mass_is_automatic)
then
1037 mass_stomach_prev_no_shrink = fish_agent%mass_stomach
1038 mass_midgut_prev_no_shrink = fish_agent%mass_midgut
1040 mass_stomach_next_no_shrink = salmon_stomach_capacity(fish_agent%mass())
1041 mass_midgut_next_no_shrink = salmon_midgut_capacity(fish_agent%mass())
1042 if (mass_stomach_next_no_shrink >= mass_stomach_prev_no_shrink) &
1043 fish_agent%mass_stomach = mass_stomach_next_no_shrink
1044 if (mass_midgut_next_no_shrink >= mass_midgut_prev_no_shrink) &
1045 fish_agent%mass_midgut = mass_midgut_next_no_shrink
1046 end if grow_stomach_midgut
1054 debug_absorp_cumulate_mismatch:
if ( is_debug )
then
1056 real(srp) :: abs_diff
1058 real(srp),
parameter :: verysmall = epsilon(1.0_srp) * 10.0_srp
1059 abs_diff=abs( fish_agent%history%food_mass_absorb_cum(history_size) &
1060 -
output_arrays(global_time_step)%food_mass_absorb_cumulate )
1061 if ( abs_diff > verysmall )
write(*,*) &
1062 "DEBUG_ABSORP_CUMULATE_MISMATCH: fish object absorption " // &
1063 "does not match output arrays, abs.diff =", abs_diff
1065 end if debug_absorp_cumulate_mismatch
1067 if ( is_logging_debug )
call &
1069 detailed_csv_n_cols )
1073 if ( is_logging_debug ) &
1082 character(len=*),
intent(in) :: file_name
1083 type(csv_file),
intent(inout) :: csv_handle
1084 integer,
intent(out) :: total_columns
1092 character(len=LABEL_LEN),
dimension(*),
parameter :: &
1093 COLUMNS_FIX = [ character(len=label_len) :: &
1116 character(len=LABEL_LEN),
dimension(MAX_COL*5) :: COLUMNS_NUM
1120 character(len=:),
allocatable :: csv_record
1123 columns_num = [
character(len=LABEL_LEN) :: &
1124 [(
"STOM_TIME_" // TOSTR(i,10),i=1,max_col)], &
1125 [(
"STOM_MASS_" // tostr(i,10),i=1,max_col)], &
1126 [(
"MIDG_TIME_" // tostr(i,10),i=1,max_col)], &
1127 [(
"MIDG_MASS_" // tostr(i,10),i=1,max_col)], &
1128 [(
"ABSORP_" // tostr(i,10),i=1,max_col)] ]
1130 csv_handle%name = file_name
1132 total_columns =
size(columns_fix) +
size(columns_num)
1135 call csv_open_write( csv_handle )
1136 if ( .not. csv_handle%status )
then
1145 csv_record = repeat(
" ", (
size(columns_fix)+
size(columns_num)) &
1149 call csv_record_append( csv_record, [ columns_fix, columns_num ] )
1150 call csv_record_write ( csv_record, csv_handle )
1151 if ( .not. csv_handle%status )
then
1153 call csv_close( csv_handle )
1163 type(csv_file),
intent(inout) :: csv_handle
1165 call csv_close( csv_handle )
1175 type(csv_file),
intent(inout) :: csv_handle
1176 integer,
intent(in) :: total_columns
1180 character(len=:),
allocatable :: csv_record
1184 csv_record = repeat(
" ", &
1185 max( csv_guess_record_length(total_columns+2, 0.0_srp), label_len ) )
1189 call csv_record_append(csv_record, global_time_step)
1190 call csv_record_append(csv_record, &
1191 tostr(global_interval_food_pattern(global_time_step)) )
1192 call csv_record_append(csv_record, &
1194 call csv_record_append(csv_record, &
1195 output_arrays(global_time_step)%food_items_not_ingested_total )
1196 call csv_record_append(csv_record, fish_agent%appetite_stomach() )
1197 call csv_record_append(csv_record, fish_agent%appetite_midgut() )
1199 call csv_record_append(csv_record, fish_agent%appetite_energy() )
1201 call csv_record_append(csv_record, &
1203 call csv_record_append(csv_record, fish_agent%st_food_mass() )
1205 call csv_record_append(csv_record, fish_agent%st_food_mass() / &
1206 fish_agent%mass_stomach )
1208 call csv_record_append(csv_record, fish_agent%n_food_items_stomach )
1209 call csv_record_append(csv_record, fish_agent%mg_food_mass() )
1211 call csv_record_append(csv_record, fish_agent%mg_food_mass() / &
1212 fish_agent%mass_midgut )
1213 call csv_record_append( &
1215 michaelis_menten(fish_agent%mg_food_mass() / &
1216 fish_agent%mass_midgut, &
1217 global_mid_gut_mm_r_max, &
1218 global_mid_gut_mm_k_m ) )
1219 call csv_record_append(csv_record, fish_agent%n_food_items_midgut )
1220 call csv_record_append(csv_record, &
1221 output_arrays(global_time_step)%food_mass_absorb_total_midgut )
1223 call csv_record_append(csv_record, &
1227 call csv_record_append(csv_record, &
1228 fish_agent%food_items_stomach(1:max_col)%time_in_process )
1229 call csv_record_append(csv_record, &
1230 fish_agent%food_items_stomach(1:max_col)%mass )
1231 call csv_record_append(csv_record, &
1232 fish_agent%food_items_midgut(1:max_col)%time_in_process )
1233 call csv_record_append(csv_record, &
1234 fish_agent%food_items_midgut(1:max_col)%mass )
1235 call csv_record_append(csv_record, &
1236 fish_agent%food_items_midgut(1:max_col)%absorped )
1239 call csv_record_write( csv_record, csv_handle )
1240 if ( .not. csv_handle%status )
then
1242 call csv_close( csv_handle )
1257 integer(LONG),
intent(in),
optional :: time_steps
1259 logical :: is_file_readable
1261 integer(LONG) :: time_steps_loc
1263 if (
present(time_steps))
then
1264 time_steps_loc = time_steps
1269 if ( global_food_pattern_file ==
"" )
then
1270 call food_provisioning_pattern_init( time_steps_loc )
1273 inquire( file=global_food_pattern_file, exist=is_file_readable )
1274 if ( is_file_readable )
then
1275 if (global_food_pattern_file_is_steps)
then
1276 call food_provisioning_get_raw( time_steps_loc, &
1277 global_food_pattern_file, &
1279 is_single=.not. global_food_pattern_file_is_propagate )
1281 call food_provisioning_get_file ( time_steps_loc, &
1282 global_food_pattern_file, &
1284 is_single=.not. global_food_pattern_file_is_propagate )
1287 write(error_unit,*)
"WARNING: ",
"Food provision file ", &
1288 trim(global_food_pattern_file),
" does not exist, ", &
1289 "use `food_provision_pattern`."
1290 call food_provisioning_pattern_init( time_steps_loc )
1300 integer,
allocatable,
dimension(:) :: food_items_encountered
1302 type(food_item),
target :: feed_check
1303 type(food_item),
pointer :: feed_pt
1306 integer(LONG) :: i, isum, istep
1307 logical :: is_given_feed
1309 allocate(food_items_encountered(global_run_model_hours * hour))
1311 food_items_encountered = 0
1314 do i = 1, global_run_model_hours * hour
1315 feed_pt => feed_check%schedule( i, is_provided=is_given_feed )
1316 if (
associated(feed_pt)) isum = isum + 1
1317 food_items_encountered(i) = isum
1327 integer,
intent(in),
optional :: rate_unit
1328 real(srp),
allocatable,
dimension(:) :: consumption
1330 integer :: rate_unit_loc
1331 integer(LONG) :: full_max, i, ii
1334 integer,
allocatable,
dimension(:) :: int_ingested, int_provided
1336 if (
present(rate_unit))
then
1337 rate_unit_loc = rate_unit
1339 rate_unit_loc = minute
1344 allocate( int_ingested(full_max/rate_unit_loc), &
1345 int_provided(full_max/rate_unit_loc), &
1346 consumption(full_max/rate_unit_loc) )
1350 consumption = 0.0_srp
1353 do i = 1 + rate_unit_loc, full_max, rate_unit_loc
1354 int_ingested(ii)=
output_arrays(i)%food_items_ingested_total - &
1356 int_provided(ii)=
output_arrays(i)%food_items_encountered - &
1362 where(int_provided > 0)
1363 consumption = real(int_ingested,srp) / real(int_provided,srp)
Return the last element of a history array with optional offset.
subroutine detailed_csv_output_write_record(csv_handle, total_columns)
Write the step-wise CSV output record with the actual data. Note that these detailed outputs are prod...
subroutine detailed_csv_output_close(csv_handle)
Close the CSV output file with the detailed step-wise data. Note that these detailed outputs are prod...
subroutine detailed_csv_output_open(file_name, csv_handle, total_columns)
Open the CSV output file with the detailed step-wise data. Note that these detailed outputs are produ...
This module defines global parameters and general-level computational utilities.
elemental real(srp) function g2kg(g)
Convert g to kg.
real(srp), public global_sda_absorp_rate_max
Defines the specific dynamic action (SDA) that depends on the absorption rate. There are two paramete...
integer, public global_run_model_hours
Default duration of the model run in hours. Note that parameter file uses hours as unit....
integer, parameter, public hour
Global time constants, number of sec in hour and min.
real(srp), public global_temperature
Ambient temperature Configuration file example:
real(srp), public global_sda_factor_max
Defines the specific dynamic action (SDA) that depends on the absorption rate. There are two paramete...
elemental real(srp) function g2mg(g)
Convert g to mg.
integer(long), public global_time_step
Global variable that defines the current time step.
Module that defines the runtime behaviour of the model.
impure subroutine output_arrays_update_step(this_fish, time_step, temperature)
Update model output arrays output_arrays.
impure subroutine test_run()
The procedure below is TEMPORARY, for testing and debugging.
impure subroutine output_arrays_init(time_steps)
Allocate model output arrays output_arrays.
logical, parameter is_extended_logging_debug_test
Flag for extended/detailed debug logging.
pure integer(long) function total_timesteps(hours)
Calculate the total number of time steps in the model from the number of hours. This in fact converts...
impure subroutine init_provisioning(time_steps)
Initialise the food provisioning schedule / pattern.
logical, parameter, private is_urinal_branchial_kj_day
Flag that defines how urinal and branchial energy loss (UE+ZE) is calculated for model output arrays....
real(srp) function, dimension(:), allocatable get_ingestion_ratio_waste(rate_unit)
calculate the array of the consumption ratio, i.e. eaten/provided, so it is also easy to calculate th...
impure subroutine output_arrays_save_csv(file_name, is_gui_dialog, is_write_error)
Save the model output arrays to a CSV data file.
impure subroutine csv_file_error_report(csv_handle, is_gui_dialog)
Report CSV file write error.
impure integer function, dimension(:), allocatable get_food_schedule_display()
Determine the food schedule array for separate display and analysis The primary role of this function...
integer, public gui_idx_progress
Progress bar widget ID for the GUI mode, needed to update at runtime.
impure subroutine stomach_transport_save_csv(csv_file)
Save the stomach transport data pattern for a single food item.
impure subroutine output_arrays_add_ingested(is_given, is_eaten, time_step, add_eaten)
Update the cumulative count of food items ingested. This cannot normally be done in output_arrays_upd...
character(len=:) function, allocatable model_output_stats_row_csv(show_header)
Produce a text string containing general model output statistics.
type(output_stats_total_def) output_stats
output_stats instantiates non-array global data structure that keeps total model output statistics,...
impure subroutine appetite_function_save_csv(csv_file)
Save the appetite function the_fish::appetite_func() pattern for plotting, testing or analysis.
type(output_arrays_step_def), dimension(:), allocatable, public output_arrays
output_arrays instantiates the global data structure that keeps the model output arrays.
pure character(len=:) function, allocatable model_output_stats_txt()
Produce a text string containing general model output statistics.
impure subroutine output_arrays_save_rate_data_csv(file_name, is_gui_dialog, is_write_error)
Save the rate data arrays to a CSV data file.
This module defines the fish and its components. The model is discrete, time is based on time steps,...
integer, parameter, public history_size
The size of the history that saves the fish data back in time.
This data structure keeps the output values for each time step. It should normally be instantiated as...
Overall output statistics that are output from the model.
Defines an umbrella class for the complete fish organism An outline of the ::fish class inheritance i...