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.
domc1d.F90 in branches/2017/dev_merge_2017/NEMOGCM/NEMO/OPA_SRC/C1D – NEMO

source: branches/2017/dev_merge_2017/NEMOGCM/NEMO/OPA_SRC/C1D/domc1d.F90 @ 9124

Last change on this file since 9124 was 9124, checked in by gm, 6 years ago

dev_merge_2017: ln_timing instead of nn_timing + restricted timing to nemo_init and routine called by step in OPA_SRC

  • Property svn:keywords set to Id
File size: 9.6 KB
Line 
1MODULE domc1d
2   !!======================================================================
3   !!                     ***  MODULE  domc1d  ***
4   !! Ocean Domain : 1D column position from lat/lon namelist specification
5   !!======================================================================
6   !! History :  3.5  !  2013-04  (D. Calvert)  Original code
7   !!----------------------------------------------------------------------
8#if defined key_c1d
9   !!----------------------------------------------------------------------
10   !!   'key_c1d'   :                                      1D Configuration
11   !!----------------------------------------------------------------------
12   !!   dom_c1d     : Determine jpizoom/jpjzoom from a given lat/lon
13   !!----------------------------------------------------------------------
14   USE phycst         ! Physical constants (and par_oce)
15   USE dom_oce , ONLY : nimpp, njmpp ! Shared/distributed memory setting
16   !
17   USE iom            ! I/O library (iom_get)
18   USE in_out_manager ! I/O manager (ctmp1)
19   USE wrk_nemo                      ! Memory allocation
20
21   IMPLICIT NONE
22   PRIVATE
23
24   PUBLIC   dom_c1d   ! called in domcfg.F90
25
26   INTEGER ::   jpizoom = 1      !: left bottom (i,j) indices of the zoom
27   INTEGER ::   jpjzoom = 1      !: in data domain indices
28
29   !!----------------------------------------------------------------------
30   !! NEMO/OPA 3.7 , NEMO Consortium (2015)
31   !! $Id$
32   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
33   !!----------------------------------------------------------------------
34CONTAINS
35   
36   SUBROUTINE dom_c1d( plat, plon )
37      !!----------------------------------------------------------------------
38      !!                   ***  ROUTINE dom_c1d  ***
39      !!
40      !! ** Purpose : Recalculate jpizoom/jpjzoom indices from lat/lon point
41      !!
42      !! ** Method  : Calculate global gphit and glamt as for dom_hgr.
43      !!              After, find closest grid point to lat/lon point as for
44      !!              dom_ngb on T grid. From this infer jpizoom and jpjzoom.
45      !!
46      !! ** Action  : Recalculate jpizoom, jpjzoom (indices of C1D zoom)
47      !!----------------------------------------------------------------------
48      REAL(wp), INTENT(in) ::  plat, plon    ! Column latitude &  longitude
49      !
50      INTEGER  ::  ji, jj   ! Dummy loop indices
51      INTEGER  ::  inum     ! Coordinate file handle (case 0)
52      INTEGER  ::  ijeq     ! Index of equator T point (case 4)
53      INTEGER  ::  ios      ! Local integer output status for namelist read
54      INTEGER , DIMENSION(2) ::   iloc   ! Minloc returned indices
55      REAL(wp) ::  zlon                            ! Wraparound longitude
56      REAL(wp) ::  zti, ztj, zarg                  ! Local scalars
57      REAL(wp) ::  glam0, gphi0                    ! Variables corresponding to parameters ppglam0 ppgphi0 set in par_oce
58      REAL(wp) ::  zlam1, zcos_alpha, ze1, ze1deg  ! Case 5 local scalars
59      REAL(wp) ::  zphi1, zsin_alpha, zim05, zjm05 !         
60      REAL(wp) , POINTER, DIMENSION(:,:) ::  gphidta, glamdta, zdist ! Global lat/lon
61      !!
62      NAMELIST/namdom/ nn_bathy, rn_bathy , rn_e3zps_min, rn_e3zps_rat, nn_msh, rn_hmin,   &
63         &             rn_atfp     , rn_rdt      ,nn_closea , ln_crs,  jphgr_msh, &
64         &             ppglam0, ppgphi0, ppe1_deg, ppe2_deg, ppe1_m, ppe2_m, &
65         &             ppsur, ppa0, ppa1, ppkth, ppacr, ppdzmin, pphmax, ldbletanh, &
66         &             ppa2, ppkth2, ppacr2
67      !!----------------------------------------------------------------------
68
69      REWIND( numnam_ref )              ! Namelist namdom in reference namelist : space & time domain (bathymetry, mesh, timestep)
70      READ  ( numnam_ref, namdom, IOSTAT = ios, ERR = 901 )
71901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namdom in reference namelist', lwp )
72      !
73      REWIND( numnam_cfg )              ! Namelist namdom in configuration namelist : space & time domain (bathymetry, mesh, timestep)
74      READ  ( numnam_cfg, namdom, IOSTAT = ios, ERR = 902 )
75902   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namdom in configuration namelist', lwp )
76
77      CALL wrk_alloc( jpidta,jpjdta,   gphidta, glamdta, zdist )
78
79      ! ============================= !
80      !  Code from dom_hgr:           !
81      !  Calculate global horizontal  !
82      !  mesh, only glamt and gphit   !
83      ! ============================= !
84      !
85      SELECT CASE( jphgr_msh )   ! type of horizontal mesh
86      !
87      CASE ( 0 )                 !  curvilinear coordinate on the sphere read in coordinate.nc file
88         !
89         CALL iom_open( 'coordinates', inum )
90         CALL iom_get( inum, jpdom_unknown, 'glamt', glamdta ) ! mig, mjg undefined at this point
91         CALL iom_get( inum, jpdom_unknown, 'gphit', gphidta ) ! so use jpdom_unknown not jpdom_data
92         CALL iom_close ( inum )
93         !
94      CASE ( 1 )                 ! geographical mesh on the sphere with regular grid-spacing
95         !
96         DO jj = 1, jpjdta
97            DO ji = 1, jpidta
98               zti = FLOAT( ji - 1 + nimpp - 1 )
99               ztj = FLOAT( jj - 1 + njmpp - 1 )
100               !
101               glamdta(ji,jj) = ppglam0 + ppe1_deg * zti
102               gphidta(ji,jj) = ppgphi0 + ppe2_deg * ztj
103            END DO
104         END DO
105         !
106      CASE ( 2:3 )               ! f- or beta-plane with regular grid-spacing
107         !
108         glam0 = 0.e0
109         gphi0 = - ppe2_m * 1.e-3
110         !
111         DO jj = 1, jpjdta
112            DO ji = 1, jpidta
113               glamdta(ji,jj) = glam0 + ppe1_m * 1.e-3 * FLOAT( ji - 1 + nimpp - 1 )
114               gphidta(ji,jj) = gphi0 + ppe2_m * 1.e-3 * FLOAT( jj - 1 + njmpp - 1 )
115            END DO
116         END DO
117         !
118      CASE ( 4 )                 ! geographical mesh on the sphere, isotropic MERCATOR type
119         !
120         IF( ppgphi0 == -90 )   CALL ctl_stop( ' Mercator grid cannot start at south pole !!!! ' )
121         !
122         zarg = rpi / 4. - rpi / 180. * ppgphi0 / 2.
123         ijeq = ABS( 180. / rpi * LOG( COS( zarg ) / SIN( zarg ) ) / ppe1_deg )
124         IF( ppgphi0 > 0 )   ijeq = -ijeq
125         !
126         DO jj = 1, jpjdta
127            DO ji = 1, jpidta
128               zti = FLOAT( ji - 1    + nimpp - 1 )
129               ztj = FLOAT( jj - ijeq + njmpp - 1 )
130               !
131               glamdta(ji,jj) = ppglam0 + ppe1_deg * zti
132               gphidta(ji,jj) = 1. / rad * ASIN ( TANH( ppe1_deg * rad * ztj ) )
133            END DO
134         END DO
135         !
136      CASE ( 5 )                 ! beta-plane with regular grid-spacing and rotated domain (GYRE configuration)
137         !
138         zlam1 = -85
139         zphi1 = 29
140         ze1 = 106000. / REAL( nn_cfg , wp )
141         !
142         zsin_alpha = - SQRT( 2. ) / 2.
143         zcos_alpha =   SQRT( 2. ) / 2.
144         ze1deg = ze1 / (ra * rad)
145         !
146         glam0 = zlam1 + zcos_alpha * ze1deg * FLOAT( jpjdta-2 ) ! Force global
147         gphi0 = zphi1 + zsin_alpha * ze1deg * FLOAT( jpjdta-2 )
148         !
149         DO jj = 1, jpjdta
150            DO ji = 1, jpidta
151               zim05 = FLOAT( ji + nimpp - 1 ) - 1.5
152               zjm05 = FLOAT( jj + njmpp - 1 ) - 1.5
153
154               glamdta(ji,jj) = glam0 + zim05 * ze1deg * zcos_alpha + zjm05 * ze1deg * zsin_alpha
155               gphidta(ji,jj) = gphi0 - zim05 * ze1deg * zsin_alpha + zjm05 * ze1deg * zcos_alpha
156            END DO
157         END DO
158         !
159      CASE DEFAULT
160         !
161         WRITE(ctmp1,*) '          bad flag value for jphgr_msh = ', jphgr_msh
162         CALL ctl_stop( ctmp1 )
163         !
164      END SELECT
165
166      ! ============================== !
167      !  Code from dom_ngb:            !
168      !  Calculate the nearest grid    !
169      !  point to the given lat/lon &  !
170      !  update jpizoom and jpjzoom    !
171      ! ============================== !
172
173      zlon         = MOD( plon         + 720., 360. )                                      ! plon    between    0 and 360
174      glamdta(:,:) = MOD( glamdta(:,:) + 720., 360. )                                      ! glamdta between    0 and 360
175      IF( zlon > 270. )   zlon = zlon - 360.                                               ! zlon    between  -90 and 270
176      IF( zlon <  90. )   WHERE( glamdta(:,:) > 180. ) glamdta(:,:) = glamdta(:,:) - 360.  ! glamdta between -180 and 180
177
178      glamdta(:,:) = glamdta(:,:) - zlon
179      gphidta(:,:) = gphidta(:,:) - plat
180      zdist(:,:)   = glamdta(:,:) * glamdta(:,:) + gphidta(:,:) * gphidta(:,:)
181     
182      iloc(:) = MINLOC( zdist(:,:) ) ! No mask; zoom indices freely defined
183      jpizoom = iloc(1) + nimpp - 2  ! Minloc index - 1; want the bottom-left
184      jpjzoom = iloc(2) + njmpp - 2  ! corner index of the zoom domain.
185
186      CALL wrk_dealloc( jpidta,jpjdta,   gphidta, glamdta, zdist )
187
188      IF (lwp) THEN
189         WRITE(numout,*)
190         WRITE(numout,*) 'dom_c1d : compute jpizoom & jpjzoom from global mesh and given coordinates'
191         WRITE(numout,*) '~~~~~~~'
192         WRITE(numout,*) '      column i zoom index             jpizoom = ', jpizoom
193         WRITE(numout,*) '      column j zoom index             jpjzoom = ', jpjzoom
194         WRITE(numout,*)
195      ENDIF
196      !
197   END SUBROUTINE dom_c1d
198
199#else
200   !!----------------------------------------------------------------------
201   !!   Default option                                  NO 1D Configuration
202   !!----------------------------------------------------------------------
203CONTAINS 
204   SUBROUTINE dom_c1d( plat, plon )     ! Empty routine
205      REAL :: plat, plon
206      WRITE(*,*) 'dom_c1d: You should not have seen this print! error?',plat,plon
207   END SUBROUTINE dom_c1d
208#endif
209
210   !!======================================================================
211END MODULE domc1d
Note: See TracBrowser for help on using the repository browser.