SURFEX v8.1
General documentation of Surfex
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 (HPROGRAM,G,KRESP,PDIR)
7 ! #########################################
8 !
9 !!**** *READ_GRID* - routine to initialise the horizontal grid of a scheme
10 !!
11 !! PURPOSE
12 !! -------
13 !!
14 !!** METHOD
15 !! ------
16 !!
17 !! EXTERNAL
18 !! --------
19 !!
20 !!
21 !! IMPLICIT ARGUMENTS
22 !! ------------------
23 !!
24 !! REFERENCE
25 !! ---------
26 !!
27 !!
28 !! AUTHOR
29 !! ------
30 !! V. Masson *Meteo France*
31 !!
32 !! MODIFICATIONS
33 !! -------------
34 !! Original 01/2003
35 !-------------------------------------------------------------------------------
36 !
37 !* 0. DECLARATIONS
38 ! ------------
39 !
40 !
41 USE modd_sfx_grid_n, ONLY : grid_t
42 !
43 USE modi_get_luout
45 USE modi_latlon_grid
46 USE modi_read_gridtype
47 !
48 USE modd_assim, ONLY : lread_all, lassim
49 !
50 USE yomhook ,ONLY : lhook, dr_hook
51 USE parkind1 ,ONLY : jprb
52 !
53 IMPLICIT NONE
54 !
55 !* 0.1 Declarations of arguments
56 ! -------------------------
57 !
58 !
59 !
60  CHARACTER(LEN=6), INTENT(IN) :: HPROGRAM ! calling program
61 TYPE(grid_t), INTENT(INOUT) :: G
62 INTEGER, INTENT(OUT) :: KRESP ! error return code
63 REAL, DIMENSION(:), INTENT(OUT), OPTIONAL :: PDIR ! heading of main axis of grid compared to North (degrees)
64 !
65 !* 0.2 Declarations of local variables
66 ! -------------------------------
67 !
68 LOGICAL :: GREAD_ALL
69 INTEGER :: ILUOUT
70 REAL(KIND=JPRB) :: ZHOOK_HANDLE
71 !---------------------------------------------------------------------------
72 !
73 !* 1. Reading of type of grid
74 ! -----------------------
75 !
76 IF (lhook) CALL dr_hook('READ_GRID',0,zhook_handle)
77 !
78 IF (lassim) THEN
79  gread_all = lread_all
80  lread_all = .true.
81 ENDIF
82 !
83  CALL read_surf(hprogram,'GRID_TYPE',g%CGRID,kresp)
84 !
85 !---------------------------------------------------------------------------
86 !
87 !* 2. Reading parameters of the grid
88 ! ------------------------------
89 !
90  CALL read_gridtype(hprogram,g%CGRID,g%NGRID_PAR,SIZE(g%XLAT),.false.)
91 !
92 ALLOCATE(g%XGRID_PAR(g%NGRID_PAR))
93  CALL read_gridtype(hprogram,g%CGRID,g%NGRID_PAR,SIZE(g%XLAT),.true.,g%XGRID_PAR,kresp)
94 !
95 !---------------------------------------------------------------------------
96 !
97 !* 3. Latitude, longitude, mesh size
98 ! ------------------------------
99 !
100  CALL get_luout(hprogram,iluout)
101 !
102 SELECT CASE (g%CGRID)
103  CASE("NONE ")
104  IF (PRESENT(pdir)) pdir(:) = 0.
105  !
106  CALL read_surf(hprogram,'LON', g%XLON,kresp)
107  IF (kresp/=0 .AND. lhook) CALL dr_hook('READ_GRID',1,zhook_handle)
108  IF (kresp/=0) RETURN
109  CALL read_surf(hprogram,'LAT', g%XLAT,kresp)
110  IF (kresp/=0 .AND. lhook) CALL dr_hook('READ_GRID',1,zhook_handle)
111  IF (kresp/=0) RETURN
112  CALL read_surf(hprogram,'MESH_SIZE',g%XMESH_SIZE,kresp)
113  IF (kresp/=0 .AND. lhook) CALL dr_hook('READ_GRID',1,zhook_handle)
114  IF (kresp/=0) RETURN
115 
116  CASE DEFAULT
117  IF (PRESENT(pdir)) THEN
118  CALL latlon_grid(g,SIZE(g%XLAT),pdir)
119  ELSE
120  CALL latlon_grid(g,SIZE(g%XLAT))
121  END IF
122 
123 END SELECT
124 !
125 IF (lassim) lread_all = gread_all
126 !
127 IF (lhook) CALL dr_hook('READ_GRID',1,zhook_handle)
128 !
129 !---------------------------------------------------------------------------
130 !
131 END SUBROUTINE read_grid
subroutine latlon_grid(G, KL, PDIR)
Definition: latlon_grid.F90:7
subroutine read_gridtype( HPROGRAM, HGRID, KGRID_PAR, KLU, OREAD, PGRID
integer, parameter jprb
Definition: parkind1.F90:32
subroutine get_luout(HPROGRAM, KLUOUT)
Definition: get_luout.F90:7
logical lhook
Definition: yomhook.F90:15
subroutine read_grid(HPROGRAM, G, KRESP, PDIR)
Definition: read_grid.F90:7