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.
dtasal_fdir.h90 in trunk/NEMO/OPA_SRC/DTA – NEMO

source: trunk/NEMO/OPA_SRC/DTA/dtasal_fdir.h90 @ 3

Last change on this file since 3 was 3, checked in by opalod, 20 years ago

Initial revision

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 5.8 KB
Line 
1   !!----------------------------------------------------------------------
2   !!                   ***  dtasal_fdir  ***
3   !!----------------------------------------------------------------------
4   !!   dta_sal   : read monthly salinity data in direct access file
5   !!----------------------------------------------------------------------
6   !!   OPA 9.0 , LODYC-IPSL  (2003)
7   !!----------------------------------------------------------------------
8
9   SUBROUTINE dta_sal( kt )
10      !!----------------------------------------------------------------------
11      !!                   ***  ROUTINE dta_sal  ***
12      !!                   
13      !! ** Purpose :   Reads monthly salinity data
14      !!                             
15      !! ** Method  :   Direct acces file case
16      !!     Read on unit numsdt the interpolated Levitus salinity onto
17      !!     the global grid.
18      !!     The value is centered at the middle of month.
19      !!     At each time step, a linear interpolation is applied between
20      !!     two monthly values.
21      !!
22      !! History :
23      !!        !  91-03  ()  Original code
24      !!        !  92-07  (M. Imbard)
25      !!   8.5  !  02-06  (G. Madec)  F90: Free form and module
26      !!----------------------------------------------------------------------
27      !! * Arguments
28      INTEGER, INTENT(in) ::   kt             ! ocean time step
29
30      !! * Local declarations
31      INTEGER ,PARAMETER :: jpmois= 12   &  ! number on month in file
32            &              ,jpf   = 1       ! number of fields
33      INTEGER :: ji,jj,jk,jl,ios, ik
34      INTEGER :: imois,iman
35      INTEGER :: iimlu,ijmlu,ikmlu,ilmlu,immlu
36      INTEGER :: i15, ibloc, ilindta
37      REAL(wp) ::  zxy, zl
38      CHARACTER (len=20) ::   cltit
39      !!----------------------------------------------------------------------
40
41
42      ! 0. Initialization
43      ! -----------------
44
45      iman  = jpmois
46      i15 = nday/16
47
48      imois = nmonth + i15 - 1
49      IF( imois == 0 ) imois = iman
50
51
52      ! 1. First call kt=nit000
53      ! -----------------------
54
55      IF( kt == nit000 .AND. nlecsa == 0 ) THEN
56         ! open sal.dta file
57         ibloc = 4096
58         ilindta = ibloc*((jpidta*jpjdta*jpbytda-1 )/ibloc+1)
59         CALL ctlopn(numsdt,'data_1m_salinity_nomask','OLD', 'UNFORMATTED', 'DIRECT',   &
60                     ilindta,numout,lwp,1)
61         nsal1 = 0
62         IF(lwp) THEN
63            WRITE(numout,*)
64            WRITE(numout,*) 'dta_sal : read monthly salinity in direct acces file in unit= ', numsdt
65            WRITE(numout,*) '~~~~~~~ '
66            WRITE(numout,*)
67         ENDIF
68
69         ! 1.2 Read first records
70         
71         ! title, dimensions and tests
72
73         READ (numsdt,REC=1,IOSTAT=ios) cltit, iimlu, ijmlu, ikmlu,   &
74                                        ilmlu, immlu
75         IF( ios /= 0 ) THEN
76            IF(lwp) WRITE(numout,*) 'e r r o r read numsdt ',ios
77            STOP 'dtasal'
78         ELSE
79            IF ( iimlu /= jpidta ) STOP 4050
80            IF ( ijmlu /= jpjdta ) STOP 4060
81            IF ( ikmlu /= jpk    ) STOP 4070
82            IF ( ilmlu /= jpmois ) STOP 4080
83            IF ( immlu /= jpf    ) STOP 4090
84            IF(lwp) WRITE(numout,*) 'nb of points in the 5 directions '
85            IF(lwp) WRITE(numout,*) iimlu, ijmlu, ikmlu, ilmlu, immlu
86         ENDIF
87
88      ENDIF
89
90
91      ! 2. Read monthly file
92      ! -------------------
93
94      IF( ( kt == nit000 .AND. nlecsa == 0 ) .OR. imois /= nsal1 ) THEN
95         nlecsa = 1
96
97         ! 2.1 Calendar computation
98
99         nsal1 = imois        ! first file record used
100         nsal2 = nsal1 + 1    ! last  file record used
101         nsal1 = MOD( nsal1, iman )
102         IF( nsal1 == 0 ) nsal1 = iman
103         nsal2 = MOD( nsal2, iman )
104         IF( nsal2 == 0 ) nsal2 = iman
105         IF(lwp) WRITE(numout,*) 'first record file used nsal1 ', nsal1
106         IF(lwp) WRITE(numout,*) 'last  record file used nsal2 ', nsal2
107
108         ! 2.3 Read monthly salinity data Levitus
109
110         CALL read3d(numsdt,saldta(1,1,1,1),nsal1+1)
111         CALL read3d(numsdt,saldta(1,1,1,2),nsal2+1)
112         
113         IF(lwp) THEN
114            WRITE(numout,*)
115            WRITE(numout,*) ' read Levitus salinity ok'
116            WRITE(numout,*)
117         ENDIF
118
119         ! 2.4 Masks
120
121         DO jl = 1, 2
122            saldta(:,:,:,jl) = saldta(:,:,:,jl)*tmask(:,:,:)
123            saldta(:,:,jpk,jl) = 0.
124            IF( lk_zps ) THEN                   ! z-coordinate with partial steps
125               DO jj = 1, jpj                           ! interpolation of salinity at the last ocean level (i.e. the partial step)
126                  DO ji = 1, jpi
127                     ik = mbathy(ji,jj) - 1
128                     IF( ik > 2 ) THEN
129                        zl = ( gdept(ik) - fsdept(ji,jj,ik) ) / ( gdept(ik) - gdept(ik-1) )
130                        saldta(ji,jj,ik,jl) = (1.-zl) * saldta(ji,jj,ik,jl) +zl * saldta(ji,jj,ik-1,jl)
131                     ENDIF
132                  END DO
133               END DO
134            ENDIF
135         END DO
136
137         IF(lwp) THEN
138            WRITE(numout,*)' salinity Levitus month ',nsal1,nsal2
139            WRITE(numout,*)
140            WRITE(numout,*) ' Levitus mounth = ',nsal1,'  level = 1'
141            CALL prihre(saldta(1,1,1,1),jpi,jpj,1,jpi,20,1,jpj,20,1.,numout)
142            WRITE(numout,*) ' Levitus mounth = ',nsal1,'  level = ',jpk/2
143            CALL prihre(saldta(1,1,jpk/2,1),jpi,jpj,1,jpi,20,1,jpj,20,1.,numout)
144            WRITE(numout,*) ' Levitus mounth = ',nsal1,'  level = ',jpkm1
145            CALL prihre(saldta(1,1,jpkm1,1),jpi,jpj,1,jpi,20,1,jpj,20,1.,numout)
146         ENDIF
147      ENDIF
148
149
150      ! 3. At every time step compute salinity data
151      ! ----------------------------------------------
152
153      zxy = FLOAT(nday + 15 - 30*i15)/30.
154      sdta(:,:,:)= ( (1.-zxy)*saldta(:,:,:,1) + zxy*saldta(:,:,:,2) )
155
156   END SUBROUTINE dta_sal
Note: See TracBrowser for help on using the repository browser.