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/2015/dev_merge_2015/NEMOGCM/NEMO/OPA_SRC/C1D – NEMO

source: branches/2015/dev_merge_2015/NEMOGCM/NEMO/OPA_SRC/C1D/domc1d.F90 @ 6060

Last change on this file since 6060 was 6060, checked in by timgraham, 8 years ago

Merged dev_r5836_noc2_VVL_BY_DEFAULT into branch

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