SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
read_grid.F90
Go to the documentation of this file.
1 !SFX_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier
2 !SFX_LIC This is part of the SURFEX software governed by the CeCILL-C licence
3 !SFX_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
4 !SFX_LIC for details. version 1.
5 ! #########
6  SUBROUTINE read_grid (&
7  hprogram,hgrid,pgrid_par,plat,plon,pmesh_size,kresp,pdir)
8 ! #########################################
9 !
10 !!**** *READ_GRID* - routine to initialise the horizontal grid of a scheme
11 !!
12 !! PURPOSE
13 !! -------
14 !!
15 !!** METHOD
16 !! ------
17 !!
18 !! EXTERNAL
19 !! --------
20 !!
21 !!
22 !! IMPLICIT ARGUMENTS
23 !! ------------------
24 !!
25 !! REFERENCE
26 !! ---------
27 !!
28 !!
29 !! AUTHOR
30 !! ------
31 !! V. Masson *Meteo France*
32 !!
33 !! MODIFICATIONS
34 !! -------------
35 !! Original 01/2003
36 !-------------------------------------------------------------------------------
37 !
38 !* 0. DECLARATIONS
39 ! ------------
40 !
41 !
42 !
43 !
44 USE modi_get_luout
46 USE modi_latlon_grid
47 USE modi_read_gridtype
48 !
49 USE modd_assim, ONLY : lread_all, lassim
50 !
51 USE yomhook ,ONLY : lhook, dr_hook
52 USE parkind1 ,ONLY : jprb
53 !
54 IMPLICIT NONE
55 !
56 !* 0.1 Declarations of arguments
57 ! -------------------------
58 !
59 !
60 !
61  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! calling program
62  CHARACTER(LEN=10), INTENT(OUT) :: hgrid ! type of horizontal grid
63 REAL, DIMENSION(:), POINTER :: pgrid_par ! parameters defining this grid
64 REAL, DIMENSION(:), INTENT(OUT) :: plat ! latitude (degrees)
65 REAL, DIMENSION(:), INTENT(OUT) :: plon ! longitude (degrees)
66 REAL, DIMENSION(:), INTENT(OUT) :: pmesh_size ! horizontal mesh size (m2)
67 INTEGER, INTENT(OUT) :: kresp ! error return code
68 REAL, DIMENSION(:), INTENT(OUT), OPTIONAL :: pdir ! heading of main axis of grid compared to North (degrees)
69 !
70 !* 0.2 Declarations of local variables
71 ! -------------------------------
72 !
73 LOGICAL :: gread_all
74 INTEGER :: igrid_par
75 INTEGER :: iluout
76 REAL(KIND=JPRB) :: zhook_handle
77 !---------------------------------------------------------------------------
78 !
79 !* 1. Reading of type of grid
80 ! -----------------------
81 !
82 IF (lhook) CALL dr_hook('READ_GRID',0,zhook_handle)
83 !
84 IF (lassim) THEN
85  gread_all = lread_all
86  lread_all = .true.
87 ENDIF
88 !
89  CALL read_surf(&
90  hprogram,'GRID_TYPE',hgrid,kresp)
91 !
92 !---------------------------------------------------------------------------
93 !
94 !* 2. Reading parameters of the grid
95 ! ------------------------------
96 !
97  CALL read_gridtype(&
98  hprogram,hgrid,igrid_par,SIZE(plat),.false.)
99 !
100 ALLOCATE(pgrid_par(igrid_par))
101  CALL read_gridtype(&
102  hprogram,hgrid,igrid_par,SIZE(plat),.true.,pgrid_par,kresp)
103 !
104 !---------------------------------------------------------------------------
105 !
106 !* 3. Latitude, longitude, mesh size
107 ! ------------------------------
108 !
109  CALL get_luout(hprogram,iluout)
110 !
111 SELECT CASE (hgrid)
112  CASE("NONE ")
113  IF (present(pdir)) pdir(:) = 0.
114  !
115  CALL read_surf(&
116  hprogram,'LON', plon,kresp)
117  IF (kresp/=0 .AND. lhook) CALL dr_hook('READ_GRID',1,zhook_handle)
118  IF (kresp/=0) RETURN
119  CALL read_surf(&
120  hprogram,'LAT', plat,kresp)
121  IF (kresp/=0 .AND. lhook) CALL dr_hook('READ_GRID',1,zhook_handle)
122  IF (kresp/=0) RETURN
123  CALL read_surf(&
124  hprogram,'MESH_SIZE',pmesh_size,kresp)
125  IF (kresp/=0 .AND. lhook) CALL dr_hook('READ_GRID',1,zhook_handle)
126  IF (kresp/=0) RETURN
127 
128  CASE default
129  IF (present(pdir)) THEN
130  CALL latlon_grid(hgrid,SIZE(pgrid_par),SIZE(plat),iluout,pgrid_par,plat,plon,pmesh_size,pdir)
131  ELSE
132  CALL latlon_grid(hgrid,SIZE(pgrid_par),SIZE(plat),iluout,pgrid_par,plat,plon,pmesh_size)
133  END IF
134 
135 END SELECT
136 !
137 IF (lassim) lread_all = gread_all
138 !
139 IF (lhook) CALL dr_hook('READ_GRID',1,zhook_handle)
140 !
141 !---------------------------------------------------------------------------
142 !
143 END SUBROUTINE read_grid
subroutine read_grid(HPROGRAM, HGRID, PGRID_PAR, PLAT, PLON, PMESH_SIZE, KRESP, PDIR)
Definition: read_grid.F90:6
subroutine read_gridtype(HPROGRAM, HGRID, KGRID_PAR, KLU, OREAD, PGRID_PAR, KRESP, HDIR)
subroutine latlon_grid(HGRID, KGRID_PAR, KL, KLUOUT, PGRID_PAR, PLAT, PLON, PMESH_SIZE, PDIR)
Definition: latlon_grid.F90:6
subroutine get_luout(HPROGRAM, KLUOUT)
Definition: get_luout.F90:6