/[lmdze]/trunk/IOIPSL/ioget_calendar.f90
ViewVC logotype

Contents of /trunk/IOIPSL/ioget_calendar.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 328 - (show annotations)
Thu Jun 13 14:40:06 2019 UTC (4 years, 11 months ago) by guez
File size: 1278 byte(s)
Change all `.f` suffixes to `.f90`. (The opposite was done in revision
82.)  Because of change of philosopy in GNUmakefile: we already had a
rewritten rule for `.f`, so it does not make the makefile longer to
replace it by a rule for `.f90`. And it spares us options of
makedepf90 and of the compiler. Also we prepare the way for a simpler
`CMakeLists.txt`.

1 MODULE ioget_calendar_m
2
3 !- This subroutine returns the name of the calendar used here.
4 !- Three options exist :
5 !- - gregorian : This is the gregorian calendar (default here)
6 !- - noleap : A calendar without leap years = 365 days
7 !- - xxxd : A calendar of xxx days (has to be a modulo of 12)
8 !- with 12 month of equal length
9
10 !- This routine will lock the calendar.
11 !- You do not want it to change after your inquiry.
12
13 use calendar, only: lock_unan
14
15 IMPLICIT NONE
16
17 PRIVATE lock_unan
18
19 CONTAINS
20
21 SUBROUTINE ioget_calendar_str (str)
22 use ioconf_calendar_m, only: calendar_used
23
24 CHARACTER(LEN=*),INTENT(OUT) :: str
25 !---------------------------------------------------------------------
26 lock_unan = .TRUE.
27
28 str = calendar_used
29 END SUBROUTINE ioget_calendar_str
30 !-
31 !===
32 !-
33 SUBROUTINE ioget_calendar_real(long_an,long_jour)
34 use calendar, only: un_jour
35 use ioconf_calendar_m, only: un_an
36
37 REAL,INTENT(OUT) :: long_an
38 REAL,INTENT(OUT), optional :: long_jour
39 !---------------------------------------------------------------------
40 lock_unan = .TRUE.
41
42 long_an = un_an
43 if (present(long_jour)) long_jour = un_jour
44 END SUBROUTINE ioget_calendar_real
45
46 END MODULE ioget_calendar_m

  ViewVC Help
Powered by ViewVC 1.1.21