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

Last change on this file since 5458 was 5458, checked in by fhourdin, 4 days ago

Concering replay

File size: 3.8 KB
RevLine 
[4094]1PROGRAM rejouer
2
[4350]3USE mod_const_mpi, ONLY: comm_lmdz
4USE inigeomphy_mod, ONLY: inigeomphy
5USE comvert_mod, ONLY: presnivs
[4110]6USE comvert_mod, only :  preff, pa
[4350]7USE ioipsl, only: getin
[4094]8
9
[4110]10
[4350]11
[5271]12      USE dimensions_mod, ONLY: iim, jjm, llm, ndm
13implicit none
[4094]14
[5271]15
[4094]16real :: airefi
17real :: zcufi    = 1.
18real :: zcvfi    = 1.
19real :: rlat_rad(1),rlon_rad(1)
20
21integer ntime
[4350]22integer jour0,mois0,an0,day_step,anneeref,dayref
[4094]23integer klev,klon
[4350]24CHARACTER (len=10) :: calend
25CHARACTER(len=20) :: calendrier
[5458]26CHARACTER(len=20) :: lmax_replay
[4094]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.
[4110]36
37preff=101325.
[4350]38!preff=100000.
[4110]39pa=50000.
40  CALL disvert()
[4094]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
[4350]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)
[5458]58
59print*,'AVANT getin'
60klev=llm
61CALL getin('lmax_replay',lmax_replay)
62print*,'APRES getin',lmax_replay
63CALL getin(lmax_replay,klev)
64print*,'replay1d lmax_replay klev',lmax_replay,klev
65
[4350]66calendrier=calend
[4361]67if ( calendrier == "earth_360d" ) calendrier="360_day"
[4350]68
69
70jour0=dayref
71mois0=(jour0-1)/30+1
72jour0=jour0-30*((jour0-1)/30)
73an0=anneeref
74
75!print*,"REPLAY1D jour0,mois0,an0",jour0,mois0,an0
76
77
[4094]78klon=1
[4350]79call iotd_ini('phys.nc',1,1,klev,0.,0.,presnivs,jour0,mois0,an0,0.,86400./day_step,calendrier)
80! Consistent with ... CALL iophys_ini(600.)
[4094]81
82!---------------------------------------------------------------------
83! Initialisation de la parametrisation
84!---------------------------------------------------------------------
[4589]85call call_ini_replay
[4094]86
87!---------------------------------------------------------------------
88! Boucle en temps sur l'appel à la parametrisation
89!---------------------------------------------------------------------
[4350]90call call_param_replay(klon,klev)
[4094]91
[4350]92end
[4094]93
94!---------------------------------------------------------------------
95!/////////////////////////////////////////////////////////////////////
96!/////////////////////////////////////////////////////////////////////
97!     routine additionnelles utiles, prises dans 1DUTILS.h
98!/////////////////////////////////////////////////////////////////////
99!/////////////////////////////////////////////////////////////////////
100!---------------------------------------------------------------------
101
102!=======================================================================
103      SUBROUTINE gr_dyn_fi(nfield,im,jm,ngrid,pdyn,pfi)
104      IMPLICIT NONE
105!   passage d'un champ de la grille scalaire a la grille physique
106!=======================================================================
107 
108!-----------------------------------------------------------------------
109!   declarations:
110!   -------------
111 
112      INTEGER im,jm,ngrid,nfield
113      REAL pdyn(im,jm,nfield)
114      REAL pfi(ngrid,nfield)
115 
116      INTEGER j,ifield,ig
117 
118!-----------------------------------------------------------------------
119!   calcul:
120!   -------
121 
122      IF(ngrid.NE.2+(jm-2)*(im-1).AND.ngrid.NE.1)                          &
123     &    STOP 'probleme de dim'
124!   traitement des poles
125      CALL SCOPY(nfield,pdyn,im*jm,pfi,ngrid)
126      CALL SCOPY(nfield,pdyn(1,jm,1),im*jm,pfi(ngrid,1),ngrid)
127 
128!   traitement des point normaux
129      DO ifield=1,nfield
130         DO j=2,jm-1
131            ig=2+(j-2)*(im-1)
132            CALL SCOPY(im-1,pdyn(1,j,ifield),1,pfi(ig,ifield),1)
133         ENDDO
134      ENDDO
135 
136      RETURN
[5390]137      END SUBROUTINE gr_dyn_fi
Note: See TracBrowser for help on using the repository browser.