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.
agrif_types.f90 in utils/tools/NESTING/src – NEMO

source: utils/tools/NESTING/src/agrif_types.f90 @ 9694

Last change on this file since 9694 was 9694, checked in by clem, 6 years ago

change the nesting tools to choose the number of points copied from mother to child grids in the namelist (npt_copy) and change the name of nb_connection_pts to npt_connect

  • Property svn:keywords set to Id
File size: 7.1 KB
RevLine 
[2136]1!************************************************************************
2! Fortran 95 OPA Nesting tools                  *
3!                          *
4!     Copyright (C) 2005 Florian Lemarié (Florian.Lemarie@imag.fr)   *
5!                          *
6!************************************************************************
7!     
8MODULE agrif_types
9  !
10  PUBLIC
11  !   
12  !*****************************
13  ! Coordinates type definition
14  !*****************************
15  TYPE Coordinates
16     !
17     REAL*8, DIMENSION(:,:), POINTER :: nav_lon,nav_lat => NULL()
18     REAL*8, DIMENSION(:,:), POINTER :: glamv, glamu, glamt, glamf => NULL()
19     REAL*8, DIMENSION(:,:), POINTER :: gphit, gphiu, gphiv, gphif => NULL()
20     REAL*8, DIMENSION(:,:), POINTER :: e1t, e1u, e1v, e1f => NULL()
21     REAL*8, DIMENSION(:,:), POINTER :: e2t, e2u, e2v, e2f => NULL()
22     REAL*8, DIMENSION(:,:), POINTER :: bathy_level => NULL()
23     REAL*8, DIMENSION(:,:), POINTER :: bathy_meter => NULL()
[9628]24     REAL*8, DIMENSION(:,:), POINTER :: wgt => NULL()
[2136]25     REAL*8, DIMENSION(:,:,:),POINTER :: fmask,umask,vmask,tmask => NULL()
26     REAL*8, DIMENSION(:,:,:),POINTER :: e3t_ps,e3w_ps,gdept_ps,gdepwps => NULL()
27     REAL*8, DIMENSION(:,:),POINTER :: gdepw_ps => NULL()
28     REAL*8, DIMENSION(:), POINTER :: gdeptht => NULL()
29     INTEGER, DIMENSION(:) , POINTER :: time_steps => NULL()
30     !     
31  END TYPE Coordinates
32  !
33  !
34  !
35  CHARACTER*8,DIMENSION(10) :: flxtab = (/'socliot1','socliot2','socliopl',&
36       'socliocl','socliohu','socliowi','soshfldo','sohefldo','sowaflup','sofbt   '/)
37  !
38  !
39  !**************************************************************
40  ! Declaration of various input file variables (namelist.input)
41  !**************************************************************
42  !
43  INTEGER irafx,irafy
44  INTEGER nxfin,nyfin
[9166]45  INTEGER, PARAMETER :: nbghostcellsfine = 1 
[2136]46  INTEGER, PARAMETER :: nbghostcellscoarse = 1
47  !     
48  INTEGER imin,jmin,imax,jmax,rho,rhot
49  INTEGER shlat
50  INTEGER N,type_bathy_interp
51  !
[9694]52  INTEGER jpizoom,jpjzoom,npt_connect,npt_copy
[2136]53  !     
[5656]54  REAL*8 rn_hmin
55  REAL*8 ppkth2, ppacr2, ppkth,ppacr,ppdzmin,pphmax,smoothing_factor,e3zps_min,e3zps_rat
56  REAL*8 psur,pa0,pa1,pa2,adatrj
[2136]57  !       
[9149]58  LOGICAL ldbletanh,ln_e3_dep
[2136]59  LOGICAL partial_steps,smoothing,bathy_update
60  LOGICAL new_topo,removeclosedseas,dimg,iom_activated
61  !       
[2455]62  CHARACTER*100 parent_meshmask_file,elevation_database,parent_bathy_meter
63  CHARACTER*100 elevation_name,parent_batmet_name
[2136]64  CHARACTER*100 parent_coordinate_file,restart_file,updated_parent_file,restart_trc_file
65  CHARACTER*100 dimg_output_file,interp_type
66  !     
67  CHARACTER(len=80),DIMENSION(20) :: flx_Files, u_files, v_files
68  CHARACTER(len=255),DIMENSION(20) :: VAR_INTERP
69  !
70  NAMELIST /input_output/iom_activated
71  !
[2455]72  NAMELIST /coarse_grid_files/parent_coordinate_file,parent_meshmask_file
[2136]73  !     
[2455]74  NAMELIST /bathymetry/new_topo,elevation_database,elevation_name,smoothing,smoothing_factor, &
[9694]75       npt_connect,npt_copy,removeclosedseas,type_bathy_interp,rn_hmin     
[2136]76  !     
77  NAMELIST /nesting/imin,imax,jmin,jmax,rho,rhot,bathy_update,updated_parent_file     
78  !
[9149]79  NAMELIST /vertical_grid/ppkth,ppacr,ppdzmin,pphmax,psur,pa0,pa1,N,ldbletanh,ln_e3_dep,pa2,ppkth2,ppacr2
[2136]80  !
[2455]81  NAMELIST /partial_cells/partial_steps,parent_bathy_meter,parent_batmet_name,e3zps_min,e3zps_rat     
[2136]82  !
83  NAMELIST /nemo_coarse_grid/ jpizoom,jpjzoom 
84  !         
85  NAMELIST /forcing_files/ flx_files, u_files, v_files 
86  !           
87  NAMELIST /interp/ VAR_INTERP
88  !     
89  NAMELIST /restart/ restart_file,shlat,dimg,dimg_output_file,adatrj,interp_type 
90
91  NAMELIST /restart_trc/ restart_trc_file,interp_type 
92  !
93CONTAINS
94  !
95  !********************************************************
96  !subroutine agrif_grid_allocate            *
97  !                     *
98  !allocation of grid type elements          *
99  !      according to nx and ny           *
100  !                     *
101  !                     *
102  !********************************************************
103  !       
104  SUBROUTINE agrif_grid_allocate(Grid,nx,ny)
105    !
106    TYPE(Coordinates) :: Grid
107    INTEGER :: nx,ny
108    !
109    ALLOCATE(Grid%nav_lon(nx,ny),Grid%nav_lat(nx,ny))
110    !
111    ALLOCATE(Grid%glamt(nx,ny),Grid%glamu(nx,ny),Grid%glamv(nx,ny),Grid%glamf(nx,ny))
112    ALLOCATE(Grid%gphit(nx,ny),Grid%gphiu(nx,ny),Grid%gphiv(nx,ny),Grid%gphif(nx,ny))
113    !
114    ALLOCATE(Grid%e1t(nx,ny),Grid%e1u(nx,ny),Grid%e1v(nx,ny),Grid%e1f(nx,ny))
115    ALLOCATE(Grid%e2t(nx,ny),Grid%e2u(nx,ny),Grid%e2v(nx,ny),Grid%e2f(nx,ny))
116    !
117    ALLOCATE(Grid%bathy_level(nx,ny))
118    !
119  END SUBROUTINE agrif_grid_allocate
120  !
121  !
122  !************************************************************************
123  !                           *
124  !   subroutine read_namelist                  *
125  !                           *
126  !   read variables contained in namelist.input file          *
127  !   filled in by user                      *
128  !                           *
129  !************************************************************************
130  !
131  SUBROUTINE read_namelist(namelistname)
132    !
133    IMPLICIT NONE
134    CHARACTER(len=80) :: namelistname
135    CHARACTER*255 :: output
136    LOGICAL :: is_it_there
137    INTEGER unit_nml
138    !     
139    FLX_FILES = '/NULL'
140    U_FILES = '/NULL'
141    V_FILES = '/NULL'
142    VAR_INTERP = 'NULL'
143    unit_nml = Agrif_Get_Unit()
144    !     
145    INQUIRE ( FILE = namelistname , EXIST = is_it_there )     
146    !
147    IF ( is_it_there ) THEN 
148       !
149       OPEN ( FILE   = namelistname , &
150            UNIT   =  unit_nml        , &
151            STATUS = 'OLD'            , &
152            FORM   = 'FORMATTED'      , &
153            ACTION = 'READ'           , &
[9694]154            ACCESS = 'SEQUENTIAL'     )
[2136]155       !
156       REWIND(unit_nml)
157       READ (unit_nml , NML = input_output)
158       READ (unit_nml , NML = coarse_grid_files)
[9694]159       READ (unit_nml , NML = bathymetry)
[2136]160       READ (unit_nml , NML = nesting) 
161       READ (unit_nml , NML = vertical_grid)
162       READ (unit_nml , NML = partial_cells)                   
163       READ (unit_nml , NML = nemo_coarse_grid ) 
164       READ (unit_nml , NML = forcing_files ) 
165       READ (unit_nml , NML = interp )   
166       READ (unit_nml , NML = restart )
167       READ (unit_nml , NML = restart_trc )
168       CLOSE(unit_nml)
169       !
170       irafx = rho
171       irafy = rho
172       imin = imin + jpizoom - 1
173       imax = imax + jpizoom - 1
174       jmin = jmin + jpjzoom - 1
175       jmax = jmax + jpjzoom - 1
176       !
[9166]177       nxfin = (imax-imin)*irafx+2*nbghostcellsfine+2
178       nyfin = (jmax-jmin)*irafy+2*nbghostcellsfine+2
[2136]179       !
180    ELSE
181       !
182       PRINT *,'namelist file ''',TRIM(namelistname),''' not found'
183       STOP 
184       !
185    END IF
186    !
187    !
188  END SUBROUTINE read_namelist
189
190  INTEGER FUNCTION agrif_int(x)
191
192    REAL :: x
193    INTEGER ::i
194
195    i = FLOOR(x) + 1
196
197    IF( ABS(x - i).LE.0.0001 )THEN
198       agrif_int = i
199    ELSE
200       agrif_int = i-1
201    ENDIF
202
203  END FUNCTION agrif_int
204  !
205  !*************************************************
206  !   function Agrif_Get_Unit                             
207  !*************************************************
208  !
209
210  INTEGER FUNCTION Agrif_Get_Unit()
211    !
212    INTEGER n
213    LOGICAL op
214    INTEGER :: nunit
215    INTEGER :: iii,out,iiimax 
216    !
217    DO n = 7,1000
218       !
219       INQUIRE(Unit=n,Opened=op)
220       !
221       IF (.NOT.op) EXIT
222       !     
223    ENDDO
224    !
225    Agrif_Get_Unit=n
226    !
227    !
228  END FUNCTION Agrif_Get_Unit
229  !
230END MODULE agrif_types
Note: See TracBrowser for help on using the repository browser.