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/2012/dev_v3_4_STABLE_2012/NEMOGCM/NEMO/TOP_SRC/PISCES – NEMO

source: branches/2012/dev_v3_4_STABLE_2012/NEMOGCM/NEMO/TOP_SRC/PISCES/trcrst_pisces.F90 @ 3881

Last change on this file since 3881 was 3881, checked in by cetlod, 11 years ago

v3_4_stable: fix on passive tracer damping, see ticket #1083

  • Property svn:keywords set to Id
File size: 5.0 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(lwp) WRITE(numout,*)
46      IF(lwp) WRITE(numout,*) ' trc_rst_read_pisces : Read specific variables from pisces model '
47      IF(lwp) WRITE(numout,*) ' ~~~~~~~~~~~~~~'
48      !
49      IF( iom_varid( knum, 'PH', ldstop = .FALSE. ) > 0 ) THEN
50         CALL iom_get( knum, jpdom_autoglo, 'PH' , hi(:,:,:)  )
51      ELSE
52!         hi(:,:,:) = 1.e-9
53         ! Set PH from  total alkalinity, borat (???), akb3 (???) and ak23 (???)
54         ! --------------------------------------------------------
55         DO jk = 1, jpk
56            DO jj = 1, jpj
57               DO ji = 1, jpi
58                  ztmas   = tmask(ji,jj,jk)
59                  ztmas1  = 1. - tmask(ji,jj,jk)
60                  zcaralk = trn(ji,jj,jk,jptal) - borat(ji,jj,jk) / (  1. + 1.E-8 / ( rtrn + akb3(ji,jj,jk) )  )
61                  zco3    = ( zcaralk - trn(ji,jj,jk,jpdic) ) * ztmas + 0.5e-3 * ztmas1
62                  zbicarb = ( 2. * trn(ji,jj,jk,jpdic) - zcaralk )
63                 hi(ji,jj,jk) = ( ak23(ji,jj,jk) * zbicarb / zco3 ) * ztmas + 1.e-9 * ztmas1
64               END DO
65            END DO
66         END DO
67      ENDIF
68      CALL iom_get( knum, jpdom_autoglo, 'Silicalim', xksi(:,:) ) 
69      IF( iom_varid( knum, 'Silicamax', ldstop = .FALSE. ) > 0 ) THEN
70         CALL iom_get( knum, jpdom_autoglo, 'Silicamax' , xksimax(:,:)  )
71      ELSE
72         xksimax(:,:) = xksi(:,:)
73      ENDIF
74
75   END SUBROUTINE trc_rst_read_pisces
76
77   SUBROUTINE trc_rst_wri_pisces( kt, kitrst, knum )
78      !!----------------------------------------------------------------------
79      !!                     ***  trc_rst_read_pisces  ***
80      !!
81      !! ** Purpose : Read in restart file specific variables from pisces model
82      !!
83      !!----------------------------------------------------------------------
84      INTEGER, INTENT(in)  :: kt      ! time step
85      INTEGER, INTENT(in)  :: kitrst  ! time step of restart write
86      INTEGER, INTENT(in)  :: knum    ! unit of the restart file
87      !!----------------------------------------------------------------------
88
89      IF(lwp) WRITE(numout,*)
90      IF(lwp) WRITE(numout,*) ' trc_rst_wri_pisces : Write specific variables from pisces model '
91      IF(lwp) WRITE(numout,*) ' ~~~~~~~~~~~~~~'
92
93      CALL iom_rstput( kt, kitrst, knum, 'PH', hi(:,:,:) )
94      CALL iom_rstput( kt, kitrst, knum, 'Silicalim', xksi(:,:) ) 
95      CALL iom_rstput( kt, kitrst, knum, 'Silicamax', xksimax(:,:) )
96
97   END SUBROUTINE trc_rst_wri_pisces
98
99
100#else
101   !!----------------------------------------------------------------------
102   !!  Dummy module :                                     No passive tracer
103   !!----------------------------------------------------------------------
104CONTAINS
105   SUBROUTINE trc_rst_read_pisces( knum )
106      INTEGER, INTENT(in)  :: knum
107      WRITE(*,*) 'trc_rst_read_pisces: You should not have seen this print! error?', knum
108   END SUBROUTINE trc_rst_read_pisces
109
110   SUBROUTINE trc_rst_wri_pisces( kt, kitrst, knum )
111     INTEGER, INTENT(in)  :: kt, kitrst, knum
112     WRITE(*,*) 'trc_rst_wri_pisces: You should not have seen this print! error?', kt, kitrst, knum
113   END SUBROUTINE trc_rst_wri_pisces
114#endif
115
116   !!======================================================================
117END MODULE trcrst_pisces
Note: See TracBrowser for help on using the repository browser.