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 branches/DEV_r1879_FCM/NEMOGCM/TOOLS/NESTING/src – NEMO

source: branches/DEV_r1879_FCM/NEMOGCM/TOOLS/NESTING/src/agrif_types.f90 @ 2143

Last change on this file since 2143 was 2143, checked in by rblod, 14 years ago

Improvement of FCM branch

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