source: LMDZ4/branches/LMDZ4-dev/libf/phylmd/ecribin.F @ 1244

Last change on this file since 1244 was 1220, checked in by lguez, 15 years ago

-- Replaced "integer*4" declarations by "integer", "real*8" by

"real(kind=8)" and "real*4" by "real". Note that these are the only
modifications in the files "radiation_AR4.F" and "sw_aeroAR4.F90".

-- Corrected the kind of arguments to "max" and "min".

-- Replaced "nH" edit descriptors, which is a deleted feature in

Fortran 95, by character strings.

-- "regr_lat_time_climoz" now allows the pressure coordinate in the

input file to be in descending order.

-- Replaced call to not standard function "float" by call to intrinsic

function "real".

-- Included file "radepsi.h" in "physiq" was not used. Removed it.

The following set of modifications is related to the management of time.

-- In "gcm", "leapfrog" and "sortvarc0", "day_ini" was defined as 1

plus number of days between the reference date "(annee_ref,
day_ref)" and the first day of the current simulation. Changed
definition: "(annee_ref, day_ini)" is the first day of the current
simulation. There is an accompanying modification for "day_end".

-- Corrected bug in call to "ioconf_startdate" in "gcm".

-- Added call to "ioconf_calendar" in "create_etat0_limit".

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 2.4 KB
Line 
1!
2! $Header$
3!
4      SUBROUTINE ecribins(unit,pz)
5      USE dimphy
6      IMPLICIT none
7c-----------------------------------------------------------------------
8#include "dimensions.h"
9cccc#include "dimphy.h"
10#include "paramet.h"
11#include "comgeom.h"
12#include "comvert.h"
13c
14c   arguments:
15c   ----------
16      INTEGER unit
17      REAL pz(klon)
18c
19c   local:
20c   ------
21      INTEGER i,j, ig
22      REAL zz(iim +1,jjm+1)
23c-----------------------------------------------------------------------
24c   passage a la grille dynamique:
25c   ------------------------------
26         DO i=1,iim +1
27            zz(i,1)=pz(1)
28            zz(i,jjm+1)=pz(klon)
29         ENDDO
30c   traitement des point normaux
31         DO j=2,jjm
32            ig=2+(j-2)*iim
33            CALL SCOPY(iim,pz(ig),1,zz(1,j),1)
34            zz(iim+1,j)=zz(1,j)
35         ENDDO
36c-----------------------------------------------------------------------
37#ifdef VPP
38      CALL ecriture(unit,zz,(iim+1)*(jjm+1))
39#else
40      WRITE(unit) zz
41#endif
42c
43
44      RETURN
45      END
46      SUBROUTINE ecribina(unit,pz)
47      USE dimphy
48      IMPLICIT none
49c-----------------------------------------------------------------------
50#include "dimensions.h"
51cccc#include "dimphy.h"
52#include "paramet.h"
53#include "comgeom.h"
54#include "comvert.h"
55c
56c   arguments:
57c   ----------
58      INTEGER unit
59      REAL pz(klon,klev)
60c
61c   local:
62c   ------
63      INTEGER i,j,ilay,ig
64      REAL zz(iim+1,jjm+1,llm)
65c-----------------------------------------------------------------------
66c   passage a la grille dynamique:
67c   ------------------------------
68      DO ilay=1,llm
69c   traitement des poles
70         DO i=1,iim +1
71            zz(i,1,ilay)=pz(1,ilay)
72            zz(i,jjm+1,ilay)=pz(klon,ilay)
73         ENDDO
74c   traitement des point normaux
75         DO j=2,jjm
76            ig=2+(j-2)*iim
77            CALL SCOPY(iim,pz(ig,ilay),1,zz(1,j,ilay),1)
78            zz(iim+1,j,ilay)=zz(1,j,ilay)
79         ENDDO
80      ENDDO
81c-----------------------------------------------------------------------
82      DO ilay = 1, llm
83#ifdef VPP
84         CALL ecriture(unit, zz(1,1,ilay), (iim+1)*(jjm+1))
85#else
86         WRITE(unit) ((zz(i,j,ilay),i=1,iim +1),j=1,jjm+1)
87#endif
88      ENDDO
89c
90      RETURN
91      END
92#ifdef VPP
93@OPTIONS NODOUBLE
94      SUBROUTINE ecriture(nunit, r8, n)
95      INTEGER nunit, n, i
96      REAL(KIND=8) r8(n)
97      REAL r4(n)
98      DO i = 1, n
99         r4(i) = r8(i)
100      ENDDO
101      WRITE(nunit)r4
102      RETURN
103      END
104#endif
Note: See TracBrowser for help on using the repository browser.