source: trunk/LMDZ.MARS/libf/phymars/eofdump_mod.F90 @ 2398

Last change on this file since 2398 was 2398, checked in by emillour, 4 years ago

Mars GCM:
Some code cleanup: use "call abort_physic()" instead of "stop" or "call abort"
EM

File size: 4.4 KB
Line 
1module eofdump_mod
2! this module controls the production of data for EOFs
3! it won't work if run in parallel (but it's OK, we don't use it anymore...)
4! Mainly kept for reference.
5implicit none
6! Dump profiles for EOFs every ieofs physics timesteps,
7! starting at first call;
8integer :: ieofs
9! Dump profiles every eofskip points in each direction
10! on the model grid.
11integer, parameter :: eofskip = 4
12! Units for writing EOF header and data:
13integer, parameter :: uehead = 82, uedata = 83
14
15contains
16
17      subroutine eofdump(ngrid,nlayer,u,v,t,rho,ps)
18
19      use mod_grid_phy_lmdz, only: nbp_lon, nbp_lat
20      implicit none
21!
22!     Dumps profiles for calculation of variability EOFs
23!     Modified to include rho, FF 09/2004
24!     Corrected small bug in sampling rate/count, EM 11/2007
25!
26!
27
28      integer,intent(in) :: ngrid ! total number of physics grid points
29      integer,intent(in) :: nlayer ! number of atmospheric layers
30      real,intent(in) :: u(ngrid,nlayer)
31      real,intent(in) :: v(ngrid,nlayer)
32      real,intent(in) :: t(ngrid,nlayer)
33      real,intent(in) :: rho(ngrid,nlayer)
34      real,intent(in) :: ps(ngrid)
35      integer,save :: count=0
36      integer i,j,l, ig
37
38      LOGICAL,SAVE :: firstcall=.true.
39
40!-------------------------------------------------------
41!     Initialization at first call:
42!     ~~~~~~~~~~~~~~~~~~~~~~~~~~~~
43      IF (firstcall) THEN
44        write(*,*) 'CALL ineofdump'
45        CALL ineofdump(ngrid,nlayer)
46        firstcall=.false.
47      END IF
48
49!-------------------------------------------------------
50!     Dumps every ieofs physics timesteps
51!
52!      write(*,*)'eofdump:count=',count,' ps(1)=',ps(1)
53!      if ((ieofs.gt.0).and.(mod(count,ieofs).eq.0)) then
54      if (mod(count+1,ieofs).eq.0) then
55!        write(*,*)'eofdump: dump --> ps(1)=',ps(1)
56        do i=1,nbp_lon,eofskip
57          do j=1+eofskip/2,nbp_lat,eofskip
58            ig = 1+ (j-2)*nbp_lon +i
59#ifdef NC_DOUBLE
60            write(uedata) (real(u(ig,l)),l=1,nlayer)
61            write(uedata) (real(v(ig,l)),l=1,nlayer)
62            write(uedata) (real(t(ig,l)),l=1,nlayer)
63            write(uedata) (real(rho(ig,l)),l=1,nlayer)
64            write(uedata) real(ps(ig))
65#else
66            write(uedata) (u(ig,l),l=1,nlayer)
67            write(uedata) (v(ig,l),l=1,nlayer)
68            write(uedata) (t(ig,l),l=1,nlayer)
69            write(uedata) (rho(ig,l),l=1,nlayer)
70            write(uedata) ps(ig)
71#endif
72          enddo
73        enddo
74      endif
75      count=count+1
76 
77      end subroutine eofdump
78
79
80      subroutine ineofdump(ngrid,nlayer)
81
82      use geometry_mod, only: longitude, latitude
83      use nrtype, only: pi
84      use time_phylmdz_mod, only: daysec, dtphys
85      USE vertical_layers_mod, ONLY: aps,bps
86      use mod_grid_phy_lmdz, only: nbp_lon, nbp_lat
87      implicit none
88!
89!     Initialise dumping of profiles for EOF calculations
90!
91
92      integer,intent(in) :: ngrid ! total number of physics grid points
93      integer,intent(in) :: nlayer ! number of atmospheric layers
94      integer ig,i,j,l   
95      logical,save :: firstcall=.true.
96      integer,save :: npgrid
97
98
99      if (firstcall) then
100         npgrid=ngrid+2*(nbp_lon-1)
101         firstcall=.false.
102      endif
103
104!
105!     Set frequency for dumping at once per day
106!
107      ieofs=nint(daysec/dtphys)
108      if (abs(float(ieofs)-daysec/dtphys).gt.1.e-8*daysec) then
109         call abort_physic("ineofdump",' 1 day .ne. n physics timesteps',1)
110      endif
111!
112!     Header
113!
114      open(uehead,file='profiles.hdr',form='formatted')
115      write(uehead,*) 0.E+0,0,0,ieofs,1,0
116      write(uehead,*) nbp_lon,npgrid/nbp_lon,npgrid,nlayer
117
118      do i=1,nbp_lon,eofskip
119        do j=1+eofskip/2,nbp_lat,eofskip   
120          ig = 1+ (j-2)*nbp_lon +i
121          if(j.eq.1) then
122            call abort_physic("ineofdump",'Error: j==1',1)
123          endif
124          if(j.eq.nbp_lat) then
125            call abort_physic("ineofdump",'Error: j==nbp_lat',1)
126          endif
127#ifdef NC_DOUBLE
128          write(uehead,*) real(longitude(ig)*180./pi),real(latitude(ig)*180./pi)
129#else
130          write(uehead,*) longitude(ig)*180./pi, latitude(ig)*180./pi
131#endif
132!         write(*,*) 'eof grid j=',j,' lat= ', latitude(ig)*180./pi
133        enddo
134      enddo
135
136#ifdef NC_DOUBLE
137      write(uehead,*) real(aps)
138      write(uehead,*) real(bps)
139#else
140      write(uehead,*) aps
141      write(uehead,*) bps
142#endif
143      close(uehead)
144!
145!     Main profile file
146!
147      open(uedata,file='profiles.dat',form='unformatted')
148      end subroutine ineofdump
149
150end module eofdump_mod
Note: See TracBrowser for help on using the repository browser.