@@ -14,6 +14,7 @@ module MOM_oda_driver_mod
14
14
use MOM_ensemble_manager, only : get_ensemble_id, get_ensemble_size
15
15
use MOM_ensemble_manager, only : get_ensemble_pelist, get_ensemble_filter_pelist
16
16
use MOM_error_handler, only : stdout, stdlog, MOM_error
17
+ use MOM_forcing_type, only : forcing, mech_forcing
17
18
use MOM_io, only : SINGLE_FILE
18
19
use MOM_interp_infra, only : init_extern_field, get_external_field_info
19
20
use MOM_interp_infra, only : time_interp_extern
@@ -28,6 +29,8 @@ module MOM_oda_driver_mod
28
29
use ocean_da_types_mod, only : grid_type, ocean_profile_type
29
30
use ocean_da_types_mod, only : ensemble_control_struct, ocean_control_struct
30
31
use ocean_da_core_mod, only : ocean_da_core_init, get_profiles
32
+ use MOM_oda_ml_mod, only: oda_ml_init, oda_ml_end, oda_ml_inference
33
+ use MOM_oda_ml_mod, only: ocean_oda_ml_struct
31
34
! This preprocessing directive enables the SPEAR online ensemble data assimilation
32
35
! configuration. Existing community based APIs for data assimilation are currently
33
36
! called offline for forecast applications using information read from a MOM6 state file.
@@ -70,6 +73,7 @@ module MOM_oda_driver_mod
70
73
integer :: id_clock_oda_init
71
74
integer :: id_clock_get_prior
72
75
integer :: id_clock_bias_adjustment
76
+ integer :: id_clock_ml_bias_correction
73
77
integer :: id_clock_ensemble_filter
74
78
integer :: id_clock_apply_increments
75
79
! >@}
@@ -97,12 +101,14 @@ module MOM_oda_driver_mod
97
101
type (ensemble_control_struct), pointer :: Ocean_increment= > NULL () ! < A separate structure for
98
102
! ! increment diagnostics
99
103
type (ocean_control_struct), pointer :: Ocean_background_ave= > NULL () ! < ocean averaged prior states in model space
104
+ type (ocean_oda_ml_struct), pointer :: ml_CS = > NULL ()
100
105
integer :: nk ! < number of vertical layers used for DA
101
106
type (ocean_grid_type), pointer :: Grid = > NULL () ! < MOM6 grid type and decomposition for the DA
102
- type (ocean_grid_type), pointer :: G = > NULL () ! < MOM6 grid type and decomposition for the model
107
+ type (ocean_grid_type), pointer :: model_G = > NULL () ! < MOM6 grid type and decomposition for the model
103
108
type (MOM_domain_type), pointer , dimension (:) :: domains = > NULL () ! < Pointer to mpp_domain objects
104
109
! ! for ensemble members
105
110
type (verticalGrid_type), pointer :: GV = > NULL () ! < vertical grid for DA
111
+ type (verticalGrid_type), pointer :: model_GV = > NULL () ! < vertical grid for DA
106
112
type (unit_scale_type), pointer :: &
107
113
US = > NULL () ! < structure containing various unit conversion factors for DA
108
114
@@ -115,6 +121,10 @@ module MOM_oda_driver_mod
115
121
! ! to bias adjustment [C T-1 ~> degC s-1]
116
122
real , pointer , dimension (:,:,:) :: S_bc_tend = > NULL () ! < The layer salinity tendency due
117
123
! ! to bias adjustment [S T-1 ~> ppt s-1]
124
+ real , pointer , dimension (:,:,:) :: T_ml_tend = > NULL () ! < The layer temperature tendency due
125
+ ! ! to ML bias adjustment [C T-1 ~> degC s-1]
126
+ real , pointer , dimension (:,:,:) :: S_ml_tend = > NULL () ! < The layer salinity tendency due
127
+ ! ! to bias adjustment [S T-1 ~> ppt s-1]
118
128
integer :: ni ! < global i-direction grid size
119
129
integer :: nj ! < global j-direction grid size
120
130
logical :: reentrant_x ! < grid is reentrant in the x direction
@@ -125,6 +135,9 @@ module MOM_oda_driver_mod
125
135
logical :: do_bias_adjustment ! < If true, use spatio-temporally varying climatological tendency
126
136
! ! adjustment for Temperature and Salinity
127
137
real :: bias_adjustment_multiplier ! < A scaling for the bias adjustment
138
+ logical :: do_ml_bias_adjustment ! < If true, use machine learning-trained tendency
139
+ ! ! adjustment for Temperature and Salinity
140
+ real :: ml_bias_adjustment_multiplier ! < A scaling for the bias adjustment
128
141
integer :: assim_method ! < Method: NO_ASSIM,EAKF_ASSIM or OI_ASSIM
129
142
integer :: ensemble_size ! < Size of the ensemble
130
143
integer :: ensemble_id = 0 ! < id of the current ensemble member
@@ -165,8 +178,8 @@ module MOM_oda_driver_mod
165
178
subroutine init_oda (Time , G , GV , US , diag_CS , CS )
166
179
167
180
type (time_type), intent (in ) :: Time ! < The current model time.
168
- type (ocean_grid_type), pointer :: G ! < domain and grid information for ocean model
169
- type (verticalGrid_type), intent (in ) :: GV ! < The ocean's vertical grid structure
181
+ type (ocean_grid_type), pointer , intent ( in ) :: G ! < domain and grid information for ocean model
182
+ type (verticalGrid_type), pointer , intent (in ) :: GV ! < The ocean's vertical grid structure
170
183
type (unit_scale_type), intent (in ) :: US ! < A dimensional unit scaling type
171
184
type (diag_ctrl), target , intent (inout ) :: diag_CS ! < A pointer to a diagnostic control structure
172
185
type (ODA_CS), pointer , intent (inout ) :: CS ! < The DA control structure
@@ -198,6 +211,7 @@ subroutine init_oda(Time, G, GV, US, diag_CS, CS)
198
211
199
212
id_clock_get_prior= cpu_clock_id(' (ODA getting prior)' )
200
213
id_clock_bias_adjustment= cpu_clock_id(' (ODA getting bias correction)' )
214
+ id_clock_ml_bias_correction= cpu_clock_id(' (ML inference of bias correction)' )
201
215
id_clock_ensemble_filter= cpu_clock_id(' (ODA ensemble filter)' )
202
216
id_clock_apply_increments= cpu_clock_id(' (ODA applying increments)' )
203
217
id_clock_oda_init= cpu_clock_id(' (ODA initialization)' )
@@ -244,6 +258,15 @@ subroutine init_oda(Time, G, GV, US, diag_CS, CS)
244
258
" A multiplicative scaling factor for the climatological tracer tendency adjustment " , &
245
259
units= " nondim" , default= 1.0 )
246
260
endif
261
+ call get_param(PF, mdl, " APPLY_ML_TRACER_TENDENCY_ADJUSTMENT" , CS% do_ml_bias_adjustment, &
262
+ " If true, add a machine learning-trained adjustment " // &
263
+ " to temperature and salinity." , &
264
+ default= .false. )
265
+ if (CS% do_ml_bias_adjustment) then
266
+ call get_param(PF, mdl, " ML_TRACER_ADJUSTMENT_FACTOR" , CS% ml_bias_adjustment_multiplier, &
267
+ " A multiplicative scaling factor for the machine learning tracer tendency adjustment " , &
268
+ units= " nondim" , default= 1.0 )
269
+ endif
247
270
call get_param(PF, mdl, " USE_BASIN_MASK" , CS% use_basin_mask, &
248
271
" If true, add a basin mask to delineate weakly connected " // &
249
272
" ocean basins for the purpose of data assimilation." , &
@@ -303,7 +326,8 @@ subroutine init_oda(Time, G, GV, US, diag_CS, CS)
303
326
call broadcast_domain(CS% domains(n)% mpp_domain)
304
327
enddo
305
328
call set_rootPE(CS% filter_pelist(1 )) ! this line is not in Feiyu's version (needed?)
306
- CS% G = > G
329
+ CS% model_G = > G
330
+ CS% model_GV = > GV
307
331
allocate (CS% Grid)
308
332
! params NIHALO_ODA, NJHALO_ODA set the DA halo size
309
333
call MOM_domains_init(CS% Grid% Domain, PF, param_suffix= ' _ODA' , US= CS% US)
@@ -406,6 +430,17 @@ subroutine init_oda(Time, G, GV, US, diag_CS, CS)
406
430
407
431
allocate (CS% T_bc_tend(G% isd:G% ied,G% jsd:G% jed,CS% GV% ke), source= 0.0 )
408
432
allocate (CS% S_bc_tend(G% isd:G% ied,G% jsd:G% jed,CS% GV% ke), source= 0.0 )
433
+
434
+ endif
435
+
436
+ if (CS% do_ml_bias_adjustment) then
437
+
438
+ allocate (CS% ml_CS)
439
+ call oda_ml_init(CS% ml_CS, CS% GV% ke)
440
+
441
+ allocate (CS% T_ml_tend(G% isd:G% ied,G% jsd:G% jed,CS% GV% ke), source= 0.0 )
442
+ allocate (CS% S_ml_tend(G% isd:G% ied,G% jsd:G% jed,CS% GV% ke), source= 0.0 )
443
+
409
444
endif
410
445
411
446
call cpu_clock_end(id_clock_oda_init)
@@ -418,7 +453,7 @@ subroutine init_oda(Time, G, GV, US, diag_CS, CS)
418
453
end subroutine init_oda
419
454
420
455
! > Copy ensemble member tracers to ensemble vector.
421
- subroutine set_prior_tracer (Time , G , GV , h , tv , model_u , model_v , model_ssh , CS )
456
+ subroutine set_prior_tracer (Time , G , GV , h , tv , model_u , model_v , model_ssh , fluxes , forces , CS )
422
457
type (time_type), intent (in ) :: Time ! < The current model time
423
458
type (ocean_grid_type), pointer :: G ! < domain and grid information for ocean model
424
459
type (verticalGrid_type), intent (in ) :: GV ! < The ocean's vertical grid structure
@@ -427,6 +462,9 @@ subroutine set_prior_tracer(Time, G, GV, h, tv, model_u, model_v, model_ssh, CS)
427
462
real , dimension (SZIB_(G),SZJ_(G),SZK_(GV)), intent (in ) :: model_u
428
463
real , dimension (SZI_(G),SZJB_(G),SZK_(GV)), intent (in ) :: model_v
429
464
real , dimension (SZI_(G),SZJ_(G)), intent (in ) :: model_ssh
465
+ type (mech_forcing), intent (in ) :: forces ! < A structure with the driving mechanical forces
466
+ type (forcing), intent (in ) :: fluxes ! < A structure with pointers to themodynamic,
467
+ ! ! tracer and mass exchange forcing fields
430
468
431
469
type (ODA_CS), pointer :: CS ! < ocean DA control structure
432
470
real , dimension (SZI_(G),SZJ_(G),CS% nk) :: T ! Temperature on the analysis grid [C ~> degC]
@@ -487,6 +525,12 @@ subroutine set_prior_tracer(Time, G, GV, h, tv, model_u, model_v, model_ssh, CS)
487
525
CS% Ocean_background_ave% U = 0.0
488
526
CS% Ocean_background_ave% V = 0.0
489
527
CS% Ocean_background_ave% SSH = 0.0
528
+ CS% Ocean_background_ave% taux = 0.0
529
+ CS% Ocean_background_ave% tauy = 0.0
530
+ CS% Ocean_background_ave% latent = 0.0
531
+ CS% Ocean_background_ave% sensible = 0.0
532
+ CS% Ocean_background_ave% lw = 0.0
533
+ CS% Ocean_background_ave% sw = 0.0
490
534
call MOM_mesg(" ODA Reset background accumulation" )
491
535
endif
492
536
@@ -495,6 +539,12 @@ subroutine set_prior_tracer(Time, G, GV, h, tv, model_u, model_v, model_ssh, CS)
495
539
CS% Ocean_background_ave% U = CS% Ocean_background_ave% U + U
496
540
CS% Ocean_background_ave% V = CS% Ocean_background_ave% V + V
497
541
CS% Ocean_background_ave% SSH = CS% Ocean_background_ave% SSH + model_ssh
542
+ CS% Ocean_background_ave% taux = CS% Ocean_background_ave% taux + forces% taux
543
+ CS% Ocean_background_ave% tauy = CS% Ocean_background_ave% tauy + forces% tauy
544
+ CS% Ocean_background_ave% latent = CS% Ocean_background_ave% latent + fluxes% latent
545
+ CS% Ocean_background_ave% sensible = CS% Ocean_background_ave% sensible + fluxes% sens
546
+ CS% Ocean_background_ave% lw = CS% Ocean_background_ave% lw + fluxes% lw
547
+ CS% Ocean_background_ave% sw = CS% Ocean_background_ave% sw + fluxes% sw
498
548
499
549
CS% prior_ave_counter = CS% prior_ave_counter + 1.0
500
550
@@ -521,13 +571,25 @@ subroutine set_prior_tracer(Time, G, GV, h, tv, model_u, model_v, model_ssh, CS)
521
571
CS% Ocean_background_ave% U = CS% Ocean_background_ave% U / (CS% prior_ave_counter)
522
572
CS% Ocean_background_ave% V = CS% Ocean_background_ave% V / (CS% prior_ave_counter)
523
573
CS% Ocean_background_ave% SSH = CS% Ocean_background_ave% SSH / (CS% prior_ave_counter)
574
+ CS% Ocean_background_ave% taux = CS% Ocean_background_ave% taux / (CS% prior_ave_counter)
575
+ CS% Ocean_background_ave% tauy = CS% Ocean_background_ave% tauy / (CS% prior_ave_counter)
576
+ CS% Ocean_background_ave% latent = CS% Ocean_background_ave% latent / (CS% prior_ave_counter)
577
+ CS% Ocean_background_ave% sensible = CS% Ocean_background_ave% sensible / (CS% prior_ave_counter)
578
+ CS% Ocean_background_ave% lw = CS% Ocean_background_ave% lw / (CS% prior_ave_counter)
579
+ CS% Ocean_background_ave% sw = CS% Ocean_background_ave% sw / (CS% prior_ave_counter)
524
580
525
581
do m= 1 ,CS% ensemble_size
526
582
call pass_var(CS% Ocean_background_ave% T,G% Domain)
527
583
call pass_var(CS% Ocean_background_ave% S,G% Domain)
528
584
call pass_var(CS% Ocean_background_ave% U,G% Domain)
529
585
call pass_var(CS% Ocean_background_ave% V,G% Domain)
530
586
call pass_var(CS% Ocean_background_ave% SSH,G% Domain)
587
+ call pass_var(CS% Ocean_background_ave% taux,G% Domain)
588
+ call pass_var(CS% Ocean_background_ave% tauy,G% Domain)
589
+ call pass_var(CS% Ocean_background_ave% latent,G% Domain)
590
+ call pass_var(CS% Ocean_background_ave% sensible,G% Domain)
591
+ call pass_var(CS% Ocean_background_ave% lw,G% Domain)
592
+ call pass_var(CS% Ocean_background_ave% sw,G% Domain)
531
593
enddo
532
594
533
595
if (.NOT. CS% assim_method == NO_ASSIM) then
@@ -643,6 +705,7 @@ subroutine oda(Time, CS)
643
705
644
706
call get_posterior_tracer(Time, CS, increment= .true. )
645
707
if (CS% do_bias_adjustment) call get_bias_correction_tracer(Time, CS% US, CS)
708
+ if (CS% do_ml_bias_adjustment) call get_ML_bias_correction(Time, CS% US, CS)
646
709
647
710
call cpu_clock_end(id_clock_ensemble_filter)
648
711
@@ -669,9 +732,9 @@ subroutine get_bias_correction_tracer(Time, US, CS)
669
732
670
733
671
734
call cpu_clock_begin(id_clock_bias_adjustment)
672
- call horiz_interp_and_extrap_tracer(CS% INC_CS% T, Time, CS% G , T_bias, &
735
+ call horiz_interp_and_extrap_tracer(CS% INC_CS% T, Time, CS% model_G , T_bias, &
673
736
valid_flag, z_in, z_edges_in, missing_value, scale= US% degC_to_C* US% s_to_T, spongeOngrid= .true. )
674
- call horiz_interp_and_extrap_tracer(CS% INC_CS% S, Time, CS% G , S_bias, &
737
+ call horiz_interp_and_extrap_tracer(CS% INC_CS% S, Time, CS% model_G , S_bias, &
675
738
valid_flag, z_in, z_edges_in, missing_value, scale= US% ppt_to_S* US% s_to_T, spongeOngrid= .true. )
676
739
677
740
! This should be replaced to use mask_z instead of the following lines
@@ -702,62 +765,46 @@ subroutine get_bias_correction_tracer(Time, US, CS)
702
765
703
766
end subroutine get_bias_correction_tracer
704
767
705
- ! > Returns posterior adjustments or full state
706
- ! !Note that only those PEs associated with an ensemble member receive data
707
- subroutine get_ML_increments (Time , CS , increment )
768
+ subroutine get_ML_bias_correction (Time , US , CS )
708
769
type (time_type), intent (in ) :: Time ! < the current model time
770
+ type (unit_scale_type), intent (in ) :: US ! < A dimensional unit scaling type
709
771
type (ODA_CS), pointer :: CS ! < ocean DA control structure
710
- logical , optional , intent (in ) :: increment ! < True if returning increment only
711
772
712
- ! type(ensemble_control_struct), pointer :: Ocean_increment=>NULL()
713
- ! integer :: m
714
- ! logical :: get_inc
773
+ ! Local variables
774
+ integer :: isd, ied, jsd, jed
775
+ integer :: i,j
715
776
777
+ call cpu_clock_begin(id_clock_ml_bias_correction)
716
778
717
- ! ! return if not analysis time (retain pointers for h and tv)
718
- ! if (Time < CS%Time .or. CS%assim_method == NO_ASSIM) return
779
+ ! ! Co-locate all variables (taux, tauy, U, V to tracer grid)
780
+
781
+ ! ! Loop through all local gridpoints
782
+ do j= CS% model_G% jsc,CS% model_G% jec ; do i= CS% model_G% isc,CS% model_G% iec
783
+
784
+ ! ! put local variables into ml_CS
785
+ CS% ml_CS% T = CS% Ocean_background_ave% T(i,j,:)
786
+ CS% ml_CS% S = CS% Ocean_background_ave% S(i,j,:)
787
+ CS% ml_CS% latent = CS% Ocean_background_ave% latent(i,j)
788
+ CS% ml_CS% sensible = CS% Ocean_background_ave% sensible(i,j)
789
+ CS% ml_CS% lw = CS% Ocean_background_ave% lw(i,j)
790
+ CS% ml_CS% sw = CS% Ocean_background_ave% sw(i,j)
791
+
792
+ ! ! Call inference subroutine with the concatenated vector
793
+ call oda_ml_inference(CS% ml_CS)
794
+
795
+ ! CS%T_ml_tend(i,j,:) = CS%ml_CS%T_inc
796
+ ! CS%S_ml_tend(i,j,:) = CS%ml_CS%S_inc
797
+ enddo ; enddo
719
798
720
- ! !! switch to global pelist
721
- ! call set_PElist(CS%filter_pelist)
722
- ! call MOM_mesg('Getting posterior')
799
+ CS% T_ml_tend = CS% T_bc_tend * CS% ml_bias_adjustment_multiplier
800
+ CS% S_ml_tend = CS% S_bc_tend * CS% ml_bias_adjustment_multiplier
723
801
724
- ! !! Calculate and redistribute increments to CS%tv right after assimilation
725
- ! !! Retain CS%tv to calculate increments for IAU updates CS%tv_inc otherwise
726
- ! get_inc = .true.
727
- ! if (present(increment)) get_inc = increment
802
+ call pass_var(CS% T_ml_tend, CS% domains(CS% ensemble_id))
803
+ call pass_var(CS% S_ml_tend, CS% domains(CS% ensemble_id))
728
804
729
- ! if (get_inc) then
730
- ! CS%Ocean_increment%T = CS%Ocean_posterior%T - CS%Ocean_prior%T
731
- ! CS%Ocean_increment%S = CS%Ocean_posterior%S - CS%Ocean_prior%S
732
- ! endif
733
- ! ! It may be necessary to check whether the increment and ocean state have the
734
- ! ! same dimensionally rescaled units.
735
- ! do m=1,CS%ensemble_size
736
- ! if (get_inc) then
737
- ! call redistribute_array(CS%mpp_domain, CS%Ocean_increment%T(:,:,:,m),&
738
- ! CS%domains(m)%mpp_domain, CS%T_tend, complete=.true.)
739
- ! call redistribute_array(CS%mpp_domain, CS%Ocean_increment%S(:,:,:,m),&
740
- ! CS%domains(m)%mpp_domain, CS%S_tend, complete=.true.)
741
- ! else
742
- ! call redistribute_array(CS%mpp_domain, CS%Ocean_posterior%T(:,:,:,m),&
743
- ! CS%domains(m)%mpp_domain, CS%T_tend, complete=.true.)
744
- ! call redistribute_array(CS%mpp_domain, CS%Ocean_posterior%S(:,:,:,m),&
745
- ! CS%domains(m)%mpp_domain, CS%S_tend, complete=.true.)
746
- ! endif
747
- ! enddo
748
-
749
-
750
- ! !! switch back to ensemble member pelist
751
- ! call set_PElist(CS%ensemble_pelist(CS%ensemble_id,:))
752
-
753
- ! call pass_var(CS%T_tend,CS%domains(CS%ensemble_id))
754
- ! call pass_var(CS%S_tend,CS%domains(CS%ensemble_id))
755
-
756
- ! !convert to a tendency (degC or PSU per second)
757
- ! CS%T_tend = CS%T_tend / (CS%assim_interval)
758
- ! CS%S_tend = CS%S_tend / (CS%assim_interval)
759
-
760
- end subroutine get_ML_increments
805
+ call cpu_clock_end(id_clock_ml_bias_correction)
806
+
807
+ end subroutine get_ML_bias_correction
761
808
762
809
! > Finalize DA module
763
810
subroutine oda_end (CS )
@@ -808,10 +855,16 @@ subroutine init_ocean_background(CS,Grid,GV)
808
855
allocate (CS% T(isd:ied,jsd:jed,nk),source= 0.0 )
809
856
allocate (CS% S(isd:ied,jsd:jed,nk),source= 0.0 )
810
857
allocate (CS% SSH(isd:ied,jsd:jed),source= 0.0 )
811
- ! allocate(CS%id_t(ens_size), source=-1)
812
- ! allocate(CS%id_s(ens_size), source=-1)
813
858
allocate (CS% U(isdB:iedB,jsd:jed,nk),source= 0.0 )
814
859
allocate (CS% V(isd:ied,jsdB:jedB,nk),source= 0.0 )
860
+ allocate (CS% taux(isdB:iedB,jsd:jed),source= 0.0 )
861
+ allocate (CS% tauy(isd:ied,jsdB:jedB),source= 0.0 )
862
+ allocate (CS% latent(isd:ied,jsd:jed),source= 0.0 )
863
+ allocate (CS% sensible(isd:ied,jsd:jed),source= 0.0 )
864
+ allocate (CS% lw(isd:ied,jsd:jed),source= 0.0 )
865
+ allocate (CS% sw(isd:ied,jsd:jed),source= 0.0 )
866
+ ! allocate(CS%id_t(ens_size), source=-1)
867
+ ! allocate(CS%id_s(ens_size), source=-1)
815
868
! allocate(CS%id_u(ens_size), source=-1)
816
869
! allocate(CS%id_v(ens_size), source=-1)
817
870
! allocate(CS%id_ssh(ens_size), source=-1)
@@ -873,18 +926,23 @@ subroutine apply_oda_tracer_increments(dt, Time_end, G, GV, tv, h, CS)
873
926
real :: h_neglect, h_neglect_edge ! small thicknesses [H ~> m or kg m-2]
874
927
875
928
if (.not. associated (CS)) return
876
- if (CS% assim_method == NO_ASSIM .and. (.not. CS% do_bias_adjustment)) return
929
+ if (CS% assim_method == NO_ASSIM .and. (.not. CS% do_bias_adjustment) &
930
+ .and. (.not. CS% do_ml_bias_adjustment)) return
877
931
878
932
call cpu_clock_begin(id_clock_apply_increments)
879
933
880
934
T_tend_inc(:,:,:) = 0.0 ; S_tend_inc(:,:,:) = 0.0 ; T_tend(:,:,:) = 0.0 ; S_tend(:,:,:) = 0.0
881
- if (CS% assim_method > 0 ) then
935
+ if (.NOT. CS% assim_method == NO_ASSIM ) then
882
936
T_tend = T_tend + CS% T_tend
883
937
S_tend = S_tend + CS% S_tend
884
938
endif
885
- if (CS% do_bias_adjustment ) then
886
- T_tend = T_tend + CS% T_bc_tend
887
- S_tend = S_tend + CS% S_bc_tend
939
+ ! if (CS%do_bias_adjustment ) then
940
+ ! T_tend = T_tend + CS%T_bc_tend
941
+ ! S_tend = S_tend + CS%S_bc_tend
942
+ ! endif
943
+ if (CS% do_ml_bias_adjustment ) then
944
+ T_tend = T_tend + CS% T_ml_tend
945
+ S_tend = S_tend + CS% S_ml_tend
888
946
endif
889
947
890
948
if (CS% answer_date >= 20190101 ) then
0 commit comments