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

Last change on this file since 1226 was 1226, checked in by aslmd, 11 years ago

LMDZ.MARS : Replaced comcstfi and planete includes by modules.

File size: 4.0 KB
Line 
1module eofdump_mod
2! this module controls the production of data for EOFs
3implicit none
4! Dump profiles for EOFs every ieofs physics timesteps,
5! starting at first call;
6integer :: ieofs
7! Dump profiles every eofskip points in each direction
8! on the model grid.
9integer, parameter :: eofskip = 4
10! Units for writing EOF header and data:
11integer, parameter :: uehead = 82, uedata = 83
12
13contains
14
15      subroutine eofdump(ngrid,nlayer,u,v,t,rho,ps)
16
17      implicit none
18!
19!     Dumps profiles for calculation of variability EOFs
20!     Modified to include rho, FF 09/2004
21!     Corrected small bug in sampling rate/count, EM 11/2007
22!
23#include "dimensions.h"
24!#include "dimphys.h"
25!
26
27      integer,intent(in) :: ngrid ! total number of physics grid points
28      integer,intent(in) :: nlayer ! number of atmospheric layers
29      real,intent(in) :: u(ngrid,nlayer)
30      real,intent(in) :: v(ngrid,nlayer)
31      real,intent(in) :: t(ngrid,nlayer)
32      real,intent(in) :: rho(ngrid,nlayer)
33      real,intent(in) :: ps(ngrid)
34      integer,save :: count=0
35      integer i,j,l, ig
36
37      LOGICAL,SAVE :: firstcall=.true.
38
39!-------------------------------------------------------
40!     Initialization at first call:
41!     ~~~~~~~~~~~~~~~~~~~~~~~~~~~~
42      IF (firstcall) THEN
43        write(*,*) 'CALL ineofdump'
44        CALL ineofdump(ngrid,nlayer)
45        firstcall=.false.
46      END IF
47
48!-------------------------------------------------------
49!     Dumps every ieofs physics timesteps
50!
51!      write(*,*)'eofdump:count=',count,' ps(1)=',ps(1)
52!      if ((ieofs.gt.0).and.(mod(count,ieofs).eq.0)) then
53      if (mod(count+1,ieofs).eq.0) then
54!        write(*,*)'eofdump: dump --> ps(1)=',ps(1)
55        do i=1,iim,eofskip
56          do j=1+eofskip/2,jjm+1,eofskip
57            ig = 1+ (j-2)*iim +i
58#ifdef NC_DOUBLE
59            write(uedata) (real(u(ig,l)),l=1,nlayer)
60            write(uedata) (real(v(ig,l)),l=1,nlayer)
61            write(uedata) (real(t(ig,l)),l=1,nlayer)
62            write(uedata) (real(rho(ig,l)),l=1,nlayer)
63            write(uedata) real(ps(ig))
64#else
65            write(uedata) (u(ig,l),l=1,nlayer)
66            write(uedata) (v(ig,l),l=1,nlayer)
67            write(uedata) (t(ig,l),l=1,nlayer)
68            write(uedata) (rho(ig,l),l=1,nlayer)
69            write(uedata) ps(ig)
70#endif
71          enddo
72        enddo
73      endif
74      count=count+1
75 
76      end subroutine eofdump
77
78
79      subroutine ineofdump(ngrid,nlayer)
80
81      use comgeomfi_h, only: long, lati
82      use comcstfi_h
83      implicit none
84!
85!     Initialise dumping of profiles for EOF calculations
86!
87#include "dimensions.h"
88!#include "dimphys.h"
89#include "comvert.h"
90!#include "comgeomfi.h"
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*(iim-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) &
109         stop'In ineofdump:  1 day .ne. n physics timesteps'
110!
111!     Header
112!
113      open(uehead,file='profiles.hdr',form='formatted')
114      write(uehead,*) 0.E+0,0,0,ieofs,1,0
115      write(uehead,*) iim,npgrid/iim,npgrid,nlayer
116
117      do i=1,iim,eofskip
118        do j=1+eofskip/2,jjm+1,eofskip   
119          ig = 1+ (j-2)*iim +i
120          if(j.eq.1) stop 'Problem in ineofdump.F'
121          if(j.eq.jjm+1) stop 'Problem in ineofdump.F'
122#ifdef NC_DOUBLE
123          write(uehead,*) real(long(ig)*180./pi),real(lati(ig)*180./pi)
124#else
125          write(uehead,*) long(ig)*180./pi, lati(ig)*180./pi
126#endif
127!         write(*,*) 'eof grid j=',j,' lat= ', lati(ig)*180./pi
128        enddo
129      enddo
130
131#ifdef NC_DOUBLE
132      write(uehead,*) real(aps)
133      write(uehead,*) real(bps)
134#else
135      write(uehead,*) aps
136      write(uehead,*) bps
137#endif
138      close(uehead)
139!
140!     Main profile file
141!
142      open(uedata,file='profiles.dat',form='unformatted')
143      end subroutine ineofdump
144
145end module eofdump_mod
Note: See TracBrowser for help on using the repository browser.