SURFEX v8.1
General documentation of Surfex
trip_prep.F90
Go to the documentation of this file.
1 !######
2 PROGRAM trip_prep
3 !###########
4 !
5 !!**** *TRIP_PREP* - driver for TRIP fields preparation
6 !!
7 !! PURPOSE
8 !! -------
9 !
10 !!** METHOD
11 !! ------
12 !!
13 !! REFERENCE
14 !! ---------
15 !!
16 !!
17 !! AUTHOR
18 !! ------
19 !! B. Decharme
20 !!
21 !! MODIFICATIONS
22 !! -------------
23 !! Original 06/2008
24 !! S.Sénési 08/11/16 : interface to XIOS
25 !!------------------------------------------------------------------
26 !
29 !
31 !
32 USE modi_init_trip_par
33 USE modi_prep_trip_run
34 !
35 USE modi_open_trip_namelist
36 USE modi_close_trip_namelist
37 USE modi_abort_trip
38 USE modi_trip_posnam
39 USE modi_read_nam_trip
40 USE modi_read_nam_trip_grid
41 USE modi_read_nam_trip_prep
42 !
43 USE modi_trip_oasis_end
44 !
45 USE modi_trip_oasis_init
46 USE modi_trip_oasis_read_nam
47 USE modi_trip_oasis_prep
48 USE modi_trip_oasis_end
49 !
50 #ifdef SFX_MPI
51 #ifdef SFX_MPL
53 #endif
54 #endif
55 USE yomhook ,ONLY : lhook, dr_hook
56 USE parkind1 ,ONLY : jprb
57 !
58 IMPLICIT NONE
59 !
60 #ifdef CPLOASIS
61 include 'mpif.h'
62 #endif
63 !
64 INTEGER :: ILON
65 INTEGER :: ILAT
66 !
67 INTEGER :: NYEAR ! current year (UTC)
68 INTEGER :: NMONTH ! current month (UTC)
69 INTEGER :: NDAY ! current day (UTC)
70 REAL :: XTIME ! current time (s)
71 !
72 INTEGER :: ILUNAM ! namelist unit number
73 LOGICAL :: GFOUND ! return logical when reading namelist
74 INTEGER :: ILOCAL_COMM ! Local communicator
75 LOGICAL :: GOASIS ! OASIS used(default=.false.)
76 LOGICAL :: GXIOS ! XIOS used(default=.false.)
77 !
78 REAL(KIND=JPRB) :: ZHOOK_HANDLE
79 !
80 NAMELIST/nam_start_date/nyear,nmonth,nday,xtime
81 !
82 ! --------------------------------------------------------------------------------------
83 ! * 0. MPI and OASIS must be initialized before any DR_HOOK call
84 ! --------------------------------------------------------------------------------------
85 !
86  CALL trip_oasis_init(goasis,gxios,ilocal_comm,lprep=.true.)
87 #ifdef SFX_MPI
88 #ifdef SFX_MPL
89 IF (ilocal_comm/=0) THEN
90  lmplusercomm = .true.
91  mplusercomm = ilocal_comm
92 ENDIF
93 #endif
94 #endif
95 !
96 IF (lhook) CALL dr_hook('TRIP_PREP',0,zhook_handle)
97 !
98 !-------------------------------------------------------------------------------
99  CALL trip_alloc_list(1)
100  ytrip_cur => ytrip_list(1)
101 !-------------------------------------------------------------------------------
102 !
104 !
105 OPEN (unit=nlisting,file=clisting_prep,form='FORMATTED',action='WRITE')
106 !
107 ! --------------------------------------------------------------------------------------
108 !* 1. Time configuration: start date of the run
109 ! --------------------------------------------------------------------------------------
110 !
111  CALL open_trip_namelist(ilunam)
112  CALL trip_posnam(ilunam,'NAM_START_DATE',gfound,nlisting)
113 IF (gfound) THEN
114  READ (unit=ilunam,nml=nam_start_date)
115 ELSE
116  WRITE(nlisting,*)'NAM_START_DATE not found in namelist'
117  WRITE(nlisting,*)'NYEAR, NMONTH, NDAY and XTIME must be initialized'
118  WRITE(nlisting,*)'as the date of the beginning of the run'
119  CALL abort_trip('NAM_START_DATE not found in namelist')
120 ENDIF
121  CALL close_trip_namelist(ilunam)
122 !
123 ! --------------------------------------------------------------------------------------
124 !* 2. Initializations
125 ! --------------------------------------------------------------------------------------
126 !
127  CALL init_trip_par
128 !
129 ! --------------------------------------------------------------------------------------
130 !* 3. Read grid and physical option namelists
131 ! --------------------------------------------------------------------------------------
132 !
133  CALL read_nam_trip(nlisting)
134 !
136 !
137  CALL read_nam_trip_grid(ytrip_cur%TPG, &
138  nlisting)
139 !
140 IF(goasis)THEN
142 ENDIF
143 !
144 ! --------------------------------------------------------------------------------------
145 !* 4. TRIP parameters preparation
146 ! --------------------------------------------------------------------------------------
147 !
148  CALL prep_trip_run(ytrip_cur%TP, ytrip_cur%TPG, &
149  nyear,nmonth,nday,xtime,ilon,ilat)
150 !
151 IF(goasis)THEN
152  CALL trip_oasis_prep(ytrip_cur%TPG, &
153  nlisting,ilon,ilat)
154 ENDIF
155 !
156 ! --------------------------------------------------------------------------------------
157 !
158 WRITE(nlisting,*) ' '
159 WRITE(nlisting,*) ' ----------------------------'
160 WRITE(nlisting,*) ' | TRIP PREP ENDS CORRECTLY |'
161 WRITE(nlisting,*) ' ----------------------------'
162 !
163 WRITE(*,*) ' '
164 WRITE(*,*) ' ----------------------------'
165 WRITE(*,*) ' | TRIP PREP ENDS CORRECTLY |'
166 WRITE(*,*) ' ----------------------------'
167 !
168  CLOSE(nlisting)
169 !
170 !-------------------------------------------------------------------------------
171  CALL trip_deallo_list
172 !-------------------------------------------------------------------------------
173 !
174 IF (lhook) CALL dr_hook('TRIP_PREP',1,zhook_handle)
175 !
176 ! --------------------------------------------------------------------------------------
177 ! * 3. MPI and OASIS must be finalized after the last DR_HOOK call
178 ! --------------------------------------------------------------------------------------
179 !
180  CALL trip_oasis_end(goasis,gxios)
181 !
182 !-------------------------------------------------------------------------------------
183 !
184 END PROGRAM trip_prep
subroutine trip_oasis_end(OOASIS, OXIOS)
integer(kind=jpim) mplusercomm
subroutine init_trip_par
subroutine trip_alloc_list(KMODEL)
type(trip_model_t), pointer ytrip_cur
subroutine trip_deallo_list
program trip_prep
Definition: trip_prep.F90:2
subroutine read_nam_trip_grid(TPG, KLISTING)
subroutine trip_oasis_init(OOASIS, OXIOS, KLOCAL_COMM, PRUNTIME, LPREP)
subroutine read_nam_trip(KLISTING)
subroutine trip_oasis_read_nam(KLISTING, PRUNTIME)
integer, parameter jprb
Definition: parkind1.F90:32
subroutine trip_oasis_prep(TPG, KLISTING, KLON, KLAT)
logical lhook
Definition: yomhook.F90:15
subroutine close_trip_namelist(KLUNAM)
character(len=28) clisting
subroutine open_trip_namelist(KLUNAM)
subroutine abort_trip(YTEXT)
Definition: abort_trip.F90:3
subroutine read_nam_trip_prep(KLISTING)
type(trip_model_t), dimension(:), allocatable, target, save ytrip_list
subroutine trip_posnam(KULNAM, HDNAML, OFOUND, KLISTING)
Definition: trip_posnam.F90:3
subroutine prep_trip_run(TP, TPG, KYEAR, KMONTH, KDAY, PTIME, KLON, KLAT)
character(len=28) clisting_prep