Back to home page

MITgcm

 
 

    


File indexing completed on 2023-09-21 05:10:50 UTC

view on githubraw file Latest commit 96b00645 on 2023-09-20 15:15:14 UTC
056c9f12b0 Dani*0001 #include "STREAMICE_OPTIONS.h"
                0002 
                0003 CStartOfInterface
                0004       SUBROUTINE STREAMICE_FIELDS_LOAD(
                0005      I                            myTime, myIter, myThid )
                0006 C     *==========================================================*
                0007 C     | SUBROUTINE AIM_FIELDS_LOAD
                0008 C     | o Control reading of AIM fields from external source.
                0009 C     *==========================================================*
                0010 C     | Loads surface boundary condition datasets for AIM.
                0011 C     | The routine is called every timetep and periodically
                0012 C     | loads a set of external fields.
                0013 C     | Monthly climatology files are read either for
                0014 C     | a) a direct use (useMMsurfFc):
                0015 C     |   Albedo, Soil moisture, Surface Temperature
                0016 C     | b) time interpolation (useFMsurfBC):
                0017 C     |   Sea & Land surf. Temp, snow, sea-ice, soil-water (2-lev)
                0018 C     | + (1rst.iter) ground albedo, vegetation, land-sea fraction
                0019 C     | Most of the work is done by the master thread while
                0020 C     | the other threads spin (but all inside MDSIO S/R).
                0021 C     *==========================================================*
                0022       IMPLICIT NONE
                0023 
                0024 C     === Global variables ===
                0025 #include "SIZE.h"
                0026 #include "EEPARAMS.h"
                0027 #include "PARAMS.h"
                0028 #include "GRID.h"
                0029 #include "STREAMICE.h"
                0030 
                0031 C     === Routine arguments ===
                0032 C     myTime :: Simulation time
                0033 C     myIter :: Simulation timestep number
                0034 C     myThid :: Thread no. that called this routine.
                0035       _RL     myTime
                0036       INTEGER myIter
                0037       INTEGER myThid
                0038 CEndOfInterface
                0039 
                0040 C     === Functions ===
                0041 
                0042 #ifdef ALLOW_STREAMICE
                0043 #ifdef ALLOW_STREAMICE_TIMEDEP_FORCING
                0044 C     === Local variables ===
                0045 C     bi,bj, i,j  :: Loop counters
                0046 C     tYear       :: Fraction within year of myTime
                0047 C     mnthIndex   :: Current time in whole months
                0048 C     prevMnthIndex
                0049 C     fNam        :: Strings used in constructing file names
                0050 C     mnthNam
                0051 C     pfact       :: used to convert Pot.Temp. to in-situ Temp.
                0052 C     loadNewData :: true when need to load new data from file
                0053       INTEGER bi,bj,i,j
                0054 c     _RL pfact
                0055       LOGICAL first, changed
                0056 C--   for use with useMMsurfFc:
                0057       CHARACTER*(MAX_LEN_FNAM) fNam
96b006450c dngo*0058       LOGICAL upd_cfric, upd_bdot_maxmelt, upd_bglen
056c9f12b0 Dani*0059 
                0060       INTEGER nm0, nm1, nmP
                0061       _RL myRelTime, fac, tmpFac
0fbff46b46 dngo*0062 
056c9f12b0 Dani*0063 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
                0064 
                0065 C--   find which month to use for surface BC
                0066 C     aim_surfForc_TimePeriod :: Length of forcing time period (e.g. 1 month)
                0067 C     aim_surfForc_NppCycle   :: Number of time period per Cycle (e.g. 12)
                0068 
96b006450c dngo*0069       upd_cfric = .FALSE.
                0070       upd_bdot_maxmelt = .FALSE.
                0071       upd_bglen = .FALSE.
                0072       IF ( bdotMaxmeltTimeDepFile .NE. ' ' .and.
                0073      &  STREAMICEbasalTracConfig.eq.'FILE' ) THEN
                0074         upd_bdot_maxmelt = .TRUE.
                0075       ENDIF
                0076       IF ( bglenTimeDepFile .NE. ' ' .and.
                0077      &  STREAMICEGlenConstConfig.eq.'FILE' ) THEN
                0078         upd_bglen = .TRUE.
                0079       ENDIF
                0080       IF ( cfricTimeDepFile .NE. ' '  ) THEN
                0081         upd_cfric = .TRUE.
                0082       ENDIF
                0083 
056c9f12b0 Dani*0084       myRelTime = myTime - startTime
                0085       first = (myRelTime .lt. 0.5*deltaTClock)
                0086       if ( streamice_forcing_period .eq. 0.D0 ) THEN
96b006450c dngo*0087 c     &     .or. externForcingCycle .eq. 0.D0 ) then
056c9f12b0 Dani*0088 C     control parameter is constant in time and only needs to be updated
                0089 C     once in the beginning
                0090        changed = .false.
                0091        nm0  = 1
                0092        nm1  = 1
                0093        fac     = 1.D0
                0094       else
                0095 
                0096 C--   Now calculate whether it is time to update the forcing arrays
                0097        if (externForcingCycle .eq. 0.0 ) THEN
                0098         CALL GET_PERIODIC_INTERVAL(
                0099      O                   nmP, nm0, nm1, tmpFac, fac,
                0100      I                   externForcingCycle, streamice_forcing_period,
0fbff46b46 dngo*0101      I                   deltaTClock,
                0102      I                   myTime+0.5*streamice_forcing_period,
056c9f12b0 Dani*0103      I                   myThid )
                0104         fac = 1.D0 - fac
                0105        else
                0106         CALL GET_PERIODIC_INTERVAL(
                0107      O                   nmP, nm0, nm1, tmpFac, fac,
                0108      I                   externForcingCycle, streamice_forcing_period,
0fbff46b46 dngo*0109      I                   deltaTClock, myTime,
056c9f12b0 Dani*0110      I                   myThid )
                0111        endif
                0112 
                0113        IF ( nm0.NE.nmP ) THEN
                0114         changed = .true.
                0115        ELSE
                0116         changed = .false.
                0117        ENDIF
                0118        IF ( first ) changed = .false.
                0119       endif
                0120 
                0121 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
                0122 
                0123 C-     Load new data:
                0124 
                0125 C-    Only one thread updates parameter in common block
                0126 C-    Wait for everyone to set loadNewData before Master updates prevMnthIndex
                0127         _BARRIER
                0128 
                0129         IF ( first ) THEN
                0130 
                0131 #ifdef STREAMICE_STRESS_BOUNDARY_CONTROL
                0132 
                0133          IF ( STREAMICEuNormalTimeDepFile .NE. ' '  ) THEN
                0134           CALL READ_REC_XY_RL(STREAMICEuNormalTimeDepFile,
0fbff46b46 dngo*0135      &                        streamice_u_normal_stress1,
056c9f12b0 Dani*0136      &                        nm0,myIter,myThid)
                0137          ENDIF
                0138 
                0139          IF ( STREAMICEvNormalTimeDepFile .NE. ' '  ) THEN
                0140           CALL READ_REC_XY_RL(STREAMICEvNormalTimeDepFile,
0fbff46b46 dngo*0141      &                        streamice_v_normal_stress1,
056c9f12b0 Dani*0142      &                        nm0,myIter,myThid)
                0143          ENDIF
                0144 
                0145          IF ( STREAMICEuShearTimeDepFile .NE. ' '  ) THEN
                0146           CALL READ_REC_XY_RL(STREAMICEuShearTimeDepFile,
0fbff46b46 dngo*0147      &                        streamice_u_shear_stress1,
056c9f12b0 Dani*0148      &                        nm0,myIter,myThid)
                0149          ENDIF
                0150 
                0151          IF ( STREAMICEvShearTimeDepFile .NE. ' '  ) THEN
                0152           CALL READ_REC_XY_RL(STREAMICEvShearTimeDepFile,
0fbff46b46 dngo*0153      &                        streamice_v_shear_stress1,
056c9f12b0 Dani*0154      &                        nm0,myIter,myThid)
                0155          ENDIF
                0156 
                0157 #endif
2a16ced2f5 Dani*0158 #ifdef ALLOW_STREAMICE_FLUX_CONTROL
                0159          IF ( STREAMICEuFluxTimeDepFile .NE. ' '  ) THEN
                0160           CALL READ_REC_XY_RL(STREAMICEuFluxTimeDepFile,
                0161      &                        u_flux_bdry_SI_1,
                0162      &                        nm0,myIter,myThid)
                0163          ENDIF
                0164          IF ( STREAMICEvFluxTimeDepFile .NE. ' '  ) THEN
                0165           CALL READ_REC_XY_RL(STREAMICEvFluxTimeDepFile,
                0166      &                        u_flux_bdry_SI_1,
                0167      &                        nm0,myIter,myThid)
                0168          ENDIF
                0169 #endif
056c9f12b0 Dani*0170 
                0171          IF ( STREAMICEBdotTimeDepFile .NE. ' '  ) THEN
                0172           CALL READ_REC_XY_RL(STREAMICEBdotTimeDepFile,
0fbff46b46 dngo*0173      &                        bdot_streamice1,
056c9f12b0 Dani*0174      &                        nm0,myIter,myThid)
                0175          ENDIF
                0176 
96b006450c dngo*0177          IF ( bdotMaxmeltTimeDepFile .NE. ' '  ) THEN
                0178           CALL READ_REC_XY_RL(bdotMaxmeltTimeDepFile,
                0179      &                        streamice_bdot_maxmelt1,
                0180      &                        nm0,myIter,myThid)
                0181          ENDIF
                0182 
                0183          IF ( bglenTimeDepFile .NE. ' '  ) THEN
                0184           CALL READ_REC_XY_RL(bglenTimeDepFile,
                0185      &                        streamice_bglen1,
                0186      &                        nm0,myIter,myThid)
                0187          ENDIF
                0188 
                0189          IF ( cfricTimeDepFile .NE. ' '  ) THEN
                0190           CALL READ_REC_XY_RL(cfricTimeDepFile,
                0191      &                        streamice_beta1,
                0192      &                        nm0,myIter,myThid)
                0193          ENDIF
                0194 
056c9f12b0 Dani*0195 C-      endif 1rst iter.
                0196         ENDIF
                0197 
                0198         IF ( first .OR. changed) THEN
                0199 
                0200 #ifdef STREAMICE_STRESS_BOUNDARY_CONTROL
                0201 
                0202          DO bj=myByLo(myThid),myByHi(myThid)
                0203           DO bi=myBxLo(myThid),myBxHi(myThid)
                0204            DO j=1,sNy
                0205             DO i=1,sNx
0fbff46b46 dngo*0206 
                0207              streamice_u_normal_stress0(i,j,bi,bj) =
056c9f12b0 Dani*0208      &        streamice_u_normal_stress1(i,j,bi,bj)
0fbff46b46 dngo*0209              streamice_v_normal_stress0(i,j,bi,bj) =
056c9f12b0 Dani*0210      &        streamice_v_normal_stress1(i,j,bi,bj)
0fbff46b46 dngo*0211              streamice_u_shear_stress0(i,j,bi,bj) =
056c9f12b0 Dani*0212      &        streamice_u_shear_stress1(i,j,bi,bj)
0fbff46b46 dngo*0213              streamice_v_shear_stress0(i,j,bi,bj) =
056c9f12b0 Dani*0214      &        streamice_v_shear_stress1(i,j,bi,bj)
                0215             ENDDO
                0216            ENDDO
                0217           ENDDO
                0218          ENDDO
0fbff46b46 dngo*0219 
056c9f12b0 Dani*0220          IF ( STREAMICEuNormalTimeDepFile .NE. ' '  ) THEN
                0221           CALL READ_REC_XY_RL(STREAMICEuNormalTimeDepFile,
0fbff46b46 dngo*0222      &                        streamice_u_normal_stress1,
056c9f12b0 Dani*0223      &                        nm1,myIter,myThid)
                0224          ENDIF
                0225 
                0226          IF ( STREAMICEvNormalTimeDepFile .NE. ' '  ) THEN
                0227           CALL READ_REC_XY_RL(STREAMICEvNormalTimeDepFile,
0fbff46b46 dngo*0228      &                        streamice_v_normal_stress1,
056c9f12b0 Dani*0229      &                        nm1,myIter,myThid)
                0230          ENDIF
                0231 
                0232          IF ( STREAMICEuShearTimeDepFile .NE. ' '  ) THEN
                0233           CALL READ_REC_XY_RL(STREAMICEuShearTimeDepFile,
0fbff46b46 dngo*0234      &                        streamice_u_shear_stress1,
056c9f12b0 Dani*0235      &                        nm1,myIter,myThid)
                0236          ENDIF
                0237 
                0238          IF ( STREAMICEvShearTimeDepFile .NE. ' '  ) THEN
                0239           CALL READ_REC_XY_RL(STREAMICEvShearTimeDepFile,
0fbff46b46 dngo*0240      &                        streamice_v_shear_stress1,
056c9f12b0 Dani*0241      &                        nm1,myIter,myThid)
                0242          ENDIF
                0243 
                0244 #endif
2a16ced2f5 Dani*0245 #ifdef ALLOW_STREAMICE_FLUX_CONTROL
                0246 
                0247          DO bj=myByLo(myThid),myByHi(myThid)
                0248           DO bi=myBxLo(myThid),myBxHi(myThid)
                0249            DO j=1,sNy
                0250             DO i=1,sNx
                0251 
                0252              u_flux_bdry_SI_0(i,j,bi,bj) =
                0253      &        u_flux_bdry_SI_1(i,j,bi,bj)
                0254              v_flux_bdry_SI_0(i,j,bi,bj) =
                0255      &        v_flux_bdry_SI_1(i,j,bi,bj)
                0256 
                0257             ENDDO
                0258            ENDDO
                0259           ENDDO
                0260          ENDDO
                0261 
                0262          IF ( STREAMICEuFluxTimeDepFile .NE. ' '  ) THEN
                0263           CALL READ_REC_XY_RL(STREAMICEuFluxTimeDepFile,
                0264      &                        u_flux_bdry_SI_1,
                0265      &                        nm1,myIter,myThid)
                0266          ENDIF
                0267 
                0268          IF ( STREAMICEuFluxTimeDepFile .NE. ' '  ) THEN
                0269           CALL READ_REC_XY_RL(STREAMICEvFluxTimeDepFile,
                0270      &                        v_flux_bdry_SI_1,
                0271      &                        nm1,myIter,myThid)
                0272          ENDIF
                0273 
                0274 #endif
                0275 
056c9f12b0 Dani*0276          DO bj=myByLo(myThid),myByHi(myThid)
                0277           DO bi=myBxLo(myThid),myBxHi(myThid)
                0278            DO j=1,sNy
                0279             DO i=1,sNx
0fbff46b46 dngo*0280              bdot_streamice0(i,j,bi,bj) =
056c9f12b0 Dani*0281      &        bdot_streamice1(i,j,bi,bj)
                0282             ENDDO
                0283            ENDDO
                0284           ENDDO
                0285          ENDDO
                0286 
96b006450c dngo*0287          DO bj=myByLo(myThid),myByHi(myThid)
                0288           DO bi=myBxLo(myThid),myBxHi(myThid)
                0289            DO j=1,sNy
                0290             DO i=1,sNx
                0291              streamice_bdot_maxmelt0(i,j,bi,bj) =
                0292      &        streamice_bdot_maxmelt1(i,j,bi,bj)
                0293             ENDDO
                0294            ENDDO
                0295           ENDDO
                0296          ENDDO
                0297 
                0298          DO bj=myByLo(myThid),myByHi(myThid)
                0299           DO bi=myBxLo(myThid),myBxHi(myThid)
                0300            DO j=1,sNy
                0301             DO i=1,sNx
                0302              streamice_bglen0(i,j,bi,bj) =
                0303      &        streamice_bglen1(i,j,bi,bj)
                0304             ENDDO
                0305            ENDDO
                0306           ENDDO
                0307          ENDDO
                0308 
                0309          DO bj=myByLo(myThid),myByHi(myThid)
                0310           DO bi=myBxLo(myThid),myBxHi(myThid)
                0311            DO j=1,sNy
                0312             DO i=1,sNx
                0313              streamice_beta0(i,j,bi,bj) =
                0314      &        streamice_beta1(i,j,bi,bj)
                0315             ENDDO
                0316            ENDDO
                0317           ENDDO
                0318          ENDDO
                0319 
056c9f12b0 Dani*0320          IF ( STREAMICEBdotTimeDepFile .NE. ' '  ) THEN
                0321           CALL READ_REC_XY_RL(STREAMICEBdotTimeDepFile,
0fbff46b46 dngo*0322      &                        bdot_streamice1,
056c9f12b0 Dani*0323      &                        nm1,myIter,myThid)
                0324          ENDIF
                0325 
96b006450c dngo*0326          IF ( bdotMaxmeltTimeDepFile .NE. ' '  ) THEN
                0327           CALL READ_REC_XY_RL(bdotMaxmeltTimeDepFile,
                0328      &                        streamice_bdot_maxmelt1,
                0329      &                        nm0,myIter,myThid)
                0330          ENDIF
                0331 
                0332          IF ( bglenTimeDepFile .NE. ' '  ) THEN
                0333           CALL READ_REC_XY_RL(bglenTimeDepFile,
                0334      &                        streamice_bglen1,
                0335      &                        nm0,myIter,myThid)
                0336          ENDIF
                0337 
                0338          IF ( cfricTimeDepFile .NE. ' '  ) THEN
                0339           CALL READ_REC_XY_RL(cfricTimeDepFile,
                0340      &                        streamice_beta1,
                0341      &                        nm0,myIter,myThid)
                0342          ENDIF
                0343 
056c9f12b0 Dani*0344 C-      endif 1rst iter.
                0345         ENDIF
                0346 
                0347         DO bj=myByLo(myThid),myByHi(myThid)
                0348          DO bi=myBxLo(myThid),myBxHi(myThid)
                0349           DO j=1,sNy
                0350            DO i=1,sNx
                0351 #ifdef STREAMICE_STRESS_BOUNDARY_CONTROL
0fbff46b46 dngo*0352              streamice_u_normal_stress(i,j,bi,bj) =
056c9f12b0 Dani*0353      &        fac    * streamice_u_normal_stress0(i,j,bi,bj)
                0354      &     + (1-fac) * streamice_u_normal_stress1(i,j,bi,bj)
0fbff46b46 dngo*0355              streamice_v_normal_stress(i,j,bi,bj) =
056c9f12b0 Dani*0356      &        fac    * streamice_v_normal_stress0(i,j,bi,bj)
                0357      &     + (1-fac) * streamice_v_normal_stress1(i,j,bi,bj)
0fbff46b46 dngo*0358              streamice_u_shear_stress(i,j,bi,bj) =
056c9f12b0 Dani*0359      &        fac    * streamice_u_shear_stress0(i,j,bi,bj)
                0360      &     + (1-fac) * streamice_u_shear_stress1(i,j,bi,bj)
0fbff46b46 dngo*0361              streamice_v_shear_stress(i,j,bi,bj) =
056c9f12b0 Dani*0362      &        fac    * streamice_v_shear_stress0(i,j,bi,bj)
                0363      &     + (1-fac) * streamice_v_shear_stress1(i,j,bi,bj)
                0364 #endif
2a16ced2f5 Dani*0365 #ifdef ALLOW_STREAMICE_FLUX_CONTROL
                0366              u_flux_bdry_pert(i,j,bi,bj) =
                0367      &        fac    * u_flux_bdry_SI_0(i,j,bi,bj)
                0368      &     + (1-fac) * u_flux_bdry_SI_1(i,j,bi,bj)
                0369              v_flux_bdry_pert(i,j,bi,bj) =
                0370      &        fac    * v_flux_bdry_SI_0(i,j,bi,bj)
                0371      &     + (1-fac) * v_flux_bdry_SI_1(i,j,bi,bj)
                0372 #endif
0fbff46b46 dngo*0373              bdot_streamice (i,j,bi,bj) =
056c9f12b0 Dani*0374      &        fac    * bdot_streamice0(i,j,bi,bj)
                0375      &     + (1-fac) * bdot_streamice1(i,j,bi,bj)
96b006450c dngo*0376              if (upd_bdot_maxmelt) then
                0377               streamice_bdot_maxmelt_v (i,j,bi,bj) =
                0378      &         fac    * streamice_bdot_maxmelt0(i,j,bi,bj)
                0379      &     +  (1-fac) * streamice_bdot_maxmelt1(i,j,bi,bj)
                0380              endif
                0381              if (upd_bglen) then
                0382               b_glen (i,j,bi,bj) =
                0383      &         fac    * streamice_bglen0(i,j,bi,bj)
                0384      &     +  (1-fac) * streamice_bglen1(i,j,bi,bj)
                0385              endif
                0386              if (upd_cfric) then
                0387               C_basal_friction (i,j,bi,bj) =
                0388      &         fac    * streamice_beta0(i,j,bi,bj)
                0389      &     +  (1-fac) * streamice_beta1(i,j,bi,bj)
                0390              endif
                0391 
056c9f12b0 Dani*0392            ENDDO
                0393           ENDDO
                0394          ENDDO
                0395         ENDDO
                0396 
0fbff46b46 dngo*0397 #ifdef STREAMICE_STRESS_BOUNDARY_CONTROL
                0398       CALL EXCH_XY_RL
c9d61f56d8 Dani*0399      & (streamice_v_shear_stress, myThid)
0fbff46b46 dngo*0400       CALL EXCH_XY_RL
c9d61f56d8 Dani*0401      & (streamice_u_shear_stress, myThid)
0fbff46b46 dngo*0402       CALL EXCH_XY_RL
c9d61f56d8 Dani*0403      & (streamice_v_normal_stress, myThid)
0fbff46b46 dngo*0404       CALL EXCH_XY_RL
c9d61f56d8 Dani*0405      & (streamice_u_normal_stress, myThid)
0fbff46b46 dngo*0406 #endif
c9d61f56d8 Dani*0407 
0fbff46b46 dngo*0408        _EXCH_XY_RL(bdot_streamice, myThid )
96b006450c dngo*0409        _EXCH_XY_RL(streamice_bdot_maxmelt_v, myThid )
                0410        _EXCH_XY_RL(b_glen, myThid )
                0411        _EXCH_XY_RL(C_basal_friction, myThid )
c9d61f56d8 Dani*0412 #ifdef ALLOW_STREAMICE_FLUX_CONTROL
                0413       CALL EXCH_XY_RL
                0414      & (u_flux_bdry_pert, myThid)
                0415       CALL EXCH_XY_RL
                0416      & (v_flux_bdry_pert, myThid)
                0417 #endif
                0418 
96b006450c dngo*0419 c      print *, "GOT HERE STREAMICE FIELDS LOAD",
                0420 c     &  first,changed,nm0,nm1,fac
056c9f12b0 Dani*0421 #endif
                0422 #endif
                0423 
                0424       RETURN
                0425       END