source: LMDZ6/trunk/libf/phylmd/dyn1d/replay1d.f90

Last change on this file was 5271, checked in by abarral, 34 hours ago

Move dimensions.h into a module
Nb: doesn't compile yet

File size: 4.4 KB
Line 
1PROGRAM rejouer
2
3USE mod_const_mpi, ONLY: comm_lmdz
4USE inigeomphy_mod, ONLY: inigeomphy
5USE comvert_mod, ONLY: presnivs
6USE comvert_mod, only :  preff, pa
7USE ioipsl, only: getin
8
9
10
11
12      USE dimensions_mod, ONLY: iim, jjm, llm, ndm
13implicit none
14
15
16real :: airefi
17real :: zcufi    = 1.
18real :: zcvfi    = 1.
19real :: rlat_rad(1),rlon_rad(1)
20
21integer ntime
22integer jour0,mois0,an0,day_step,anneeref,dayref
23integer klev,klon
24CHARACTER (len=10) :: calend
25CHARACTER(len=20) :: calendrier
26
27
28!---------------------------------------------------------------------
29! L'appel a inigeomphy n'est utile que pour avoir getin_p dans
30! les initialisations
31!---------------------------------------------------------------------
32  zcufi=1.
33  zcvfi=1.
34  rlat_rad(1)=0.
35  rlon_rad(1)=0.
36
37preff=101325.
38!preff=100000.
39pa=50000.
40  CALL disvert()
41  CALL inigeomphy(1,1,llm, &
42               1, comm_lmdz, &
43           (/rlat_rad(1),0./),(/0./), &
44           (/0.,0./),(/rlon_rad(1),0./),  &
45           (/ (/airefi,0./),(/0.,0./) /), &
46           (/zcufi,0.,0.,0./), &
47           (/zcvfi,0./))
48
49CALL suphel
50!ntime=4320
51ntime=10000000
52dayref=1
53anneeref=2000
54call getin('dayref',dayref)
55call getin('anneeref',anneeref)
56call getin('calend',calend)
57call getin('day_step',day_step)
58calendrier=calend
59if ( calendrier == "earth_360d" ) calendrier="360_day"
60
61
62jour0=dayref
63mois0=(jour0-1)/30+1
64jour0=jour0-30*((jour0-1)/30)
65an0=anneeref
66
67!print*,"REPLAY1D jour0,mois0,an0",jour0,mois0,an0
68
69
70klon=1
71klev=llm
72call iotd_ini('phys.nc',1,1,klev,0.,0.,presnivs,jour0,mois0,an0,0.,86400./day_step,calendrier)
73! Consistent with ... CALL iophys_ini(600.)
74
75!---------------------------------------------------------------------
76! Initialisation de la parametrisation
77!---------------------------------------------------------------------
78call call_ini_replay
79
80!---------------------------------------------------------------------
81! Boucle en temps sur l'appel à la parametrisation
82!---------------------------------------------------------------------
83call call_param_replay(klon,klev)
84
85end
86
87!---------------------------------------------------------------------
88!/////////////////////////////////////////////////////////////////////
89!/////////////////////////////////////////////////////////////////////
90!     routine additionnelles utiles, prises dans 1DUTILS.h
91!/////////////////////////////////////////////////////////////////////
92!/////////////////////////////////////////////////////////////////////
93!---------------------------------------------------------------------
94
95!=======================================================================
96      SUBROUTINE abort_gcm(modname, message, ierr)
97      USE IOIPSL
98! Stops the simulation cleanly, closing files and printing various
99! comments
100!=======================================================================
101!
102!  Input: modname = name of calling program
103!         message = stuff to print
104!         ierr    = severity of situation ( = 0 normal )
105 
106      character(len=*) modname
107      integer ierr
108      character(len=*) message
109 
110      write(*,*) 'in abort_gcm'
111      call histclo
112      write(*,*) 'out of histclo'
113      write(*,*) 'Stopping in ', modname
114      write(*,*) 'Reason = ',message
115      call getin_dump
116!
117      if (ierr .eq. 0) then
118        write(*,*) 'Everything is cool'
119      else
120        write(*,*) 'Houston, we have a problem ', ierr
121      endif
122      STOP
123      END
124
125!=======================================================================
126      SUBROUTINE gr_dyn_fi(nfield,im,jm,ngrid,pdyn,pfi)
127      IMPLICIT NONE
128!   passage d'un champ de la grille scalaire a la grille physique
129!=======================================================================
130 
131!-----------------------------------------------------------------------
132!   declarations:
133!   -------------
134 
135      INTEGER im,jm,ngrid,nfield
136      REAL pdyn(im,jm,nfield)
137      REAL pfi(ngrid,nfield)
138 
139      INTEGER j,ifield,ig
140 
141!-----------------------------------------------------------------------
142!   calcul:
143!   -------
144 
145      IF(ngrid.NE.2+(jm-2)*(im-1).AND.ngrid.NE.1)                          &
146     &    STOP 'probleme de dim'
147!   traitement des poles
148      CALL SCOPY(nfield,pdyn,im*jm,pfi,ngrid)
149      CALL SCOPY(nfield,pdyn(1,jm,1),im*jm,pfi(ngrid,1),ngrid)
150 
151!   traitement des point normaux
152      DO ifield=1,nfield
153         DO j=2,jm-1
154            ig=2+(j-2)*(im-1)
155            CALL SCOPY(im-1,pdyn(1,j,ifield),1,pfi(ig,ifield),1)
156         ENDDO
157      ENDDO
158 
159      RETURN
160      END
Note: See TracBrowser for help on using the repository browser.