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.
trcrst_pisces.F90 in branches/2011/dev_r2802_TOP_substepping/NEMOGCM/NEMO/TOP_SRC/PISCES – NEMO

source: branches/2011/dev_r2802_TOP_substepping/NEMOGCM/NEMO/TOP_SRC/PISCES/trcrst_pisces.F90 @ 2830

Last change on this file since 2830 was 2830, checked in by kpedwards, 13 years ago

Updates to average physics variables for TOP substepping.

  • Property svn:keywords set to Id
File size: 12.6 KB
Line 
1MODULE trcrst_pisces
2   !!======================================================================
3   !!                       ***  MODULE trcrst_pisces  ***
4   !! TOP :   create, write, read the restart files of PISCES tracer
5   !!======================================================================
6   !! History :   1.0  !  2010-01 (C. Ethe) Original
7   !!----------------------------------------------------------------------
8#if defined key_pisces
9   !!----------------------------------------------------------------------
10   !!   'key_pisces'                                               pisces tracers
11   !!----------------------------------------------------------------------
12   !!   trc_rst_read_pisces   : read  restart file
13   !!   trc_rst_wri_pisces    : write restart file
14   !!----------------------------------------------------------------------
15   USE oce_trc         ! Ocean variables
16   USE par_trc         ! TOP parameters
17   USE trc             ! TOP variables
18   USE trcsms_pisces          ! pisces sms trends
19   USE sms_pisces          ! pisces sms variables
20   USE iom
21   USE trcdta
22
23   IMPLICIT NONE
24   PRIVATE
25
26   PUBLIC  trc_rst_read_pisces   ! called by trcini.F90 module
27   PUBLIC  trc_rst_wri_pisces   ! called by trcini.F90 module
28
29CONTAINS
30   
31   SUBROUTINE trc_rst_read_pisces( knum ) 
32      !!----------------------------------------------------------------------
33      !!                     ***  trc_rst_read_pisces  *** 
34      !!
35      !! ** Purpose : Read in restart file specific variables from pisces model
36      !!
37      !!----------------------------------------------------------------------
38      INTEGER, INTENT(in)  :: knum  ! unit of the restart file
39      INTEGER  ::  ji, jj, jk
40      REAL(wp) ::  zcaralk, zbicarb, zco3
41      REAL(wp) ::  ztmas, ztmas1
42      !!----------------------------------------------------------------------
43
44      !
45      IF( lk_dtatrc .AND. ln_pisclo ) CALL pis_dmp_clo  ! restoring of nutrients on close seas
46      IF( ln_pisdmp )                 CALL pis_dmp_ini  ! relaxation of some tracers
47      !
48      IF(lwp) WRITE(numout,*)
49      IF(lwp) WRITE(numout,*) ' trc_rst_read_pisces : Read specific variables from pisces model '
50      IF(lwp) WRITE(numout,*) ' ~~~~~~~~~~~~~~'
51      !
52      IF( iom_varid( knum, 'PH', ldstop = .FALSE. ) > 0 ) THEN
53         CALL iom_get( knum, jpdom_autoglo, 'PH' , hi(:,:,:)  )
54      ELSE
55         ! Set PH from  total alkalinity, borat (???), akb3 (???) and ak23 (???)
56         ! --------------------------------------------------------
57         DO jk = 1, jpk
58            DO jj = 1, jpj
59               DO ji = 1, jpi
60                  ztmas   = tmask(ji,jj,jk)
61                  ztmas1  = 1. - tmask(ji,jj,jk)
62                  zcaralk = trn(ji,jj,jk,jptal) - borat(ji,jj,jk) / (  1. + 1.E-8 / ( rtrn + akb3(ji,jj,jk) )  )
63                  zco3    = ( zcaralk - trn(ji,jj,jk,jpdic) ) * ztmas + 0.5e-3 * ztmas1
64                  zbicarb = ( 2. * trn(ji,jj,jk,jpdic) - zcaralk )
65                  hi(ji,jj,jk) = ( ak23(ji,jj,jk) * zbicarb / zco3 ) * ztmas + 1.e-9 * ztmas1
66               END DO
67            END DO
68         END DO
69      ENDIF
70      CALL iom_get( knum, jpdom_autoglo, 'Silicalim', xksi(:,:) ) 
71      IF( iom_varid( knum, 'Silicamax', ldstop = .FALSE. ) > 0 ) THEN
72         CALL iom_get( knum, jpdom_autoglo, 'Silicamax' , xksimax(:,:)  )
73      ELSE
74         xksimax(:,:) = xksi(:,:)
75      ENDIF
76
77   END SUBROUTINE trc_rst_read_pisces
78
79   SUBROUTINE trc_rst_wri_pisces( kt, kitrst, knum )
80      !!----------------------------------------------------------------------
81      !!                     ***  trc_rst_read_pisces  ***
82      !!
83      !! ** Purpose : Read in restart file specific variables from pisces model
84      !!
85      !!----------------------------------------------------------------------
86      INTEGER, INTENT(in)  :: kt      ! time step
87      INTEGER, INTENT(in)  :: kitrst  ! time step of restart write
88      INTEGER, INTENT(in)  :: knum    ! unit of the restart file
89      !!----------------------------------------------------------------------
90
91      IF(lwp) WRITE(numout,*)
92      IF(lwp) WRITE(numout,*) ' trc_rst_wri_pisces : Write specific variables from pisces model '
93      IF(lwp) WRITE(numout,*) ' ~~~~~~~~~~~~~~'
94
95      CALL iom_rstput( kt, kitrst, knum, 'PH', hi(:,:,:) )
96      CALL iom_rstput( kt, kitrst, knum, 'Silicalim', xksi(:,:) ) 
97      CALL iom_rstput( kt, kitrst, knum, 'Silicamax', xksimax(:,:) )
98
99   END SUBROUTINE trc_rst_wri_pisces
100
101   SUBROUTINE pis_dmp_ini
102      !!----------------------------------------------------------------------
103      !!                    ***  pis_dmp_ini  ***
104      !!
105      !! ** purpose  : Relaxation of some tracers
106      !!----------------------------------------------------------------------
107      REAL(wp) ::  alkmean = 2426.     ! mean value of alkalinity ( Glodap ; for Goyet 2391. )
108      REAL(wp) ::  po4mean = 2.165     ! mean value of phosphates
109      REAL(wp) ::  no3mean = 30.90     ! mean value of nitrate
110      REAL(wp) ::  silmean = 91.51     ! mean value of silicate
111
112      REAL(wp) :: zarea, zalksum, zpo4sum, zno3sum, zsilsum
113
114
115      IF(lwp)  WRITE(numout,*)
116
117      IF( cp_cfg == "orca" .AND. .NOT. lk_c1d ) THEN      ! ORCA condiguration (not 1D) !
118         !                                                    ! --------------------------- !
119         ! set total alkalinity, phosphate, nitrate & silicate
120
121         zarea   = 1. / areatot * 1.e6
122# if defined key_degrad
123         zalksum = glob_sum( trn(:,:,:,jptal) * cvol(:,:,:) * facvol(:,:,:) ) * zarea
124         zpo4sum = glob_sum( trn(:,:,:,jppo4) * cvol(:,:,:) * facvol(:,:,:) ) * zarea / 122.
125         zno3sum = glob_sum( trn(:,:,:,jpno3) * cvol(:,:,:) * facvol(:,:,:) ) * zarea / 7.6
126         zsilsum = glob_sum( trn(:,:,:,jpsil) * cvol(:,:,:) * facvol(:,:,:) ) * zarea
127# else
128         zalksum = glob_sum( trn(:,:,:,jptal) * cvol(:,:,:)  ) * zarea
129         zpo4sum = glob_sum( trn(:,:,:,jppo4) * cvol(:,:,:)  ) * zarea / 122.
130         zno3sum = glob_sum( trn(:,:,:,jpno3) * cvol(:,:,:)  ) * zarea / 7.6
131         zsilsum = glob_sum( trn(:,:,:,jpsil) * cvol(:,:,:)  ) * zarea
132# endif
133
134         IF(lwp) WRITE(numout,*) '       TALK mean : ', zalksum
135         trn(:,:,:,jptal) = trn(:,:,:,jptal) * alkmean / zalksum
136           
137         IF(lwp) WRITE(numout,*) '       PO4  mean : ', zpo4sum
138         trn(:,:,:,jppo4) = trn(:,:,:,jppo4) * po4mean / zpo4sum
139
140         IF(lwp) WRITE(numout,*) '       NO3  mean : ', zno3sum
141         trn(:,:,:,jpno3) = trn(:,:,:,jpno3) * no3mean / zno3sum
142
143         IF(lwp) WRITE(numout,*) '       SiO3 mean : ', zsilsum
144         trn(:,:,:,jpsil) = MIN( 400.e-6,trn(:,:,:,jpsil) * silmean / zsilsum )
145         !
146      ENDIF
147
148!#if defined key_kriest
149!     !! Initialize number of particles from a standart restart file
150!     !! The name of big organic particles jpgoc has been only change
151!     !! and replace by jpnum but the values here are concentration
152!     trn(:,:,:,jppoc) = trn(:,:,:,jppoc) + trn(:,:,:,jpnum)
153!     trn(:,:,:,jpnum) = trn(:,:,:,jppoc) / ( 6. * xkr_massp )
154!#endif
155
156   END SUBROUTINE pis_dmp_ini
157
158   SUBROUTINE pis_dmp_clo   
159      !!---------------------------------------------------------------------
160      !!                  ***  ROUTINE pis_dmp_clo  ***
161      !!
162      !! ** Purpose :   Closed sea domain initialization
163      !!
164      !! ** Method  :   if a closed sea is located only in a model grid point
165      !!                we restore to initial data
166      !!
167      !! ** Action  :   ictsi1(), ictsj1() : south-west closed sea limits (i,j)
168      !!                ictsi2(), ictsj2() : north-east Closed sea limits (i,j)
169      !!----------------------------------------------------------------------
170      INTEGER, PARAMETER           ::   npicts   = 4       !: number of closed sea
171      INTEGER, DIMENSION(npicts)   ::   ictsi1, ictsj1     !: south-west closed sea limits (i,j)
172      INTEGER, DIMENSION(npicts)   ::   ictsi2, ictsj2     !: north-east closed sea limits (i,j)
173      INTEGER :: ji, jj, jk, jn, jc            ! dummy loop indices
174      !!----------------------------------------------------------------------
175
176      IF(lwp) WRITE(numout,*) 
177      IF(lwp) WRITE(numout,*)' pis_dmp_clo : closed seas '
178      IF(lwp) WRITE(numout,*)'~~~~~~~'
179
180      ! initial values
181      ictsi1(:) = 1  ;  ictsi2(:) = 1
182      ictsj1(:) = 1  ;  ictsj2(:) = 1
183
184      ! set the closed seas (in data domain indices)
185      ! -------------------
186
187      IF( cp_cfg == "orca" ) THEN
188         !
189         SELECT CASE ( jp_cfg )
190         !                                           ! =======================
191         CASE ( 2 )                                  !  ORCA_R2 configuration
192            !                                        ! =======================
193            !                                            ! Caspian Sea
194            ictsi1(1)   =  11  ;  ictsj1(1)   = 103
195            ictsi2(1)   =  17  ;  ictsj2(1)   = 112
196            !                                            ! Great North American Lakes
197            ictsi1(2)   =  97  ;  ictsj1(2)   = 107
198            ictsi2(2)   = 103  ;  ictsj2(2)   = 111
199            !                                            ! Black Sea 1 : west part of the Black Sea
200            ictsi1(3)   = 174  ; ictsj1(3)   = 107
201            ictsi2(3)   = 181  ; ictsj2(3)   = 112
202            !                                            ! Black Sea 2 : est part of the Black Sea
203            ictsi1(4)   =   2  ;  ictsj1(4)   = 107
204            ictsi2(4)   =   6  ;  ictsj2(4)   = 112
205            !                                        ! =======================
206         CASE ( 4 )                                  !  ORCA_R4 configuration
207            !                                        ! =======================
208            !                                            ! Caspian Sea
209            ictsi1(1)   =  4  ;  ictsj1(1)   = 53
210            ictsi2(1)   =  4  ;  ictsj2(1)   = 56
211            !                                            ! Great North American Lakes
212            ictsi1(2)   = 49  ;  ictsj1(2)   = 55
213            ictsi2(2)   = 51  ;  ictsj2(2)   = 56
214            !                                            ! Black Sea
215            ictsi1(3)   = 88  ;  ictsj1(3)   = 55
216            ictsi2(3)   = 91  ;  ictsj2(3)   = 56
217            !                                            ! Baltic Sea
218            ictsi1(4)   = 75  ;  ictsj1(4)   = 59
219            ictsi2(4)   = 76  ;  ictsj2(4)   = 61
220            !                                        ! =======================
221            !                                        ! =======================
222         CASE ( 025 )                                ! ORCA_R025 configuration
223            !                                        ! =======================
224                                                     ! Caspian + Aral sea
225            ictsi1(1)   = 1330 ; ictsj1(1)   = 645
226            ictsi2(1)   = 1400 ; ictsj2(1)   = 795
227            !                                        ! Azov Sea
228            ictsi1(2)   = 1284 ; ictsj1(2)   = 722
229            ictsi2(2)   = 1304 ; ictsj2(2)   = 747
230            !
231         END SELECT
232         !
233      ENDIF
234
235      ! convert the position in local domain indices
236      ! --------------------------------------------
237      DO jc = 1, npicts
238         ictsi1(jc)   = mi0( ictsi1(jc) )
239         ictsj1(jc)   = mj0( ictsj1(jc) )
240
241         ictsi2(jc)   = mi1( ictsi2(jc) )
242         ictsj2(jc)   = mj1( ictsj2(jc) )
243      END DO
244
245#if defined key_dtatrc
246      ! Restore close seas values to initial data
247      CALL trc_dta( nittrc000 ) 
248      DO jn = 1, jptra
249         IF( lutini(jn) ) THEN
250            DO jc = 1, npicts
251               DO jk = 1, jpkm1
252                  DO jj = ictsj1(jc), ictsj2(jc)
253                     DO ji = ictsi1(jc), ictsi2(jc)
254                        trn(ji,jj,jk,jn) = trdta(ji,jj,jk,jn) * tmask(ji,jj,jk) 
255                        trb(ji,jj,jk,jn) = trn(ji,jj,jk,jn)
256                     ENDDO
257                  ENDDO
258               ENDDO
259            ENDDO
260         ENDIF
261      ENDDO
262#endif
263   !
264   END SUBROUTINE pis_dmp_clo
265
266#else
267   !!----------------------------------------------------------------------
268   !!  Dummy module :                                     No passive tracer
269   !!----------------------------------------------------------------------
270CONTAINS
271   SUBROUTINE trc_rst_read_pisces( knum )
272      INTEGER, INTENT(in)  :: knum
273      WRITE(*,*) 'trc_rst_read_pisces: You should not have seen this print! error?', knum
274   END SUBROUTINE trc_rst_read_pisces
275
276   SUBROUTINE trc_rst_wri_pisces( kt, kitrst, knum )
277     INTEGER, INTENT(in)  :: kt, kitrst, knum
278     WRITE(*,*) 'trc_rst_wri_pisces: You should not have seen this print! error?', kt, kitrst, knum
279   END SUBROUTINE trc_rst_wri_pisces
280#endif
281
282   !!======================================================================
283END MODULE trcrst_pisces
Note: See TracBrowser for help on using the repository browser.