376 CHARACTER(LEN=80),
parameter ::
br_orig =
'orig' 377 CHARACTER(LEN=80),
parameter ::
br_gotm =
'gotm' 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" 494 CHARACTER(LEN=80),
parameter::
speed =
"speed" 495 CHARACTER(LEN=80),
parameter::
stress =
"stress" 498 CHARACTER(LEN=80),
parameter::
uniform =
"uniform" 576 CHARACTER(LEN=80) name
577 CHARACTER(LEN=80) file
603 namelist /nml_open_boundary_control/ &
875 REAL(
dp),
PARAMETER,
DIMENSION(4) ::
alpha_rk = (/0.2500_dp,1.0_dp/3.0_dp,0.5000_dp,1.0_dp/)
880 REAL(
dp),
PARAMETER ::
pi = 3.141592653589793238_dp
881 REAL(
dp),
PARAMETER ::
pi2 = 2.0_dp * 3.141592653589793238_dp
888 real(
dp),
parameter ::
slp0 = 101325.0_sp
969 INTEGER,
ALLOCATABLE ::
nvg(:,:)
991 REAL(
sp),
ALLOCATABLE,
TARGET ::
xm(:)
992 REAL(
sp),
ALLOCATABLE,
TARGET ::
ym(:)
993 REAL(
sp),
ALLOCATABLE,
TARGET ::
xmc(:)
994 REAL(
sp),
ALLOCATABLE,
TARGET ::
ymc(:)
995 REAL(
sp),
ALLOCATABLE,
TARGET ::
lon(:)
996 REAL(
sp),
ALLOCATABLE,
TARGET ::
lat(:)
1001 REAL(
sp),
ALLOCATABLE,
TARGET ::
vx(:)
1002 REAL(
sp),
ALLOCATABLE,
TARGET ::
vy(:)
1003 REAL(
sp),
ALLOCATABLE,
TARGET ::
xc(:)
1004 REAL(
sp),
ALLOCATABLE,
TARGET ::
yc(:)
1018 INTEGER,
ALLOCATABLE,
TARGET ::
nv(:,:)
1020 INTEGER,
ALLOCATABLE,
TARGET ::
nbe(:,:)
1022 INTEGER,
ALLOCATABLE,
TARGET ::
ntve(:)
1023 INTEGER,
ALLOCATABLE,
TARGET ::
ntsn(:)
1026 INTEGER,
ALLOCATABLE,
TARGET ::
isbc(:)
1028 INTEGER,
ALLOCATABLE,
TARGET ::
iec(:,:)
1030 INTEGER,
ALLOCATABLE,
TARGET ::
nbsn(:,:)
1032 INTEGER,
ALLOCATABLE,
TARGET ::
niec(:,:)
1033 INTEGER,
ALLOCATABLE,
TARGET ::
ntrg(:)
1034 INTEGER,
ALLOCATABLE,
TARGET ::
nbve(:,:)
1036 INTEGER,
ALLOCATABLE,
TARGET ::
nbvt(:,:)
1090 REAL(
sp),
ALLOCATABLE,
TARGET ::
z(:,:)
1091 REAL(
sp),
ALLOCATABLE,
TARGET ::
zz(:,:)
1092 REAL(
sp),
ALLOCATABLE,
TARGET ::
dz(:,:)
1093 REAL(
sp),
ALLOCATABLE,
TARGET ::
dzz(:,:)
1094 REAL(
sp),
ALLOCATABLE,
TARGET ::
z1(:,:)
1095 REAL(
sp),
ALLOCATABLE,
TARGET ::
zz1(:,:)
1096 REAL(
sp),
ALLOCATABLE,
TARGET ::
dz1(:,:)
1103 REAL(
sp),
ALLOCATABLE,
TARGET ::
ua(:)
1104 REAL(
sp),
ALLOCATABLE,
TARGET ::
va(:)
1115 REAL(
sp),
ALLOCATABLE,
TARGET ::
h1(:)
1116 REAL(
sp),
ALLOCATABLE,
TARGET ::
d1(:)
1131 REAL(
sp),
ALLOCATABLE,
TARGET ::
h(:)
1132 REAL(
sp),
ALLOCATABLE,
TARGET ::
d(:)
1133 REAL(
sp),
ALLOCATABLE,
TARGET ::
dt(:)
1134 REAL(
sp),
ALLOCATABLE,
TARGET ::
el(:)
1135 REAL(
sp),
ALLOCATABLE,
TARGET ::
et(:)
1268 REAL(
sp),
ALLOCATABLE,
TARGET ::
u(:,:)
1269 REAL(
sp),
ALLOCATABLE,
TARGET ::
v(:,:)
1279 REAL(
sp),
ALLOCATABLE,
TARGET ::
w(:,:)
1280 REAL(
sp),
ALLOCATABLE,
TARGET ::
ww(:,:)
1281 REAL(
sp),
ALLOCATABLE,
TARGET ::
uf(:,:)
1282 REAL(
sp),
ALLOCATABLE,
TARGET ::
vf(:,:)
1283 REAL(
sp),
ALLOCATABLE,
TARGET ::
wt(:,:)
1284 REAL(
sp),
ALLOCATABLE,
TARGET ::
rho(:,:)
1286 REAL(
sp),
ALLOCATABLE,
TARGET ::
t(:,:)
1288 REAL(
sp),
ALLOCATABLE,
TARGET ::
s(:,:)
1290 REAL(
sp),
ALLOCATABLE,
TARGET ::
q2(:,:)
1291 REAL(
sp),
ALLOCATABLE,
TARGET ::
l(:,:)
1292 REAL(
sp),
ALLOCATABLE,
TARGET ::
q2l(:,:)
1293 REAL(
sp),
ALLOCATABLE,
TARGET ::
km(:,:)
1294 REAL(
sp),
ALLOCATABLE,
TARGET ::
kh(:,:)
1295 REAL(
sp),
ALLOCATABLE,
TARGET ::
kq(:,:)
1296 REAL(
sp),
ALLOCATABLE,
TARGET ::
aam(:,:)
1297 REAL(
sp),
ALLOCATABLE,
TARGET ::
q2f(:,:)
1299 REAL(
sp),
ALLOCATABLE,
TARGET ::
km1(:,:)
1307 REAL(
sp),
ALLOCATABLE,
TARGET ::
t1(:,:)
1308 REAL(
sp),
ALLOCATABLE,
TARGET ::
s1(:,:)
1310 REAL(
sp),
ALLOCATABLE,
TARGET ::
tf1(:,:)
1311 REAL(
sp),
ALLOCATABLE,
TARGET ::
sf1(:,:)
1313 REAL(
sp),
ALLOCATABLE,
TARGET ::
t0(:,:)
1314 REAL(
sp),
ALLOCATABLE,
TARGET ::
t2(:,:)
1315 REAL(
sp),
ALLOCATABLE,
TARGET ::
s0(:,:)
1316 REAL(
sp),
ALLOCATABLE,
TARGET ::
s2(:,:)
1321 REAL(
sp),
ALLOCATABLE,
TARGET ::
wts(:,:)
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(:,:)
1362 REAL(
sp),
ALLOCATABLE,
TARGET ::
hyw(:,:)
1369 SUBROUTINE n2e3d(NVAR,EVAR)
1372 REAL(SP),
DIMENSION(0:MT,1:KB),
INTENT(IN) :: NVAR
1373 REAL(SP),
DIMENSION(0:NT,1:KB),
INTENT(INOUT) :: EVAR
1378 evar(i,k) =
one_third*(nvar(
nv(i,1),k)+nvar(
nv(i,2),k)+nvar(
nv(i,3),k))
1382 END SUBROUTINE n2e3d 1389 SUBROUTINE n2e2d(NVAR,EVAR)
1392 REAL(SP),
DIMENSION(0:MT),
INTENT(IN) :: NVAR
1393 REAL(SP),
DIMENSION(0:NT),
INTENT(INOUT) :: EVAR
1400 END SUBROUTINE n2e2d 1407 SUBROUTINE e2n2d(EVAR,NVAR)
1410 REAL(SP),
DIMENSION(0:NT),
INTENT(IN ) :: EVAR
1411 REAL(SP),
DIMENSION(0:MT),
INTENT(INOUT) :: NVAR
1419 END SUBROUTINE e2n2d 1426 SUBROUTINE e2n3d(EVAR,NVAR)
1429 REAL(SP),
DIMENSION(0:NT,1:KB),
INTENT(IN ) :: EVAR
1430 REAL(SP),
DIMENSION(0:MT,1:KB),
INTENT(INOUT) :: NVAR
1435 nvar(i,k) = sum(evar(
nbve(i,1:
ntve(i)),k))/float(
ntve(i))
1439 END SUBROUTINE e2n3d 1450 logical,
intent(in) :: dbg_set
integer, dimension(:,:), allocatable, target ienode
integer, dimension(:), allocatable, target ntsn
real(sp), dimension(:), allocatable, target alpha
logical equator_beta_plane
real(sp), dimension(:,:), allocatable, target q2
real(sp) precipitation_evp
real(sp), dimension(:), allocatable, target partition
character(len=80) wave_kind
real(sp), dimension(:), allocatable, target epor
real(sp), dimension(:), allocatable, target elrk1
logical scalar_positivity_control
real(sp), dimension(:,:), allocatable, target km
real(sp), dimension(:), allocatable, target va
character(len=80) casename
real(sp), dimension(:), allocatable, target d
character(len=80) airpressure_kind
character(len=80) icing_forcing_file
real(sp), dimension(:,:), allocatable, target yije
character(len=80), parameter sttc
character(len=80) coriolis_file
character(len=80) obc_longshore_flow_file
logical wetting_drying_on
integer, parameter gridunit
real(sp), dimension(:), allocatable, target cor
real(sp), dimension(:), allocatable, target d1
logical surface_wave_mixing
logical ncav_grid_metrics
real(sp), dimension(:), allocatable, target adx2d
real(sp), dimension(:), allocatable, target qprec
character(len=80) date_format
real(sp), dimension(:,:), allocatable, target t2
real(sp), dimension(:,:), allocatable, target q2lf
real(sp) vertical_mixing_coefficient
character(len=80), parameter sw_dens3
real(sp), dimension(:), allocatable, target psty
real(dp), dimension(4), parameter alpha_rk
character(len=80) wind_type
real(sp), dimension(:), allocatable, target elrk
real(sp) ice_spec_humidity
integer, parameter nmlunit
real(sp), dimension(:,:), allocatable, target s_ave
real(sp), dimension(:,:), allocatable, target s
real(sp), dimension(:,:), allocatable biodis
real(sp), dimension(:), allocatable, target h
character(len=80) lag_start_file
real(sp), dimension(:), allocatable, target rbc_geo_gl
integer, dimension(:), allocatable, target ibclsf
real(sp), dimension(:,:), allocatable, target viscofh
subroutine alloc_vars(dbg_set)
character(len=80) startup_ts_type
real(dp), parameter rearth
real(sp), dimension(:), allocatable emean
real(sp), dimension(:), allocatable, target art
real(sp), dimension(:,:), allocatable, target advx
real(sp), dimension(:), allocatable, target dtfa
character(len=80) namelist_name
character(len=80) river_info_file
character(len=80) precipitation_kind
real(sp), dimension(:), allocatable, target el
real(sp), dimension(:), allocatable, target uark
real(sp), dimension(:), allocatable, target advua
character(len=80) data_assimilation_file
real(sp), dimension(:,:), allocatable, target v
character(len=80) heating_file
real(sp), dimension(:,:), allocatable, target vqdist
character(len=80), parameter stype_uniform
integer, dimension(:), allocatable type_obc
real(sp), dimension(:), allocatable, target wper
integer, dimension(:), allocatable, target lisbce_1
real(sp), dimension(:), allocatable, target wub_bot
character(len=80) depth_file
character(len=80), dimension(:), allocatable tide_type
real(sp), dimension(:), allocatable, target qevap2
type(river), dimension(:), allocatable rivers
real(sp), dimension(:,:), allocatable, target rho1
real(sp), dimension(:), allocatable, target pfpxb
real(sp) airpressure_value
integer, dimension(:), allocatable, target nbclsf
character(len=80), parameter startup_type_hotstart
real(sp), dimension(:,:), allocatable, target dltxnec
real(sp), dimension(:), allocatable, target qdis2
character(len=80), parameter startup_type_linear
character(len=80) startup_type
integer, parameter subdunit
real(sp), dimension(:), allocatable, target wtsurf_watts
real(sp), dimension(:,:), allocatable, target dltxncve
character(len=80) startup_uv_type
character(len=80) sediment_parameter_file
real(sp), dimension(:), allocatable, target art1
integer, parameter timeprec
real(sp), dimension(:), allocatable, target qdis
real(sp), dimension(:), allocatable, target yc
character(len=80) river_name
real(sp), dimension(:,:), allocatable, target u_ave
character(len=80), parameter sw_dens1
integer, parameter julobcunit
character(len=80) startup_bio_type
real(sp), dimension(:,:), allocatable, target t1
real(sp), dimension(:), allocatable cc_hvc
real(sp), dimension(:,:), allocatable, target w
real(sp), dimension(:), allocatable, target wubot_n
real(sp) horizontal_prandtl_number
character(len=80) ice_longwave_type
real(sp) heating_longwave_lengthscale
character(len=120) ncav_subdomain_files
integer, parameter max_layers
character(len=80) obc_temp_file
real(sp), dimension(:), allocatable, target dltxye
real(sp), dimension(:), allocatable, target dltxc
character(len=80) wave_file
real(sp), dimension(:), allocatable xcg
real(sp), dimension(max_layers) river_vertical_distribution
logical temperature_active
character(len=80), parameter startup_type_constant
logical high_latitude_wave
real(sp), dimension(:), allocatable ycg
character(len=80) sediment_parameter_type
character(len=80) rst_out_interval
real(sp), dimension(:), allocatable, target ymc
character(len=80) lag_first_out
real(sp), dimension(:), allocatable, target egf
character(len=80) output_dir
real(sp) bottom_roughness_minimum
character(len=80) startup_turb_type
real(sp), dimension(:,:), allocatable, target dzz1
character(len=80), parameter startup_type_coldstart
real(sp), dimension(:,:), allocatable, target dltytrie
character(len=80) ncav_out_interval
real(sp), dimension(:,:), allocatable, target xije
real(sp), dimension(:), allocatable, target elf_air
real(sp) heating_radiation
real(sp), dimension(:), allocatable, target latc
real(sp), dimension(:), allocatable, target icing_0kts
real(sp), dimension(:,:), allocatable, target v_ave
real(sp), dimension(:,:), allocatable, target dltyncve
character(len=80) precipitation_file
character(len=80) infofile
real(sp), dimension(:), allocatable vbeta2d
real(sp), dimension(:,:), allocatable, target a1u
real(sp), dimension(:), allocatable, target el_ave
integer, dimension(:), allocatable, target isonb_w
real(sp), dimension(:,:), allocatable, target rho
real(sp) heating_shortwave_lengthscale
real(sp), dimension(:,:), allocatable, target awx
integer, parameter n_sed_max
real(sp), dimension(:), allocatable, target pfpyb
integer, pointer nprocs_total
real(sp), dimension(:,:), allocatable, target hyw
real(sp), dimension(:,:), allocatable, target vf
real(sp), dimension(:), allocatable, target sitac
character(len=80), parameter startup_type_crashrestart
real(sp), dimension(:,:), allocatable, target ww
real(sp), dimension(:), allocatable, target wusurf_save
character(len=80), parameter non_uniform
real(sp), dimension(:,:), allocatable, target q2l
real(sp), dimension(:), allocatable, target art2
real(sp), dimension(:), allocatable, target bfwdis2
character(len=80) grid_file_units
character(len=80) bedflag_file
character(len=80) interval_rho_mean
integer, dimension(:), allocatable, target ntrg
real(sp), dimension(:,:), allocatable apt
real(sp), dimension(:), allocatable, target el_eqi
real(sp) salt_min
= bounds checking
character(len=80) lag_out_file
real(sp), dimension(:,:), allocatable, target viscofm
real(sp), dimension(:,:), allocatable, target tmean1
logical backward_advection
real(sp), dimension(:,:), allocatable, target r_ave
integer, parameter datestrlen
real(sp), dimension(:), allocatable, target egf_atmo
real(sp), dimension(:,:), allocatable, target u
integer, dimension(:), allocatable, target isbc
logical ncav_vertical_vel
real(sp), dimension(:), allocatable, target f_alfa
character(len=200) projection_reference
real(sp), dimension(:,:), allocatable, target s1
real(sp), dimension(:), allocatable, target angleq
real(sp), dimension(:), allocatable, target wlength
integer, dimension(:,:), allocatable, target iec
character(len=80), parameter startup_type_default
real(sp), dimension(:), allocatable, target vard
real(dp), parameter rofvros
real(sp), dimension(:,:), allocatable, target drhox
real(sp) groundwater_salt
real(sp), dimension(:,:), allocatable, target vbeta
real(sp), dimension(:), allocatable, target wubot
real(sp), dimension(:), allocatable, target sdis
integer, parameter river_char_len
real(sp), dimension(:,:), allocatable, target aw0
integer, dimension(:,:), allocatable, target niec
integer, dimension(:,:), allocatable, target nbvt
real(sp) obc_temp_nudging_timescale
character(len=80) date_reference
character(len=80) horizontal_mixing_kind
logical obc_elevation_forcing_on
integer, dimension(:), allocatable i_obc_gl
real(sp), dimension(:), allocatable, target icing_wndy
real(sp), dimension(:), allocatable, target pstx
character(len=80) river_kind
integer, dimension(:), allocatable, target riv_gl2loc
real(sp) vertical_prandtl_number
real(sp), dimension(:,:), allocatable, target smean1
real(sp), dimension(:), allocatable, target el1
real(sp), dimension(:), allocatable beta_eqi
real(sp) ice_sea_level_pressure
real(sp), dimension(:), allocatable, target et
real(sp), dimension(:), allocatable period
real(sp), dimension(:,:), allocatable, target rdisq
real(sp), dimension(:,:), allocatable, target awy
real(sp), dimension(:), allocatable, target vort
logical convective_overturning
real(sp), dimension(:), allocatable, target wdir
real(sp), dimension(:), allocatable, target vx
real(sp), dimension(:), allocatable, target phpn
integer, parameter itsunit
character(len=80) institution
real(sp), dimension(:), allocatable, target dltye
real(sp), dimension(:), allocatable ubeta2d
real(sp), dimension(:), allocatable, target bfwslt
real(sp), dimension(:), allocatable, target uard
character(len=80) icing_forcing_kind
character(len=80) sponge_file
character(len=80), parameter br_gotm
real(sp), dimension(:), allocatable, target grav_e
real(sp), dimension(:), allocatable, target swrad
character(len=80), parameter speed
real(sp), dimension(:,:), allocatable, target tf1
integer, parameter assimunit
integer, parameter, public ipt_base
real(sp), dimension(:,:), allocatable, target uf
real(sp), dimension(2) startup_s_vals
character(len=80) startup_file
character(len=80) river_file
real(sp), dimension(:), allocatable, target wvbot
real(sp), dimension(:), allocatable, target wper_bot
real(sp), dimension(:), allocatable, target wvsurf2
logical groundwater_salt_on
real(sp), dimension(:), allocatable zkl
character(len=80), parameter fvcom_rrkf_without_ssa
real(sp), dimension(:), allocatable, target vaf
character(len=80) heating_type
real(sp), dimension(:), allocatable nn_hvc
real(sp), dimension(:,:), allocatable, target wtts
logical ncav_surface_heat
subroutine e2n2d(EVAR, NVAR)
character(len=80) rst_first_out
real(sp), dimension(:), allocatable, target egf_air
real(sp), dimension(:), allocatable, target vy
real(sp), dimension(:,:), allocatable, target ubeta
character(len=80) ice_forcing_kind
integer, dimension(:), allocatable, target ntve
character(len=80) obc_node_list_file
real(sp), dimension(:), allocatable, target xmc
character(len=80) baroclinic_pressure_gradient
integer, dimension(:,:), allocatable, target nbe
character(len=80) lag_out_interval
integer, dimension(:), allocatable i_obc_n
real(sp), dimension(:,:), allocatable, target sf1
character(len=80) case_title
logical obc_longshore_flow_on
real(sp), dimension(:), allocatable, target lonc
integer, parameter depthunit
character(len=80) timezone
real(sp), dimension(:), allocatable, target elf
real(sp), dimension(:,:), allocatable, target advy
real(sp), dimension(:), allocatable yg
character(len=12), parameter semidiurnal
real(sp), dimension(:), allocatable, target egf_eqi
type(time) runfile_starttime
real(sp), dimension(:), allocatable, target bfwdis
character(len=80) groundwater_file
real(sp) obc_salt_nudging_timescale
integer, dimension(:), allocatable i_obc_n_output
real(sp), dimension(:), allocatable, target cc_z0b
real(sp), dimension(:), allocatable, target wusurf
integer river_grid_location
character(len=80) biological_model_file
real(sp), dimension(:), allocatable, target bfwtmp
logical obc_depth_control_on
integer, dimension(:,:), allocatable nvg
integer, dimension(:,:), allocatable, target nv
character(len=80) grid_file
real(sp), dimension(:), allocatable, target wvbot_n
integer, parameter spongeunit
integer, parameter oiassimunit
integer, dimension(:), allocatable, target ibclsf_output
real(sp), dimension(:), allocatable zku
character(len=80) sediment_model_file
real(sp), dimension(:), allocatable, target icing_10kts
real(sp), dimension(:,:), allocatable, target dltyecec
character(len=80), parameter sw_dens2
real(sp), dimension(:,:), allocatable, target t_ave
logical noflux_bot_condition
character(len=80), parameter br_orig
real(sp), dimension(:), allocatable, target xijc
integer, dimension(:,:), allocatable, target n_icellq
integer, dimension(:), allocatable node_bfw
character(len=80) lag_restart_file
real(sp), dimension(:), allocatable, target elrk_eqi
real(sp), dimension(:), allocatable, target xm
character(len=80) nc_first_out
real(sp), dimension(2) startup_t_vals
character(len=20), dimension(n_sed_max) sed_names
real(sp), dimension(:), allocatable, target qarea
real(sp), dimension(:,:), allocatable, target zz1
real(sp), dimension(:,:), allocatable, target drhoy
character(len=80) heating_kind
real(sp), dimension(:,:), allocatable, target dltynec
real(sp), dimension(:,:), allocatable, target dzz
real(sp) groundwater_flow
character(len=80) fvcom_website
real(sp), dimension(:,:), allocatable elsbc
real(sp), dimension(:,:), allocatable, target aam
real(sp), dimension(:), allocatable, target wdf_ang
character(len=80) ice_forcing_file
character(len=80) fvcom_version
character(len=80) obc_meanflow_file
character(len=80) groundwater_kind
real(sp), dimension(:), allocatable, target dltyc
real(sp), dimension(:), allocatable, target wusurf2
real(sp), dimension(:), allocatable, target rbc_wdf_gl
real(sp), dimension(:), allocatable, target sita_gd
real(sp) groundwater_temp
integer, dimension(:), allocatable i_obc_gl_w
character(len=80), parameter stress
character(len=80) wind_kind
logical use_real_world_time
real(sp), dimension(:,:), allocatable, target wt
real(sp), dimension(:), allocatable, target ua
real(sp), dimension(:), allocatable apt_eqi
subroutine n2e2d(NVAR, EVAR)
real(sp), dimension(:), allocatable, target qevap
real(sp), dimension(:,:), allocatable, target tmean
integer obc_tideout_interval
character(len=80) nc_file_name
real(sp), dimension(:,:), allocatable, target q2f
real(sp), dimension(:,:), allocatable, target dz
real(sp), dimension(:), allocatable, target sitae
integer, parameter testunit
character(len=80) end_date
real(sp), dimension(:,:), allocatable, target l
character(len=80), parameter startup_type_forecast
real(sp), dimension(:,:), allocatable, target kh
real(sp), dimension(:), allocatable, target ady2d
real(sp), dimension(:), allocatable, target elf_atmo
real(sp), dimension(:,:), allocatable, target w_ave
real(sp), dimension(:), allocatable, target swrad_watts
character(len=80), parameter fvcom_kalman_4
real(sp), dimension(:), allocatable, target tps
logical recalculate_rho_mean
real(sp), dimension(:), allocatable, target taubm_n
integer, dimension(:), allocatable type_obc_gl
character(len=80), parameter fvcom_enkf_without_ssa
integer, parameter probeunit
integer, dimension(:), allocatable, target icellq
integer obc_tideout_initial
real(sp), dimension(:), allocatable, target yijc
real(sp), dimension(:,:), allocatable, target dltxtrie
character(len=80), parameter fvcom_enkf_with_ssa
real(sp), dimension(:,:), allocatable, target a2u
real(sp), dimension(:), allocatable, target lat
integer, dimension(:,:), allocatable, target nbve
real(sp), dimension(:,:), allocatable bfwqdis
real(sp), dimension(:), allocatable, target dt1
real(sp), dimension(:,:), allocatable, target z
character(len=80), parameter cnstnt
character(len=80), parameter vrbl
real(sp), dimension(:), allocatable, target el_air
character(len=80), parameter fvcom_nudge_oi_assim
real(dp), parameter deg2rad
real(sp), dimension(:), allocatable, target icing_satmp
integer, parameter sigmaunit
real(sp) horizontal_mixing_coefficient
real(sp), dimension(:), allocatable, target h1
real(sp), dimension(:), allocatable, target lon
real(sp), dimension(:), allocatable, target xc
character(len=80), parameter fvcom_rrkf_with_ssa
real(sp), dimension(:), allocatable, target vvwind
real(sp), dimension(:), allocatable, target uaf
real(sp), dimension(:,:), allocatable phai
real(sp), dimension(:), allocatable, target dry2d
character(len=80) bottom_roughness_type
real(sp), dimension(:), allocatable, target taubm
integer, dimension(:), allocatable, target lisbce_2
integer, parameter obcunit
real(sp), dimension(:,:), allocatable, target dz1
character(len=80) sea_water_density_function
integer, dimension(:), allocatable, target lisbce_3
real(sp), dimension(:,:), allocatable, target dltxecec
real(sp), dimension(:), allocatable, target whs
real(sp), dimension(:,:), allocatable, target t0
real(sp) precipitation_prc
character(len=80) bedflag_type
real(sp), dimension(:,:), allocatable, target kh_ave
real(sp), dimension(:,:), allocatable, target z1
real(sp), dimension(:), allocatable, target wdf_dist
real(sp), dimension(:), allocatable, target dltxyc
real(sp), dimension(:), allocatable, target elf1
real(sp), dimension(:), allocatable, target qprec2
real(sp), dimension(:), allocatable, target elf_eqi
real(sp), dimension(:), allocatable, target grav_n
real(sp), dimension(:,:), allocatable, target km_ave
character(len=80) horizontal_mixing_type
real(sp), dimension(:), allocatable, target el_atmo
integer, dimension(:), allocatable, target isbce
real(sp), dimension(:), allocatable, target wvsurf_save
subroutine n2e3d(NVAR, EVAR)
logical data_assimilation
real(sp), dimension(:), allocatable hg
character(len=80) ncav_file_name
integer, parameter coriolisunit
character(len=80), parameter uniform
real(sp), dimension(:), allocatable, target cc_sponge
character(len=80), parameter tmdpndnt
character(len=80) input_dir
character(len=80) horizontal_mixing_file
character(len=80) probes_file
real(sp), dimension(:), allocatable, target elrk_atmo
integer, parameter kfunit
integer, dimension(:), allocatable bfw_gl2loc
real(sp), dimension(:), allocatable, target rbc_geo
character(len=80), parameter stype_restart
real(sp) heating_longwave_perctage
character(len=80) fvcom_run_mode
integer, dimension(:,:), allocatable, target nbsn
real(dp), parameter one_third
real(sp), dimension(:,:), allocatable, target smean
character(len=80) airpressure_file
real(sp), dimension(:,:), allocatable, target wts
real(sp), dimension(:,:), allocatable, target t
character(len=80), parameter stype_geometric
character(len=80) ncav_first_out
real(sp), dimension(:), allocatable, target ah_bottom
character(len=80) sigma_levels_file
real(sp), dimension(:), allocatable, target tdis
integer ncav_output_stack
character(len=80) river_ts_setting
real(sp), dimension(:), allocatable, target rbc_wdf
real(sp), dimension(:), allocatable, target vlctyq
character(len=80), parameter stype_tanh
real(sp), dimension(:), allocatable, target wtsurf
character(len=80) bottom_roughness_file
real(sp), dimension(:,:), allocatable, target s2
real(sp), dimension(:), allocatable, target dltxe
character(len=80), parameter fvcom_pure_sim
real(sp), dimension(:), allocatable, target cbc
character(len=80) obc_elevation_file
character(len=80) river_inflow_location
character(len=80) prg_name
real(sp), dimension(:), allocatable, target vark
real(sp), dimension(:,:), allocatable, target km1
real(sp), dimension(:,:), allocatable, target s0
integer, dimension(:), allocatable, target inodeq
character(len=80) obc_salt_file
integer, parameter nestunit
real(sp), dimension(:), allocatable, target advva
character(len=80) lag_scal_choice
integer, dimension(:), allocatable, target isonb
real(sp) bottom_roughness_lengthscale
real(sp), dimension(:,:), allocatable seddis
real(sp), dimension(:,:), allocatable, target zz
character(len=12), parameter diurnal
character(len=120) nc_subdomain_files
subroutine e2n3d(EVAR, NVAR)
real(sp), dimension(:), allocatable, target elrk_air
character(len=80) restart_file_name
real(sp), dimension(:), allocatable, target et1
character(len=80), parameter prdc
character(len=80) start_date
real(sp), dimension(:,:), allocatable, target kq
real(sp), dimension(:), allocatable xg
integer, dimension(:), allocatable i_obc_n_w
character(len=80) wind_file
character(len=80), parameter startup_type_setvalues
real(sp), dimension(:,:), allocatable, target rmean
character(len=80) vertical_mixing_type
integer, parameter lsfunit
real(sp), dimension(:), allocatable, target wvsurf
type(time) recalc_rho_mean
real(sp), dimension(:), allocatable, target uuwind
real(sp), dimension(:), allocatable, target dt
real(sp), dimension(:,:), allocatable, target rmean1
character(len=80) bottom_roughness_kind
real(sp), dimension(:), allocatable, target drx2d
character(len=80), parameter startup_type_observed
real(sp), dimension(:), allocatable, target ym
character(len=80) nc_out_interval
real(sp), dimension(:), allocatable, target icing_wndx
logical groundwater_temp_on
integer, dimension(:), allocatable, target ibclsf_gl
character(len=80), parameter stype_generalized