MOM6
mom_opacity Module Reference

Data Types

type  opacity_cs
 

Functions/Subroutines

subroutine, public set_opacity (optics, fluxes, G, GV, CS)
 
subroutine opacity_from_chl (optics, fluxes, G, CS, chl_in)
 
real function, public opacity_morel (chl_data)
 
real function sw_pen_frac_morel (chl_data)
 
real function, public opacity_manizza (chl_data)
 
subroutine, public opacity_init (Time, G, param_file, diag, tracer_flow, CS, optics)
 
subroutine, public opacity_end (CS, optics)
 

Variables

integer, parameter no_scheme = 0
 
integer, parameter manizza_05 = 1
 
integer, parameter morel_88 = 2
 
integer, parameter single_exp = 3
 
integer, parameter double_exp = 4
 
character *(10), parameter manizza_05_string = "MANIZZA_05"
 
character *(10), parameter morel_88_string = "MOREL_88"
 
character *(10), parameter single_exp_string = "SINGLE_EXP"
 
character *(10), parameter double_exp_string = "DOUBLE_EXP"
 

Function/Subroutine Documentation

◆ opacity_end()

subroutine, public mom_opacity::opacity_end ( type(opacity_cs), pointer  CS,
type(optics_type), optional, pointer  optics 
)

Definition at line 692 of file MOM_opacity.F90.

Referenced by mom_diabatic_driver::diabatic_driver_end().

692  type(opacity_cs), pointer :: cs
693  type(optics_type), pointer, optional :: optics
694 
695  if (associated(cs%id_opacity)) deallocate(cs%id_opacity)
696  if (associated(cs)) deallocate(cs)
697 
698  if (present(optics)) then ; if (associated(optics)) then
699  if (ASSOCIATED(optics%opacity_band)) deallocate(optics%opacity_band)
700  if (ASSOCIATED(optics%sw_pen_band)) deallocate(optics%sw_pen_band)
701  endif ; endif
702 
Here is the caller graph for this function:

◆ opacity_from_chl()

subroutine mom_opacity::opacity_from_chl ( type(optics_type), intent(inout)  optics,
type(forcing), intent(in)  fluxes,
type(ocean_grid_type), intent(in)  G,
type(opacity_cs), pointer  CS,
real, dimension( g %isd: g %ied, g %jsd: g %jed, g %ke), intent(in), optional  chl_in 
)
private
Parameters
[in]fluxesA structure containing pointers to any possible forcing fields. Unused fields have NULL ptrs.
[in]gThe ocean's grid structure.
csThe control structure.
[in]chl_inA 3-d field of chlorophyll A,

Definition at line 251 of file MOM_opacity.F90.

References manizza_05, mom_error_handler::mom_error(), morel_88, opacity_morel(), and sw_pen_frac_morel().

Referenced by set_opacity().

251  type(optics_type), intent(inout) :: optics
252  type(forcing), intent(in) :: fluxes !< A structure containing pointers to any
253  !! possible forcing fields. Unused fields
254  !! have NULL ptrs.
255  type(ocean_grid_type), intent(in) :: g !< The ocean's grid structure.
256  type(opacity_cs), pointer :: cs !< The control structure.
257  real, dimension(SZI_(G),SZJ_(G),SZK_(G)), &
258  intent(in), optional :: chl_in !< A 3-d field of chlorophyll A,
259  !! in mg m-3.
260 ! Arguments: fluxes - A structure containing pointers to any possible
261 ! forcing fields. Unused fields have NULL ptrs.
262 ! (out) opacity - The inverse of the vertical absorption decay
263 ! scale for penetrating shortwave radiation, in m-1.
264 ! (in) G - The ocean's grid structure.
265 ! (in) chl_in - A 3-d field of chlorophyll A, in mg m-3.
266 
267  real :: chl_data(szi_(g),szj_(g)) ! The chlorophyll A concentrations in
268  ! a layer, in mg/m^3.
269  real :: inv_nbands ! The inverse of the number of bands of penetrating
270  ! shortwave radiation.
271  real :: inv_nbands_nir ! The inverse of the number of bands of penetrating
272  ! near-infrafed radiation.
273  real :: sw_pen_tot ! The sum across the bands of the penetrating
274  ! shortwave radiation, in W m-2.
275  real :: sw_vis_tot ! The sum across the visible bands of shortwave
276  ! radiation, in W m-2.
277  real :: sw_nir_tot ! The sum across the near infrared bands of shortwave
278  ! radiation, in W m-2.
279  type(time_type) :: day
280  character(len=128) :: mesg
281  integer :: days, seconds
282  integer :: i, j, k, n, is, ie, js, je, nz, nbands
283  logical :: multiband_vis_input, multiband_nir_input
284 
285  is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec ; nz = g%ke
286 
287 ! In this model, the Morel (modified) and Manizza (modified) schemes
288 ! use the "blue" band in the paramterizations to determine the e-folding
289 ! depth of the incoming shortwave attenuation. The red portion is lumped
290 ! into the net heating at the surface.
291 !
292 ! Morel, A., Optical modeling of the upper ocean in relation to its biogenous
293 ! matter content (case-i waters).,J. Geo. Res., {93}, 10,749--10,768, 1988.
294 !
295 
296 ! Manizza, M., C.~L. Quere, A.~Watson, and E.~T. Buitenhuis, Bio-optical
297 ! feedbacks amoung phytoplankton, upper ocean physics and sea-ice in a
298 ! global model, Geophys. Res. Let., , L05,603, 2005.
299 
300  nbands = optics%nbands
301 
302  if (nbands <= 1) then ; inv_nbands = 1.0
303  else ; inv_nbands = 1.0 / real(nbands) ; endif
304 
305  if (nbands <= 2) then ; inv_nbands_nir = 0.0
306  else ; inv_nbands_nir = 1.0 / real(nbands - 2.0) ; endif
307 
308  multiband_vis_input = (associated(fluxes%sw_vis_dir) .and. &
309  associated(fluxes%sw_vis_dif))
310  multiband_nir_input = (associated(fluxes%sw_nir_dir) .and. &
311  associated(fluxes%sw_nir_dif))
312 
313  chl_data(:,:) = 0.0
314  if(present(chl_in)) then
315  do j=js,je ; do i=is,ie ; chl_data(i,j) = chl_in(i,j,1) ; enddo ; enddo
316  do k=1,nz; do j=js,je ; do i=is,ie
317  if ((g%mask2dT(i,j) > 0.5) .and. (chl_in(i,j,k) < 0.0)) then
318  write(mesg,'(" Negative chl_in of ",(1pe12.4)," found at i,j,k = ", &
319  & 3(1x,i3), " lon/lat = ",(1pe12.4)," E ", (1pe12.4), " N.")') &
320  chl_in(i,j,k), i, j, k, g%geoLonT(i,j), g%geoLatT(i,j)
321  call mom_error(fatal,"MOM_opacity opacity_from_chl: "//trim(mesg))
322  endif
323  enddo; enddo; enddo
324  else
325  ! Only the 2-d surface chlorophyll can be read in from a file. The
326  ! same value is assumed for all layers.
327  call get_time(cs%Time,seconds,days)
328  call time_interp_external(cs%sbc_chl, cs%Time, chl_data)
329  do j=js,je ; do i=is,ie
330  if ((g%mask2dT(i,j) > 0.5) .and. (chl_data(i,j) < 0.0)) then
331  write(mesg,'(" Time_interp negative chl of ",(1pe12.4)," at i,j = ",&
332  & 2(i3), "lon/lat = ",(1pe12.4)," E ", (1pe12.4), " N.")') &
333  chl_data(i,j), i, j, g%geoLonT(i,j), g%geoLatT(i,j)
334  call mom_error(fatal,"MOM_opacity opacity_from_chl: "//trim(mesg))
335  endif
336  enddo ; enddo
337  endif
338 
339  if (cs%id_chl > 0) then
340  if(present(chl_in)) then
341  call post_data(cs%id_chl, chl_in(:,:,1), cs%diag)
342  else
343  call post_data(cs%id_chl, chl_data, cs%diag)
344  endif
345  endif
346 
347  select case (cs%opacity_scheme)
348  case (manizza_05)
349 !$OMP parallel do default(none) shared(is,ie,js,je,fluxes,optics,CS,G,multiband_nir_input, &
350 !$OMP nbands,Inv_nbands_nir,multiband_vis_input ) &
351 !$OMP private(SW_vis_tot,SW_nir_tot)
352  do j=js,je ; do i=is,ie
353  sw_vis_tot = 0.0 ; sw_nir_tot = 0.0
354  if (g%mask2dT(i,j) > 0.5) then
355  if (multiband_vis_input) then
356  sw_vis_tot = fluxes%sw_vis_dir(i,j) + fluxes%sw_vis_dif(i,j)
357  else ! Follow Manizza 05 in assuming that 42% of SW is visible.
358  sw_vis_tot = 0.42 * fluxes%sw(i,j)
359  endif
360  if (multiband_nir_input) then
361  sw_nir_tot = fluxes%sw_nir_dir(i,j) + fluxes%sw_nir_dif(i,j)
362  else
363  sw_nir_tot = fluxes%sw(i,j) - sw_vis_tot
364  endif
365  endif
366 
367  ! Band 1 is Manizza blue.
368  optics%sw_pen_band(1,i,j) = cs%blue_frac*sw_vis_tot
369  ! Band 2 (if used) is Manizza red.
370  if (nbands > 1) &
371  optics%sw_pen_band(2,i,j) = (1.0-cs%blue_frac)*sw_vis_tot
372  ! All remaining bands are NIR, for lack of something better to do.
373  do n=3,nbands
374  optics%sw_pen_band(n,i,j) = inv_nbands_nir * sw_nir_tot
375  enddo
376  enddo ; enddo
377  case (morel_88)
378 !$OMP parallel do default(none) shared(is,ie,js,je,G,multiband_vis_input,chl_data, &
379 !$OMP fluxes,nbands,optics,Inv_nbands) &
380 !$OMP private(SW_pen_tot)
381  do j=js,je ; do i=is,ie
382  sw_pen_tot = 0.0
383  if (g%mask2dT(i,j) > 0.5) then ; if (multiband_vis_input) then
384  sw_pen_tot = sw_pen_frac_morel(chl_data(i,j)) * &
385  (fluxes%sw_vis_dir(i,j) + fluxes%sw_vis_dif(i,j))
386  else
387  sw_pen_tot = sw_pen_frac_morel(chl_data(i,j)) * &
388  0.5*fluxes%sw(i,j)
389  endif ; endif
390 
391  do n=1,nbands
392  optics%sw_pen_band(n,i,j) = inv_nbands*sw_pen_tot
393  enddo
394  enddo ; enddo
395  case default
396  call mom_error(fatal, "opacity_from_chl: CS%opacity_scheme is not valid.")
397  end select
398 
399 !$OMP parallel do default(none) shared(nz,is,ie,js,je,CS,G,chl_in,optics,nbands) &
400 !$OMP firstprivate(chl_data)
401  do k=1,nz
402  if (present(chl_in)) then
403  do j=js,je ; do i=is,ie ; chl_data(i,j) = chl_in(i,j,k) ; enddo ; enddo
404  endif
405 
406  select case (cs%opacity_scheme)
407  case (manizza_05)
408  do j=js,je ; do i=is,ie
409  if (g%mask2dT(i,j) <= 0.5) then
410  do n=1,optics%nbands
411  optics%opacity_band(n,i,j,k) = cs%opacity_land_value
412  enddo
413  else
414  ! Band 1 is Manizza blue.
415  optics%opacity_band(1,i,j,k) = 0.0232 + 0.074*chl_data(i,j)**0.674
416  if (nbands >= 2) & ! Band 2 is Manizza red.
417  optics%opacity_band(2,i,j,k) = 0.225 + 0.037*chl_data(i,j)**0.629
418  ! All remaining bands are NIR, for lack of something better to do.
419  do n=3,nbands ; optics%opacity_band(n,i,j,k) = 2.86 ; enddo
420  endif
421  enddo ; enddo
422  case (morel_88)
423  do j=js,je ; do i=is,ie
424  optics%opacity_band(1,i,j,k) = cs%opacity_land_value
425  if (g%mask2dT(i,j) > 0.5) &
426  optics%opacity_band(1,i,j,k) = opacity_morel(chl_data(i,j))
427 
428  do n=2,optics%nbands
429  optics%opacity_band(n,i,j,k) = optics%opacity_band(1,i,j,k)
430  enddo
431  enddo ; enddo
432 
433  case default
434  call mom_error(fatal, "opacity_from_chl: CS%opacity_scheme is not valid.")
435  end select
436  enddo
437 
438 
Ocean grid type. See mom_grid for details.
Definition: MOM_grid.F90:19
Here is the call graph for this function:
Here is the caller graph for this function:

◆ opacity_init()

subroutine, public mom_opacity::opacity_init ( type(time_type), intent(in), target  Time,
type(ocean_grid_type), intent(in)  G,
type(param_file_type), intent(in)  param_file,
type(diag_ctrl), intent(inout), target  diag,
type(tracer_flow_control_cs), intent(in), target  tracer_flow,
type(opacity_cs), pointer  CS,
type(optics_type), pointer  optics 
)
Parameters
[in]timeThe current model time.
[in]gThe ocean's grid structure.
[in]param_fileA structure to parse for run-time parameters.
[in,out]diagA structure that is used to regulate diagnostic output.
csA pointer that is set to point to the control structure for this module.

Definition at line 488 of file MOM_opacity.F90.

References double_exp, double_exp_string, manizza_05, manizza_05_string, morel_88, morel_88_string, no_scheme, single_exp, and single_exp_string.

Referenced by mom_diabatic_driver::diabatic_driver_init().

488  type(time_type), target, intent(in) :: time !< The current model time.
489  type(ocean_grid_type), intent(in) :: g !< The ocean's grid structure.
490  type(param_file_type), intent(in) :: param_file !< A structure to parse for run-time
491  !! parameters.
492  type(diag_ctrl), target, intent(inout) :: diag !< A structure that is used to regulate diagnostic
493  !! output.
494  type(tracer_flow_control_cs), &
495  target, intent(in) :: tracer_flow
496  type(opacity_cs), pointer :: cs !< A pointer that is set to point to the control
497  !! structure for this module.
498  type(optics_type), pointer :: optics
499 ! Arguments: Time - The current model time.
500 ! (in) G - The ocean's grid structure.
501 ! (in) param_file - A structure indicating the open file to parse for
502 ! model parameter values.
503 ! (in) diag - A structure that is used to regulate diagnostic output.
504 !
505 ! (in/out) CS - A pointer that is set to point to the control structure
506 ! for this module
507 ! This include declares and sets the variable "version".
508 #include "version_variable.h"
509  character(len=200) :: inputdir ! The directory where NetCDF input files
510  character(len=240) :: filename
511  character(len=200) :: tmpstr
512  character(len=40) :: mdl = "MOM_opacity"
513  character(len=40) :: bandnum, shortname
514  character(len=200) :: longname
515  character(len=40) :: scheme_string
516  logical :: use_scheme
517  integer :: isd, ied, jsd, jed, nz, n
518  isd = g%isd ; ied = g%ied ; jsd = g%jsd ; jed = g%jed ; nz = g%ke
519 
520  if (associated(cs)) then
521  call mom_error(warning, "opacity_init called with an associated"// &
522  "associated control structure.")
523  return
524  else ; allocate(cs) ; endif
525 
526  cs%diag => diag
527  cs%Time => time
528  cs%tracer_flow_CSp => tracer_flow
529 
530  ! Read all relevant parameters and write them to the model log.
531  call log_version(param_file, mdl, version, "")
532 
533 ! parameters for CHL_A routines
534  call get_param(param_file, mdl, "VAR_PEN_SW", cs%var_pen_sw, &
535  "If true, use one of the CHL_A schemes specified by \n"//&
536  "OPACITY_SCHEME to determine the e-folding depth of \n"//&
537  "incoming short wave radiation.", default=.false.)
538 
539  cs%opacity_scheme = no_scheme ; scheme_string = ""
540  if (cs%var_pen_sw) then
541  call get_param(param_file, mdl, "OPACITY_SCHEME", tmpstr, &
542  "This character string specifies how chlorophyll \n"//&
543  "concentrations are translated into opacities. Currently \n"//&
544  "valid options include:\n"//&
545  " \t\t MANIZZA_05 - Use Manizza et al., GRL, 2005. \n"//&
546  " \t\t MOREL_88 - Use Morel, JGR, 1988.", &
547  default=manizza_05_string)
548  if (len_trim(tmpstr) > 0) then
549  tmpstr = uppercase(tmpstr)
550  select case (tmpstr)
551  case (manizza_05_string)
552  cs%opacity_scheme = manizza_05 ; scheme_string = manizza_05_string
553  case (morel_88_string)
554  cs%opacity_scheme = morel_88 ; scheme_string = morel_88_string
555  case default
556  call mom_error(fatal, "opacity_init: #DEFINE OPACITY_SCHEME "//&
557  trim(tmpstr) // "in input file is invalid.")
558  end select
559  call mom_mesg('opacity_init: opacity scheme set to "'//trim(tmpstr)//'".', 5)
560  endif
561  if (cs%opacity_scheme == no_scheme) then
562  call mom_error(warning, "opacity_init: No scheme has successfully "//&
563  "been specified for the opacity. Using the default MANIZZA_05.")
564  cs%opacity_scheme = manizza_05 ; scheme_string = manizza_05_string
565  endif
566 
567  call get_param(param_file, mdl, "CHL_FROM_FILE", cs%chl_from_file, &
568  "If true, chl_a is read from a file.", default=.true.)
569  if (cs%chl_from_file) then
570  call time_interp_external_init()
571 
572  call get_param(param_file, mdl, "INPUTDIR", inputdir, default=".")
573  call get_param(param_file, mdl, "CHL_FILE", cs%chl_file, &
574  "CHL_FILE is the file containing chl_a concentrations in \n"//&
575  "the variable CHL_A. It is used when VAR_PEN_SW and \n"//&
576  "CHL_FROM_FILE are true.", fail_if_missing=.true.)
577 
578  filename = trim(slasher(inputdir))//trim(cs%chl_file)
579  call log_param(param_file, mdl, "INPUTDIR/CHL_FILE", filename)
580  cs%sbc_chl = init_external_field(filename,'CHL_A',domain=g%Domain%mpp_domain)
581  endif
582 
583  call get_param(param_file, mdl, "BLUE_FRAC_SW", cs%blue_frac, &
584  "The fraction of the penetrating shortwave radiation \n"//&
585  "that is in the blue band.", default=0.5, units="nondim")
586  else
587  call get_param(param_file, mdl, "EXP_OPACITY_SCHEME", tmpstr, &
588  "This character string specifies which exponential \n"//&
589  "opacity scheme to utilize. Currently \n"//&
590  "valid options include:\n"//&
591  " \t\t SINGLE_EXP - Single Exponent decay. \n"//&
592  " \t\t DOUBLE_EXP - Double Exponent decay.", &
593  default=single_exp_string)!New default for "else" above (non-Chl scheme)
594  if (len_trim(tmpstr) > 0) then
595  tmpstr = uppercase(tmpstr)
596  select case (tmpstr)
597  case (single_exp_string)
598  cs%opacity_scheme = single_exp ; scheme_string = single_exp_string
599  case (double_exp_string)
600  cs%opacity_scheme = double_exp ; scheme_string = double_exp_string
601  end select
602  call mom_mesg('opacity_init: opacity scheme set to "'//trim(tmpstr)//'".', 5)
603  endif
604  call get_param(param_file, mdl, "PEN_SW_SCALE", cs%pen_sw_scale, &
605  "The vertical absorption e-folding depth of the \n"//&
606  "penetrating shortwave radiation.", units="m", default=0.0)
607  !BGR/ Added for opacity_scheme==double_exp read in 2nd exp-decay and fraction
608  if (cs%Opacity_scheme == double_exp ) then
609  call get_param(param_file, mdl, "PEN_SW_SCALE_2ND", cs%pen_sw_scale_2nd, &
610  "The (2nd) vertical absorption e-folding depth of the \n"//&
611  "penetrating shortwave radiation \n"//&
612  "(use if SW_EXP_MODE==double.)",&
613  units="m", default=0.0)
614  call get_param(param_file, mdl, "SW_1ST_EXP_RATIO", cs%sw_1st_exp_ratio, &
615  "The fraction of 1st vertical absorption e-folding depth \n"//&
616  "penetrating shortwave radiation if SW_EXP_MODE==double.",&
617  units="m", default=0.0)
618  elseif (cs%OPACITY_SCHEME == single_exp) then
619  !/Else disable 2nd_exp scheme
620  cs%pen_sw_scale_2nd = 0.0
621  cs%sw_1st_exp_ratio = 1.0
622  endif
623  call get_param(param_file, mdl, "PEN_SW_FRAC", cs%pen_sw_frac, &
624  "The fraction of the shortwave radiation that penetrates \n"//&
625  "below the surface.", units="nondim", default=0.0)
626 
627  endif
628  call get_param(param_file, mdl, "PEN_SW_NBANDS", optics%nbands, &
629  "The number of bands of penetrating shortwave radiation.", &
630  default=1)
631  if (cs%Opacity_scheme == double_exp ) then
632  if (optics%nbands.ne.2) then
633  call mom_error(fatal, "set_opacity: "// &
634  "Cannot use a double_exp opacity scheme with nbands!=2.")
635  endif
636  elseif (cs%Opacity_scheme == single_exp ) then
637  if (optics%nbands.ne.1) then
638  call mom_error(fatal, "set_opacity: "// &
639  "Cannot use a single_exp opacity scheme with nbands!=1.")
640  endif
641  endif
642  if (.not.ASSOCIATED(optics%min_wavelength_band)) &
643  allocate(optics%min_wavelength_band(optics%nbands))
644  if (.not.ASSOCIATED(optics%max_wavelength_band)) &
645  allocate(optics%max_wavelength_band(optics%nbands))
646 
647  if (cs%opacity_scheme == manizza_05) then
648  optics%min_wavelength_band(1) =0
649  optics%max_wavelength_band(1) =550
650  if (optics%nbands >= 2) then
651  optics%min_wavelength_band(2)=550
652  optics%max_wavelength_band(2)=700
653  endif
654  if (optics%nbands > 2) then
655  do n=3,optics%nbands
656  optics%min_wavelength_band(n) =700
657  optics%max_wavelength_band(n) =2800
658  enddo
659  endif
660  endif
661 
662  call get_param(param_file, mdl, "OPACITY_LAND_VALUE", cs%opacity_land_value, &
663  "The value to use for opacity over land. The default is \n"//&
664  "10 m-1 - a value for muddy water.", units="m-1", default=10.0)
665 
666  if (.not.ASSOCIATED(optics%opacity_band)) &
667  allocate(optics%opacity_band(optics%nbands,isd:ied,jsd:jed,nz))
668  if (.not.ASSOCIATED(optics%sw_pen_band)) &
669  allocate(optics%sw_pen_band(optics%nbands,isd:ied,jsd:jed))
670  allocate(cs%id_opacity(optics%nbands)) ; cs%id_opacity(:) = -1
671 
672  cs%id_sw_pen = register_diag_field('ocean_model', 'SW_pen', diag%axesT1, time, &
673  'Penetrating shortwave radiation flux into ocean', 'Watt meter-2')
674  cs%id_sw_vis_pen = register_diag_field('ocean_model', 'SW_vis_pen', diag%axesT1, time, &
675  'Visible penetrating shortwave radiation flux into ocean', 'Watt meter-2')
676  do n=1,optics%nbands
677  write(bandnum,'(i3)') n
678  shortname = 'opac_'//trim(adjustl(bandnum))
679  longname = 'Opacity for shortwave radiation in band '//trim(adjustl(bandnum))
680  cs%id_opacity(n) = register_diag_field('ocean_model', shortname, diag%axesTL, time, &
681  longname, 'meter-1')
682  enddo
683  if (cs%var_pen_sw) &
684  cs%id_chl = register_diag_field('ocean_model', 'Chl_opac', diag%axesT1, time, &
685  'Surface chlorophyll A concentration used to find opacity', 'mg meter-3')
686 
687 
Ocean grid type. See mom_grid for details.
Definition: MOM_grid.F90:19
Here is the caller graph for this function:

◆ opacity_manizza()

real function, public mom_opacity::opacity_manizza ( real, intent(in)  chl_data)

Definition at line 478 of file MOM_opacity.F90.

478  real, intent(in) :: chl_data
479  real :: opacity_manizza
480 ! Argument : chl_data - The chlorophyll-A concentration in mg m-3.
481 ! This sets the blue-wavelength opacity according to the scheme proposed by
482 ! Manizza, M. et al, 2005.
483 
484  opacity_manizza = 0.0232 + 0.074*chl_data**0.674

◆ opacity_morel()

real function, public mom_opacity::opacity_morel ( real, intent(in)  chl_data)

Definition at line 442 of file MOM_opacity.F90.

Referenced by opacity_from_chl().

442  real, intent(in) :: chl_data
443  real :: opacity_morel
444 ! Argument : chl_data - The chlorophyll-A concentration in mg m-3.
445 ! The following are coefficients for the optical model taken from Morel and
446 ! Antoine (1994). These coeficients represent a non uniform distribution of
447 ! chlorophyll-a through the water column. Other approaches may be more
448 ! appropriate when using an interactive ecosystem model that predicts
449 ! three-dimensional chl-a values.
450  real, dimension(6), parameter :: &
451  z2_coef=(/7.925, -6.644, 3.662, -1.815, -0.218, 0.502/)
452  real :: chl, chl2 ! The log10 of chl_data (in mg m-3), and Chl^2.
453 
454  chl = log10(min(max(chl_data,0.02),60.0)) ; chl2 = chl*chl
455  opacity_morel = 1.0 / ( (z2_coef(1) + z2_coef(2)*chl) + chl2 * &
456  ((z2_coef(3) + chl*z2_coef(4)) + chl2*(z2_coef(5) + chl*z2_coef(6))) )
Here is the caller graph for this function:

◆ set_opacity()

subroutine, public mom_opacity::set_opacity ( type(optics_type), intent(inout)  optics,
type(forcing), intent(in)  fluxes,
type(ocean_grid_type), intent(in)  G,
type(verticalgrid_type), intent(in)  GV,
type(opacity_cs), pointer  CS 
)
Parameters
[in]fluxesA structure containing pointers to any possible forcing fields. Unused fields have NULL ptrs.
[in]gThe ocean's grid structure.
[in]gvThe ocean's vertical grid structure.
csThe control structure earlier set up by opacity_init.

Definition at line 122 of file MOM_opacity.F90.

References double_exp, mom_tracer_flow_control::get_chl_from_model(), manizza_05, mom_error_handler::mom_error(), opacity_from_chl(), and mom_diag_mediator::query_averaging_enabled().

Referenced by mom_diabatic_driver::diabatic().

122  type(optics_type), intent(inout) :: optics
123  type(forcing), intent(in) :: fluxes !< A structure containing pointers to any
124  !! possible forcing fields. Unused fields
125  !! have NULL ptrs.
126  type(ocean_grid_type), intent(in) :: g !< The ocean's grid structure.
127  type(verticalgrid_type), intent(in) :: gv !< The ocean's vertical grid structure.
128  type(opacity_cs), pointer :: cs !< The control structure earlier set up by
129  !! opacity_init.
130 
131 ! Arguments: (inout) opacity - The inverse of the vertical absorption decay
132 ! scale for penetrating shortwave radiation, in m-1.
133 ! (inout) fluxes - A structure containing pointers to any possible
134 ! forcing fields. Unused fields have NULL ptrs.
135 ! (in) G - The ocean's grid structure.
136 ! (in) GV - The ocean's vertical grid structure.
137 ! (in) CS - The control structure earlier set up by opacity_init.
138 
139 ! local variables
140  integer :: i, j, k, n, is, ie, js, je, nz
141  real :: inv_sw_pen_scale ! The inverse of the e-folding scale, in m-1.
142  real :: inv_nbands ! The inverse of the number of bands of penetrating
143  ! shortwave radiation.
144  logical :: call_for_surface ! if horizontal slice is the surface layer
145  real :: tmp(szi_(g),szj_(g),szk_(g)) ! A 3-d temporary array.
146  real :: chl(szi_(g),szj_(g),szk_(g)) ! The concentration of chlorophyll-A
147  ! in mg m-3.
148  real :: pen_sw_tot(szi_(g),szj_(g)) ! The penetrating shortwave radiation
149  ! summed across all bands, in W m-2.
150  is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec ; nz = g%ke
151 
152  if (.not. associated(cs)) call mom_error(fatal, "set_opacity: "// &
153  "Module must be initialized via opacity_init before it is used.")
154 
155  if (cs%var_pen_sw) then
156  if (cs%chl_from_file) then
157  call opacity_from_chl(optics, fluxes, g, cs)
158  else
159  call get_chl_from_model(chl, g, cs%tracer_flow_CSp)
160  call opacity_from_chl(optics, fluxes, g, cs, chl)
161  endif
162  else ! Use sw e-folding scale set by MOM_input
163  if (optics%nbands <= 1) then ; inv_nbands = 1.0
164  else ; inv_nbands = 1.0 / real(optics%nbands) ; endif
165 
166  ! Make sure there is no division by 0.
167  inv_sw_pen_scale = 1.0 / max(cs%pen_sw_scale, 0.1*gv%Angstrom_z, &
168  gv%H_to_m*gv%H_subroundoff)
169 !$OMP parallel default(none) shared(is,ie,js,je,nz,optics,inv_sw_pen_scale,fluxes,CS,Inv_nbands,GV)
170  if ( cs%Opacity_scheme == double_exp ) then
171 !$OMP do
172  do k=1,nz ; do j=js,je ; do i=is,ie
173  optics%opacity_band(1,i,j,k) = inv_sw_pen_scale
174  optics%opacity_band(2,i,j,k) = 1.0 / max(cs%pen_sw_scale_2nd, &
175  0.1*gv%Angstrom_z,gv%H_to_m*gv%H_subroundoff)
176  enddo ; enddo ; enddo
177  if (.not.associated(fluxes%sw) .or. (cs%pen_SW_scale <= 0.0)) then
178 !$OMP do
179  do j=js,je ; do i=is,ie ; do n=1,optics%nbands
180  optics%sw_pen_band(n,i,j) = 0.0
181  enddo ; enddo ; enddo
182  else
183 !$OMP do
184  do j=js,je ; do i=is,ie ;
185  optics%sw_pen_band(1,i,j) = (cs%SW_1st_EXP_RATIO) * fluxes%sw(i,j)
186  optics%sw_pen_band(2,i,j) = (1.-cs%SW_1st_EXP_RATIO) * fluxes%sw(i,j)
187  enddo ; enddo ;
188  endif
189  else
190  do k=1,nz ; do j=js,je ; do i=is,ie ; do n=1,optics%nbands
191  optics%opacity_band(n,i,j,k) = inv_sw_pen_scale
192  enddo ; enddo ; enddo ; enddo
193  if (.not.associated(fluxes%sw) .or. (cs%pen_SW_scale <= 0.0)) then
194 !$OMP do
195  do j=js,je ; do i=is,ie ; do n=1,optics%nbands
196  optics%sw_pen_band(n,i,j) = 0.0
197  enddo ; enddo ; enddo
198  else
199 !$OMP do
200  do j=js,je ; do i=is,ie ; do n=1,optics%nbands
201  optics%sw_pen_band(n,i,j) = cs%pen_SW_frac * inv_nbands * fluxes%sw(i,j)
202  enddo ; enddo ; enddo
203  endif
204  endif
205 !$OMP end parallel
206  endif
207  if (query_averaging_enabled(cs%diag)) then
208  if (cs%id_sw_pen > 0) then
209 !$OMP parallel do default(none) shared(is,ie,js,je,Pen_SW_tot,optics)
210  do j=js,je ; do i=is,ie
211  pen_sw_tot(i,j) = 0.0
212  do n=1,optics%nbands
213  pen_sw_tot(i,j) = pen_sw_tot(i,j) + optics%sw_pen_band(n,i,j)
214  enddo
215  enddo ; enddo
216  call post_data(cs%id_sw_pen, pen_sw_tot, cs%diag)
217  endif
218  if (cs%id_sw_vis_pen > 0) then
219  if (cs%opacity_scheme == manizza_05) then
220 !$OMP parallel do default(none) shared(is,ie,js,je,Pen_SW_tot,optics)
221  do j=js,je ; do i=is,ie
222  pen_sw_tot(i,j) = 0.0
223  do n=1,min(optics%nbands,2)
224  pen_sw_tot(i,j) = pen_sw_tot(i,j) + optics%sw_pen_band(n,i,j)
225  enddo
226  enddo ; enddo
227  else
228 !$OMP parallel do default(none) shared(is,ie,js,je,Pen_SW_tot,optics)
229  do j=js,je ; do i=is,ie
230  pen_sw_tot(i,j) = 0.0
231  do n=1,optics%nbands
232  pen_sw_tot(i,j) = pen_sw_tot(i,j) + optics%sw_pen_band(n,i,j)
233  enddo
234  enddo ; enddo
235  endif
236  call post_data(cs%id_sw_vis_pen, pen_sw_tot, cs%diag)
237  endif
238  do n=1,optics%nbands ; if (cs%id_opacity(n) > 0) then
239 !$OMP parallel do default(none) shared(nz,is,ie,js,je,tmp,optics,n)
240  do k=1,nz ; do j=js,je ; do i=is,ie
241  tmp(i,j,k) = optics%opacity_band(n,i,j,k)
242  enddo ; enddo ; enddo
243  call post_data(cs%id_opacity(n), tmp, cs%diag)
244  endif ; enddo
245  endif
246 
Ocean grid type. See mom_grid for details.
Definition: MOM_grid.F90:19
Here is the call graph for this function:
Here is the caller graph for this function:

◆ sw_pen_frac_morel()

real function mom_opacity::sw_pen_frac_morel ( real, intent(in)  chl_data)
private

Definition at line 460 of file MOM_opacity.F90.

Referenced by opacity_from_chl().

460  real, intent(in) :: chl_data
461  real :: sw_pen_frac_morel
462 ! Argument : chl_data - The chlorophyll-A concentration in mg m-3.
463 ! The following are coefficients for the optical model taken from Morel and
464 ! Antoine (1994). These coeficients represent a non uniform distribution of
465 ! chlorophyll-a through the water column. Other approaches may be more
466 ! appropriate when using an interactive ecosystem model that predicts
467 ! three-dimensional chl-a values.
468  real :: chl, chl2 ! The log10 of chl_data in mg m-3, and Chl^2.
469  real, dimension(6), parameter :: &
470  v1_coef=(/0.321, 0.008, 0.132, 0.038, -0.017, -0.007/)
471 
472  chl = log10(min(max(chl_data,0.02),60.0)) ; chl2 = chl*chl
473  sw_pen_frac_morel = 1.0 - ( (v1_coef(1) + v1_coef(2)*chl) + chl2 * &
474  ((v1_coef(3) + chl*v1_coef(4)) + chl2*(v1_coef(5) + chl*v1_coef(6))) )
Here is the caller graph for this function:

Variable Documentation

◆ double_exp

integer, parameter mom_opacity::double_exp = 4
private

Definition at line 111 of file MOM_opacity.F90.

Referenced by opacity_init(), and set_opacity().

◆ double_exp_string

character*(10), parameter mom_opacity::double_exp_string = "DOUBLE_EXP"
private

Definition at line 117 of file MOM_opacity.F90.

Referenced by opacity_init().

117 character*(10), parameter :: DOUBLE_EXP_STRING = "DOUBLE_EXP"

◆ manizza_05

integer, parameter mom_opacity::manizza_05 = 1
private

Definition at line 111 of file MOM_opacity.F90.

Referenced by opacity_from_chl(), opacity_init(), and set_opacity().

◆ manizza_05_string

character*(10), parameter mom_opacity::manizza_05_string = "MANIZZA_05"
private

Definition at line 114 of file MOM_opacity.F90.

Referenced by opacity_init().

114 character*(10), parameter :: MANIZZA_05_STRING = "MANIZZA_05"

◆ morel_88

integer, parameter mom_opacity::morel_88 = 2
private

Definition at line 111 of file MOM_opacity.F90.

Referenced by opacity_from_chl(), and opacity_init().

◆ morel_88_string

character*(10), parameter mom_opacity::morel_88_string = "MOREL_88"
private

Definition at line 115 of file MOM_opacity.F90.

Referenced by opacity_init().

115 character*(10), parameter :: MOREL_88_STRING = "MOREL_88"

◆ no_scheme

integer, parameter mom_opacity::no_scheme = 0

Definition at line 111 of file MOM_opacity.F90.

Referenced by opacity_init().

111 integer, parameter :: no_scheme = 0, manizza_05 = 1, morel_88 = 2, &
112  single_exp = 3, double_exp = 4

◆ single_exp

integer, parameter mom_opacity::single_exp = 3
private

Definition at line 111 of file MOM_opacity.F90.

Referenced by opacity_init().

◆ single_exp_string

character*(10), parameter mom_opacity::single_exp_string = "SINGLE_EXP"
private

Definition at line 116 of file MOM_opacity.F90.

Referenced by opacity_init().

116 character*(10), parameter :: SINGLE_EXP_STRING = "SINGLE_EXP"