New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
limhdf.F90 in branches/UKMO/dev_r5785_SSS_obsoper/NEMOGCM/NEMO/LIM_SRC_3 – NEMO

source: branches/UKMO/dev_r5785_SSS_obsoper/NEMOGCM/NEMO/LIM_SRC_3/limhdf.F90 @ 7773

Last change on this file since 7773 was 7773, checked in by mattmartin, 7 years ago

Committing updates after doing the following:

  • merging the branch dev_r4650_general_vert_coord_obsoper@7763 into this branch
  • updating it so that the following OBS changes were implemented correctly on top of the simplification changes:
    • generalised vertical coordinate for profile obs. This was done so that is now the default option.
    • sst bias correction implemented with the new simplified obs code.
    • included the biogeochemical obs types int he new simplified obs code.
    • included the changes to exclude obs in the boundary for limited area models
    • included other changes for the efficiency of the obs operator to remove global arrays.
File size: 10.2 KB
RevLine 
[825]1MODULE limhdf
2   !!======================================================================
3   !!                    ***  MODULE limhdf   ***
4   !! LIM ice model : horizontal diffusion of sea-ice quantities
5   !!======================================================================
[2715]6   !! History :  LIM  !  2000-01 (LIM) Original code
7   !!             -   !  2001-05 (G. Madec, R. Hordoir) opa norm
8   !!            1.0  !  2002-08 (C. Ethe)  F90, free form
9   !!----------------------------------------------------------------------
[825]10#if defined key_lim3
11   !!----------------------------------------------------------------------
[834]12   !!   'key_lim3'                                      LIM3 sea-ice model
[825]13   !!----------------------------------------------------------------------
[3625]14   !!   lim_hdf       : diffusion trend on sea-ice variable
[5682]15   !!   lim_hdf_init  : initialisation of diffusion trend on sea-ice variable
[825]16   !!----------------------------------------------------------------------
[3625]17   USE dom_oce        ! ocean domain
18   USE ice            ! LIM-3: ice variables
19   USE lbclnk         ! lateral boundary condition - MPP exchanges
20   USE lib_mpp        ! MPP library
21   USE wrk_nemo       ! work arrays
22   USE prtctl         ! Print control
23   USE in_out_manager ! I/O manager
24   USE lib_fortran    ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined) 
[825]25
26   IMPLICIT NONE
27   PRIVATE
28
[5682]29   PUBLIC   lim_hdf         ! called by lim_trp
30   PUBLIC   lim_hdf_init    ! called by sbc_lim_init
[825]31
[5682]32   LOGICAL  ::   linit = .TRUE.                             ! initialization flag (set to flase after the 1st call)
33   INTEGER  ::   nn_convfrq                                 !:  convergence check frequency of the Crant-Nicholson scheme
[2715]34   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::   efact   ! metric coefficient
[825]35
36   !! * Substitution
37#  include "vectopt_loop_substitute.h90"
38   !!----------------------------------------------------------------------
[4161]39   !! NEMO/LIM3 4.0 , UCL - NEMO Consortium (2010)
[1156]40   !! $Id$
[2715]41   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
[825]42   !!----------------------------------------------------------------------
43CONTAINS
44
45   SUBROUTINE lim_hdf( ptab )
46      !!-------------------------------------------------------------------
47      !!                  ***  ROUTINE lim_hdf  ***
48      !!
[2715]49      !! ** purpose :   Compute and add the diffusive trend on sea-ice variables
[825]50      !!
51      !! ** method  :   Second order diffusive operator evaluated using a
[2715]52      !!              Cranck-Nicholson time Scheme.
[825]53      !!
54      !! ** Action  :    update ptab with the diffusive contribution
55      !!-------------------------------------------------------------------
[2715]56      REAL(wp), DIMENSION(jpi,jpj), INTENT( inout ) ::   ptab    ! Field on which the diffusion is applied
57      !
[5682]58      INTEGER                           ::  ji, jj                    ! dummy loop indices
59      INTEGER                           ::  iter, ierr           ! local integers
60      REAL(wp)                          ::  zrlxint, zconv     ! local scalars
61      REAL(wp), POINTER, DIMENSION(:,:) ::  zrlx, zflu, zflv, zdiv0, zdiv, ztab0
62      CHARACTER(lc)                     ::  charout                   ! local character
63      REAL(wp), PARAMETER               ::  zrelax = 0.5_wp           ! relaxation constant for iterative procedure
64      REAL(wp), PARAMETER               ::  zalfa  = 0.5_wp           ! =1.0/0.5/0.0 = implicit/Cranck-Nicholson/explicit
65      INTEGER , PARAMETER               ::  its    = 100              ! Maximum number of iteration
[825]66      !!-------------------------------------------------------------------
[2715]67     
[3294]68      CALL wrk_alloc( jpi, jpj, zrlx, zflu, zflv, zdiv0, zdiv, ztab0 )
[825]69
[2715]70      !                       !==  Initialisation  ==!
71      !
72      IF( linit ) THEN              ! Metric coefficient (compute at the first call and saved in efact)
73         ALLOCATE( efact(jpi,jpj) , STAT=ierr )
74         IF( lk_mpp    )   CALL mpp_sum( ierr )
75         IF( ierr /= 0 )   CALL ctl_stop( 'STOP', 'lim_hdf : unable to allocate arrays' )
[825]76         DO jj = 2, jpjm1 
77            DO ji = fs_2 , fs_jpim1   ! vector opt.
[5682]78               efact(ji,jj) = ( e2u(ji,jj) + e2u(ji-1,jj) + e1v(ji,jj) + e1v(ji,jj-1) ) * r1_e12t(ji,jj)
[825]79            END DO
80         END DO
81         linit = .FALSE.
82      ENDIF
[2715]83      !                             ! Time integration parameters
84      !
85      ztab0(:, : ) = ptab(:,:)      ! Arrays initialization
86      zdiv0(:, 1 ) = 0._wp
87      zdiv0(:,jpj) = 0._wp
[4990]88      zflu (jpi,:) = 0._wp   
89      zflv (jpi,:) = 0._wp
90      zdiv0(1,  :) = 0._wp
91      zdiv0(jpi,:) = 0._wp
[825]92
[2715]93      zconv = 1._wp           !==  horizontal diffusion using a Crant-Nicholson scheme  ==!
[825]94      iter  = 0
[2715]95      !
[5682]96      DO WHILE( zconv > ( 2._wp * 1.e-04 ) .AND. iter <= its )   ! Sub-time step loop
[2715]97         !
98         iter = iter + 1                                 ! incrementation of the sub-time step number
99         !
100         DO jj = 1, jpjm1                                ! diffusive fluxes in U- and V- direction
[825]101            DO ji = 1 , fs_jpim1   ! vector opt.
[5682]102               zflu(ji,jj) = pahu(ji,jj) * e2u(ji,jj) * r1_e1u(ji,jj) * ( ptab(ji+1,jj) - ptab(ji,jj) )
103               zflv(ji,jj) = pahv(ji,jj) * e1v(ji,jj) * r1_e2v(ji,jj) * ( ptab(ji,jj+1) - ptab(ji,jj) )
[825]104            END DO
105         END DO
[2715]106         !
107         DO jj= 2, jpjm1                                 ! diffusive trend : divergence of the fluxes
[825]108            DO ji = fs_2 , fs_jpim1   ! vector opt.
[5682]109               zdiv(ji,jj) = ( zflu(ji,jj) - zflu(ji-1,jj) + zflv(ji,jj) - zflv(ji,jj-1) ) * r1_e12t(ji,jj)
[825]110            END DO
111         END DO
[2715]112         !
113         IF( iter == 1 )   zdiv0(:,:) = zdiv(:,:)        ! save the 1st evaluation of the diffusive trend in zdiv0
114         !
115         DO jj = 2, jpjm1                                ! iterative evaluation
[825]116            DO ji = fs_2 , fs_jpim1   ! vector opt.
[2715]117               zrlxint = (   ztab0(ji,jj)    &
118                  &       +  rdt_ice * (           zalfa   * ( zdiv(ji,jj) + efact(ji,jj) * ptab(ji,jj) )   &
[5682]119                  &                      + ( 1.0 - zalfa ) *   zdiv0(ji,jj) )                               & 
120                  &      ) / ( 1.0 + zalfa * rdt_ice * efact(ji,jj) )
121               zrlx(ji,jj) = ptab(ji,jj) + zrelax * ( zrlxint - ptab(ji,jj) )
[825]122            END DO
123         END DO
[2715]124         CALL lbc_lnk( zrlx, 'T', 1. )                   ! lateral boundary condition
125         !
[5682]126         IF ( MOD( iter, nn_convfrq ) == 0 )  THEN    ! convergence test every nn_convfrq iterations (perf. optimization)
127            zconv = 0._wp
128            DO jj = 2, jpjm1
129               DO ji = fs_2, fs_jpim1
130                  zconv = MAX( zconv, ABS( zrlx(ji,jj) - ptab(ji,jj) )  )
131               END DO
[825]132            END DO
[5682]133            IF( lk_mpp )   CALL mpp_max( zconv )      ! max over the global domain
134         ENDIF
[2715]135         !
136         ptab(:,:) = zrlx(:,:)
137         !
[825]138      END DO                                       ! end of sub-time step loop
139
[4161]140      ! -----------------------
141      !!! final step (clem) !!!
142      DO jj = 1, jpjm1                                ! diffusive fluxes in U- and V- direction
143         DO ji = 1 , fs_jpim1   ! vector opt.
[5682]144            zflu(ji,jj) = pahu(ji,jj) * e2u(ji,jj) * r1_e1u(ji,jj) * ( ptab(ji+1,jj) - ptab(ji,jj) )
145            zflv(ji,jj) = pahv(ji,jj) * e1v(ji,jj) * r1_e2v(ji,jj) * ( ptab(ji,jj+1) - ptab(ji,jj) )
[4161]146         END DO
147      END DO
148      !
149      DO jj= 2, jpjm1                                 ! diffusive trend : divergence of the fluxes
150         DO ji = fs_2 , fs_jpim1   ! vector opt.
[5682]151            zdiv(ji,jj) = ( zflu(ji,jj) - zflu(ji-1,jj) + zflv(ji,jj) - zflv(ji,jj-1) ) * r1_e12t(ji,jj)
[4161]152            ptab(ji,jj) = ztab0(ji,jj) + 0.5 * ( zdiv(ji,jj) + zdiv0(ji,jj) )
153         END DO
154      END DO
155      CALL lbc_lnk( ptab, 'T', 1. )                   ! lateral boundary condition
156      !!! final step (clem) !!!
157      ! -----------------------
158
[825]159      IF(ln_ctl)   THEN
[2715]160         zrlx(:,:) = ptab(:,:) - ztab0(:,:)
[825]161         WRITE(charout,FMT="(' lim_hdf  : zconv =',D23.16, ' iter =',I4,2X)") zconv, iter
[2715]162         CALL prt_ctl( tab2d_1=zrlx, clinfo1=charout )
[825]163      ENDIF
[2715]164      !
[3294]165      CALL wrk_dealloc( jpi, jpj, zrlx, zflu, zflv, zdiv0, zdiv, ztab0 )
[2715]166      !
[825]167   END SUBROUTINE lim_hdf
168
[5682]169   
170   SUBROUTINE lim_hdf_init
171      !!-------------------------------------------------------------------
172      !!                  ***  ROUTINE lim_hdf_init  ***
173      !!
174      !! ** Purpose : Initialisation of horizontal diffusion of sea-ice
175      !!
176      !! ** Method  : Read the namicehdf namelist
177      !!
178      !! ** input   : Namelist namicehdf
179      !!-------------------------------------------------------------------
180      INTEGER  ::   ios                 ! Local integer output status for namelist read
181      NAMELIST/namicehdf/ nn_convfrq
182      !!-------------------------------------------------------------------
183      !
184      IF(lwp) THEN
185         WRITE(numout,*)
186         WRITE(numout,*) 'lim_hdf : Ice horizontal diffusion'
187         WRITE(numout,*) '~~~~~~~'
188      ENDIF
189      !
190      REWIND( numnam_ice_ref )              ! Namelist namicehdf in reference namelist : Ice horizontal diffusion
191      READ  ( numnam_ice_ref, namicehdf, IOSTAT = ios, ERR = 901)
192901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namicehdf in reference namelist', lwp )
193
194      REWIND( numnam_ice_cfg )              ! Namelist namicehdf in configuration namelist : Ice horizontal diffusion
195      READ  ( numnam_ice_cfg, namicehdf, IOSTAT = ios, ERR = 902 )
196902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namicehdf in configuration namelist', lwp )
197      IF(lwm) WRITE ( numoni, namicehdf )
198      !
199      IF(lwp) THEN                          ! control print
200         WRITE(numout,*)
201         WRITE(numout,*)'   Namelist of ice parameters for ice horizontal diffusion computation '
202         WRITE(numout,*)'      convergence check frequency of the Crant-Nicholson scheme   nn_convfrq   = ', nn_convfrq
203      ENDIF
204      !
205   END SUBROUTINE lim_hdf_init
[825]206#else
207   !!----------------------------------------------------------------------
208   !!   Default option          Dummy module           NO LIM sea-ice model
209   !!----------------------------------------------------------------------
210#endif
211
212   !!======================================================================
213END MODULE limhdf
Note: See TracBrowser for help on using the repository browser.