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.
types.f90 in branches/UKMO/dev_r5518_new_runoff_coupling/NEMOGCM/TOOLS/GRIDGEN/src – NEMO

source: branches/UKMO/dev_r5518_new_runoff_coupling/NEMOGCM/TOOLS/GRIDGEN/src/types.f90 @ 8163

Last change on this file since 8163 was 8163, checked in by dancopsey, 7 years ago

Clear out SVN keywords.

File size: 6.5 KB
Line 
1MODULE types
2  !
3  PUBLIC
4  !   
5  !*****************************
6  ! Coordinates type definition
7  !*****************************
8  TYPE coordinates
9     REAL*8, DIMENSION(:,:), POINTER  :: nav_lon,nav_lat              => NULL()
10     REAL*8, DIMENSION(:,:), POINTER  :: glamv, glamu, glamt, glamf   => NULL()
11     REAL*8, DIMENSION(:,:), POINTER  :: gphit, gphiu, gphiv, gphif   => NULL()
12     REAL*8, DIMENSION(:,:), POINTER  :: e1t, e1u, e1v, e1f           => NULL()
13     REAL*8, DIMENSION(:,:), POINTER  :: e2t, e2u, e2v, e2f           => NULL()
14     INTEGER, DIMENSION(:) , POINTER  :: time_steps                   => NULL()
15  END TYPE coordinates
16  !
17  !
18  !
19  TYPE mixed_coordinates
20     REAL*8, DIMENSION(:,:), POINTER  :: nav_lon,nav_lat              => NULL()
21     REAL*8, DIMENSION(:,:), POINTER  :: glam                         => NULL()
22     REAL*8, DIMENSION(:,:), POINTER  :: gphi                         => NULL()
23     REAL*8, DIMENSION(:,:), POINTER  :: e1                           => NULL()
24     REAL*8, DIMENSION(:,:), POINTER  :: e2                           => NULL()
25     INTEGER, DIMENSION(:) , POINTER  :: time_steps                   => NULL()
26  END TYPE mixed_coordinates
27  !
28  !**************************************************************
29  ! Declaration of global variables
30  !**************************************************************
31  !size of input ORCA grid
32  INTEGER :: nsizex, nsizey   
33  INTEGER :: nmid           
34  !
35  !kind of input grid
36  INTEGER :: npivot 
37  !
38  INTEGER :: nequator
39  !
40  LOGICAL :: nglobal
41  !
42  INTEGER :: nresx, nresy
43  !
44  !distance between middle of input grid and the border of sub-domain
45  INTEGER :: nval1, nval2
46  !
47  INTEGER :: nxcoag, nycoag     !size of the sub-domain inside input ORCA grid
48  INTEGER :: nxgmix, nygmix     !size of the mixed grid
49  INTEGER :: nxfine, nyfine     !size of fine grid
50  !
51  TYPE(coordinates), SAVE :: scoagrd         !coarse grid
52  TYPE(coordinates), SAVE :: sfingrd         !fine grid
53  TYPE(mixed_coordinates), SAVE :: smixgrd   !mixed grid to store all components (T,U,V,F)
54  !                                           of the coarse grid in the same one
55  !
56  !
57  !
58  !**************************************************************
59  ! Declaration of various input file variables (namelist.input)
60  !**************************************************************
61  INTEGER nn_imin,nn_jmin,nn_imax,nn_jmax,nn_rhox,nn_rhoy
62  LOGICAL ln_iom_activated
63  CHARACTER*100 cn_parent_coordinate_file, cn_position_pivot
64  !     
65  NAMELIST /input_output/ln_iom_activated
66  NAMELIST /coarse_grid_files/cn_parent_coordinate_file,cn_position_pivot
67  NAMELIST /nesting/nn_imin,nn_jmin,nn_imax,nn_jmax,nn_rhox,nn_rhoy     
68  !
69  !
70  !
71CONTAINS
72  !********************************************************
73  !             subroutine grid_allocate           *
74  !                                                *
75  !         allocation of grid type elements          *
76  !             according to nx and ny             *
77  !                                                 *
78  !********************************************************
79  SUBROUTINE grid_allocate(Grid,nx,ny)
80    !
81    TYPE(coordinates) :: Grid
82    INTEGER :: nx,ny
83    !
84    ALLOCATE(Grid%nav_lon(nx,ny),Grid%nav_lat(nx,ny))
85    ALLOCATE(Grid%glamt(nx,ny),Grid%glamu(nx,ny),Grid%glamv(nx,ny),Grid%glamf(nx,ny))
86    ALLOCATE(Grid%gphit(nx,ny),Grid%gphiu(nx,ny),Grid%gphiv(nx,ny),Grid%gphif(nx,ny))
87    ALLOCATE(Grid%e1t(nx,ny),Grid%e1u(nx,ny),Grid%e1v(nx,ny),Grid%e1f(nx,ny))
88    ALLOCATE(Grid%e2t(nx,ny),Grid%e2u(nx,ny),Grid%e2v(nx,ny),Grid%e2f(nx,ny))
89   !
90  END SUBROUTINE grid_allocate
91  !
92  !
93  !
94  SUBROUTINE grid_deallocate(Grid)
95    !
96    TYPE(coordinates) :: Grid
97    !
98    DEALLOCATE(Grid%nav_lon,Grid%nav_lat)
99    DEALLOCATE(Grid%glamt,Grid%glamu,Grid%glamv,Grid%glamf)
100    DEALLOCATE(Grid%gphit,Grid%gphiu,Grid%gphiv,Grid%gphif)
101    DEALLOCATE(Grid%e1t,Grid%e1u,Grid%e1v,Grid%e1f)
102    DEALLOCATE(Grid%e2t,Grid%e2u,Grid%e2v,Grid%e2f)
103   !
104  END SUBROUTINE grid_deallocate
105  !
106  !
107  !
108  !********************************************************
109  !           subroutine mixed_grid_allocate       *
110  !                                                 *
111  !          allocation of grid type elements         *
112  !               according to nx and ny           *
113  !                                                *
114  !********************************************************
115  SUBROUTINE mixed_grid_allocate(Grid,nx,ny)
116    !
117    TYPE(mixed_coordinates) :: Grid
118    INTEGER :: nx,ny
119    !
120    ALLOCATE(Grid%nav_lon(nx,ny),Grid%nav_lat(nx,ny))
121    ALLOCATE(Grid%glam(nx,ny))
122    ALLOCATE(Grid%gphi(nx,ny))
123    ALLOCATE(Grid%e1(nx,ny))
124    ALLOCATE(Grid%e2(nx,ny))
125   !
126  END SUBROUTINE mixed_grid_allocate
127  !
128  !
129  !
130  SUBROUTINE mixed_grid_deallocate(Grid)
131    !
132    TYPE(mixed_coordinates) :: Grid
133    !
134    DEALLOCATE(Grid%nav_lon,Grid%nav_lat)
135    DEALLOCATE(Grid%glam)
136    DEALLOCATE(Grid%gphi)
137    DEALLOCATE(Grid%e1)
138    DEALLOCATE(Grid%e2)
139   !
140  END SUBROUTINE mixed_grid_deallocate
141  !
142  !
143  !
144  !********************************************************
145  !             subroutine read_namelist           *
146  !                                                *
147  !   read variables contained in namelist.input file   *
148  !                filled in by user               *
149  !                                             *
150  !********************************************************
151  SUBROUTINE read_namelist(namelistname)
152    !
153    IMPLICIT NONE
154    CHARACTER(len=80) :: namelistname
155    CHARACTER*255 :: output
156    LOGICAL :: is_it_there
157    INTEGER unit_nml
158    !
159    unit_nml = Get_Unit()
160    !     
161    INQUIRE ( FILE = namelistname , EXIST = is_it_there )     
162    !
163    IF ( is_it_there ) THEN 
164       !
165       OPEN ( FILE   =  namelistname, &
166              UNIT   =  unit_nml,     &
167              STATUS = 'OLD',      &
168              FORM   = 'FORMATTED',   &
169              ACTION = 'READ',        &
170              ACCESS = 'SEQUENTIAL'     )   
171       !
172       REWIND(unit_nml)
173       READ (unit_nml , NML = coarse_grid_files)
174       READ (unit_nml , NML = nesting) 
175       CLOSE(unit_nml)
176      !
177    ELSE
178       !
179       PRINT *,'namelist file ''',TRIM(namelistname),''' not found'
180       STOP 
181       !
182    END IF
183    !
184  END SUBROUTINE read_namelist
185  !
186  !
187  !
188  !*************************************************
189  !              function Get_Unit                             
190  !*************************************************
191  INTEGER FUNCTION Get_Unit()
192    !
193    INTEGER n
194    LOGICAL op
195    INTEGER :: nunit
196    INTEGER :: iii,out,iiimax 
197    !
198    DO n = 7,1000
199       !
200       INQUIRE(Unit=n,Opened=op)
201       !
202       IF (.NOT.op) EXIT
203       !     
204    ENDDO
205    !
206    Get_Unit=n
207    !
208  END FUNCTION Get_Unit
209  !
210END MODULE types
Note: See TracBrowser for help on using the repository browser.