My Project
mod_main.f90
Go to the documentation of this file.
1 
2 
3 
4 
5 
6 
7 
8 
9 
10 
11 
12 !/===========================================================================/
13 ! Copyright (c) 2007, The University of Massachusetts Dartmouth
14 ! Produced at the School of Marine Science & Technology
15 ! Marine Ecosystem Dynamics Modeling group
16 ! All rights reserved.
17 !
18 ! FVCOM has been developed by the joint UMASSD-WHOI research team. For
19 ! details of authorship and attribution of credit please see the FVCOM
20 ! technical manual or contact the MEDM group.
21 !
22 !
23 ! This file is part of FVCOM. For details, see http://fvcom.smast.umassd.edu
24 ! The full copyright notice is contained in the file COPYRIGHT located in the
25 ! root directory of the FVCOM code. This original header must be maintained
26 ! in all distributed versions.
27 !
28 ! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS"
29 ! AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO,
30 ! THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR
31 ! PURPOSE ARE DISCLAIMED.
32 !
33 !/---------------------------------------------------------------------------/
34 ! CVS VERSION INFORMATION
35 ! $Id$
36 ! $Name$
37 ! $Revision$
38 !/===========================================================================/
39 
40 !==============================================================================|
41 ! GLOBAL LIMITS AND ARRAY SIZING PARAMETERS !
42 !==============================================================================|
43 
44 MODULE lims
45  USE mod_prec
46  IMPLICIT NONE
47  SAVE
48 
49  INTEGER ngl !!GLOBAL NUMBER OF ELEMENTS
50  INTEGER mgl !!GLOBAL NUMBER OF NODES
51  INTEGER numqbc_gl !!GLOBAL NUMBER OF FRESHWATER INFLOW NODES (RIVERS)
52  INTEGER nobclsf_gl !!GLOBAL NUMBER OF LONGSHORE FLOW ADJUSTED OPEN BOUNDARY NODES
53  INTEGER ndrft_gl !!GLOBAL NUMBER OF LAGRANGIAN TRACKING PARTICLES
54 
55  INTEGER n !!LOCAL NUMBER OF ELEMENTS
56  INTEGER m !!LOCAL NUMBER OF NODES
57  INTEGER numqbc !!LOCAL NUMBER OF FRESHWATER INFLOW NODES
58  INTEGER nobclsf !!LOCAL NUMBER OF LONGSHORE FLOW ADJUSTED OPEN BOUNDARY NODES
59  INTEGER ndrft !!LOCAL NUMBER OF LAGRANGIAN TRACKING PARTICLES
60  INTEGER nisbce_1 !!LOCAL NUMBER OF ELEMENTS WITH ISBCE = 1
61  INTEGER nisbce_2 !!LOCAL NUMBER OF ELEMENTS WITH ISBCE = 2
62  INTEGER nisbce_3 !!LOCAL NUMBER OF ELEMENTS WITH ISBCE = 3
63 
64  INTEGER kb !!NUMBER OF SIGMA LEVELS
65  INTEGER kbm1 !!NUMBER OF SIGMA LEVELS-1
66  INTEGER kbm2 !!NUMBER OF SIGMA LEVELS-2
67  INTEGER myid !!UNIQUE PROCESSOR ID (1 => NPROCS)
68  INTEGER msrid
69  INTEGER ioprocid !!PROCESSOR ID OF THE PRINTER NODE IF PRESENT
70 ! INTEGER KSL !!NUMBER OF STANDARD SEA LEVELS
71  INTEGER,POINTER:: nprocs_total !!TOTAL NUMBER OF PROCESSORS
72  INTEGER,TARGET :: nprocs !!NUMBER OF PROCESSORS IN FVCOM
73  INTEGER ne !!NUMBER OF UNIQUE EDGES (LOCAL DOMAIN ONLY)
74  INTEGER ncv !!NUMBER OF INTERNAL CONTROL VOLUMES (EXTENDED LOCAL ONLY)
75 
76  INTEGER ncv_i !!NUMBER OF INTERNAL CONTROL VOLUMES (LOCAL ONLY)
77  INTEGER nt !!TOTAL OF LOCAL INTERNAL + HALO ELEMENTS
78  INTEGER mt !!TOTAL OF LOCAL INTERNAL + HALO NODES
79  INTEGER mx_nbr_elem !!MAX NUMBER OF ELEMENTS SURROUNDING A NODE
80 
81  REAL(sp) :: memtot,memcnt
82 
83 
84 END MODULE lims
85 
86 
87 
88 !==============================================================================|
89 ! CONTROL VARIABLES |
90 !==============================================================================|
91 
92 MODULE control
93  USE mod_time
94  USE mod_prec
95  USE netcdf
96  IMPLICIT NONE
97  SAVE
98 
99  ! Stuff set inside FVCOM at compile time:
100  LOGICAL :: serial !!TRUE IF SINGLE PROCESSOR
101  LOGICAL :: msr !!TRUE IF MASTER PROCESSOR (MYID==1)
102  LOGICAL :: par !!TRUE IF MULTIPROCESSOR RUN
103  LOGICAL :: ioproc !!TRUE IF PROCESSOR IS THE IOPROC
104  LOGICAL :: in_mpi_io_loop !!TRUE IF OUTNODE IS ALREADY IN THE LOOP
105  CHARACTER(LEN=80) prg_name
106 
107  INTEGER mpi_fvcom_group !! PROCESSORS WORKING ON FVCOM
108 ! INTEGER MPI_OTHER_GROUP !! ADD OTHER GROUPS HERE
109 
110  ! FVCOM info strings
111  CHARACTER(LEN=80) fvcom_version !!STRING DESCRIBING VERSION
112  CHARACTER(LEN=80) institution !!STRING DESCRIBING FVCOM MOTHER SHIP
113  CHARACTER(LEN=80) fvcom_website !!STRING DESCRIBING WEBSITE FOR FVCOM INFO
114 
115  ! Set at command line
116  CHARACTER(LEN=80) casename !!LETTER ACRONYM SPECIFYING CASE
117  CHARACTER(LEN=80) infofile !!INFO FILE
118 
119  ! FOR LOADING RUNFILE
121  CHARACTER(LEN=80) namelist_name
122 
123  !--Parameters in NameList NML_CASE
124  CHARACTER(LEN=80) case_title !!CASE TITLE
125  CHARACTER(Len=80) date_format !!DATE FORMAT: ie 2007-11-19 => YMD
126  CHARACTER(Len=80) timezone !!Name of TIME ZONE OR NONE
127  CHARACTER(Len=80) start_date !!DATE TO START MODEL
128  CHARACTER(Len=80) end_date !!DATE TO END MODEL
129  CHARACTER(Len=80) date_reference !!USER DEFINED REFERENCE DATE OR DEFAULT
130 
132  namelist /nml_case/ &
133  & case_title, &
134  & timezone, &
135  & date_format, &
136  & date_reference, &
137  & start_date, &
138  & end_date
139 
140  !--Paramters in NameList NML_STARTUP
141  CHARACTER(LEN=80) startup_type !!'hotstart' or 'coldstart'
142  CHARACTER(LEN=80) startup_file !!NAME OF START FILE
143  CHARACTER(LEN=80) startup_ts_type !!TYPE OF TS START
144  CHARACTER(LEN=80) startup_uv_type !!TYPE OF TS START
145  CHARACTER(LEN=80) startup_turb_type !!TYPE OF TS START
146  REAL(sp) :: startup_t_vals(2)
147  REAL(sp) :: startup_s_vals(2)
150  REAL(sp) :: startup_dmax
151 
153 
154  CHARACTER(LEN=80), parameter :: startup_type_coldstart = 'coldstart'
155  CHARACTER(LEN=80), parameter :: startup_type_hotstart = 'hotstart'
156  CHARACTER(LEN=80), parameter :: startup_type_crashrestart = 'crashrestart'
157  CHARACTER(LEN=80), parameter :: startup_type_forecast = 'forecast'
158 
160 
161  CHARACTER(LEN=80), parameter :: startup_type_default = 'default'
162  CHARACTER(LEN=80), parameter :: startup_type_constant = 'constant'
163  CHARACTER(LEN=80), parameter :: startup_type_linear = 'linear'
164  CHARACTER(LEN=80), parameter :: startup_type_observed = 'observed'
165  CHARACTER(LEN=80), parameter :: startup_type_setvalues = 'set values'
166 
167 
168  namelist /nml_startup/ &
169  & startup_type, & ! coldstart, hotstart, crashrestart
170  & startup_file, &
171  & startup_uv_type, & ! default, set values
172  & startup_turb_type, & ! default, set values
173  & startup_ts_type, & ! constant, linear, observed, set values
174  & startup_t_vals, &
175  & startup_s_vals, &
176  & startup_u_vals, &
177  & startup_v_vals, &
178  & startup_dmax
179 
180 
181 
182  !--Parameters in NameList NML_IO
183  CHARACTER(LEN=80) input_dir !!MAIN INPUT DIRECTORY
184  CHARACTER(LEN=80) output_dir !!PARENT OUTPUT DIRECTORY
185  INTEGER ireport !!INTERVAL (IINT) FOR REPORTING OF FLOWFIELD STATISTICS
186  LOGICAL visit_all_vars !!SET THE LEVEL OF COMPLEXITY IN VISIT
187  LOGICAL wait_for_visit !!WAIT FOR VISIT TO CONNECT BEFORE BEGINING INTEGRATION
188  LOGICAL use_mpi_io_mode !!TURN ON THE PRINTER NODE FOR MPI JOBS
189 
190  namelist /nml_io/ &
191  & input_dir, &
192  & output_dir, &
193  & ireport, &
194  & visit_all_vars, &
195  & wait_for_visit, &
197 
198  !--Parameters in NameList NML_INTEGRATION
199 
200 ! FOR EXPLICIT TIME STEP MODEL
201  REAL(dp) extstep_seconds!!EXTERNAL TIME STEP IN SECONDS;
202  !! THIS VALUE WILL BE TRUNCATED TO MICROSECONDS!!
203  INTEGER isplit !!NUMBER OF ITERATIONS OF EXTERNAL MODE/INTERNAL STEP
204 
205 ! FOR SEMI-IMPLICIT TIME STEP MODEL
206  REAL(dp) intstep_seconds!!INTERNAL TIME STEP IN SECONDS FOR SEMI IMPLICIT;
207 
208  INTEGER iramp !!RAMP FACTOR USED TO EASE STARTUP = f(IINT)
209  REAL(sp) static_ssh_adj !!WATER LEVEL CONSTANT ADJUSTMENT
210  REAL(sp) min_depth !!MINIMUM ALLOWABLE DEPTH
211 
212  namelist /nml_integration/ &
213  & extstep_seconds, &
214  & isplit, &
215  & iramp, &
216  & min_depth, &
218 
219 
220 
221  !--Parameters in NameList NML_RESTART
222  LOGICAL rst_on !!TRUE IF OUTPUT RESART FILES
223  CHARACTER(LEN=80) rst_first_out !!DATE OF FIRST RESTART FILE OUTPUT
224  CHARACTER(LEN=80) rst_out_interval !!INTERVAL IN DECIMAL DAYS FOR CREATING A RESTART FILE
225  INTEGER rst_output_stack !!NUMBER OF TIMESTEPS PER FILE
226 
227  CHARACTER(LEN=80) restart_file_name !!NAME OF RESTART FILE
228  ! ONLY VALID TILL THE NAME IS INCRIMENTED IF THE STKCNT IS EXCEEDED
229 
230  namelist /nml_restart/ &
231  & rst_on, &
232  & rst_first_out, &
233  & rst_out_interval, &
235 
236 
237  !--Parameters in NameList NML_NETCDF
238  LOGICAL nc_on
239  CHARACTER(LEN=80) nc_first_out !! DATE TO START NETCDF OUTPUT
240  CHARACTER(LEN=80) nc_out_interval !! OUTPUT INTERVAL IN DECIMAL DAYS
241  INTEGER nc_output_stack !! NUMBER OF TIMESTEPS PER FILE
242  CHARACTER(LEN=120) nc_subdomain_files !! DOMAIN OUTPUT SPECS
243  ! GRID STUFF
245  LOGICAL nc_file_date
246  ! MODEL DATA
247  LOGICAL nc_velocity
248  LOGICAL nc_salt_temp
252  LOGICAL nc_vorticity
253  LOGICAL nc_nh_qp
254  LOGICAL nc_nh_rhs
255  LOGICAL nc_ice
256 
257  ! FORCING DATA
258  LOGICAL nc_wind_vel
260  LOGICAL nc_wave_para
261  LOGICAL nc_wave_stress
265  LOGICAL nc_bio
266  LOGICAL nc_wqm
267 
268  CHARACTER(LEN=80) nc_file_name !!NAME OF NC FILE
269  ! ONLY VALID TILL THE NAME IS INCRIMENTED IF THE STKCNT IS EXCEEDED
270 
271  namelist /nml_netcdf/ &
272  & nc_on, &
273  & nc_first_out, &
274  & nc_out_interval, &
275  & nc_output_stack, &
277  & nc_grid_metrics, &
278  & nc_file_date, &
279  & nc_velocity, &
280  & nc_salt_temp, &
281  & nc_turbulence, &
282  & nc_average_vel, &
283  & nc_vertical_vel, &
284  & nc_wind_vel, &
285  & nc_wind_stress, &
286  & nc_evap_precip, &
287  & nc_surface_heat, &
288  & nc_groundwater, &
289  & nc_bio, &
290  & nc_wqm, &
291  & nc_vorticity
292 
293  !--Parameters in NameList NML_NETCDF_AV
294  LOGICAL ncav_on !! TURN ON NETCDF AVERAGING
295  CHARACTER(LEN=80) ncav_first_out !! DATE TO START NETCDF AVERAGE OUTPUT
296  CHARACTER(LEN=80) ncav_out_interval !! OUTPUT INTERVAL IN DECIMAL DAYS
297  INTEGER ncav_output_stack !! NUMBER OF TIMESTEPS PER FILE
298  CHARACTER(LEN=120) ncav_subdomain_files !! DOMAIN OUTPUT SPECS
299  ! GRID STUFF
302  ! MODEL DATA
309  LOGICAL ncav_nh_qp
310  LOGICAL ncav_nh_rhs
311  LOGICAL ncav_ice
312 
313  ! FORCING DATA
316  LOGICAL ncav_wave_para
321  LOGICAL ncav_bio
322  LOGICAL ncav_wqm
323 
324  CHARACTER(LEN=80) ncav_file_name !!NAME OF NCAV FILE
325  ! ONLY VALID TILL THE NAME IS INCRIMENTED IF THE STKCNT IS EXCEEDED
326 
327  namelist /nml_netcdf_av/ &
328  & ncav_on, &
329  & ncav_first_out, &
330  & ncav_out_interval, &
331  & ncav_output_stack, &
333  & ncav_grid_metrics, &
334  & ncav_file_date, &
335  & ncav_velocity, &
336  & ncav_salt_temp, &
337  & ncav_turbulence, &
338  & ncav_average_vel, &
339  & ncav_vertical_vel, &
340 
341  & ncav_wind_vel, &
342  & ncav_wind_stress, &
343  & ncav_evap_precip, &
344  & ncav_surface_heat, &
345  & ncav_groundwater, &
346  & ncav_bio, &
347  & ncav_wqm, &
349 
350  !--Parameters in NameList NML_PHYSICS
351  CHARACTER(LEN=80) horizontal_mixing_type
352  CHARACTER(LEN=80) horizontal_mixing_file
353  CHARACTER(LEN=80) horizontal_mixing_kind
356 
357 ! REMOVED HORCON, THIS IS NOW STORED IN THE ARRAYS, NN_HVC AND CC_HVC
358 ! REAL(SP) HORCON ! FVCOM NAME
359  REAL(sp) hprnu ! FVCOM NAME
360 
361  CHARACTER(LEN=80) vertical_mixing_type
364 
365  REAL(sp) umol ! FVCOM NAME
366  REAL(sp) vprnu ! FVCOM NAME
367 
368  CHARACTER(LEN=80) bottom_roughness_kind
369  CHARACTER(LEN=80) bottom_roughness_type
370  CHARACTER(LEN=80) bottom_roughness_file
371  REAL(sp) bottom_roughness_minimum !!MINIMUM BOTTOM DRAG COEFFICIENT
372  REAL(sp) bottom_roughness_lengthscale !!BOTTOM FRICTION DEPTH LENGTH SCALE
373 
374  REAL(sp) cbcmin ! FVCOM NAME
375 
376  CHARACTER(LEN=80),parameter :: br_orig = 'orig'
377  CHARACTER(LEN=80),parameter :: br_gotm = 'gotm'
378 
381  LOGICAL barotropic
382  CHARACTER(LEN=80) sea_water_density_function
386 !J. Ge
387  ! for tracer advection
390 !J. Ge
392 
393  ! AT PRESENT YOU CAN NOT COMPILE WITH WET DRY WITHOUT USING IT!
395 
397  CHARACTER(LEN=80) interval_rho_mean
398 
399  CHARACTER(LEN=80),parameter :: sw_dens1 = 'dens1'
400  CHARACTER(LEN=80),parameter :: sw_dens2 = 'dens2'
401  CHARACTER(LEN=80),parameter :: sw_dens3 = 'dens3'
402 
403  LOGICAL adcor_on
406 
407  namelist /nml_physics/ &
423  & barotropic, &
427  & interval_rho_mean, &
428  & temperature_active, &
429  & salinity_active, &
431 !J. Ge
432  & backward_advection, &
433  & backward_step, &
434 !J. Ge
435  & wetting_drying_on, &
436  & adcor_on, &
437  & equator_beta_plane, &
439 
440 
441  !--Parameters in NameList NML_SURFACE_FORCING
442 
443  LOGICAL wind_on
444  CHARACTER(LEN=80) wind_type
445  CHARACTER(LEN=80) wind_file
446  CHARACTER(LEN=80) wind_kind
447  REAL(sp) wind_x
448  REAL(sp) wind_y
449 
450  LOGICAL heating_on
451  CHARACTER(LEN=80) heating_type
452  CHARACTER(LEN=80) heating_file
453  CHARACTER(LEN=80) heating_kind
459 
460  !FVCOM NAMES
461  REAL(sp) rheat ! LONG WAVE PERCENTAGE
462  REAL(sp) zeta1 ! LONG WAVE LENGTH
463  REAL(sp) zeta2 ! SHORT WAVE LENGTH
464 
465 
467  CHARACTER(LEN=80) precipitation_file
468  CHARACTER(LEN=80) precipitation_kind
471 
473  CHARACTER(LEN=80) airpressure_file
474  CHARACTER(LEN=80) airpressure_kind
476 
477  LOGICAL wave_on
478  CHARACTER(LEN=80) wave_file
479  CHARACTER(LEN=80) wave_kind
480  REAL(sp) :: wave_height
481  REAL(sp) :: wave_length
483  REAL(sp) :: wave_period
484  REAL(sp) :: wave_per_bot
485  REAL(sp) :: wave_ub_bot
486 
487  ! FORCING KINDS
488  CHARACTER(LEN=80),parameter:: cnstnt = "constant"
489  CHARACTER(LEN=80),parameter:: sttc = "static"
490  CHARACTER(LEN=80),parameter:: tmdpndnt = "time dependant"
491  CHARACTER(LEN=80),parameter:: prdc = "periodic"
492  CHARACTER(LEN=80),parameter:: vrbl = "variable"
493 
494  CHARACTER(LEN=80), parameter:: speed = "speed"
495  CHARACTER(LEN=80), parameter:: stress = "stress"
496 
497 !J. Ge
498  CHARACTER(LEN=80),parameter:: uniform = "uniform"
499  CHARACTER(LEN=80),parameter:: non_uniform = "non-uniform"
500 !J. Ge
501 
502  namelist /nml_surface_forcing/ &
503  & wind_on, &
504  & wind_type, &
505  & wind_file, &
506  & wind_kind, &
507  & wind_x, &
508  & wind_y, &
509  & heating_on, &
510  & heating_type, &
511  & heating_kind, &
512  & heating_file, &
516  & heating_radiation, &
517  & heating_netflux, &
518  & precipitation_on, &
519  & precipitation_kind, &
520  & precipitation_file, &
521  & precipitation_prc, &
522  & precipitation_evp, &
523  & airpressure_on, &
524  & airpressure_kind, &
525  & airpressure_file, &
526  & airpressure_value, &
527  & wave_on, &
528  & wave_file, &
529  & wave_kind, &
530  & wave_height, &
531  & wave_length, &
532  & wave_direction, &
533  & wave_period, &
534  & wave_per_bot, &
535  & wave_ub_bot
536 
537  !--Parameters in NameList NML_RIVER_TYPE
538  CHARACTER(LEN=80) river_ts_setting ! METHOD TO CALCULATE T&S AT
539  ! THE RIVER MOUTH
540  CHARACTER(LEN=80) river_inflow_location ! IS THE FLUX
541  CHARACTER(LEN=80) river_kind ! PERIODIC OR VARIABLE
542  CHARACTER(LEN=80) river_info_file ! RIVERS INFORMATION FILE
543  ! SPECIFIED FOR NODES OR EDGES
544  INTEGER river_number ! THE NUMBER OF RIVERS
545 
546  namelist /nml_river_type/ &
547  & river_number, &
548  & river_kind, &
549  & river_ts_setting, &
550  & river_info_file, &
552 
553 
554  !--Parameters in NameList NML_RIVER
555  INTEGER, PARAMETER :: river_char_len=60
556 
557  INTEGER, PARAMETER :: max_layers = 100
558 
559  CHARACTER(LEN=80) river_name
560  CHARACTER(LEN=80) river_file
562 
563  ! ASSUMING MAXIMUM NUMBER OF LAYERS!
565 
566  namelist /nml_river/ &
567  & river_name, &
568  & river_file, &
569  & river_grid_location, &
571 
572 
573  ! THIS TYPE PROVIDES INTERMEDIATE STORAGE FOR RIVER INFO UNTILL
574  ! THE RIVER FORCING IS SET UP IN MOD_FORCE
575  type river
576  CHARACTER(LEN=80) name
577  CHARACTER(LEN=80) file
578  INTEGER location
579  REAL(sp) :: distribution(max_layers)
580  end type river
581 
582  type(river), Allocatable, DIMENSION(:) :: rivers
583 
584  !--Parameters in NameList NML_OPEN_BOUNDARY
585  LOGICAL obc_on
586  CHARACTER(LEN=80) obc_node_list_file
588  CHARACTER(LEN=80) obc_elevation_file
589  INTEGER obc_ts_type
591  CHARACTER(LEN=80) obc_temp_file
594  CHARACTER(LEN=80) obc_salt_file
596  LOGICAL obc_meanflow
597  CHARACTER(LEN=80) obc_meanflow_file
599  CHARACTER(LEN=80) obc_longshore_flow_file
602 
603  namelist /nml_open_boundary_control/ &
604  & obc_on, &
605  & obc_node_list_file, &
607  & obc_elevation_file, &
608  & obc_ts_type, &
609  & obc_temp_nudging, &
610  & obc_temp_file, &
612  & obc_salt_nudging, &
613  & obc_salt_file, &
615  & obc_meanflow, &
616  & obc_meanflow_file, &
622 
623 
624  !--Parameters in NameList GRID_COORDINATES
625  CHARACTER(LEN=80) grid_file
626  CHARACTER(LEN=80) grid_file_units
627  CHARACTER(LEN=200) projection_reference
628  CHARACTER(LEN=80) sigma_levels_file
629  CHARACTER(LEN=80) depth_file
630  CHARACTER(LEN=80) coriolis_file
631  CHARACTER(LEN=80) sponge_file
632 
633  LOGICAL use_proj
634 ! THESE ARE THE FVCOM NAMES FOR
635  !SIGMA_LEVELS = KB
636  !SIGMA_LAYERS = KBM1 = KB - 1
637  !SIGMA_LEVELS - 2 = KBM2
638 
639  namelist /nml_grid_coordinates/ &
640  & grid_file, &
641  & grid_file_units, &
643  & sigma_levels_file, &
644  & depth_file, &
645  & coriolis_file, &
646  & sponge_file
647 
648  !--Parameters in NameList NML_GROUNDWATER
650  CHARACTER(LEN=80) groundwater_kind
651  CHARACTER(LEN=80) groundwater_file
657 
658 
659 
660  namelist /nml_groundwater/ &
661  & groundwater_on, &
664  & groundwater_kind, &
665  & groundwater_file, &
666  & groundwater_flow, &
667  & groundwater_temp, &
669 
670  !--Parameters in NameList NML_LAG_PART
672  CHARACTER(LEN=80) lag_start_file
673  CHARACTER(LEN=80) lag_out_file
674  CHARACTER(LEN=80) lag_first_out
675  CHARACTER(LEN=80) lag_restart_file
676  CHARACTER(LEN=80) lag_out_interval
677  CHARACTER(LEN=80) lag_scal_choice
678 
679 !!$ LOGICAL LAG_TEMPERATURE
680 !!$ LOGICAL LAG_SALINITY
681 !!$ LOGICAL LAG_DENSITY
682 !!$ LOGICAL LAG_EDDY_VISCOSITY
683 !!$ LOGICAL LAG_DIFFUSIVITY
684 
685  namelist /nml_lag/ &
686  & lag_particles_on, &
687  & lag_start_file, &
688  & lag_out_file, &
689  & lag_first_out, &
690  & lag_restart_file, &
691  & lag_out_interval, &
693 
694 
695 !!$ & LAG_TEMPERATURE, &
696 !!$ & LAG_SALINITY, &
697 !!$ & LAG_DENSITY, &
698 !!$ & LAG_EDDY_VISCOSITY, &
699 !!$ & LAG_DIFFUSIVITY
700 
701  !--Parameters in NameList NML_ADDITIONAL_MODELS
702 ! LOGICAL WATER_QUALITY_MODEL
703 ! CHARACTER(LEN=80) WATER_QUALITY_MODEL_FILE
705  CHARACTER(LEN=80) data_assimilation_file
707 ! J. Ge for online biology
708  CHARACTER(LEN=80) biological_model_file
709 !--------------------------
710 
711  CHARACTER(LEN=80) startup_bio_type !!TYPE OF BIO START
713  CHARACTER(LEN=80) sediment_model_file
714  CHARACTER(LEN=80) sediment_parameter_type
715  CHARACTER(LEN=80) sediment_parameter_file
716  CHARACTER(LEN=80) bedflag_type
717  CHARACTER(LEN=80) bedflag_file
718 
719  LOGICAL icing_model
720  CHARACTER(LEN=80) icing_forcing_file
721  CHARACTER(LEN=80) icing_forcing_kind
723  REAL(sp) ::icing_wspd
724 
725  LOGICAL ice_model
726  CHARACTER(LEN=80) ice_forcing_file
727  CHARACTER(LEN=80) ice_forcing_kind
729  REAL(sp) ::ice_air_temp
733  CHARACTER(LEN=80) ice_longwave_type
734 
736 
737  !ADDITIONAL MODEL DATA
738  INTEGER :: n_sed
739  INTEGER, PARAMETER :: n_sed_max = 10
740  CHARACTER(LEN=20) :: sed_names(n_sed_max)
741  REAL(sp), ALLOCATABLE :: seddis(:,:)
742 
743 
744  REAL(sp), ALLOCATABLE :: biodis(:,:)
745 
746 
747  ! FVCOM RUN MODE PARAMETERS
748  CHARACTER(LEN=80) fvcom_run_mode
749  CHARACTER(LEN=80),parameter :: fvcom_pure_sim = 'pure sim'
750 ! CHARACTER(LEN=80),parameter :: FVCOM_NUDGE_AVG_SST = 'nudge avg sst'
751 ! CHARACTER(LEN=80),parameter :: FVCOM_NUDGE_AVG_TSGRD = 'nudge avg ts'
752  CHARACTER(LEN=80),parameter :: fvcom_nudge_oi_assim = 'nudge or OI assim'
753 ! CHARACTER(LEN=80),parameter :: FVCOM_OI_ASSIM = 'OI ASSIM'
754 ! CHARACTER(LEN=80),parameter :: FVCOM_KALMAN_RRKF = 'Kalman RRKF'
755  CHARACTER(LEN=80),parameter :: fvcom_rrkf_without_ssa = 'RRKF WITHOUT SSH/SST'
756  CHARACTER(LEN=80),parameter :: fvcom_rrkf_with_ssa = 'RRKF WITH SSH/SST'
757  CHARACTER(LEN=80),parameter :: fvcom_enkf_without_ssa = 'ENKF WITHOUT SSH/SST'
758  CHARACTER(LEN=80),parameter :: fvcom_enkf_with_ssa = 'ENKF WITH SSH/SST'
759  CHARACTER(LEN=80),parameter :: fvcom_kalman_4 = 'Kalman 4'
760 
761  namelist /nml_additional_models/ &
762 ! & WATER_QUALITY_MODEL, &
763 ! & WATER_QUALITY_MODEL_FILE, &
764  & data_assimilation, &
766  & biological_model, &
767  & startup_bio_type, &
768 !--------- J. Ge for biology --------------
770 !------------------------------------------
771  & sediment_model, &
775  & bedflag_type, &
776  & bedflag_file, &
777  & icing_model, &
778  & icing_forcing_file, &
779  & icing_forcing_kind, &
780  & icing_air_temp, &
781  & icing_wspd, &
782  & ice_model, &
783  & ice_forcing_file, &
784  & ice_forcing_kind, &
786  & ice_air_temp, &
787  & ice_spec_humidity, &
788  & ice_shortwave, &
789  & ice_longwave_type, &
790  & ice_cloud_cover, &
792 
793  !--Parameters in NameList NML_PROBE
794  LOGICAL probes_on
796  CHARACTER(len=80) probes_file
797 
798  namelist /nml_probes/ &
799  & probes_on, &
800  & probes_number, &
801  & probes_file
802 
803  !--Parameters in NameList NML_BOUNDSCHK
804  !=> bounds checking
805  LOGICAL :: force_archive = .false.
806  LOGICAL :: boundschk_on = .false.
807  INTEGER :: chk_interval
808  REAL(sp) :: veloc_mag_max
809  REAL(sp) :: zeta_mag_max
810  REAL(sp) :: temp_max
811  REAL(sp) :: temp_min
812  REAL(sp) :: salt_max
813  REAL(sp) :: salt_min
814 
815  namelist /nml_boundschk/ &
816  & boundschk_on, &
817  & chk_interval, &
818  & veloc_mag_max, &
819  & zeta_mag_max, &
820  & temp_max, &
821  & temp_min, &
822  & salt_max, &
823  & salt_min
824 
825 
826 !--Time Variables for FVCOM-----------------------------------------!
827  TYPE(time) :: inttime
828  TYPE(time) :: exttime
829  Type(time) :: rktime
830  TYPE(time) :: zerotime
831 
832  TYPE(time) :: endtime
833  Type(time) :: starttime
836 
839 
840  ! ZERO PHASE TIME FOR SPECTRAL (NON JULIAN) TIDE
841  TYPE(time) :: spectime
842 
843  REAL(sp) :: dte !!EXTERNAL TIME STEP (Seconds)
844  REAL(sp) :: dti !!INTERNAL TIME STEP (Seconds)
845  REAL(sp) :: ramp
846 
847  TYPE(time) :: imdte !!EXTERNAL TIME STEP
848  TYPE(time) :: imdti !!INTERNAL TIME STEP
849 
850  INTEGER(itime) :: iint !!INTERNAL TIME STEP ITERATION NUMBER (ISTART => IEND)
851  INTEGER(itime) :: iext !!EXTERNAL TIME STEP ITERATION NUMBER (1 => ISPLIT)
852  INTEGER(itime) :: istart !!STARTING INTERNAL TIME STEP ITERATION NUMBER
853  INTEGER(itime) :: iend !!ENDING INTERNAL TIME STEP ITERATION NUMBER
854  INTEGER(itime) :: nsteps !!Number OF INTERAL TIME STEPS IN SIMULATION
855 
856  ! Time variables for File IO
857 
858  INTEGER, PARAMETER:: timeprec = 6
859  !! THIS IS THE LENGHT THAT LOOKS NICE FOR GIVEN TIME PREC
860  INTEGER, PARAMETER:: datestrlen = 20+timeprec
861 
862 ! CHARACTER(LEN=80) :: IO_FILE_DATE
863 ! CHARACTER(LEN=80) :: IO_timestr
864 ! real(SP) :: IO_days
865 ! integer :: IO_mjd
866 ! integer :: IO_msec
867 ! integer :: IO_IINT
868 
869 
870 
871 !--Constants-------------------------------------------------------------------!
872 
873  ! SELECT WHETHER YOU WANT TO MAKE TIME MORE EXACT (SP CAUSES
874  ! ROUND OF ERROR BUT IS THE TRADITIONAL PRECISION)
875  REAL(dp), PARAMETER, DIMENSION(4) :: alpha_rk = (/0.2500_dp,1.0_dp/3.0_dp,0.5000_dp,1.0_dp/)
876 ! REAL(SP), PARAMETER, DIMENSION(4) :: ALPHA_RK = (/0.2500_DP,1.0_DP/3.0_DP,0.5000_DP,1.0_DP/)
877 
878 
879  REAL(dp), PARAMETER :: grav = 9.81_sp
880  REAL(dp), PARAMETER :: pi = 3.141592653589793238_dp
881  REAL(dp), PARAMETER :: pi2 = 2.0_dp * 3.141592653589793238_dp
882  REAL(dp), PARAMETER :: zero = 0.0_dp
883  REAL(dp), PARAMETER :: one_third = 1.0_dp/3.0_dp
884  REAL(dp), PARAMETER :: rearth = 6371.0e03_dp !!Earth Radius in Meters
885  REAL(dp), PARAMETER :: deg2rad = pi2/360.0_dp !!Radians/Degree
886  REAL(dp), PARAMETER :: tpi = deg2rad*rearth !TPI=pi*rearth/180.=3.14159265/180.0*6371.*1000.
887  REAL(dp), PARAMETER :: rofvros = 0.9775171065_dp!!RATIO OF THE DENSITY OF FRESH AND SEA WATER 1000./1023.
888  real(dp), parameter :: slp0 = 101325.0_sp !! mean sea surface pressure (Pa)
889 
890 
891 !--Parameter Controlling Vertical Coordinate Distribution------------
892  !----------!
893  CHARACTER(LEN=80) :: stype
894  CHARACTER(LEN=80), PARAMETER :: stype_uniform= "UNIFORM"
895  CHARACTER(LEN=80), PARAMETER :: stype_geometric= "GEOMETRIC"
896  CHARACTER(LEN=80), PARAMETER :: stype_tanh= "TANH"
897  CHARACTER(LEN=80), PARAMETER :: stype_generalized= "GENERALIZED"
898  CHARACTER(LEN=80), PARAMETER :: stype_restart= "RESTART"
899 !--Sigma Level Parameters for case GEOMETRIC OF UNIFORM------------------------!
900  REAL(sp) :: p_sigma !!PARAMETER CONTROLLING SIGMA LEVEL DISTRIBUTION
901 
902 !--General Vertical Level Parameters for case TANH ----------------------------!
903  REAL(sp) :: du2 !!PARAMETER CONTROLLING LEVEL DISTRIBUTION OF SURFACE
904  REAL(sp) :: dl2 !!PARAMETER CONTROLLING LEVEL DISTRIBUTION OF BOTTOM
905 
906 !--General Vertical Level Parameters for case GENERALIZED ---------------------!
907  REAL(sp) :: duu !!THE UPPER BOUNDARY OF PARALLEL COORDINATE
908  REAL(sp) :: dll !!THE LOWER BOUNDARY OF PARALLEL COORDINATE
909  REAL(sp) :: hmin1 !!THE MIN DEPTH AT WHICH THE LAYERS ARE CONSTANT
910 
911  INTEGER :: ku !!THE NUMBERS OF LAYERS ABOVE UPPER BOUNDARY
912  INTEGER :: kl !!THE NUMBVER OF LAYERS BELOW LOWER BOUNDARY
913 
914  REAL(sp), ALLOCATABLE :: zku(:) !!THE DEPTHS OF PARALLEL LAYERS ABOVE UPPER BOUNDARY
915  REAL(sp), ALLOCATABLE :: zkl(:) !!THE DEPTHS OF PARALLEL LAYERS BELOW LOWER BOUNDARY
916 
917  REAL(sp) :: hmax !!GLOBAL MAXIMUM DEPTH IN DEPTH FILE
918  REAL(sp) :: hmin !!GLOBAL MINIMUM DEPTH IN DEPTH FILE
919 
920 
921  ! All file identifiers go here
922  INTEGER :: ipt !! IUNIT FOR LOG FILE OUTPUT
923  INTEGER, PUBLIC, PARAMETER :: ipt_base= 7000 ! FOR PAR LOG FILES
924 
925  INTEGER, PARAMETER :: testunit = 200 !! TEST TO SEE IF OUTPUT DIR EXISTS/WRITABLE
926  INTEGER, PARAMETER :: nmlunit = 10 !! NAMELIST RUN FILE
927  INTEGER, PARAMETER :: itsunit=11
928  INTEGER, PARAMETER :: obcunit=12
929  INTEGER, PARAMETER :: gridunit=13
930  INTEGER, PARAMETER :: sigmaunit=14
931  INTEGER, PARAMETER :: depthunit=15
932  INTEGER, PARAMETER :: coriolisunit=16
933  INTEGER, PARAMETER :: spongeunit=17
934  INTEGER, PARAMETER :: lsfunit=18
935  INTEGER, PARAMETER :: assimunit=19
936  INTEGER, PARAMETER :: oiassimunit=23
937  INTEGER, PARAMETER :: probeunit=20
938  INTEGER, PARAMETER :: julobcunit=21
939  INTEGER, PARAMETER :: kfunit=22
940  INTEGER, PARAMETER :: nestunit=30
941  INTEGER, PARAMETER :: subdunit=31
942 
943  INTEGER :: rivernmlunit
944 
945 
946 END MODULE control
947 
948 !==============================================================================|
949 !==============================================================================|
950 !==============================================================================|
951 ! ALL VARS |
952 ! CONATINS:
953 ! FVCOM VARIABLES
954 ! N2E3D: simple average from nodes to elements for 3D variables
955 ! N2E2D: simple average from nodes to elements for 2D variables
956 ! E2N3D: simple average from elements to nodes for 3D variables
957 ! E2N2D: simple average from elements to nodes for 2D variables
958 !==============================================================================|
959 MODULE all_vars
960  USE mod_prec
961  USE lims
962  USE control
963  IMPLICIT NONE
964  SAVE
965 
966 
967 !--------------------------Temporary Array------------------------------------------!
968 
969  INTEGER, ALLOCATABLE :: nvg(:,:)
970 
971 !--------------------------Global Grid Variables------------------------------------!
972 
973 !! REAL(SP), POINTER :: XG(:) !!GLOBAL X-COORD AT NODE
974 !! REAL(SP), POINTER :: YG(:) !!GLOBAL X-COORD AT NODE
975  REAL(sp), ALLOCATABLE :: xg(:) !!GLOBAL X-COORD AT NODE
976  REAL(sp), ALLOCATABLE :: yg(:) !!GLOBAL X-COORD AT NODE
977  REAL(sp), ALLOCATABLE :: hg(:) !!GLOBAL DEPTH AT NODE
978 ! REAL(SP), ALLOCATABLE :: CORG(:) !!GLOBAL COORIOLIS AT NODE
979  REAL(sp), ALLOCATABLE :: xcg(:) !!GLOBAL X-COORD AT FACE CENTER
980  REAL(sp), ALLOCATABLE :: ycg(:) !!GLOBAL X-COORD AT FACE CENTER
981 
982 !--------------------------Grid Metrics---------------------------------------------!
983 
984  ! JUST DON'T ALLOCATE THINGS THAT YOU DON'T NEED IN A PARTICULAR
985  ! MODULE IT IS A PAIN IN THE NECK TO NO HAVE THE VARIABLE DECLARED
986 
987 
988 !# if !defined(SPHERICAL)
990 !# endif
991  REAL(sp), ALLOCATABLE,TARGET :: xm(:) !!X-COORD AT NODE IN METERS
992  REAL(sp), ALLOCATABLE,TARGET :: ym(:) !!Y-COORD AT NODE IN METERS
993  REAL(sp), ALLOCATABLE,TARGET :: xmc(:) !!X-COORD AT CELL CENTER IN METERS
994  REAL(sp), ALLOCATABLE,TARGET :: ymc(:) !!Y-COORD AT CELL CENTER IN METERS
995  REAL(sp), ALLOCATABLE,TARGET :: lon(:) !!LONGITUDE AT THE NODE
996  REAL(sp), ALLOCATABLE,TARGET :: lat(:) !!LATITUDE AT THE NODE
997  REAL(sp), ALLOCATABLE,TARGET :: lonc(:) !!LONGITUDE AT THE NODE
998  REAL(sp), ALLOCATABLE,TARGET :: latc(:) !!LATITUDE AT THE NODE
999  ! VX,VY and XC,YC are used for either meters or spherical depending on
1000  ! make file option 'SPHERICAL'
1001  REAL(sp), ALLOCATABLE,TARGET :: vx(:) !!X-COORD AT GRID POINT
1002  REAL(sp), ALLOCATABLE,TARGET :: vy(:) !!Y-COORD AT GRID POINT
1003  REAL(sp), ALLOCATABLE,TARGET :: xc(:) !!X-COORD AT FACE CENTER
1004  REAL(sp), ALLOCATABLE,TARGET :: yc(:) !!Y-COORD AT FACE CENTER
1005 
1006  ! NOTES: SHOULD MAKE AN ARRAY TO STORE 1/ART, 1/ART2 and 1/ART2
1007  ! IT is faster and safer
1008 
1009  REAL(sp), ALLOCATABLE,TARGET :: art(:) !!AREA OF ELEMENT
1010  REAL(sp), ALLOCATABLE,TARGET :: art1(:) !!AREA OF NODE-BASE CONTROl VOLUME
1011  REAL(sp), ALLOCATABLE,TARGET :: art2(:) !!AREA OF ELEMENTS AROUND NODE
1012 !--Gravity (vary with latitute) -----------------------------------------------!
1013  REAL(sp),ALLOCATABLE,TARGET :: grav_n(:),grav_e(:) ! CALCULATED AS A
1014  ! FUNCTION OF LATITUDE IN SPHERICAL COORDINATES MODEL
1015 
1016 !----------------Node, Boundary Condition, and Control Volume-----------------------!
1017 
1018  INTEGER, ALLOCATABLE,TARGET :: nv(:,:) !!NODE NUMBERING FOR ELEMENTS
1019 ! INTEGER, ALLOCATABLE,TARGET :: NVGL(:,:) !!NODE GLOBAL NUMBERING OF LOCAL ELEMENTS
1020  INTEGER, ALLOCATABLE,TARGET :: nbe(:,:) !!INDICES OF ELMNT NEIGHBORS
1021 ! INTEGER, POINTER :: NBEGL(:,:) !!GLOBAL INDICES OF LOCAL ELEMENT NEIGHBORS
1022  INTEGER, ALLOCATABLE,TARGET :: ntve(:) !! NUMBER OF ELEMENTS SURROUNDING EACH NODE
1023  INTEGER, ALLOCATABLE,TARGET :: ntsn(:) !! NUMBER OF NODES SURROUNDING EACH NODE
1024  INTEGER, ALLOCATABLE,TARGET :: isonb(:) !!NODE MARKER = 0,1,2
1025  INTEGER, ALLOCATABLE,TARGET :: isonb_w(:) !!NODE MARKER = 0,1,2
1026  INTEGER, ALLOCATABLE,TARGET :: isbc(:)
1027  INTEGER, ALLOCATABLE,TARGET :: isbce(:)
1028  INTEGER, ALLOCATABLE,TARGET :: iec(:,:)
1029  INTEGER, ALLOCATABLE,TARGET :: ienode(:,:)
1030  INTEGER, ALLOCATABLE,TARGET :: nbsn(:,:) !! INDICES OF NODES SURROUNDING EACH NODE
1031 ! INTEGER, POINTER :: NBSNGL(:,:) !! GLOBAL INDICIES OF NODES SURROUNDING EACH LOCAL NODE
1032  INTEGER, ALLOCATABLE,TARGET :: niec(:,:)
1033  INTEGER, ALLOCATABLE,TARGET :: ntrg(:)
1034  INTEGER, ALLOCATABLE,TARGET :: nbve(:,:) !! INDICIES OF ELEMENTS SURROUNDING EACH NODE
1035 ! INTEGER, POINTER :: NBVEGL(:,:) !! GLOBAL INDICIES OF ELEMENTS SURROUNDING EACH LOCAL NODE
1036  INTEGER, ALLOCATABLE,TARGET :: nbvt(:,:)
1037  INTEGER, ALLOCATABLE,TARGET :: lisbce_1(:) !!LIST OF ELEMENTS WITH ISBCE=1
1038  INTEGER, ALLOCATABLE,TARGET :: lisbce_2(:) !!LIST OF ELEMENTS WITH ISBCE=2
1039  INTEGER, ALLOCATABLE,TARGET :: lisbce_3(:) !!LIST OF ELEMENTS WITH ISBCE=3
1040  REAL(sp),ALLOCATABLE,TARGET :: dltxc(:)
1041  REAL(sp),ALLOCATABLE,TARGET :: dltyc(:)
1042  REAL(sp),ALLOCATABLE,TARGET :: dltxyc(:)
1043  REAL(sp),ALLOCATABLE,TARGET :: sitae(:)
1044  REAL(sp),ALLOCATABLE,TARGET :: xijc(:)
1045  REAL(sp),ALLOCATABLE,TARGET :: yijc(:)
1046  ! POSITION OF NODAL CONTROL VOLUME CORNERS
1047  REAL(sp),ALLOCATABLE,TARGET :: xije(:,:)
1048  REAL(sp),ALLOCATABLE,TARGET :: yije(:,:)
1049  ! LENGTH OF NODAL CONTROL VOLUME EDGES
1050  REAL(sp),ALLOCATABLE,TARGET :: dltxe(:)
1051  REAL(sp),ALLOCATABLE,TARGET :: dltye(:)
1052  REAL(sp),ALLOCATABLE,TARGET :: dltxye(:)
1053  REAL(sp),ALLOCATABLE,TARGET :: sitac(:)
1054 
1055 
1056  REAL(sp),ALLOCATABLE,TARGET :: epor(:) !!ELEMENT FLUX POROSITY (=0. IF ISBCE = 2)
1057 
1058  ! LENGTH BETWEEN NODE AND CONTROL VOLUMEN EDGE CENTER
1059  REAL(sp),ALLOCATABLE,TARGET :: dltxncve(:,:)!! DeLTa X Node to Control Volume Edge
1060  REAL(sp),ALLOCATABLE,TARGET :: dltyncve(:,:)!! DeLTa Y Node to Control Volume Edge
1061 
1062 
1063  REAL(sp),ALLOCATABLE,TARGET :: dltytrie(:,:)!! DeLTa Y TRIangle Edge
1064  REAL(sp),ALLOCATABLE,TARGET :: dltxtrie(:,:)!! DeLTa X TRIangle Edge
1065 
1066  REAL(sp),ALLOCATABLE,TARGET :: dltxecec(:,:)!! DeLTa X Edge Center to Edge Center
1067  REAL(sp),ALLOCATABLE,TARGET :: dltyecec(:,:)!! DeLTa Y Edge Center to Edge Center
1068 
1069  REAL(sp),ALLOCATABLE,TARGET :: dltxnec(:,:)!! DeLTa X Node to Edge Center
1070  REAL(sp),ALLOCATABLE,TARGET :: dltynec(:,:)!! DeLTa Y Node to Edge Center
1071 
1072 
1073  ! LONG SHORE FLOW VARIABLES
1074  INTEGER, ALLOCATABLE,TARGET :: ibclsf_gl(:) !!GLOBAL NODE NUMBER OF LSF BOUNDARY
1075  REAL(sp),ALLOCATABLE,TARGET :: rbc_geo_gl(:) !!GLOBAL GEOSTROPHIC FRICTION CORRECTION NODES
1076  REAL(sp),ALLOCATABLE,TARGET :: rbc_wdf_gl(:) !!GLOBAL WIND DRIVEN FLOW CORRECTION NODES
1077 
1078  REAL(sp),ALLOCATABLE,TARGET :: wdf_ang(:) !!ANGLE ALLONG THE OPEN BOUNDARY
1079  REAL(sp),ALLOCATABLE,TARGET :: wdf_dist(:) !!DISTANCE ALLONG THE OPEN BOUNDARY
1080  INTEGER, ALLOCATABLE,TARGET :: ibclsf(:) !!LOCAL NODE NUMBER OF LSF BOUNDARY
1081  INTEGER, ALLOCATABLE,TARGET :: ibclsf_output(:) !! LIST OF LOCAL LSF NODES GLOBAL NUMBER FOR OUTPUT
1082  INTEGER, ALLOCATABLE,TARGET :: nbclsf(:) !!LOCAL NODE NUMBER OF THE NEXT LSF BOUNDARY
1083  REAL(sp),ALLOCATABLE,TARGET :: rbc_geo(:) !!LOCAL GEOSTROPHIC FRICTION CORRECTION NODES
1084  REAL(sp),ALLOCATABLE,TARGET :: rbc_wdf(:) !!LOCAL WIND DRIVEN FLOW CORRECTION NODES
1085 
1086 ! INTEGER, ALLOCATABLE,TARGET :: N_ICELLQ(:,:) !!FLUX ANGLE
1087 
1088 !----------------2-d arrays for the general vertical coordinate -------------------------------!
1089 
1090  REAL(sp), ALLOCATABLE,TARGET :: z(:,:) !!SIGMA COORDINATE VALUE
1091  REAL(sp), ALLOCATABLE,TARGET :: zz(:,:) !!INTRA LEVEL SIGMA VALUE
1092  REAL(sp), ALLOCATABLE,TARGET :: dz(:,:) !!DELTA-SIGMA VALUE
1093  REAL(sp), ALLOCATABLE,TARGET :: dzz(:,:) !!DELTA OF INTRA LEVEL SIGMA
1094  REAL(sp), ALLOCATABLE,TARGET :: z1(:,:) !!SIGMA COORDINATE VALUE
1095  REAL(sp), ALLOCATABLE,TARGET :: zz1(:,:) !!INTRA LEVEL SIGMA VALUE
1096  REAL(sp), ALLOCATABLE,TARGET :: dz1(:,:) !!DELTA-SIGMA VALUE
1097  REAL(sp), ALLOCATABLE,TARGET :: dzz1(:,:) !!DELTA OF INTRA LEVEL SIGMA
1098 ! REAL(SP), ALLOCATABLE,TARGET :: DPTHSL(:) !!Z-DEPTHS FOR SALINITY/TEMP ICs
1099 
1100 
1101 !---------------2-d flow variable arrays at elements-------------------------------!
1102 
1103  REAL(sp), ALLOCATABLE,TARGET :: ua(:) !!VERTICALLY AVERAGED X-VELOC
1104  REAL(sp), ALLOCATABLE,TARGET :: va(:) !!VERTICALLY AVERAGED Y-VELOC
1105  REAL(sp), ALLOCATABLE,TARGET :: uaf(:) !!UA FROM PREVIOUS RK STAGE
1106  REAL(sp), ALLOCATABLE,TARGET :: vaf(:) !!VA FROM PREVIOUS RK STAGE
1107 !# if !defined (SEMI_IMPLICIT)
1108  REAL(sp), ALLOCATABLE,TARGET :: uark(:) !!UA FROM PREVIOUS TIMESTEP
1109  REAL(sp), ALLOCATABLE,TARGET :: vark(:) !!VA FROM PREVIOUS TIMESTEP
1110  REAL(sp), ALLOCATABLE,TARGET :: uard(:) !!UA AVERAGED OVER EXTERNAL INT
1111  REAL(sp), ALLOCATABLE,TARGET :: vard(:) !!VA AVERAGED OVER EXTERNAL INT
1112 !# endif
1113  REAL(sp), ALLOCATABLE,TARGET :: cor(:) !!CORIOLIS PARAMETER
1114  REAL(sp), ALLOCATABLE,TARGET :: f_alfa(:)
1115  REAL(sp), ALLOCATABLE,TARGET :: h1(:) !!BATHYMETRIC DEPTH
1116  REAL(sp), ALLOCATABLE,TARGET :: d1(:) !!CURRENT DEPTH
1117  REAL(sp), ALLOCATABLE,TARGET :: dt1(:) !!DEPTH AT PREVIOUS TIME STEP
1118  REAL(sp), ALLOCATABLE,TARGET :: el1(:) !!CURRENT SURFACE ELEVATION
1119  REAL(sp), ALLOCATABLE,TARGET :: et1(:) !!SURFACE ELEVATION AT PREVIOUS TIME STEP
1120 !# if !defined (SEMI_IMPLICIT)
1121  REAL(sp), ALLOCATABLE,TARGET :: elrk1(:) !!SURFACE ELEVATION AT BEGINNING OF RK INT
1122 !# endif
1123  REAL(sp), ALLOCATABLE,TARGET :: elf1(:) !!SURFACE ELEVATION STORAGE FOR RK INT
1124  REAL(sp), ALLOCATABLE,TARGET :: dtfa(:) !!ADJUSTED DEPTH FOR MASS CONSERVATION
1125 
1126 
1127  REAL(sp), ALLOCATABLE,TARGET :: cc_sponge(:) !!SPONGE DAMPING COEFFICIENT FOR MOMENTUM
1128 
1129 !---------------2-d flow variable arrays at nodes----------------------------------!
1130 
1131  REAL(sp), ALLOCATABLE,TARGET :: h(:) !!BATHYMETRIC DEPTH
1132  REAL(sp), ALLOCATABLE,TARGET :: d(:) !!CURRENT DEPTH
1133  REAL(sp), ALLOCATABLE,TARGET :: dt(:) !!DEPTH AT PREVIOUS TIME STEP
1134  REAL(sp), ALLOCATABLE,TARGET :: el(:) !!CURRENT SURFACE ELEVATION
1135  REAL(sp), ALLOCATABLE,TARGET :: et(:) !!SURFACE ELEVATION AT PREVIOUS TIME STEP
1136  REAL(sp), ALLOCATABLE,TARGET :: egf(:) !!AVERAGE SURFACE ELEVATION OVER EXTERNAL INT
1137 !# if !defined (SEMI_IMPLICIT)
1138  REAL(sp), ALLOCATABLE,TARGET :: elrk(:) !!SURFACE ELEVATION AT BEGINNING OF RK INT
1139 !# endif
1140  REAL(sp), ALLOCATABLE,TARGET :: elf(:) !!SURFACE ELEVATION STORAGE FOR RK INT
1141 
1142  ! DEFINED HERE, BUT ONLY USED IF EQI&ATMO ARE DEFINED
1143  REAL(sp), ALLOCATABLE,TARGET :: elf_eqi(:)
1144 !# if !defined (SEMI_IMPLICIT)
1145  REAL(sp), ALLOCATABLE,TARGET :: elrk_eqi(:)
1146 !# endif
1147  REAL(sp), ALLOCATABLE,TARGET :: el_eqi(:)
1148  REAL(sp), ALLOCATABLE,TARGET :: egf_eqi(:)
1149 
1150  REAL(sp), ALLOCATABLE,TARGET :: elf_atmo(:)
1151 !# if !defined (SEMI_IMPLICIT)
1152  REAL(sp), ALLOCATABLE,TARGET :: elrk_atmo(:)
1153 !# endif
1154  REAL(sp), ALLOCATABLE,TARGET :: el_atmo(:)
1155  REAL(sp), ALLOCATABLE,TARGET :: egf_atmo(:)
1156 
1157  ! DEFINED HERE, BUT ONLY USED IF AIR PRESSURE ARE DEFINED
1158  REAL(sp), ALLOCATABLE,TARGET :: elf_air(:)
1159 !# if !defined (SEMI_IMPLICIT)
1160  REAL(sp), ALLOCATABLE,TARGET :: elrk_air(:)
1161 !# endif
1162  REAL(sp), ALLOCATABLE,TARGET :: el_air(:)
1163  REAL(sp), ALLOCATABLE,TARGET :: egf_air(:)
1164 
1165  REAL(sp), ALLOCATABLE,TARGET :: vort(:)
1166 
1167 
1168 !---------------surface/bottom boundary conditions---------------------------------!
1169 
1170  REAL(sp), ALLOCATABLE,TARGET :: cbc(:) !!BOTTOM FRICTION
1171  REAL(sp), ALLOCATABLE,TARGET :: cc_z0b(:) !!BOTTOM ROUGHNESS VARIABLE
1172 
1173  REAL(sp), ALLOCATABLE,TARGET :: swrad_watts(:) !!SURFACE INCIDENT RADIATION
1174  REAL(sp), ALLOCATABLE,TARGET :: wtsurf_watts(:) !!NET HEAT FLUX AT SURFACE
1175 
1176  ! THESE TWO ARE DIVIDED BY THE SPECFIC HEAT AND AVERAGE DENSITY!
1177  REAL(sp), ALLOCATABLE,TARGET :: swrad(:) !!SURFACE INCIDENT RADIATION
1178  REAL(sp), ALLOCATABLE,TARGET :: wtsurf(:) !!NET HEAT FLUX AT SURFACE
1179 
1180  ! SUSPECTED UNITS FOR SURFACE STRESS: N/M * 1/RHO_BAR ... see bcond_gcn.F
1181 !# if !defined (SEMI_IMPLICIT)
1182  REAL(sp), ALLOCATABLE,TARGET :: wusurf2(:) !!SURFACE FRICTION FOR EXT
1183  REAL(sp), ALLOCATABLE,TARGET :: wvsurf2(:) !!SURFACE FRICTION FOR EXT
1184 !# endif
1185  REAL(sp), ALLOCATABLE,TARGET :: wubot(:) !!BOTTOM FRICTION
1186  REAL(sp), ALLOCATABLE,TARGET :: wvbot(:) !!BOTTOM FRICTION
1187  REAL(sp), ALLOCATABLE,TARGET :: taubm(:) !!BOTTOM FRICTION MAGNITUDE(Caution is Tau' [no Rho])
1188  REAL(sp), ALLOCATABLE,TARGET :: wubot_n(:) !!BOTTOM FRICTION ON NODES (Caution is Tau' [no Rho])
1189  REAL(sp), ALLOCATABLE,TARGET :: wvbot_n(:) !!BOTTOM FRICTION ON NODES (Caution is Tau' [no Rho])
1190  REAL(sp), ALLOCATABLE,TARGET :: taubm_n(:) !!BOTTOM FRICTION MAGNITUDE ON NODES (Caution is Tau' [no Rho])
1191  REAL(sp), ALLOCATABLE,TARGET :: wusurf(:) !!SURFACE FRICTION FOR INT
1192  REAL(sp), ALLOCATABLE,TARGET :: wvsurf(:) !!SURFACE FRICTION FOR INT
1193  REAL(sp), ALLOCATABLE,TARGET :: wusurf_save(:) !!SURFACE FRICTION FOR INT
1194  REAL(sp), ALLOCATABLE,TARGET :: wvsurf_save(:) !!SURFACE FRICTION FOR INT
1195  ! BFWDIS - UNITS: m3s-1 Cubic meters per second
1196  REAL(sp), ALLOCATABLE,TARGET :: bfwdis(:) !!GROUNDWATER FLUX AT CURRENT TIME
1197 !# if !defined (SEMI_IMPLICIT)
1198  REAL(sp), ALLOCATABLE,TARGET :: bfwdis2(:) !!GROUNDWATER FLUX FOR EXT
1199 !# endif
1200  REAL(sp), ALLOCATABLE,TARGET :: bfwtmp(:) !!GROUNDWATER TEMP AT CURRENT TIME
1201  REAL(sp), ALLOCATABLE,TARGET :: bfwslt(:) !!GROUNDWATER SALT AT CURRENT TIME
1202 
1203 
1204  ! ICING MODEL DATA
1205  REAL(sp), ALLOCATABLE,TARGET :: icing_wndx(:)
1206  REAL(sp), ALLOCATABLE,TARGET :: icing_wndy(:)
1207  REAL(sp), ALLOCATABLE,TARGET :: icing_satmp(:)
1208  REAL(sp), ALLOCATABLE,TARGET :: icing_0kts(:)
1209  REAL(sp), ALLOCATABLE,TARGET :: icing_10kts(:)
1210 
1211  ! NOT SURE WHETHER RIVER STUFF BELONGS HERE OR IN ALL_VARS???
1212 
1213  ! RIVER STUFF
1214  INTEGER, ALLOCATABLE,TARGET :: inodeq(:) !!LOCAL FRESH WATER INFLOW NODES
1215  INTEGER, ALLOCATABLE,TARGET :: icellq(:) !!LOCAL FRESH WATER INFLOW ELEMENT
1216  INTEGER, ALLOCATABLE,TARGET :: n_icellq(:,:) !!TWO NODES BOUNDING THE INFLOW ELEMENT
1217  REAL(sp), ALLOCATABLE,TARGET :: vqdist(:,:) !!DISCHARGE VERTICAL DISTRIBUTION
1218  INTEGER, ALLOCATABLE,TARGET :: riv_gl2loc(:)
1219 
1220  REAL(sp), ALLOCATABLE,TARGET :: qdis(:) !!RIVER FLUX AT CURRENT TIME
1221 !# if !defined (SEMI_IMPLICIT)
1222  REAL(sp), ALLOCATABLE,TARGET :: qdis2(:) !!RIVER FLUX (EXT MODE, NOT USED)
1223 !# endif
1224  REAL(sp), ALLOCATABLE,TARGET :: tdis(:) !!RIVER WATER TEMP AT CURRENT TIME
1225  REAL(sp), ALLOCATABLE,TARGET :: sdis(:) !!RIVER WATER SLNT AT CURRENT TIME
1226  REAL(sp), ALLOCATABLE,TARGET :: qarea(:) !!AREA OF RIVER DISCHARGE
1227  REAL(sp), ALLOCATABLE,TARGET :: rdisq(:,:) !!AREA OF FLUX
1228  REAL(sp), ALLOCATABLE,TARGET :: angleq(:) !!RIVER DISCHARGE ANGLE
1229  REAL(sp), ALLOCATABLE,TARGET :: vlctyq(:) !!RIVER DISCHARGE VELOCITY
1230 
1231  ! SURFACE MET STUFF
1232  REAL(sp), ALLOCATABLE,TARGET :: uuwind(:) !!SURFACE X-WIND
1233  REAL(sp), ALLOCATABLE,TARGET :: vvwind(:) !!SURFACE Y-WIND
1234  ! PRECIP/EVAP are in units of meters/second
1235 !# if !defined (SEMI_IMPLICIT)
1236  REAL(sp), ALLOCATABLE,TARGET :: qprec2(:) !!SURFACE PRECIPITATION FOR EXT
1237  REAL(sp), ALLOCATABLE,TARGET :: qevap2(:) !!SURFACE EVAPORATION FOR EXT
1238 !# endif
1239  REAL(sp), ALLOCATABLE,TARGET :: qprec(:) !!SURFACE PRECIPITATION FOR INT
1240  REAL(sp), ALLOCATABLE,TARGET :: qevap(:) !!SURFACE EVAPORATION FOR INT
1241 
1242  REAL(sp), ALLOCATABLE,TARGET :: whs(:) !!SURFACE WAVE HEIGHT
1243  REAL(sp), ALLOCATABLE,TARGET :: wdir(:) !!SURFACE WAVE DIRECTION
1244  REAL(sp), ALLOCATABLE,TARGET :: wper(:) !!SURFACE WAVE PERIOD
1245  REAL(sp), ALLOCATABLE,TARGET :: wlength(:) !!SURFACE WAVE LENGTH
1246  REAL(sp), ALLOCATABLE,TARGET :: wper_bot(:) !!BOTTOM WAVE PERIOD
1247  REAL(sp), ALLOCATABLE,TARGET :: wub_bot(:) !!BOTTOM ORBITAL VELOCITY
1248 
1249 
1250 !----------------boundary conditions: meteo conditions-----------------!
1251 
1252 !-----------------------2-d flow fluxes--------------------------------------------!
1253 
1254  REAL(sp), ALLOCATABLE,TARGET :: pstx(:) !!EXT MODE BAROTROPIC TERMS
1255  REAL(sp), ALLOCATABLE,TARGET :: psty(:) !!EXT MODE BAROTROPIC TERMS
1256  REAL(sp), ALLOCATABLE,TARGET :: advua(:)
1257  REAL(sp), ALLOCATABLE,TARGET :: advva(:)
1258  REAL(sp), ALLOCATABLE,TARGET :: adx2d(:)
1259  REAL(sp), ALLOCATABLE,TARGET :: ady2d(:)
1260  REAL(sp), ALLOCATABLE,TARGET :: drx2d(:)
1261  REAL(sp), ALLOCATABLE,TARGET :: dry2d(:)
1262  REAL(sp), ALLOCATABLE,TARGET :: tps(:) !!WORKING ARRAY
1263  REAL(sp), ALLOCATABLE,TARGET :: advx(:,:)
1264  REAL(sp), ALLOCATABLE,TARGET :: advy(:,:)
1265 
1266 !---------------- internal mode arrays-(element based)----------------------------!
1267 
1268  REAL(sp), ALLOCATABLE,TARGET :: u(:,:) !X-VELOCITY
1269  REAL(sp), ALLOCATABLE,TARGET :: v(:,:) !Y-VELOCITY
1270 
1271  REAL(sp), ALLOCATABLE,TARGET :: ubeta(:,:) !X-VELOCITY temp time step
1272  REAL(sp), ALLOCATABLE,TARGET :: vbeta(:,:) !Y-VELOCITY temp time step
1273 
1274  REAL(sp), ALLOCATABLE :: ubeta2d(:)
1275  REAL(sp), ALLOCATABLE :: vbeta2d(:)
1276 
1277  REAL(sp), ALLOCATABLE, TARGET :: partition(:) !gwc
1278 
1279  REAL(sp), ALLOCATABLE,TARGET :: w(:,:) !VERTICAL VELOCITY IN SIGMA SYSTEM
1280  REAL(sp), ALLOCATABLE,TARGET :: ww(:,:) !Z-VELOCITY
1281  REAL(sp), ALLOCATABLE,TARGET :: uf(:,:) !X-VELOCITY FROM PREVIOUS TIMESTEP
1282  REAL(sp), ALLOCATABLE,TARGET :: vf(:,:) !Y-VELOCITY FROM PREVIOUS TIMESTEP
1283  REAL(sp), ALLOCATABLE,TARGET :: wt(:,:) !Z-VELOCITY FROM PREVIOUS TIMESTEP
1284  REAL(sp), ALLOCATABLE,TARGET :: rho(:,:) !DENSITY AT ELEMENTS
1285  REAL(sp), ALLOCATABLE,TARGET :: rmean(:,:) !INITIAL DENSITY AT ELEMENTS
1286  REAL(sp), ALLOCATABLE,TARGET :: t(:,:) !TEMPERATURE AT ELEMENTS
1287  REAL(sp), ALLOCATABLE,TARGET :: tmean(:,:) !INITIAL TEMPERATURE AT ELEMENTS
1288  REAL(sp), ALLOCATABLE,TARGET :: s(:,:) !SALINITY AT ELEMENTS
1289  REAL(sp), ALLOCATABLE,TARGET :: smean(:,:) !INITIAL SALINITY AT ELEMENTS
1290  REAL(sp), ALLOCATABLE,TARGET :: q2(:,:) !2 X TURBULENT KINETIC ENERGY AT NODES
1291  REAL(sp), ALLOCATABLE,TARGET :: l(:,:) !TURBULENT LENGTH MACROSCALE
1292  REAL(sp), ALLOCATABLE,TARGET :: q2l(:,:) !2 X TURBULENT KE X LENGTH AT NODES
1293  REAL(sp), ALLOCATABLE,TARGET :: km(:,:) !TURBULENT EDDY VISCOSITY FOR MOMENTUM
1294  REAL(sp), ALLOCATABLE,TARGET :: kh(:,:) !TURBULENT DIFFUSIVITY FOR SALINITY/TEMP
1295  REAL(sp), ALLOCATABLE,TARGET :: kq(:,:) !TURBULENT DIFFUSIVITY FOR Q2/Q2L
1296  REAL(sp), ALLOCATABLE,TARGET :: aam(:,:) !STORAGE FOR OUTPUT OF HORIZONTAL VISCOSITY
1297  REAL(sp), ALLOCATABLE,TARGET :: q2f(:,:) !WORKING ARRAY FOR UPDATING Q2
1298  REAL(sp), ALLOCATABLE,TARGET :: q2lf(:,:) !WORKING ARRAY FOR UPDATING Q2F
1299  REAL(sp), ALLOCATABLE,TARGET :: km1(:,:) !TURBULENT EDDY VISCOSITY FOR MOMENTUM
1300 
1301  ! VARIABLE HORIZONTAL VISCOSITY COEFFICENTS
1302  REAL(sp), ALLOCATABLE :: cc_hvc(:)
1303  REAL(sp), ALLOCATABLE :: nn_hvc(:)
1304 
1305  !-----------------------3d variable arrays-(node based)-----------------------------!
1306 
1307  REAL(sp), ALLOCATABLE,TARGET :: t1(:,:) !!TEMPERATURE AT NODES
1308  REAL(sp), ALLOCATABLE,TARGET :: s1(:,:) !!SALINITY AT NODES
1309  REAL(sp), ALLOCATABLE,TARGET :: rho1(:,:) !!DENSITY AT NODES
1310  REAL(sp), ALLOCATABLE,TARGET :: tf1(:,:) !!TEMPERATURE FROM PREVIOUS TIME
1311  REAL(sp), ALLOCATABLE,TARGET :: sf1(:,:) !!SALINITY FROM PREVIOUS TIME
1312 !J. Ge for tracer advection
1313  REAL(sp), ALLOCATABLE,TARGET :: t0(:,:) !!TEMPERATURE AT NODES AT PREVIOUS TIME STEP
1314  REAL(sp), ALLOCATABLE,TARGET :: t2(:,:) !!TEMPERATURE AT NODES AT PREVIOUS TWO STEP
1315  REAL(sp), ALLOCATABLE,TARGET :: s0(:,:) !!SALINITY AT NODES AT PREVIOUS TIME STEP
1316  REAL(sp), ALLOCATABLE,TARGET :: s2(:,:) !!SALINITY AT NODES AT PREVIOUS TWO STEP
1317 !J. Ge for tracer advection
1318  REAL(sp), ALLOCATABLE,TARGET :: tmean1(:,:) !!MEAN INITIAL TEMP
1319  REAL(sp), ALLOCATABLE,TARGET :: smean1(:,:) !!MEAN INITIAL SALINITY
1320  REAL(sp), ALLOCATABLE,TARGET :: rmean1(:,:) !!MEAN INITIAL DENSITY
1321  REAL(sp), ALLOCATABLE,TARGET :: wts(:,:) !!VERTICAL VELOCITY IN SIGMA SYSTEM
1322  REAL(sp), ALLOCATABLE,TARGET :: wtts(:,:) !!WTS FROM PREVIOUS TIMESTEP
1323 
1324  !---------------------------internal mode fluxes------------------------------------!
1325 
1326  REAL(sp), ALLOCATABLE,TARGET :: drhox(:,:) !!BAROCLINIC PG IN X DIRECTION
1327  REAL(sp), ALLOCATABLE,TARGET :: drhoy(:,:) !!BAROCLINIC PG IN Y DIRECTION
1328 
1329  !------------shape coefficient arrays and control volume metrics--------------------!
1330 
1331  REAL(sp), ALLOCATABLE,TARGET :: a1u(:,:)
1332  REAL(sp), ALLOCATABLE,TARGET :: a2u(:,:)
1333  REAL(sp), ALLOCATABLE,TARGET :: awx(:,:)
1334  REAL(sp), ALLOCATABLE,TARGET :: awy(:,:)
1335  REAL(sp), ALLOCATABLE,TARGET :: aw0(:,:)
1336  REAL(sp), ALLOCATABLE,TARGET :: alpha(:)
1337 
1338 
1339  !-----salinity and temperature bottom diffusion condition/bottom depth gradients----!
1340 
1341  REAL(sp), ALLOCATABLE,TARGET :: phpn(:)
1342  REAL(sp), ALLOCATABLE,TARGET :: pfpxb(:)
1343  REAL(sp), ALLOCATABLE,TARGET :: pfpyb(:)
1344  REAL(sp), ALLOCATABLE,TARGET :: sita_gd(:)
1345  REAL(sp), ALLOCATABLE,TARGET :: ah_bottom(:)
1346 
1347  !-----arrays used for averaging of flow quantities for output-----------------------!
1348 
1349  REAL(sp), ALLOCATABLE,TARGET :: u_ave(:,:) !U AVERAGED OVER INT_AVGE ITERATIONS
1350  REAL(sp), ALLOCATABLE,TARGET :: v_ave(:,:) !V AVERAGED OVER INT_AVGE ITERATIONS
1351  REAL(sp), ALLOCATABLE,TARGET :: w_ave(:,:) !WW AVERAGED OVER INT_AVGE ITERATIONS
1352  REAL(sp), ALLOCATABLE,TARGET :: km_ave(:,:) !KM AVERAGED OVER INT_AVGE ITERATIONS
1353  REAL(sp), ALLOCATABLE,TARGET :: kh_ave(:,:) !KH AVERAGED OVER INT_AVGE ITERATIONS
1354  REAL(sp), ALLOCATABLE,TARGET :: t_ave(:,:) !T1 AVERAGED OVER INT_AVGE ITERATIONS
1355  REAL(sp), ALLOCATABLE,TARGET :: s_ave(:,:) !S1 AVERAGED OVER INT_AVGE ITERATIONS
1356  REAL(sp), ALLOCATABLE,TARGET :: r_ave(:,:) !RHO1 AVERAGED OVER INT_AVGE ITERATIONS
1357  REAL(sp), ALLOCATABLE,TARGET :: el_ave(:) !EL AVERAGED OVER INT_AVGE ITERATIONS
1358 
1359  REAL(sp), ALLOCATABLE,TARGET :: viscofh(:,:)
1360  REAL(sp), ALLOCATABLE,TARGET :: viscofm(:,:)
1361 
1362  REAL(sp), ALLOCATABLE,TARGET :: hyw(:,:)
1363 
1364 
1365 CONTAINS
1366 
1367 
1368 !==============================================================================|
1369  SUBROUTINE n2e3d(NVAR,EVAR)
1370 !==============================================================================|
1371  IMPLICIT NONE
1372  REAL(SP), DIMENSION(0:MT,1:KB), INTENT(IN) :: NVAR
1373  REAL(SP), DIMENSION(0:NT,1:KB), INTENT(INOUT) :: EVAR
1374  INTEGER I,K
1375 !------------------------------------------------------------------------------|
1376  DO k=1,kb
1377  DO i = 1, nt
1378  evar(i,k) = one_third*(nvar(nv(i,1),k)+nvar(nv(i,2),k)+nvar(nv(i,3),k))
1379  END DO
1380  END DO
1381  RETURN
1382  END SUBROUTINE n2e3d
1383 !==============================================================================|
1384 
1385 !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1386 !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1387 
1388 !==============================================================================|
1389  SUBROUTINE n2e2d(NVAR,EVAR)
1390 !==============================================================================|
1391  IMPLICIT NONE
1392  REAL(SP), DIMENSION(0:MT), INTENT(IN) :: NVAR
1393  REAL(SP), DIMENSION(0:NT), INTENT(INOUT) :: EVAR
1394  INTEGER I,K
1395 !------------------------------------------------------------------------------|
1396  DO i = 1, nt
1397  evar(i) = one_third*(nvar(nv(i,1))+nvar(nv(i,2))+nvar(nv(i,3)))
1398  END DO
1399  RETURN
1400  END SUBROUTINE n2e2d
1401 !==============================================================================|
1402 
1403 !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1404 !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1405 
1406 !==============================================================================|
1407  SUBROUTINE e2n2d(EVAR,NVAR)
1408 !==============================================================================|
1409  IMPLICIT NONE
1410  REAL(SP), DIMENSION(0:NT), INTENT(IN ) :: EVAR
1411  REAL(SP), DIMENSION(0:MT), INTENT(INOUT) :: NVAR
1412 
1413  INTEGER I,K
1414 !------------------------------------------------------------------------------|
1415  DO i=1,m
1416  nvar(i) = sum(evar(nbve(i,1:ntve(i))))/float(ntve(i))
1417  END DO
1418  RETURN
1419  END SUBROUTINE e2n2d
1420 !==============================================================================|
1421 
1422 !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1423 !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1424 
1425 !==============================================================================|
1426  SUBROUTINE e2n3d(EVAR,NVAR)
1427 !==============================================================================|
1428  IMPLICIT NONE
1429  REAL(SP), DIMENSION(0:NT,1:KB), INTENT(IN ) :: EVAR
1430  REAL(SP), DIMENSION(0:MT,1:KB), INTENT(INOUT) :: NVAR
1431  INTEGER I,K
1432 !------------------------------------------------------------------------------|
1433  DO k=1,kb
1434  DO i=1,m
1435  nvar(i,k) = sum(evar(nbve(i,1:ntve(i)),k))/float(ntve(i))
1436  END DO
1437  END DO
1438  RETURN
1439  END SUBROUTINE e2n3d
1440 !==============================================================================|
1441 
1442 !==============================================================================|
1443 ! Allocate and Initialize Most Arrays !
1444 !==============================================================================|
1445 
1446  SUBROUTINE alloc_vars(dbg_set)
1448 !==============================================================================!
1449  IMPLICIT NONE
1450  logical,intent(in) :: dbg_set
1451  INTEGER NCT,NDB
1452 !==============================================================================!
1453  ndb = 1 !!GWC BASE THIS ON KIND
1454 
1455  nct = nt*3 ! A DIMENSION USED FOR ALLOCATION!
1456 
1457 !==============================================================================!
1458 ! ALLOCATE: !
1459 !==============================================================================!
1460 
1461 !--------------------------Grid Metrics---------------------------------------------!
1462 
1463  ALLOCATE(lon(0:mt)) ;lon = zero !!LONGITUDE AT THE NODE
1464  ALLOCATE(lat(0:mt)) ;lat = zero !!LATITUDE AT THE NODE
1465  ALLOCATE(lonc(0:nt)) ;lonc = zero !!LONGITUDE AT THE NODE
1466  ALLOCATE(latc(0:nt)) ;latc = zero !!LATITUDE AT THE NODE
1467  ALLOCATE(xm(0:mt)) ;xm = zero !!X-COORD AT NODE IN METERS
1468  ALLOCATE(ym(0:mt)) ;ym = zero !!Y-COORD AT NODE IN METERS
1469  ALLOCATE(xmc(0:nt)) ;xmc = zero !!X-COORD AT FACE CENTER IN METERS
1470  ALLOCATE(ymc(0:nt)) ;ymc = zero !!Y-COORD AT FACE CENTER IN METERS
1471  ALLOCATE(xc(0:nt)) ;xc = zero !!X-COORD AT FACE CENTER
1472  ALLOCATE(yc(0:nt)) ;yc = zero !!Y-COORD AT FACE CENTER
1473  ALLOCATE(vx(0:mt)) ;vx = zero !!X-COORD AT GRID POINT
1474  ALLOCATE(vy(0:mt)) ;vy = zero !!Y-COORD AT GRID POINT
1475  ALLOCATE(art(0:nt)) ;art = zero !!AREA OF ELEMENT
1476  ALLOCATE(art1(0:mt)) ;art1 = zero !!AREA OF NODE-BASE CONTROl VOLUME
1477  ALLOCATE(art2(0:mt)) ;art2 = zero !!AREA OF ELEMENTS AROUND NODE
1478  ALLOCATE(grav_n(0:mt)) ;grav_n = zero !! VARIABLE GRAVITY
1479  ALLOCATE(grav_e(0:nt)) ;grav_e = zero !! VARIABLE GRAVITY
1480 
1481  memcnt = mt*9*ndb + nt*8*ndb + memcnt
1482 
1483 !----------------Node, Boundary Condition, and Control Volume-----------------------!
1484 
1485 ! ALLOCATED IN setup_domain.F But count the memory here
1486 ! ALLOCATE(NV(0:NT,4)) ;NV = 0 !!NODE NUMBERING FOR ELEMENTS
1487 ! ALLOCATE(NVGL(0:NT,3)) ;NVGL = 0 !!GLOBAL NODE NUMBERING FOR LOCAL ELEMENTS
1488  ALLOCATE(nbe(0:nt,3)) ;nbe = 0 !!INDICES OF ELMNT NEIGHBORS
1489  ALLOCATE(ntve(0:mt)) ;ntve = 0
1490  ALLOCATE(ntsn(0:mt)) ;ntsn = 0
1491  ALLOCATE(isonb(0:mt)) ;isonb = 0 !!NODE MARKER = 0,1,2
1492  ALLOCATE(isonb_w(0:mt)) ;isonb_w = 0 !!NODE MARKER = 0,1,2
1493  ALLOCATE(isbce(0:nt)) ;isbce = 0
1494  ALLOCATE(niec(nct,2)) ;niec = 0
1495  ALLOCATE(ntrg(nct)) ;ntrg = 0
1496 
1497  ! POSITION OF NODAL CONTROL VOLUME CORNERS
1498  ALLOCATE(xije(nct,2)) ;xije = zero
1499  ALLOCATE(yije(nct,2)) ;yije = zero
1500  ! LENGTH OF NODAL CONTROL VOLUME EDGES
1501  ALLOCATE(dltxe(nct)) ;dltxe = zero
1502  ALLOCATE(dltye(nct)) ;dltye = zero
1503  ALLOCATE(dltxye(nct)) ;dltxye = zero !! TOTAL LENGTH
1504  ALLOCATE(sitae(nct)) ;sitae = zero !! ANGLE
1505 
1506  ! LENGTH BETWEEN NODE AND CONTROL VOLUMEN EDGE CENTER
1507  ALLOCATE(dltxncve(nct,2)) ; dltxncve = zero !! DeLTa X Node to Control Volume Edge
1508  ALLOCATE(dltyncve(nct,2)) ; dltyncve = zero !! DeLTa Y Node to Control Volume Edge
1509 
1510 
1511  ! THE FOLLOWING ARRAYS COULD BE REPLACED WITH (N,3) ARRAYS
1512  ! BUT THE INDEXING WOULD BE COMPLEX AND THERE ARE SIGN ISSUES!
1513 
1514  ! TRIANGLE EDGE LENGTH FOR EDGES SURROUNDING EACH NODE
1515  ! NTSN Can not be greater than 13!
1516  ALLOCATE(dltxtrie(m,12)) ;dltxtrie = zero !! DeLTa X TRIangle Edge
1517  ALLOCATE(dltytrie(m,12)) ;dltytrie = zero !! DeLTa Y TRIangle Edge
1518 
1519  ALLOCATE(dltxnec(m,12)) ;dltxnec = zero !! DeLTa X Node to Edge Center
1520  ALLOCATE(dltynec(m,12)) ;dltynec = zero !! DeLTa Y Node to Edge Center
1521 
1522  ! DISTANCE BETWEEN TRIANGLE EDGE CENTERS FOR EACH TRIANGLE AROUND A NODE
1523  ! NTVE Can not be greater than 13!
1524  ALLOCATE(dltxecec(m,12)) ;dltxecec = zero !! DeLTa X Edge Center to Edge Center
1525  ALLOCATE(dltyecec(m,12)) ;dltyecec = zero !! DeLTa Y Edge Center to Edge Center
1526 
1527 
1528 
1529  memcnt = nt*4 + mt*3 +m*6*12*ndb + nct*3 + nct*12*ndb + memcnt
1530 
1531 !----------------2-d arrays for the general vertical coordinate -------------------------------!
1532 
1533  ALLOCATE(z(0:mt,kb)) ; z = zero !!SIGMA COORDINATE VALUE
1534  ALLOCATE(zz(0:mt,kb)) ; zz = zero !!INTRA LEVEL SIGMA VALUE
1535  ALLOCATE(dz(0:mt,kb)) ; dz = zero !!DELTA-SIGMA VALUE
1536  ALLOCATE(dzz(0:mt,kb)) ; dzz = zero !!DELTA OF INTRA LEVEL SIGMA
1537  ALLOCATE(z1(0:nt,kb)) ; z1 = zero !!SIGMA COORDINATE VALUE
1538  ALLOCATE(zz1(0:nt,kb)) ; zz1 = zero !!INTRA LEVEL SIGMA VALUE
1539  ALLOCATE(dz1(0:nt,kb)) ; dz1 = zero !!DELTA-SIGMA VALUE
1540  ALLOCATE(dzz1(0:nt,kb)) ; dzz1 = zero !!DELTA OF INTRA LEVEL SIGMA
1541  memcnt = mt*kb*4*ndb + nt*kb*4*ndb +memcnt
1542 
1543 !---------------2-d flow variable arrays at elements-------------------------------!
1544 
1545  ALLOCATE(ua(0:nt)) ;ua = zero !!VERTICALLY AVERAGED X-VELOC
1546  ALLOCATE(va(0:nt)) ;va = zero !!VERTICALLY AVERAGED Y-VELOC
1547  ALLOCATE(uaf(0:nt)) ;uaf = zero !!UA FROM PREVIOUS RK STAGE
1548  ALLOCATE(vaf(0:nt)) ;vaf = zero !!VA FROM PREVIOUS RK STAGE
1549  ALLOCATE(uark(0:nt)) ;uark = zero !!UA FROM PREVIOUS TIMESTEP
1550  ALLOCATE(vark(0:nt)) ;vark = zero !!VA FROM PREVIOUS TIMESTEP
1551  ALLOCATE(uard(0:nt)) ;uard = zero !!UA AVERAGED OVER EXTERNAL INT
1552  ALLOCATE(vard(0:nt)) ;vard = zero !!VA AVERAGED OVER EXTERNAL INT
1553  ALLOCATE(cor(0:nt)) ;cor = zero !!CORIOLIS PARAMETER
1554  ALLOCATE(f_alfa(0:nt)) ;f_alfa = 1.0_sp !!EQUATORIAL BETA PLANE PARAMETER
1555  ALLOCATE(h1(0:nt)) ;h1 = zero !!BATHYMETRIC DEPTH
1556  ALLOCATE(d1(0:nt)) ;d1 = zero !!DEPTH
1557  ALLOCATE(dt1(0:nt)) ;dt1 = zero !!DEPTH
1558  ALLOCATE(el1(0:nt)) ;el1 = zero !!SURFACE ELEVATION
1559  ALLOCATE(elf1(0:nt)) ;elf1 = zero !!SURFACE ELEVATION
1560  ALLOCATE(dtfa(0:mt)) ;dtfa = zero !!ADJUSTED DEPTH FOR MASS CONSERVATION
1561  ALLOCATE(et1(0:nt)) ;et1 = zero !!SURFACE ELEVATION
1562  ALLOCATE(elrk1(0:nt)) ;elrk1 = zero !!SURFACE ELEVATION
1563  ALLOCATE(cc_sponge(0:nt)) ;cc_sponge = zero !!SPONGE DAMPING COEFFICIENT FOR MOMENTUM
1564  memcnt = nt*17*ndb + mt*ndb + memcnt
1565 
1566 !---------------2-d flow variable arrays at nodes----------------------------------!
1567 
1568  ALLOCATE(h(0:mt)) ;h = zero !!BATHYMETRIC DEPTH
1569  ALLOCATE(d(0:mt)) ;d = zero !!DEPTH
1570  ALLOCATE(dt(0:mt)) ;dt = zero !!DEPTH
1571  ALLOCATE(el(0:mt)) ;el = zero !!SURFACE ELEVATION
1572  ALLOCATE(elf(0:mt)) ;elf = zero !!SURFACE ELEVATION
1573  ALLOCATE(et(0:mt)) ;et = zero !!SURFACE ELEVATION
1574  ALLOCATE(egf(0:mt)) ;egf = zero !!SURFACE ELEVATION
1575  ALLOCATE(elrk(0:mt)) ;elrk = zero !!SURFACE ELEVATION
1576  memcnt = mt*8*ndb + memcnt
1577 
1578 
1579 
1580 
1581  ALLOCATE(vort(0:mt)) ; vort = zero
1582  memcnt = mt*ndb + memcnt
1583 
1584 !---------------surface/bottom/edge boundary conditions-----------------------------!
1585 
1586  ALLOCATE(cbc(0:nt)) ;cbc = zero !!BOTTOM FRICTION
1587  ALLOCATE(cc_z0b(0:nt)) ;cc_z0b = zero !!BOTTOM ROUGHNESS VARIABLE
1588 !# if !defined (SEMI_IMPLICIT)
1589  ALLOCATE(wusurf2(0:nt)) ;wusurf2= zero !!SURFACE FRICTION FOR EXT
1590  ALLOCATE(wvsurf2(0:nt)) ;wvsurf2= zero !!SURFACE FRICTION FOR EXT
1591 !# endif
1592  ALLOCATE(wubot(0:nt)) ;wubot = zero !!BOTTOM FRICTION
1593  ALLOCATE(wvbot(0:nt)) ;wvbot = zero !!BOTTOM FRICTION
1594  ALLOCATE(taubm(0:nt)) ;taubm = zero !!BOTTOM FRICTION
1595  ALLOCATE(wubot_n(0:mt)) ;wubot_n = zero !!U-Component bottom shear stress on nodes
1596  ALLOCATE(wvbot_n(0:mt)) ;wvbot_n = zero !!V-Component bottom shear stress on nodes
1597  ALLOCATE(taubm_n(0:mt)) ;taubm_n = zero !!Magnitude bottom shear stress on nodes
1598  ALLOCATE(wusurf(0:nt)) ;wusurf = zero !!SURFACE FRICTION FOR INT
1599  ALLOCATE(wvsurf(0:nt)) ;wvsurf = zero !!SURFACE FRICTION FOR INT
1600  ALLOCATE(wusurf_save(0:nt)) ;wusurf_save = zero!!SURFACE FRICTION FOR INT
1601  ALLOCATE(wvsurf_save(0:nt)) ;wvsurf_save = zero!!SURFACE FRICTION FOR INT
1602  ALLOCATE(uuwind(0:nt)) ;uuwind = zero !!SURFACE X-WIND
1603  ALLOCATE(vvwind(0:nt)) ;vvwind = zero !!SURFACE Y-WIND
1604  ALLOCATE(swrad(0:mt)) ;swrad = zero !!SURFACE INCIDENT RADIATION
1605  ALLOCATE(wtsurf(0:mt)) ;wtsurf = zero
1606  ALLOCATE(swrad_watts(0:mt)) ;swrad_watts = zero !!SURFACE INCIDENT RADIATION
1607  ALLOCATE(wtsurf_watts(0:mt)) ;wtsurf_watts = zero
1608 
1609  ALLOCATE(qprec2(0:mt)) ;qprec2 = zero !!SURFACE PRECIPITATION FOR EXT
1610  ALLOCATE(qevap2(0:mt)) ;qevap2 = zero !!SURFACE EVAPORATION FOR EXT
1611  ALLOCATE(qprec(0:mt)) ;qprec = zero !!SURFACE PRECIPITATION FOR INT
1612  ALLOCATE(qevap(0:mt)) ;qevap = zero !!SURFACE EVAPORATION FOR INT
1613 
1614 
1615 
1616  memcnt = nt*10*ndb + mt*8*ndb + memcnt
1617 
1618  IF (icing_model) THEN
1619  ALLOCATE(icing_wndx(0:mt)) ;icing_wndx = zero
1620  ALLOCATE(icing_wndy(0:mt)) ;icing_wndy = zero
1621  ALLOCATE(icing_satmp(0:mt));icing_satmp = zero
1622  ALLOCATE(icing_0kts(0:mt)) ;icing_0kts = zero
1623  ALLOCATE(icing_10kts(0:mt));icing_10kts= zero
1624 
1625  memcnt = memcnt + mt*4*ndb
1626  END IF
1627 
1628 
1629 !--------------------------------------------------------------
1630 !--------------------------------------------------------------
1631 
1632  ALLOCATE(bfwdis(0:mt)) ;bfwdis = zero !!GROUNDWATER FLUX FOR INT
1633  ALLOCATE(bfwdis2(0:mt)) ;bfwdis2= zero !!GROUNDWATER FLUX FOR EXT
1634  ALLOCATE(bfwslt(0:mt)) ;bfwslt = zero !!GROUNDWATER SALT AT CURRENT TIME
1635  ALLOCATE(bfwtmp(0:mt)) ;bfwtmp = zero !!GROUNDWATER TEMP AT CURRENT TIME
1636 
1637  memcnt = mt*4*ndb + memcnt
1638 
1639 !-----------------------2-d flow fluxes---------------------------------------------!
1640 
1641  ALLOCATE(pstx(0:nt)) ;pstx = zero !!EXT MODE BAROTROPIC TERMS
1642  ALLOCATE(psty(0:nt)) ;psty = zero !!EXT MODE BAROTROPIC TERMS
1643  ALLOCATE(advua(0:nt)) ;advua = zero
1644  ALLOCATE(advva(0:nt)) ;advva = zero
1645  ALLOCATE(adx2d(0:nt)) ;adx2d = zero
1646  ALLOCATE(ady2d(0:nt)) ;ady2d = zero
1647  ALLOCATE(drx2d(0:nt)) ;drx2d = zero
1648  ALLOCATE(dry2d(0:nt)) ;dry2d = zero
1649  ALLOCATE(advx(0:nt,kb)) ;advx = zero
1650  ALLOCATE(advy(0:nt,kb)) ;advy = zero
1651  ALLOCATE(tps(0:nt)) ;tps = zero !!WORKING ARRAY
1652  memcnt = nt*9*ndb + nt*kb*2*ndb + memcnt
1653 
1654 
1655 !---------------- internal mode arrays-(element based)----------------------------!
1656 
1657  ALLOCATE(u(0:nt,kb)) ;u = zero !!X-VELOCITY
1658  ALLOCATE(v(0:nt,kb)) ;v = zero !!Y-VELOCITY
1659  ALLOCATE(ubeta(0:nt,kb)) ;ubeta = zero !!X-VELOCITY temp time step
1660  ALLOCATE(vbeta(0:nt,kb)) ;vbeta = zero !!X-VELOCITY temp time step
1661  ALLOCATE(ubeta2d(0:nt)) ;ubeta2d = zero
1662  ALLOCATE(vbeta2d(0:nt)) ;vbeta2d = zero
1663 
1664  ALLOCATE(w(0:nt,kb)) ;w = zero !!VERTICAL VELOCITY IN SIGMA SYSTEM
1665  ALLOCATE(ww(0:nt,kb)) ;ww = zero !!Z-VELOCITY
1666  ALLOCATE(uf(0:nt,kb)) ;uf = zero !!X-VELOCITY FROM PREVIOUS TIMESTEP
1667  ALLOCATE(vf(0:nt,kb)) ;vf = zero !!Y-VELOCITY FROM PREVIOUS TIMESTEP
1668  ALLOCATE(wt(0:nt,kb)) ;wt = zero !!Z-VELOCITY FROM PREVIOUS TIMESTEP
1669  ALLOCATE(rho(0:nt,kb)) ;rho = zero !!DENSITY AT ELEMENTS
1670  ALLOCATE(rmean(0:nt,kb)) ;rmean = zero !!MEAN INITIAL DENSITY AT ELEMENTS
1671  ALLOCATE(t(0:nt,kb)) ;t = zero !!TEMPERATURE AT ELEMENTS
1672  ALLOCATE(tmean(0:nt,kb)) ;tmean = zero !!MEAN INITIAL TEMPERATURE AT ELEMENTS
1673  ALLOCATE(s(0:nt,kb)) ;s = zero !!SALINITY AT ELEMENTS
1674  ALLOCATE(smean(0:nt,kb)) ;smean = zero !!MEAN INITIAL SALINITY AT ELEMENTS
1675  memcnt = nt*kb*13*ndb + memcnt
1676 
1677 !-----------------------3d variable arrays-(node based)-----------------------------!
1678 
1679  ALLOCATE(t1(0:mt,kb)) ;t1 = zero !!TEMPERATURE AT NODES
1680  ALLOCATE(s1(0:mt,kb)) ;s1 = zero !!SALINITY AT NODES
1681 !J. Ge for tracer advection
1682  ALLOCATE(t0(0:mt,kb)) ;t0 = zero !!TEMPERATURE FROM PREVIOUS TIME STEP
1683  ALLOCATE(t2(0:mt,kb)) ;t2 = zero !!TEMPERATURE FROM PREVIOUS TWO STEP
1684  ALLOCATE(s0(0:mt,kb)) ;s0 = zero !!SALINITY FROM PREVIOUS TIME STEP
1685  ALLOCATE(s2(0:mt,kb)) ;s2 = zero !!SALINITY FROM PREVIOUS TWO STEP
1686 !J. Ge for tracer advection
1687  ALLOCATE(rho1(0:mt,kb)) ;rho1 = zero !!DENSITY AT NODES
1688  ALLOCATE(tf1(0:mt,kb)) ;tf1 = zero !!TEMPERATURE FROM PREVIOUS TIME
1689  ALLOCATE(sf1(0:mt,kb)) ;sf1 = zero !!SALINITY FROM PREVIOUS TIME
1690  ALLOCATE(tmean1(0:mt,kb)) ;tmean1 = zero !!MEAN INITIAL TEMP
1691  ALLOCATE(smean1(0:mt,kb)) ;smean1 = zero !!MEAN INITIAL SALINITY
1692  ALLOCATE(rmean1(0:mt,kb)) ;rmean1 = zero !!MEAN INITIAL DENSITY
1693  ALLOCATE(wts(0:mt,kb)) ;wts = zero !!VERTICAL VELOCITY IN SIGMA SYSTEM
1694  ALLOCATE(wtts(0:mt,kb)) ;wtts = zero !!WTS FROM PREVIOUS TIMESTEP
1695  ALLOCATE(q2(0:mt,kb)) ;q2 = zero !!TURBULENT KINETIC ENERGY AT NODES
1696  ALLOCATE(q2l(0:mt,kb)) ;q2l = zero !!TURBULENT KE*LENGTH AT NODES
1697  ALLOCATE(l(0:mt,kb)) ;l = zero !!TURBULENT LENGTH SCALE AT ELEMENTS
1698  ALLOCATE(km(0:mt,kb)) ;km = zero !!TURBULENT QUANTITY
1699  ALLOCATE(kh(0:mt,kb)) ;kh = zero !!TURBULENT QUANTITY
1700  ALLOCATE(kq(0:mt,kb)) ;kq = zero !!TURBULENT QUANTITY
1701  ALLOCATE(aam(0:mt,kb)) ;aam = zero !!??
1702  ALLOCATE(km1(0:nt,kb)) ;km1 = zero !!TURBULENT QUANTITY AT ELEMENTS
1703 
1704 
1705  ALLOCATE(cc_hvc(0:nt)) ;cc_hvc = zero !!VISCOSITY COEFFICIENT AT ELEMENTS
1706  ALLOCATE(nn_hvc(0:mt)) ;nn_hvc = zero !!VISCOSITY COEFFICIENT AT NODES
1707 
1708  memcnt = mt*kb*18*ndb + nt*kb*ndb + memcnt + (mt+nt)*ndb
1709 
1710 
1711 !---------------------------internal mode fluxes------------------------------------!
1712 
1713  ALLOCATE(drhox(0:nt,kb)) ;drhox = zero
1714  ALLOCATE(drhoy(0:nt,kb)) ;drhoy = zero
1715  ALLOCATE(q2f(0:mt,kb)) ;q2f = zero
1716  ALLOCATE(q2lf(0:mt,kb)) ;q2lf = zero
1717  memcnt = nt*kb*2*ndb + mt*kb*2*ndb + memcnt
1718 
1719 !------------shape coefficient arrays and control volume metrics--------------------!
1720 
1721  ALLOCATE(a1u(0:nt,4)) ;a1u = zero
1722  ALLOCATE(a2u(0:nt,4)) ;a2u = zero
1723  ALLOCATE(awx(0:nt,3)) ;awx = zero
1724  ALLOCATE(awy(0:nt,3)) ;awy = zero
1725  ALLOCATE(aw0(0:nt,3)) ;aw0 = zero
1726  ALLOCATE(alpha(0:nt)) ;alpha = zero
1727  memcnt = nt*4*2*ndb + nt*3*3*ndb + nt*ndb + memcnt
1728 
1729 !-----salinity and temperature bottom diffusion condition/bottom depth gradients----!
1730 
1731  ALLOCATE(phpn(0:mt)) ;phpn = zero
1732  ALLOCATE(pfpxb(mt)) ;pfpxb = zero
1733  ALLOCATE(pfpyb(mt)) ;pfpyb = zero
1734  ALLOCATE(sita_gd(0:mt)) ;sita_gd = zero
1735  ALLOCATE(ah_bottom(mt)) ;ah_bottom = zero
1736  memcnt = mt*5*ndb + memcnt
1737 
1738  ALLOCATE(viscofh(0:mt,kb)) ;viscofh = zero
1739  ALLOCATE(viscofm(0:nt,kb)) ;viscofm = zero
1740  memcnt = mt*kb*ndb + nt*kb*ndb + memcnt
1741 
1742  ALLOCATE(hyw(0:mt,kb)) ;hyw = zero
1743 !-----special initialization which probably do nothing------------------------------!
1744 
1745  dt1(0) = 100.0_sp
1746 
1747 !---------------report approximate memory usage-------------------------------------!
1748 
1749 
1750  RETURN
1751  END SUBROUTINE alloc_vars
1752 !==============================================================================|
1753 
1754 
1755 END MODULE all_vars
1756 
1757 !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%|
1758 
1759 MODULE bcs
1760  USE mod_types
1761  USE mod_prec
1762  IMPLICIT NONE
1763  SAVE
1764 
1765 !----------------boundary conditions: Julian tidal forcing--------------------------!
1766 
1767  TYPE(bc) :: elo_tm !!TIME MAP FOR SURFACE ELEVATION DATA
1768 
1769 
1770 !----------------GLobal Boundary Condition Information ----------------------------!
1771 
1772 
1773  INTEGER, ALLOCATABLE :: i_obc_gl(:) !!GLOBAL ID OF OPEN BOUNDARY NODES
1774  INTEGER, ALLOCATABLE :: i_obc_gl_w(:) !!GLOBAL ID OF OPEN BOUNDARY NODES FOR WAVE
1775  INTEGER :: iobcn_gl !!LOCAL NUMBER OF OPEN BOUNDARY NODES FOR FVCOM
1776  INTEGER :: iobcn_gl_w !!LOCAL NUMBER OF OPEN BOUNDARY NODES FOR WAVE
1777  INTEGER :: iobcn !!LOCAL NUMBER OF OPEN BOUNDARY NODES FOR FVCOM
1778  INTEGER :: iobcn_w !!LOCAL NUMBER OF OPEN BOUNDARY NODES FOR SWAVE
1779  INTEGER, ALLOCATABLE :: i_obc_n(:) !!OPEN BOUNDARY NODE LIST FOR FVCOM
1780  INTEGER, ALLOCATABLE :: i_obc_n_w(:) !!OPEN BOUNDARY NODE LIST FOR SWAVE
1781  INTEGER, ALLOCATABLE :: i_obc_n_output(:)!!LIST OF LOCAL OBC GLOBAL NODES FOR OUTPUT
1782  INTEGER, ALLOCATABLE :: type_obc_gl(:) !!OUTER BOUNDARY NODE TYPE (FOR SURFACE ELEVATION)
1783  INTEGER, ALLOCATABLE :: type_obc(:) !!OUTER BOUNDARY NODE TYPE (FOR SURFACE ELEVATION)
1784  INTEGER :: obc_ntime
1785 
1786 !----------------boundary conditions: ground water----------------------------------!
1787 
1788  INTEGER, ALLOCATABLE :: node_bfw(:) !!LOCAL GROUNDWATER NODES
1789  INTEGER, ALLOCATABLE :: bfw_gl2loc(:) !!GLOBAL TO LOCAL MAPPING OF GWATER NODES
1790  REAL(sp), ALLOCATABLE :: bfwqdis(:,:) !!GROUNDWATER FRESH WATER FLUX DATA
1791 ! TYPE(BC) :: BFW_TM !!TIME MAP FOR GROUNDWATER DATA
1792 
1793 !----------------boundary conditions: spectral tidal forcing----------------------!
1794  INTEGER :: ntidecomps
1795  REAL(sp), ALLOCATABLE :: period(:) !!TIDE PERIOD
1796  REAL(sp), ALLOCATABLE :: apt(:,:) !!TIDE AMPLITUDE
1797  REAL(sp), ALLOCATABLE :: phai(:,:) !!TIDE PHASE
1798  REAL(sp), ALLOCATABLE :: emean(:) !!MEAN SURFACE ELEVATION
1799 
1800  ! ONLY USED IF COMPILED WITH EQUI_TIDE
1801  REAL(sp), ALLOCATABLE :: apt_eqi(:) !! EQUILIBIRUIM TIDE AMPLITUDE
1802  REAL(sp), ALLOCATABLE :: beta_eqi(:) !! EQUILIBIRUIM TIDE LOVE NUMBER
1803  CHARACTER(LEN=80), ALLOCATABLE :: tide_type(:) !! EQUILIBIRUIM TIDE AMPLITUDE
1804 
1805  CHARACTER(LEN=12), PARAMETER :: diurnal="DIURNAL"
1806  CHARACTER(LEN=12), PARAMETER :: semidiurnal="SEMIDIURNAL"
1807 
1808 
1809 !-- Old Tidal Periods before they became part of the forcing file ---------:
1810 ! s2 m2 n2 k1 p1 o1
1811 !PERIOD = (/43200.0_SP, 44712.0_SP, 45570.0_SP, 86164.0_SP, 86637.0_SP, 92950.0_SP/)
1812 
1813 
1814 !----------------boundary conditions: Julian tidal forcing--------------------------!
1815 
1816  REAL(sp), ALLOCATABLE :: elsbc(:,:) !!INPUT SURFACE ELEVATION
1817 
1818 END MODULE bcs
logical nc_nh_rhs
Definition: mod_main.f90:254
integer, dimension(:,:), allocatable, target ienode
Definition: mod_main.f90:1029
integer, dimension(:), allocatable, target ntsn
Definition: mod_main.f90:1023
real(sp), dimension(:), allocatable, target alpha
Definition: mod_main.f90:1336
integer(itime) iend
Definition: mod_main.f90:853
logical equator_beta_plane
Definition: mod_main.f90:404
real(sp), dimension(:,:), allocatable, target q2
Definition: mod_main.f90:1290
real(sp) precipitation_evp
Definition: mod_main.f90:469
real(sp), dimension(:), allocatable, target partition
Definition: mod_main.f90:1277
character(len=80) wave_kind
Definition: mod_main.f90:479
logical ncav_evap_precip
Definition: mod_main.f90:318
real(sp), dimension(:), allocatable, target epor
Definition: mod_main.f90:1056
real(sp), dimension(:), allocatable, target elrk1
Definition: mod_main.f90:1121
logical scalar_positivity_control
Definition: mod_main.f90:380
logical nc_wind_stress
Definition: mod_main.f90:259
real(sp), dimension(:,:), allocatable, target km
Definition: mod_main.f90:1293
integer kl
Definition: mod_main.f90:912
real(sp), dimension(:), allocatable, target va
Definition: mod_main.f90:1104
character(len=80) casename
Definition: mod_main.f90:116
real(dp) extstep_seconds
Definition: mod_main.f90:201
real(sp), dimension(:), allocatable, target d
Definition: mod_main.f90:1132
integer ne
Definition: mod_main.f90:73
character(len=80) airpressure_kind
Definition: mod_main.f90:474
logical use_proj
Definition: mod_main.f90:633
logical serial
Definition: mod_main.f90:100
real(sp) vymax
Definition: mod_main.f90:989
character(len=80) icing_forcing_file
Definition: mod_main.f90:720
real(sp), dimension(:,:), allocatable, target yije
Definition: mod_main.f90:1048
logical obc_temp_nudging
Definition: mod_main.f90:590
character(len=80), parameter sttc
Definition: mod_main.f90:489
logical wait_for_visit
Definition: mod_main.f90:187
type(bc) elo_tm
Definition: mod_main.f90:1767
character(len=80) coriolis_file
Definition: mod_main.f90:630
character(len=80) obc_longshore_flow_file
Definition: mod_main.f90:599
integer nc_output_stack
Definition: mod_main.f90:241
logical wetting_drying_on
Definition: mod_main.f90:394
integer, parameter gridunit
Definition: mod_main.f90:929
real(sp), dimension(:), allocatable, target cor
Definition: mod_main.f90:1113
logical nc_velocity
Definition: mod_main.f90:247
real(sp), dimension(:), allocatable, target d1
Definition: mod_main.f90:1116
logical surface_wave_mixing
Definition: mod_main.f90:391
logical ncav_grid_metrics
Definition: mod_main.f90:300
real(sp), dimension(:), allocatable, target adx2d
Definition: mod_main.f90:1258
real(sp), dimension(:), allocatable, target qprec
Definition: mod_main.f90:1239
character(len=80) date_format
Definition: mod_main.f90:125
real(sp) wave_ub_bot
Definition: mod_main.f90:485
real(sp), dimension(:,:), allocatable, target t2
Definition: mod_main.f90:1314
real(sp), dimension(:,:), allocatable, target q2lf
Definition: mod_main.f90:1298
real(sp) vertical_mixing_coefficient
Definition: mod_main.f90:362
character(len=80), parameter sw_dens3
Definition: mod_main.f90:401
real(sp), dimension(:), allocatable, target psty
Definition: mod_main.f90:1255
real(dp), dimension(4), parameter alpha_rk
Definition: mod_main.f90:875
character(len=80) wind_type
Definition: mod_main.f90:444
real(sp), dimension(:), allocatable, target elrk
Definition: mod_main.f90:1138
real(sp) ice_spec_humidity
Definition: mod_main.f90:730
logical msr
Definition: mod_main.f90:101
integer, parameter nmlunit
Definition: mod_main.f90:926
real(sp), dimension(:,:), allocatable, target s_ave
Definition: mod_main.f90:1355
real(sp), dimension(:,:), allocatable, target s
Definition: mod_main.f90:1288
real(sp), dimension(:,:), allocatable biodis
Definition: mod_main.f90:744
real(sp), dimension(:), allocatable, target h
Definition: mod_main.f90:1131
integer mt
Definition: mod_main.f90:78
character(len=80) lag_start_file
Definition: mod_main.f90:672
real(sp), dimension(:), allocatable, target rbc_geo_gl
Definition: mod_main.f90:1075
real(dp), parameter tpi
Definition: mod_main.f90:886
logical ncav_wave_stress
Definition: mod_main.f90:317
real(sp) hmin1
Definition: mod_main.f90:909
real(sp) hmin
Definition: mod_main.f90:918
integer, dimension(:), allocatable, target ibclsf
Definition: mod_main.f90:1080
real(sp), dimension(:,:), allocatable, target viscofh
Definition: mod_main.f90:1359
subroutine alloc_vars(dbg_set)
Definition: mod_main.f90:1447
character(len=80) startup_ts_type
Definition: mod_main.f90:143
real(dp), parameter rearth
Definition: mod_main.f90:884
real(sp), dimension(:), allocatable emean
Definition: mod_main.f90:1798
real(sp), dimension(:), allocatable, target art
Definition: mod_main.f90:1009
real(sp), dimension(:,:), allocatable, target advx
Definition: mod_main.f90:1263
real(sp), dimension(:), allocatable, target dtfa
Definition: mod_main.f90:1124
integer iramp
Definition: mod_main.f90:208
character(len=80) namelist_name
Definition: mod_main.f90:121
real(sp) ice_shortwave
Definition: mod_main.f90:732
logical obc_salt_nudging
Definition: mod_main.f90:593
logical nc_evap_precip
Definition: mod_main.f90:262
logical ncav_average_vel
Definition: mod_main.f90:307
logical barotropic
Definition: mod_main.f90:381
character(len=80) river_info_file
Definition: mod_main.f90:542
character(len=80) precipitation_kind
Definition: mod_main.f90:468
type(time) zerotime
Definition: mod_main.f90:830
real(sp), dimension(:), allocatable, target el
Definition: mod_main.f90:1134
real(sp), dimension(:), allocatable, target uark
Definition: mod_main.f90:1108
type(time) imdte
Definition: mod_main.f90:847
logical nc_average_vel
Definition: mod_main.f90:251
real(sp), dimension(:), allocatable, target advua
Definition: mod_main.f90:1256
character(len=80) data_assimilation_file
Definition: mod_main.f90:705
real(sp) hmax
Definition: mod_main.f90:917
real(sp) wind_y
Definition: mod_main.f90:448
real(sp), dimension(:,:), allocatable, target v
Definition: mod_main.f90:1269
character(len=80) heating_file
Definition: mod_main.f90:452
real(sp) startup_v_vals
Definition: mod_main.f90:149
real(sp), dimension(:,:), allocatable, target vqdist
Definition: mod_main.f90:1217
character(len=80), parameter stype_uniform
Definition: mod_main.f90:894
integer, dimension(:), allocatable type_obc
Definition: mod_main.f90:1783
real(sp), dimension(:), allocatable, target wper
Definition: mod_main.f90:1244
integer, dimension(:), allocatable, target lisbce_1
Definition: mod_main.f90:1037
real(sp), dimension(:), allocatable, target wub_bot
Definition: mod_main.f90:1247
real(sp) umol
Definition: mod_main.f90:365
logical force_archive
Definition: mod_main.f90:805
integer obc_ntime
Definition: mod_main.f90:1784
real(sp) zeta_mag_max
Definition: mod_main.f90:809
character(len=80) depth_file
Definition: mod_main.f90:629
character(len=80), dimension(:), allocatable tide_type
Definition: mod_main.f90:1803
real(sp), dimension(:), allocatable, target qevap2
Definition: mod_main.f90:1237
type(river), dimension(:), allocatable rivers
Definition: mod_main.f90:582
real(sp), dimension(:,:), allocatable, target rho1
Definition: mod_main.f90:1309
integer obc_ts_type
Definition: mod_main.f90:589
real(sp), dimension(:), allocatable, target pfpxb
Definition: mod_main.f90:1342
real(sp) airpressure_value
Definition: mod_main.f90:475
integer myid
Definition: mod_main.f90:67
subroutine namelist
Definition: namelist.f90:41
type(time) referencedate
Definition: mod_main.f90:835
integer, dimension(:), allocatable, target nbclsf
Definition: mod_main.f90:1082
integer ncv
Definition: mod_main.f90:74
character(len=80), parameter startup_type_hotstart
Definition: mod_main.f90:155
real(sp), dimension(:,:), allocatable, target dltxnec
Definition: mod_main.f90:1069
real(sp), dimension(:), allocatable, target qdis2
Definition: mod_main.f90:1222
character(len=80), parameter startup_type_linear
Definition: mod_main.f90:163
integer iobcn_w
Definition: mod_main.f90:1778
character(len=80) startup_type
Definition: mod_main.f90:141
integer, parameter subdunit
Definition: mod_main.f90:941
real(sp), dimension(:), allocatable, target wtsurf_watts
Definition: mod_main.f90:1174
real(sp) dte
Definition: mod_main.f90:843
integer iobcn_gl_w
Definition: mod_main.f90:1776
real(dp), parameter pi
Definition: mod_main.f90:880
real(sp), dimension(:,:), allocatable, target dltxncve
Definition: mod_main.f90:1059
integer chk_interval
Definition: mod_main.f90:807
character(len=80) startup_uv_type
Definition: mod_main.f90:144
character(len=80) sediment_parameter_file
Definition: mod_main.f90:715
real(sp) ice_air_temp
Definition: mod_main.f90:729
real(sp), dimension(:), allocatable, target art1
Definition: mod_main.f90:1010
integer, parameter timeprec
Definition: mod_main.f90:858
real(sp), dimension(:), allocatable, target qdis
Definition: mod_main.f90:1220
real(sp) wave_period
Definition: mod_main.f90:483
real(sp), dimension(:), allocatable, target yc
Definition: mod_main.f90:1004
character(len=80) river_name
Definition: mod_main.f90:559
real(sp), dimension(:,:), allocatable, target u_ave
Definition: mod_main.f90:1349
character(len=80), parameter sw_dens1
Definition: mod_main.f90:399
integer, parameter julobcunit
Definition: mod_main.f90:938
character(len=80) startup_bio_type
Definition: mod_main.f90:711
real(sp), dimension(:,:), allocatable, target t1
Definition: mod_main.f90:1307
logical obc_on
Definition: mod_main.f90:585
logical use_mpi_io_mode
Definition: mod_main.f90:188
real(sp), dimension(:), allocatable cc_hvc
Definition: mod_main.f90:1302
real(sp), dimension(:,:), allocatable, target w
Definition: mod_main.f90:1279
real(sp), dimension(:), allocatable, target wubot_n
Definition: mod_main.f90:1188
real(sp) horizontal_prandtl_number
Definition: mod_main.f90:355
character(len=80) ice_longwave_type
Definition: mod_main.f90:733
real(sp) heating_longwave_lengthscale
Definition: mod_main.f90:455
integer ndrft
Definition: mod_main.f90:59
character(len=120) ncav_subdomain_files
Definition: mod_main.f90:298
real(sp) dti
Definition: mod_main.f90:844
integer, parameter max_layers
Definition: mod_main.f90:557
character(len=80) obc_temp_file
Definition: mod_main.f90:591
real(sp) temp_min
Definition: mod_main.f90:811
real(sp), dimension(:), allocatable, target dltxye
Definition: mod_main.f90:1052
logical forecast_mode
Definition: mod_main.f90:159
logical par
Definition: mod_main.f90:102
real(sp), dimension(:), allocatable, target dltxc
Definition: mod_main.f90:1040
character(len=80) wave_file
Definition: mod_main.f90:478
real(sp), dimension(:), allocatable xcg
Definition: mod_main.f90:979
logical ncav_velocity
Definition: mod_main.f90:303
real(sp), dimension(max_layers) river_vertical_distribution
Definition: mod_main.f90:564
integer, target nprocs
Definition: mod_main.f90:72
logical temperature_active
Definition: mod_main.f90:384
character(len=80), parameter startup_type_constant
Definition: mod_main.f90:162
logical high_latitude_wave
Definition: mod_main.f90:735
real(sp), dimension(:), allocatable ycg
Definition: mod_main.f90:980
character(len=80) sediment_parameter_type
Definition: mod_main.f90:714
character(len=80) rst_out_interval
Definition: mod_main.f90:224
real(sp), dimension(:), allocatable, target ymc
Definition: mod_main.f90:994
character(len=80) lag_first_out
Definition: mod_main.f90:674
type(time) inttime
Definition: mod_main.f90:827
real(sp), dimension(:), allocatable, target egf
Definition: mod_main.f90:1136
integer ncv_i
Definition: mod_main.f90:76
character(len=80) output_dir
Definition: mod_main.f90:184
real(sp) bottom_roughness_minimum
Definition: mod_main.f90:371
logical nc_nh_qp
Definition: mod_main.f90:253
character(len=80) startup_turb_type
Definition: mod_main.f90:145
real(sp), dimension(:,:), allocatable, target dzz1
Definition: mod_main.f90:1097
character(len=80), parameter startup_type_coldstart
Definition: mod_main.f90:154
real(sp), dimension(:,:), allocatable, target dltytrie
Definition: mod_main.f90:1063
character(len=80) ncav_out_interval
Definition: mod_main.f90:296
real(sp), dimension(:,:), allocatable, target xije
Definition: mod_main.f90:1047
real(sp) zeta1
Definition: mod_main.f90:462
logical nc_turbulence
Definition: mod_main.f90:249
real(sp), dimension(:), allocatable, target elf_air
Definition: mod_main.f90:1158
real(dp), parameter grav
Definition: mod_main.f90:879
real(sp) heating_radiation
Definition: mod_main.f90:457
real(sp), dimension(:), allocatable, target latc
Definition: mod_main.f90:998
real(sp), dimension(:), allocatable, target icing_0kts
Definition: mod_main.f90:1208
real(sp), dimension(:,:), allocatable, target v_ave
Definition: mod_main.f90:1350
real(sp), dimension(:,:), allocatable, target dltyncve
Definition: mod_main.f90:1060
type(time) starttime
Definition: mod_main.f90:833
character(len=80) precipitation_file
Definition: mod_main.f90:467
character(len=80) infofile
Definition: mod_main.f90:117
logical obc_meanflow
Definition: mod_main.f90:596
real(sp), dimension(:), allocatable vbeta2d
Definition: mod_main.f90:1275
real(sp), dimension(:,:), allocatable, target a1u
Definition: mod_main.f90:1331
real(sp), dimension(:), allocatable, target el_ave
Definition: mod_main.f90:1357
integer, dimension(:), allocatable, target isonb_w
Definition: mod_main.f90:1025
real(sp), dimension(:,:), allocatable, target rho
Definition: mod_main.f90:1284
logical ncav_turbulence
Definition: mod_main.f90:305
real(sp) heating_shortwave_lengthscale
Definition: mod_main.f90:456
real(sp), dimension(:,:), allocatable, target awx
Definition: mod_main.f90:1333
integer m
Definition: mod_main.f90:56
integer, parameter n_sed_max
Definition: mod_main.f90:739
type(time) exttime
Definition: mod_main.f90:828
real(sp) hprnu
Definition: mod_main.f90:359
real(sp), dimension(:), allocatable, target pfpyb
Definition: mod_main.f90:1343
integer ndrft_gl
Definition: mod_main.f90:53
integer, pointer nprocs_total
Definition: mod_main.f90:71
real(sp), dimension(:,:), allocatable, target hyw
Definition: mod_main.f90:1362
real(sp), dimension(:,:), allocatable, target vf
Definition: mod_main.f90:1282
logical nc_salt_temp
Definition: mod_main.f90:248
real(sp), dimension(:), allocatable, target sitac
Definition: mod_main.f90:1053
character(len=80), parameter startup_type_crashrestart
Definition: mod_main.f90:156
real(sp), dimension(:,:), allocatable, target ww
Definition: mod_main.f90:1280
real(sp), dimension(:), allocatable, target wusurf_save
Definition: mod_main.f90:1193
character(len=80), parameter non_uniform
Definition: mod_main.f90:499
real(sp), dimension(:,:), allocatable, target q2l
Definition: mod_main.f90:1292
integer(itime) istart
Definition: mod_main.f90:852
real(sp), dimension(:), allocatable, target art2
Definition: mod_main.f90:1011
real(sp) vymin
Definition: mod_main.f90:989
real(sp), dimension(:), allocatable, target bfwdis2
Definition: mod_main.f90:1198
character(len=80) grid_file_units
Definition: mod_main.f90:626
character(len=80) bedflag_file
Definition: mod_main.f90:717
character(len=80) interval_rho_mean
Definition: mod_main.f90:397
integer, dimension(:), allocatable, target ntrg
Definition: mod_main.f90:1033
real(sp), dimension(:,:), allocatable apt
Definition: mod_main.f90:1796
real(sp), dimension(:), allocatable, target el_eqi
Definition: mod_main.f90:1147
real(sp) salt_min
= bounds checking
Definition: mod_main.f90:813
character(len=80) lag_out_file
Definition: mod_main.f90:673
real(sp), dimension(:,:), allocatable, target viscofm
Definition: mod_main.f90:1360
real(sp), dimension(:,:), allocatable, target tmean1
Definition: mod_main.f90:1318
logical backward_advection
Definition: mod_main.f90:388
real(sp), dimension(:,:), allocatable, target r_ave
Definition: mod_main.f90:1356
integer, parameter datestrlen
Definition: mod_main.f90:860
real(sp), dimension(:), allocatable, target egf_atmo
Definition: mod_main.f90:1155
real(sp), dimension(:,:), allocatable, target u
Definition: mod_main.f90:1268
integer, dimension(:), allocatable, target isbc
Definition: mod_main.f90:1026
logical ncav_vertical_vel
Definition: mod_main.f90:306
logical ncav_salt_temp
Definition: mod_main.f90:304
real(sp), dimension(:), allocatable, target f_alfa
Definition: mod_main.f90:1114
character(len=200) projection_reference
Definition: mod_main.f90:627
real(sp), dimension(:,:), allocatable, target s1
Definition: mod_main.f90:1308
real(sp), dimension(:), allocatable, target angleq
Definition: mod_main.f90:1228
real(sp), dimension(:), allocatable, target wlength
Definition: mod_main.f90:1245
integer, dimension(:,:), allocatable, target iec
Definition: mod_main.f90:1028
character(len=80), parameter startup_type_default
Definition: mod_main.f90:161
real(sp), dimension(:), allocatable, target vard
Definition: mod_main.f90:1111
logical ncav_wind_stress
Definition: mod_main.f90:315
real(dp), parameter rofvros
Definition: mod_main.f90:887
logical nc_vertical_vel
Definition: mod_main.f90:250
logical ncav_bio
Definition: mod_main.f90:321
real(sp), dimension(:,:), allocatable, target drhox
Definition: mod_main.f90:1326
real(sp) groundwater_salt
Definition: mod_main.f90:655
real(sp) ice_cloud_cover
Definition: mod_main.f90:731
real(sp), dimension(:,:), allocatable, target vbeta
Definition: mod_main.f90:1272
real(sp), dimension(:), allocatable, target wubot
Definition: mod_main.f90:1185
integer probes_number
Definition: mod_main.f90:795
real(sp), dimension(:), allocatable, target sdis
Definition: mod_main.f90:1225
integer, parameter river_char_len
Definition: mod_main.f90:555
real(sp), dimension(:,:), allocatable, target aw0
Definition: mod_main.f90:1335
integer, dimension(:,:), allocatable, target niec
Definition: mod_main.f90:1032
integer, dimension(:,:), allocatable, target nbvt
Definition: mod_main.f90:1036
real(sp) obc_temp_nudging_timescale
Definition: mod_main.f90:592
real(sp) heating_netflux
Definition: mod_main.f90:458
character(len=80) date_reference
Definition: mod_main.f90:129
character(len=80) horizontal_mixing_kind
Definition: mod_main.f90:353
logical obc_elevation_forcing_on
Definition: mod_main.f90:587
integer, dimension(:), allocatable i_obc_gl
Definition: mod_main.f90:1773
real(sp), dimension(:), allocatable, target icing_wndy
Definition: mod_main.f90:1206
real(sp), dimension(:), allocatable, target pstx
Definition: mod_main.f90:1254
character(len=80) river_kind
Definition: mod_main.f90:541
integer, dimension(:), allocatable, target riv_gl2loc
Definition: mod_main.f90:1218
real(sp) vertical_prandtl_number
Definition: mod_main.f90:363
real(sp), dimension(:,:), allocatable, target smean1
Definition: mod_main.f90:1319
real(sp), dimension(:), allocatable, target el1
Definition: mod_main.f90:1118
integer(itime) iint
Definition: mod_main.f90:850
real(sp), dimension(:), allocatable beta_eqi
Definition: mod_main.f90:1802
logical nc_groundwater
Definition: mod_main.f90:264
logical visit_all_vars
Definition: mod_main.f90:186
real(sp) ice_sea_level_pressure
Definition: mod_main.f90:728
real(sp), dimension(:), allocatable, target et
Definition: mod_main.f90:1135
real(sp), dimension(:), allocatable period
Definition: mod_main.f90:1795
real(sp), dimension(:,:), allocatable, target rdisq
Definition: mod_main.f90:1227
real(sp), dimension(:,:), allocatable, target awy
Definition: mod_main.f90:1334
real(sp), dimension(:), allocatable, target vort
Definition: mod_main.f90:1165
logical convective_overturning
Definition: mod_main.f90:379
real(sp), dimension(:), allocatable, target wdir
Definition: mod_main.f90:1243
real(sp) vprnu
Definition: mod_main.f90:366
real(sp), dimension(:), allocatable, target vx
Definition: mod_main.f90:1001
real(sp), dimension(:), allocatable, target phpn
Definition: mod_main.f90:1341
integer, parameter itsunit
Definition: mod_main.f90:927
character(len=80) institution
Definition: mod_main.f90:112
real(sp), dimension(:), allocatable, target dltye
Definition: mod_main.f90:1051
real(dp) intstep_seconds
Definition: mod_main.f90:206
integer n_sed
Definition: mod_main.f90:738
real(sp) memcnt
Definition: mod_main.f90:81
real(sp), dimension(:), allocatable ubeta2d
Definition: mod_main.f90:1274
real(sp), dimension(:), allocatable, target bfwslt
Definition: mod_main.f90:1201
real(sp), dimension(:), allocatable, target uard
Definition: mod_main.f90:1110
character(len=80) icing_forcing_kind
Definition: mod_main.f90:721
character(len=80) sponge_file
Definition: mod_main.f90:631
character(len=80), parameter br_gotm
Definition: mod_main.f90:377
real(sp), dimension(:), allocatable, target grav_e
Definition: mod_main.f90:1013
real(sp), dimension(:), allocatable, target swrad
Definition: mod_main.f90:1177
character(len=80), parameter speed
Definition: mod_main.f90:494
integer iobcn
Definition: mod_main.f90:1777
integer ntidecomps
Definition: mod_main.f90:1794
real(sp), dimension(:,:), allocatable, target tf1
Definition: mod_main.f90:1310
integer, parameter assimunit
Definition: mod_main.f90:935
integer kb
Definition: mod_main.f90:64
integer, parameter, public ipt_base
Definition: mod_main.f90:923
real(sp), dimension(:,:), allocatable, target uf
Definition: mod_main.f90:1281
real(sp), dimension(2) startup_s_vals
Definition: mod_main.f90:147
character(len=80) startup_file
Definition: mod_main.f90:142
logical cmdln_restart
Definition: mod_main.f90:152
character(len=80) river_file
Definition: mod_main.f90:560
real(sp), dimension(:), allocatable, target wvbot
Definition: mod_main.f90:1186
real(sp), dimension(:), allocatable, target wper_bot
Definition: mod_main.f90:1246
real(sp), dimension(:), allocatable, target wvsurf2
Definition: mod_main.f90:1183
logical groundwater_salt_on
Definition: mod_main.f90:656
real(sp), dimension(:), allocatable zkl
Definition: mod_main.f90:915
character(len=80), parameter fvcom_rrkf_without_ssa
Definition: mod_main.f90:755
real(sp), dimension(:), allocatable, target vaf
Definition: mod_main.f90:1106
character(len=80) heating_type
Definition: mod_main.f90:451
real(sp), dimension(:), allocatable nn_hvc
Definition: mod_main.f90:1303
real(sp), dimension(:,:), allocatable, target wtts
Definition: mod_main.f90:1322
integer, parameter sp
Definition: mod_prec.f90:48
logical ncav_surface_heat
Definition: mod_main.f90:319
subroutine e2n2d(EVAR, NVAR)
Definition: mod_main.f90:1408
logical nc_on
Definition: mod_main.f90:238
integer kbm2
Definition: mod_main.f90:66
real(sp) rheat
Definition: mod_main.f90:461
character(len=80) rst_first_out
Definition: mod_main.f90:223
real(sp), dimension(:), allocatable, target egf_air
Definition: mod_main.f90:1163
real(sp) wave_direction
Definition: mod_main.f90:482
integer n
Definition: mod_main.f90:55
real(sp), dimension(:), allocatable, target vy
Definition: mod_main.f90:1002
real(sp), dimension(:,:), allocatable, target ubeta
Definition: mod_main.f90:1271
character(len=80) ice_forcing_kind
Definition: mod_main.f90:727
integer, dimension(:), allocatable, target ntve
Definition: mod_main.f90:1022
integer river_number
Definition: mod_main.f90:544
character(len=80) obc_node_list_file
Definition: mod_main.f90:586
integer mpi_fvcom_group
Definition: mod_main.f90:107
real(sp), dimension(:), allocatable, target xmc
Definition: mod_main.f90:993
logical sediment_model
Definition: mod_main.f90:712
character(len=80) baroclinic_pressure_gradient
Definition: mod_main.f90:383
integer, dimension(:,:), allocatable, target nbe
Definition: mod_main.f90:1020
character(len=80) lag_out_interval
Definition: mod_main.f90:676
integer, dimension(:), allocatable i_obc_n
Definition: mod_main.f90:1779
integer ioprocid
Definition: mod_main.f90:69
real(sp), dimension(:,:), allocatable, target sf1
Definition: mod_main.f90:1311
character(len=80) case_title
Definition: mod_main.f90:124
logical obc_longshore_flow_on
Definition: mod_main.f90:598
real(sp), dimension(:), allocatable, target lonc
Definition: mod_main.f90:997
integer, parameter depthunit
Definition: mod_main.f90:931
logical ncav_wind_vel
Definition: mod_main.f90:314
character(len=80) timezone
Definition: mod_main.f90:126
real(sp), dimension(:), allocatable, target elf
Definition: mod_main.f90:1140
real(sp), dimension(:,:), allocatable, target advy
Definition: mod_main.f90:1264
real(dp), parameter slp0
Definition: mod_main.f90:888
real(sp), dimension(:), allocatable yg
Definition: mod_main.f90:976
character(len=12), parameter semidiurnal
Definition: mod_main.f90:1806
integer nisbce_2
Definition: mod_main.f90:61
real(sp), dimension(:), allocatable, target egf_eqi
Definition: mod_main.f90:1148
type(time) runfile_starttime
Definition: mod_main.f90:834
real(sp), dimension(:), allocatable, target bfwdis
Definition: mod_main.f90:1196
character(len=80) groundwater_file
Definition: mod_main.f90:651
real(sp) obc_salt_nudging_timescale
Definition: mod_main.f90:595
integer, dimension(:), allocatable i_obc_n_output
Definition: mod_main.f90:1781
real(sp), dimension(:), allocatable, target cc_z0b
Definition: mod_main.f90:1171
real(sp), dimension(:), allocatable, target wusurf
Definition: mod_main.f90:1191
real(sp) startup_u_vals
Definition: mod_main.f90:148
integer ireport
Definition: mod_main.f90:185
integer river_grid_location
Definition: mod_main.f90:561
type(time) spectime
Definition: mod_main.f90:841
character(len=80) biological_model_file
Definition: mod_main.f90:708
logical nc_ice
Definition: mod_main.f90:255
real(sp), dimension(:), allocatable, target bfwtmp
Definition: mod_main.f90:1200
logical obc_depth_control_on
Definition: mod_main.f90:601
integer, dimension(:,:), allocatable nvg
Definition: mod_main.f90:969
integer, dimension(:,:), allocatable, target nv
Definition: mod_main.f90:1018
character(len=80) grid_file
Definition: mod_main.f90:625
real(sp), dimension(:), allocatable, target wvbot_n
Definition: mod_main.f90:1189
type(time) endtime
Definition: mod_main.f90:832
integer, parameter spongeunit
Definition: mod_main.f90:933
real(sp) temp_max
Definition: mod_main.f90:810
real(sp) veloc_mag_max
Definition: mod_main.f90:808
integer, parameter oiassimunit
Definition: mod_main.f90:936
integer, dimension(:), allocatable, target ibclsf_output
Definition: mod_main.f90:1081
logical precipitation_on
Definition: mod_main.f90:466
logical wave_on
Definition: mod_main.f90:477
real(sp), dimension(:), allocatable zku
Definition: mod_main.f90:914
character(len=80) sediment_model_file
Definition: mod_main.f90:713
real(sp), dimension(:), allocatable, target icing_10kts
Definition: mod_main.f90:1209
real(sp), dimension(:,:), allocatable, target dltyecec
Definition: mod_main.f90:1067
character(len=80), parameter sw_dens2
Definition: mod_main.f90:400
logical ice_model
Definition: mod_main.f90:725
logical nc_surface_heat
Definition: mod_main.f90:263
real(sp), dimension(:,:), allocatable, target t_ave
Definition: mod_main.f90:1354
logical noflux_bot_condition
Definition: mod_main.f90:405
character(len=80), parameter br_orig
Definition: mod_main.f90:376
real(sp), dimension(:), allocatable, target xijc
Definition: mod_main.f90:1044
integer, dimension(:,:), allocatable, target n_icellq
Definition: mod_main.f90:1216
integer, dimension(:), allocatable node_bfw
Definition: mod_main.f90:1788
character(len=80) lag_restart_file
Definition: mod_main.f90:675
logical salinity_active
Definition: mod_main.f90:385
real(sp), dimension(:), allocatable, target elrk_eqi
Definition: mod_main.f90:1145
real(sp), dimension(:), allocatable, target xm
Definition: mod_main.f90:991
character(len=80) nc_first_out
Definition: mod_main.f90:239
real(sp), dimension(2) startup_t_vals
Definition: mod_main.f90:146
real(dp), parameter zero
Definition: mod_main.f90:882
character(len=20), dimension(n_sed_max) sed_names
Definition: mod_main.f90:740
real(sp), dimension(:), allocatable, target qarea
Definition: mod_main.f90:1226
real(sp), dimension(:,:), allocatable, target zz1
Definition: mod_main.f90:1095
real(sp), dimension(:,:), allocatable, target drhoy
Definition: mod_main.f90:1327
character(len=80) heating_kind
Definition: mod_main.f90:453
real(sp), dimension(:,:), allocatable, target dltynec
Definition: mod_main.f90:1070
integer mgl
Definition: mod_main.f90:50
real(sp), dimension(:,:), allocatable, target dzz
Definition: mod_main.f90:1093
real(sp) groundwater_flow
Definition: mod_main.f90:652
logical ncav_groundwater
Definition: mod_main.f90:320
logical lag_particles_on
Definition: mod_main.f90:671
character(len=80) fvcom_website
Definition: mod_main.f90:113
real(sp), dimension(:,:), allocatable elsbc
Definition: mod_main.f90:1816
real(sp), dimension(:,:), allocatable, target aam
Definition: mod_main.f90:1296
logical nc_grid_metrics
Definition: mod_main.f90:244
real(sp), dimension(:), allocatable, target wdf_ang
Definition: mod_main.f90:1078
logical nc_file_date
Definition: mod_main.f90:245
character(len=80) ice_forcing_file
Definition: mod_main.f90:726
real(dp), parameter pi2
Definition: mod_main.f90:881
character(len=80) fvcom_version
Definition: mod_main.f90:111
character(len=80) obc_meanflow_file
Definition: mod_main.f90:597
character(len=80) groundwater_kind
Definition: mod_main.f90:650
real(sp), dimension(:), allocatable, target dltyc
Definition: mod_main.f90:1041
real(sp), dimension(:), allocatable, target wusurf2
Definition: mod_main.f90:1182
real(sp), dimension(:), allocatable, target rbc_wdf_gl
Definition: mod_main.f90:1076
real(sp), dimension(:), allocatable, target sita_gd
Definition: mod_main.f90:1344
logical ncav_vorticity
Definition: mod_main.f90:308
real(sp) groundwater_temp
Definition: mod_main.f90:653
integer, dimension(:), allocatable i_obc_gl_w
Definition: mod_main.f90:1774
character(len=80), parameter stress
Definition: mod_main.f90:495
character(len=80) wind_kind
Definition: mod_main.f90:446
logical nc_vorticity
Definition: mod_main.f90:252
logical use_real_world_time
Definition: mod_main.f90:131
real(sp), dimension(:,:), allocatable, target wt
Definition: mod_main.f90:1283
real(sp), dimension(:), allocatable, target ua
Definition: mod_main.f90:1103
logical groundwater_on
Definition: mod_main.f90:649
real(sp), dimension(:), allocatable apt_eqi
Definition: mod_main.f90:1801
logical ncav_on
Definition: mod_main.f90:294
subroutine n2e2d(NVAR, EVAR)
Definition: mod_main.f90:1390
logical airpressure_on
Definition: mod_main.f90:472
real(sp), dimension(:), allocatable, target qevap
Definition: mod_main.f90:1240
real(sp), dimension(:,:), allocatable, target tmean
Definition: mod_main.f90:1287
integer(itime) iext
Definition: mod_main.f90:851
integer obc_tideout_interval
Definition: mod_main.f90:600
character(len=80) nc_file_name
Definition: mod_main.f90:268
real(sp), dimension(:,:), allocatable, target q2f
Definition: mod_main.f90:1297
real(sp), dimension(:,:), allocatable, target dz
Definition: mod_main.f90:1092
real(sp), dimension(:), allocatable, target sitae
Definition: mod_main.f90:1043
integer, parameter testunit
Definition: mod_main.f90:925
character(len=80) end_date
Definition: mod_main.f90:128
real(sp), dimension(:,:), allocatable, target l
Definition: mod_main.f90:1291
integer mx_nbr_elem
Definition: mod_main.f90:79
character(len=80), parameter startup_type_forecast
Definition: mod_main.f90:157
real(sp), dimension(:,:), allocatable, target kh
Definition: mod_main.f90:1294
logical nc_wave_stress
Definition: mod_main.f90:261
real(sp), dimension(:), allocatable, target ady2d
Definition: mod_main.f90:1259
integer numqbc_gl
Definition: mod_main.f90:51
real(sp), dimension(:), allocatable, target elf_atmo
Definition: mod_main.f90:1150
real(sp), dimension(:,:), allocatable, target w_ave
Definition: mod_main.f90:1351
real(sp), dimension(:), allocatable, target swrad_watts
Definition: mod_main.f90:1173
character(len=80), parameter fvcom_kalman_4
Definition: mod_main.f90:759
real(sp), dimension(:), allocatable, target tps
Definition: mod_main.f90:1262
logical recalculate_rho_mean
Definition: mod_main.f90:396
real(sp), dimension(:), allocatable, target taubm_n
Definition: mod_main.f90:1190
integer, dimension(:), allocatable type_obc_gl
Definition: mod_main.f90:1782
character(len=80), parameter fvcom_enkf_without_ssa
Definition: mod_main.f90:757
integer, parameter probeunit
Definition: mod_main.f90:937
integer, dimension(:), allocatable, target icellq
Definition: mod_main.f90:1215
logical icing_model
Definition: mod_main.f90:719
integer obc_tideout_initial
Definition: mod_main.f90:600
real(sp), dimension(:), allocatable, target yijc
Definition: mod_main.f90:1045
real(sp), dimension(:,:), allocatable, target dltxtrie
Definition: mod_main.f90:1064
real(sp) static_ssh_adj
Definition: mod_main.f90:209
type(time) delt_rho_mean
Definition: mod_main.f90:837
character(len=80), parameter fvcom_enkf_with_ssa
Definition: mod_main.f90:758
integer nisbce_3
Definition: mod_main.f90:62
real(sp), dimension(:,:), allocatable, target a2u
Definition: mod_main.f90:1332
real(sp) wave_height
Definition: mod_main.f90:480
real(sp), dimension(:), allocatable, target lat
Definition: mod_main.f90:996
integer, dimension(:,:), allocatable, target nbve
Definition: mod_main.f90:1034
integer, parameter dp
Definition: mod_prec.f90:52
integer nobclsf
Definition: mod_main.f90:58
real(sp), dimension(:,:), allocatable bfwqdis
Definition: mod_main.f90:1790
real(sp), dimension(:), allocatable, target dt1
Definition: mod_main.f90:1117
real(sp), dimension(:,:), allocatable, target z
Definition: mod_main.f90:1090
character(len=80), parameter cnstnt
Definition: mod_main.f90:488
character(len=80), parameter vrbl
Definition: mod_main.f90:492
integer rst_output_stack
Definition: mod_main.f90:225
real(sp) vxmax
Definition: mod_main.f90:989
real(sp), dimension(:), allocatable, target el_air
Definition: mod_main.f90:1162
character(len=80), parameter fvcom_nudge_oi_assim
Definition: mod_main.f90:752
real(dp), parameter deg2rad
Definition: mod_main.f90:885
real(sp) icing_air_temp
Definition: mod_main.f90:722
logical blank_namelist
Definition: mod_main.f90:120
real(sp), dimension(:), allocatable, target icing_satmp
Definition: mod_main.f90:1207
integer(itime) nsteps
Definition: mod_main.f90:854
integer, parameter sigmaunit
Definition: mod_main.f90:930
real(sp) horizontal_mixing_coefficient
Definition: mod_main.f90:354
real(sp), dimension(:), allocatable, target h1
Definition: mod_main.f90:1115
real(sp), dimension(:), allocatable, target lon
Definition: mod_main.f90:995
type(time) imdti
Definition: mod_main.f90:848
real(sp), dimension(:), allocatable, target xc
Definition: mod_main.f90:1003
character(len=80), parameter fvcom_rrkf_with_ssa
Definition: mod_main.f90:756
real(sp), dimension(:), allocatable, target vvwind
Definition: mod_main.f90:1233
real(sp), dimension(:), allocatable, target uaf
Definition: mod_main.f90:1105
real(sp), dimension(:,:), allocatable phai
Definition: mod_main.f90:1797
real(sp), dimension(:), allocatable, target dry2d
Definition: mod_main.f90:1261
character(len=80) bottom_roughness_type
Definition: mod_main.f90:369
integer numqbc
Definition: mod_main.f90:57
real(sp), dimension(:), allocatable, target taubm
Definition: mod_main.f90:1187
integer, dimension(:), allocatable, target lisbce_2
Definition: mod_main.f90:1038
real(sp) zeta2
Definition: mod_main.f90:463
real(sp) duu
Definition: mod_main.f90:907
integer, parameter obcunit
Definition: mod_main.f90:928
real(sp), dimension(:,:), allocatable, target dz1
Definition: mod_main.f90:1096
character(len=80) sea_water_density_function
Definition: mod_main.f90:382
integer, dimension(:), allocatable, target lisbce_3
Definition: mod_main.f90:1039
real(sp), dimension(:,:), allocatable, target dltxecec
Definition: mod_main.f90:1066
real(sp), dimension(:), allocatable, target whs
Definition: mod_main.f90:1242
real(sp), dimension(:,:), allocatable, target t0
Definition: mod_main.f90:1313
real(sp) p_sigma
Definition: mod_main.f90:900
real(sp) precipitation_prc
Definition: mod_main.f90:470
logical adcor_on
Definition: mod_main.f90:403
character(len=80) bedflag_type
Definition: mod_main.f90:716
real(sp), dimension(:,:), allocatable, target kh_ave
Definition: mod_main.f90:1353
real(sp), dimension(:,:), allocatable, target z1
Definition: mod_main.f90:1094
logical wind_on
Definition: mod_main.f90:443
integer backward_step
Definition: mod_main.f90:389
real(sp), dimension(:), allocatable, target wdf_dist
Definition: mod_main.f90:1079
real(sp) wave_length
Definition: mod_main.f90:481
logical nc_wind_vel
Definition: mod_main.f90:258
real(sp), dimension(:), allocatable, target dltxyc
Definition: mod_main.f90:1042
real(sp), dimension(:), allocatable, target elf1
Definition: mod_main.f90:1123
real(sp), dimension(:), allocatable, target qprec2
Definition: mod_main.f90:1236
real(sp), dimension(:), allocatable, target elf_eqi
Definition: mod_main.f90:1143
real(sp) startup_dmax
Definition: mod_main.f90:150
real(sp), dimension(:), allocatable, target grav_n
Definition: mod_main.f90:1013
real(sp), dimension(:,:), allocatable, target km_ave
Definition: mod_main.f90:1352
integer nisbce_1
Definition: mod_main.f90:60
character(len=80) horizontal_mixing_type
Definition: mod_main.f90:351
real(sp), dimension(:), allocatable, target el_atmo
Definition: mod_main.f90:1154
integer, dimension(:), allocatable, target isbce
Definition: mod_main.f90:1027
real(sp), dimension(:), allocatable, target wvsurf_save
Definition: mod_main.f90:1194
real(sp) memtot
Definition: mod_main.f90:81
subroutine n2e3d(NVAR, EVAR)
Definition: mod_main.f90:1370
logical data_assimilation
Definition: mod_main.f90:704
logical ioproc
Definition: mod_main.f90:103
real(sp), dimension(:), allocatable hg
Definition: mod_main.f90:977
character(len=80) ncav_file_name
Definition: mod_main.f90:324
integer, parameter coriolisunit
Definition: mod_main.f90:932
character(len=80), parameter uniform
Definition: mod_main.f90:498
logical boundschk_on
Definition: mod_main.f90:806
real(sp), dimension(:), allocatable, target cc_sponge
Definition: mod_main.f90:1127
integer iobcn_gl
Definition: mod_main.f90:1775
character(len=80), parameter tmdpndnt
Definition: mod_main.f90:490
character(len=80) input_dir
Definition: mod_main.f90:183
logical ncav_wave_para
Definition: mod_main.f90:316
character(len=80) horizontal_mixing_file
Definition: mod_main.f90:352
character(len=80) probes_file
Definition: mod_main.f90:796
real(sp), dimension(:), allocatable, target elrk_atmo
Definition: mod_main.f90:1152
real(sp) ramp
Definition: mod_main.f90:845
integer, parameter kfunit
Definition: mod_main.f90:939
integer, dimension(:), allocatable bfw_gl2loc
Definition: mod_main.f90:1789
real(sp), dimension(:), allocatable, target rbc_geo
Definition: mod_main.f90:1083
character(len=80), parameter stype_restart
Definition: mod_main.f90:898
real(sp) heating_longwave_perctage
Definition: mod_main.f90:454
character(len=80) fvcom_run_mode
Definition: mod_main.f90:748
integer, dimension(:,:), allocatable, target nbsn
Definition: mod_main.f90:1030
logical heating_on
Definition: mod_main.f90:450
real(dp), parameter one_third
Definition: mod_main.f90:883
logical rst_on
Definition: mod_main.f90:222
real(sp), dimension(:,:), allocatable, target smean
Definition: mod_main.f90:1289
character(len=80) airpressure_file
Definition: mod_main.f90:473
real(sp), dimension(:,:), allocatable, target wts
Definition: mod_main.f90:1321
real(sp), dimension(:,:), allocatable, target t
Definition: mod_main.f90:1286
character(len=80), parameter stype_geometric
Definition: mod_main.f90:895
character(len=80) ncav_first_out
Definition: mod_main.f90:295
real(sp), dimension(:), allocatable, target ah_bottom
Definition: mod_main.f90:1345
integer msrid
Definition: mod_main.f90:68
character(len=80) sigma_levels_file
Definition: mod_main.f90:628
real(sp), dimension(:), allocatable, target tdis
Definition: mod_main.f90:1224
integer ncav_output_stack
Definition: mod_main.f90:297
character(len=80) river_ts_setting
Definition: mod_main.f90:538
real(sp) wave_per_bot
Definition: mod_main.f90:484
real(sp), dimension(:), allocatable, target rbc_wdf
Definition: mod_main.f90:1084
real(sp), dimension(:), allocatable, target vlctyq
Definition: mod_main.f90:1229
logical ncav_ice
Definition: mod_main.f90:311
character(len=80), parameter stype_tanh
Definition: mod_main.f90:896
integer ipt
Definition: mod_main.f90:922
real(sp), dimension(:), allocatable, target wtsurf
Definition: mod_main.f90:1178
character(len=80) bottom_roughness_file
Definition: mod_main.f90:370
real(sp), dimension(:,:), allocatable, target s2
Definition: mod_main.f90:1316
logical in_mpi_io_loop
Definition: mod_main.f90:104
logical probes_on
Definition: mod_main.f90:794
real(sp), dimension(:), allocatable, target dltxe
Definition: mod_main.f90:1050
character(len=80), parameter fvcom_pure_sim
Definition: mod_main.f90:749
real(sp), dimension(:), allocatable, target cbc
Definition: mod_main.f90:1170
character(len=80) obc_elevation_file
Definition: mod_main.f90:588
character(len=80) river_inflow_location
Definition: mod_main.f90:540
character(len=80) prg_name
Definition: mod_main.f90:105
real(sp), dimension(:), allocatable, target vark
Definition: mod_main.f90:1109
real(sp), dimension(:,:), allocatable, target km1
Definition: mod_main.f90:1299
real(sp) dll
Definition: mod_main.f90:908
real(sp), dimension(:,:), allocatable, target s0
Definition: mod_main.f90:1315
logical ncav_nh_qp
Definition: mod_main.f90:309
real(sp) cbcmin
Definition: mod_main.f90:374
logical nc_bio
Definition: mod_main.f90:265
integer kbm1
Definition: mod_main.f90:65
integer, dimension(:), allocatable, target inodeq
Definition: mod_main.f90:1214
logical nc_wqm
Definition: mod_main.f90:266
character(len=80) obc_salt_file
Definition: mod_main.f90:594
integer, parameter nestunit
Definition: mod_main.f90:940
logical ncav_nh_rhs
Definition: mod_main.f90:310
real(sp), dimension(:), allocatable, target advva
Definition: mod_main.f90:1257
character(len=80) lag_scal_choice
Definition: mod_main.f90:677
integer, dimension(:), allocatable, target isonb
Definition: mod_main.f90:1024
real(sp) bottom_roughness_lengthscale
Definition: mod_main.f90:372
integer rivernmlunit
Definition: mod_main.f90:943
real(sp), dimension(:,:), allocatable seddis
Definition: mod_main.f90:741
real(sp), dimension(:,:), allocatable, target zz
Definition: mod_main.f90:1091
integer nt
Definition: mod_main.f90:77
character(len=12), parameter diurnal
Definition: mod_main.f90:1805
character(len=120) nc_subdomain_files
Definition: mod_main.f90:242
subroutine e2n3d(EVAR, NVAR)
Definition: mod_main.f90:1427
real(sp), dimension(:), allocatable, target elrk_air
Definition: mod_main.f90:1160
real(sp) salt_max
Definition: mod_main.f90:812
character(len=80) restart_file_name
Definition: mod_main.f90:227
real(sp), dimension(:), allocatable, target et1
Definition: mod_main.f90:1119
integer ku
Definition: mod_main.f90:911
character(len=80), parameter prdc
Definition: mod_main.f90:491
integer ngl
Definition: mod_main.f90:49
character(len=80) start_date
Definition: mod_main.f90:127
real(sp), dimension(:,:), allocatable, target kq
Definition: mod_main.f90:1295
real(sp), dimension(:), allocatable xg
Definition: mod_main.f90:975
integer, dimension(:), allocatable i_obc_n_w
Definition: mod_main.f90:1780
character(len=80) wind_file
Definition: mod_main.f90:445
character(len=80), parameter startup_type_setvalues
Definition: mod_main.f90:165
real(sp), dimension(:,:), allocatable, target rmean
Definition: mod_main.f90:1285
character(len=80) vertical_mixing_type
Definition: mod_main.f90:361
real(sp) wind_x
Definition: mod_main.f90:447
integer, parameter lsfunit
Definition: mod_main.f90:934
real(sp), dimension(:), allocatable, target wvsurf
Definition: mod_main.f90:1192
real(sp) icing_wspd
Definition: mod_main.f90:723
type(time) recalc_rho_mean
Definition: mod_main.f90:838
real(sp), dimension(:), allocatable, target uuwind
Definition: mod_main.f90:1232
real(sp), dimension(:), allocatable, target dt
Definition: mod_main.f90:1133
real(sp), dimension(:,:), allocatable, target rmean1
Definition: mod_main.f90:1320
character(len=80) stype
Definition: mod_main.f90:893
real(sp) du2
Definition: mod_main.f90:903
character(len=80) bottom_roughness_kind
Definition: mod_main.f90:368
integer isplit
Definition: mod_main.f90:203
real(sp), dimension(:), allocatable, target drx2d
Definition: mod_main.f90:1260
logical ncav_file_date
Definition: mod_main.f90:301
real(sp) min_depth
Definition: mod_main.f90:210
character(len=80), parameter startup_type_observed
Definition: mod_main.f90:164
real(sp), dimension(:), allocatable, target ym
Definition: mod_main.f90:992
character(len=80) nc_out_interval
Definition: mod_main.f90:240
logical ncav_wqm
Definition: mod_main.f90:322
integer nobclsf_gl
Definition: mod_main.f90:52
real(sp), dimension(:), allocatable, target icing_wndx
Definition: mod_main.f90:1205
real(sp) vxmin
Definition: mod_main.f90:989
logical nc_wave_para
Definition: mod_main.f90:260
logical biological_model
Definition: mod_main.f90:706
logical groundwater_temp_on
Definition: mod_main.f90:654
integer, dimension(:), allocatable, target ibclsf_gl
Definition: mod_main.f90:1074
character(len=80), parameter stype_generalized
Definition: mod_main.f90:897
real(sp) dl2
Definition: mod_main.f90:904
type(time) rktime
Definition: mod_main.f90:829