SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
prep_grid_gauss.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 prep_grid_gauss (&
7  hfiletype,hinterp_type,kni)
8 ! ##########################################################################
9 !
10 !!**** *PREP_GRID_GAUSS* - reads EXTERNALIZED Surface grid.
11 !!
12 !! PURPOSE
13 !! -------
14 !!
15 !!** METHOD
16 !! ------
17 !!
18 !! EXTERNAL
19 !! --------
20 !!
21 !! IMPLICIT ARGUMENTS
22 !! ------------------
23 !!
24 !!
25 !! REFERENCE
26 !! ---------
27 !!
28 !!
29 !! AUTHOR
30 !! ------
31 !!
32 !! V. Masson
33 !!
34 !! MODIFICATIONS
35 !! -------------
36 !! Original 06/2003
37 !! M. Jidane Nov 2013 : correct allocation of NINLO and reading of INLOPA
38 !! F. Taillefer Dec 2013 : debug estimation of XILO2
39 !-------------------------------------------------------------------------------
40 !
41 !* 0. DECLARATIONS
42 ! ------------
43 !
44 !
45 !
46 !
48 !
49 USE modd_grid_gauss, ONLY : xila1, xilo1, xila2, xilo2, ninla, ninlo, nilen, lrotpole, xcoef, xlap, xlop
50 !
51 USE yomhook ,ONLY : lhook, dr_hook
52 USE parkind1 ,ONLY : jprb
53 !
54 IMPLICIT NONE
55 !
56 !* 0.1. Declaration of arguments
57 ! ------------------------
58 !
59 !
60 !
61  CHARACTER(LEN=6), INTENT(IN) :: hfiletype ! file type
62  CHARACTER(LEN=6), INTENT(OUT) :: hinterp_type ! Grid type
63 INTEGER, INTENT(OUT) :: kni ! number of points
64 !
65 !* 0.2 Declaration of local variables
66 ! ------------------------------
67 !
68  CHARACTER(LEN=12) :: yrecfm ! Name of the article to be read
69 INTEGER :: iresp
70 !
71 !
72 INTEGER :: jl ! loop counter
73 REAL, DIMENSION(:), ALLOCATABLE :: zw ! work array
74 !
75 INTEGER :: inlati ! number of pseudo-latitudes
76 INTEGER :: inlati2 ! number of half pseudo-latitudes
77 REAL :: zlapo ! latitude of the rotated pole (deg)
78 REAL :: zlopo ! longitude of the rotated pole (deg)
79 REAL :: zcodil ! stretching factor (must be greater than or equal to 1)
80 INTEGER, DIMENSION(:), ALLOCATABLE :: inlopa ! number of pseudo-longitudes on each
81  ! pseudo-latitude circle
82 REAL(KIND=JPRB) :: zhook_handle
83 !
84 !-----------------------------------------------------------------------
85 IF (lhook) CALL dr_hook('PREP_GRID_GAUSS',0,zhook_handle)
86 !-----------------------------------------------------------------------
87 !
88 !* 1 Projection
89 ! ----------
90 !
91 yrecfm = 'LAPO'
92  CALL read_surf(&
93  hfiletype,yrecfm,zlapo,iresp)
94 yrecfm = 'LOPO'
95  CALL read_surf(&
96  hfiletype,yrecfm,zlopo,iresp)
97 yrecfm = 'CODIL'
98  CALL read_surf(&
99  hfiletype,yrecfm,zcodil,iresp)
100 !
101 !-----------------------------------------------------------------------
102 !
103 !* 2 Grid
104 ! ----
105 !
106 yrecfm = 'NLATI'
107  CALL read_surf(&
108  hfiletype,yrecfm,inlati,iresp)
109 !
110 IF (ALLOCATED(inlopa)) DEALLOCATE(inlopa)
111 ALLOCATE(inlopa(inlati))
112 IF (ALLOCATED(ninlo)) DEALLOCATE(ninlo)
113 ALLOCATE(ninlo(inlati))
114 yrecfm = 'NLOPA'
115  CALL read_surf(&
116  hfiletype,yrecfm,inlopa,iresp,hdir='A')
117 !
118 kni = sum(inlopa)
119 !
120 !-----------------------------------------------------------------------
121 !
122 !* 3 Computes additional quantities used in interpolation
123 ! ----------------------------------------------------
124 !
125 inlati2 = nint(REAL(inlati)/2.0)
126 ninla = inlati
127 nilen = kni
128 xlop = zlopo
129 xlap = zlapo
130 xcoef = zcodil
131 !
132 ninlo(:) = inlopa(:)
133 !
134 !* type of transform
135 IF (zlapo>89.99 .AND. abs(zlopo)<0.00001) THEN
136  lrotpole = .false.
137 ELSE
138  lrotpole = .true.
139 ENDIF
140 !
141 xila1=90.0*(1.0-0.5/REAL(inlati))
142 xilo1=0.0
143 xila2=-90.0*(1.0-0.5/REAL(inlati))
144 xilo2=360.0*(REAL(inlopa(inlati2))-1.0)/REAL(inlopa(inlati2))
145 !
146 hinterp_type = 'HORIBL'
147 !-----------------------------------------------------------------------
148 IF (lhook) CALL dr_hook('PREP_GRID_GAUSS',1,zhook_handle)
149 !-----------------------------------------------------------------------
150 !
151 END SUBROUTINE prep_grid_gauss
subroutine prep_grid_gauss(HFILETYPE, HINTERP_TYPE, KNI)