/[lmdze]/trunk/libf/IOIPSL/ioipslmpp.f90
ViewVC logotype

Contents of /trunk/libf/IOIPSL/ioipslmpp.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 32 - (show annotations)
Tue Apr 6 17:52:58 2010 UTC (14 years, 1 month ago) by guez
File size: 2932 byte(s)
Split "stringop.f90" into single-procedure files. Gathered files in directory
"IOIPSL/Stringop".

Split "flincom.f90" into "flincom.f90" and "flinget.f90". Removed
unused procedures from module "flincom". Removed unused argument
"filename" of procedure "flinopen_nozoom".

Removed unused files.

Split "grid_change.f90" into "grid_change.f90" and
"gr_phy_write_3d.f90".

Removed unused procedures from modules "calendar", "ioipslmpp",
"grid_atob", "gath_cpl" and "getincom". Removed unused procedures in
files "ppm3d.f" and "thermcell.f".

Split "mathelp.f90" into "mathelp.f90" and "mathop.f90".

Removed unused variable "dpres" of module "comvert".

Use argument "itau" instead of local variables "iadvtr" and "first" to
control algorithm in procedure "fluxstokenc".

Removed unused arguments of procedure "integrd".

Removed useless computations at the end of procedure "leapfrog".

Merged common block "matrfil" into module "parafilt".

1 !$Header: /home/ioipsl/CVSROOT/IOIPSL/src/Attic/ioipslmpp.f90,v 2.0 2004/04/05 14:50:16 adm Exp $
2 !-
3 MODULE ioipslmpp
4 !---------------------------------------------------------------------
5 USE errioipsl, ONLY : histerr
6 !-
7 IMPLICIT NONE
8 !-
9 PRIVATE
10 PUBLIC :: ioipslmpp_file, ioipslmpp_addatt
11 !-
12 LOGICAL,SAVE :: ison_mpp=.FALSE., lock=.FALSE.
13 !-
14 ! Number of distributed dimension for mpp
15 !-
16 INTEGER,PARAMETER :: jpp=4
17 !-
18 INTEGER,SAVE :: pe_number, pe_total_number
19 INTEGER,SAVE,DIMENSION(jpp) :: &
20 & domain_global_size, domain_local_size, domain_abs_first, &
21 & domain_abs_last, domain_halo_start_size, domain_halo_end_size
22 !-
23 CONTAINS
24 !-
25 !===
26 !-
27 SUBROUTINE ioipslmpp_file (filename)
28 !---------------------------------------------------------------------
29 !- Update the netCDF file to include the PE number on which this
30 !- copy of IOIPSL runs.
31 !- This routine is called by histbeg and not by user anyway
32 !---------------------------------------------------------------------
33 IMPLICIT NONE
34 !-
35 CHARACTER(LEN=*),INTENT(inout) :: filename
36 !-
37 INTEGER :: il
38 CHARACTER(LEN=3) :: str
39 !---------------------------------------------------------------------
40 IF (ison_mpp) THEN
41 WRITE(str,'(I3.3)') pe_number
42 !-- Tester la taille de la chaine
43 il = INDEX(filename,'.nc')
44 filename = filename(1:il-1)//'_'//str//'.nc'
45 ENDIF
46 !-
47 ! This as to be done after ioipslmpp
48 !-
49 lock = .TRUE.
50 !---------------------------------------------------------------------
51 END SUBROUTINE ioipslmpp_file
52 !-
53 !===
54 !-
55 SUBROUTINE ioipslmpp_addatt (fid)
56 !---------------------------------------------------------------------
57 !- Adds the attributed to the netCDF file.
58 !- This routine is called by histend and not by user anyway
59 !---------------------------------------------------------------------
60 USE netcdf
61 !-
62 IMPLICIT NONE
63 !-
64 INTEGER,INTENT(in) :: fid
65 !-
66 INTEGER :: iret
67 !---------------------------------------------------------------------
68 IF (ison_mpp) THEN
69 iret = NF90_PUT_ATT (fid,NF90_GLOBAL, &
70 & 'PE_number',pe_number)
71 iret = NF90_PUT_ATT (fid,NF90_GLOBAL, &
72 & 'PE_total_number',pe_total_number)
73 iret = NF90_PUT_ATT (fid,NF90_GLOBAL, &
74 & 'DOMAIN_global_size',domain_global_size(1:jpp))
75 iret = NF90_PUT_ATT (fid,NF90_GLOBAL, &
76 & 'DOMAIN_local_size',domain_local_size(1:jpp))
77 iret = NF90_PUT_ATT (fid,NF90_GLOBAL, &
78 & 'DOMAIN_absolute_first_point_number',domain_abs_first(1:jpp))
79 iret = NF90_PUT_ATT (fid,NF90_GLOBAL, &
80 & 'DOMAIN_absolute_last_point_number',domain_abs_last(1:jpp))
81 iret = NF90_PUT_ATT (fid,NF90_GLOBAL, &
82 & 'DOMAIN_start_halo_size',domain_halo_start_size(1:jpp))
83 iret = NF90_PUT_ATT (fid,NF90_GLOBAL, &
84 & 'DOMAIN_end_halo_size',domain_halo_end_size(1:jpp))
85 ENDIF
86 !-
87 ! This as to be done after ioipslmpp
88 !-
89 lock = .TRUE.
90 !------------------------------
91 END SUBROUTINE ioipslmpp_addatt
92 !-
93 !===
94 !-
95 END MODULE ioipslmpp

  ViewVC Help
Powered by ViewVC 1.1.21