/[lmdze]/trunk/dyn3d/gcm.f90
ViewVC logotype

Contents of /trunk/dyn3d/gcm.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 352 - (show annotations)
Thu Jan 16 19:20:50 2020 UTC (4 years, 3 months ago) by guez
File size: 3223 byte(s)
Introduce XIOS in program gcm

Introduce XIOS in program gcm. Minimum (and useless) calls: initialize
and finalize.

Take advantage in CMakeLists of improved packaging of libraries:
NetCDF95 brings dependency on NetCDF-Fortran and NetCDF. Compile gcm
with MPI for XIOS.

1 PROGRAM gcm
2
3 ! Authors: P. Le Van, L. Fairhead, F. Hourdin
4 ! From "gcm.F", version 1.4, 2006/04/04
5
6 ! General circulation model of LMD. Avec coordonn\'ee verticale
7 ! hybride, avec nouveaux op\'erateurs de dissipation "*" ("gradiv2",
8 ! "divgrad2", "nxgraro2"). Possibilit\'e de choisir le sch\'ema pour
9 ! l'advection de "q", en modifiant "iadv" dans "traceur.def".
10
11 ! Libraries:
12 use netcdf95, only: nf95_close
13 use xios, only: xios_initialize, xios_finalize
14
15 use comconst, only: dtvr, iniconst
16 use comdissnew, only: read_comdissnew
17 use comgeom, only: aire_2d, inigeom
18 use comgeomphy, only: airephy
19 use conf_gcm_m, only: day_step, iperiod, iphysiq, nday, conf_gcm, iflag_phys
20 use conf_guide_m, only: conf_guide
21 use dimensions, only: iim, jjm, llm, nqmx
22 USE disvert_m, ONLY : disvert
23 use dynetat0_m, only: dynetat0, day_ini
24 use dynetat0_chosen_m, only: dynetat0_chosen
25 use dynredem0_m, only: dynredem0
26 use grid_change, only: dyn_phy, init_dyn_phy
27 use histclo_m, only: histclo
28 use infotrac_init_m, only: infotrac_init
29 use inidissip_m, only: inidissip
30 use inifilr_m, only: inifilr
31 use inithist_m, only: inithist
32 use init_dynzon_m, only: init_dynzon
33 USE ioconf_calendar_m, only: ioconf_calendar
34 use leapfrog_m, only: leapfrog
35 use suphec_m, only: suphec
36 use unit_nml_m, only: unit_nml, set_unit_nml
37 use createnewfield_m, only: NbField, Ncid
38
39 IMPLICIT NONE
40
41 ! Variables dynamiques :
42 REAL ucov(iim + 1, jjm + 1, llm), vcov(iim + 1, jjm, llm) ! vent covariant
43 REAL teta(iim + 1, jjm + 1, llm) ! temp\'erature potentielle
44 REAL q(iim + 1, jjm + 1, llm, nqmx) ! mass fraction of advected species
45 REAL ps(iim + 1, jjm + 1) ! pression au sol (Pa)
46 REAL masse(iim + 1, jjm + 1, llm) ! masse d'air
47 REAL phis(iim + 1, jjm + 1) ! g\'eopotentiel au sol
48
49 LOGICAL:: true_calendar = .false. ! default value
50 integer i
51
52 namelist /main_nml/true_calendar
53
54 !------------------------------------------------------------
55
56 call set_unit_nml
57 open(unit_nml, file="used_namelists.txt", status="replace", action="write")
58
59 CALL conf_gcm
60 call read_comdissnew
61
62 print *, "Enter namelist 'main_nml'."
63 read (unit=*, nml=main_nml)
64 write(unit_nml, nml=main_nml)
65
66 call xios_initialize("LMDZE")
67
68 ! Choix du calendrier :
69 if (true_calendar) then
70 call ioconf_calendar('gregorian')
71 else
72 call ioconf_calendar('360d')
73 endif
74
75 call infotrac_init
76 CALL iniconst
77 CALL dynetat0_chosen
78 CALL dynetat0(vcov, ucov, teta, q, masse, ps, phis)
79 CALL disvert
80 CALL inigeom ! initialisation de la g\'eometrie
81 CALL inifilr ! initialisation du filtre
82 CALL inidissip
83 call init_dyn_phy
84
85 ! Initialisation de la physique :
86 IF (iflag_phys) THEN
87 airephy = pack(aire_2d, dyn_phy)
88 CALL suphec
89 ENDIF
90
91 ! Initialisation des entr\'ees-sorties :
92 CALL dynredem0(day_ini + nday, phis)
93 CALL inithist(t_ops = dtvr, t_wrt = dtvr)
94 call init_dynzon(dt_app = dtvr * iperiod)
95
96 CALL conf_guide
97 CALL leapfrog(ucov, vcov, teta, ps, masse, phis, q)
98
99 close(unit_nml)
100 call histclo
101
102 do i = 1, nbfield
103 call nf95_close(Ncid(i))
104 end do
105
106 call xios_finalize
107
108 print *, 'Simulation finished'
109 print *, 'Everything is cool'
110
111 END PROGRAM gcm

  ViewVC Help
Powered by ViewVC 1.1.21