source: trunk/LMDZ.COMMON/libf/evolution/info_PEM_mod.F90 @ 3980

Last change on this file since 3980 was 3980, checked in by jbclement, 2 days ago

PEM:
Renaming the file "info_PEM.txt" into "launchPEM.info".
JBC

File size: 3.2 KB
Line 
1MODULE info_PEM_mod
2
3implicit none
4
5integer :: iPCM, iPEM, nPCM, nPCM_ini ! Data about the chained simulation of PCM/PEM runs
6
7!=======================================================================
8contains
9!=======================================================================
10
11SUBROUTINE info_PEM(i_myear_leg,stopPEM,i_myear,n_myear)
12
13!=======================================================================
14!
15! Purpose: Update the first line of "launchPEM.info" to count the number of simulated Martian years
16!          Write in "launchPEM.info" the reason why the PEM stopped and the number of simulated years
17!
18! Author: RV, JBC
19!=======================================================================
20
21use time_evol_mod, only: convert_years, year_bp_ini
22
23implicit none
24
25!----- Arguments
26integer, intent(in) :: stopPEM          ! Reason to stop
27real,    intent(in) :: i_myear_leg      ! # of years
28real,    intent(in) :: i_myear, n_myear ! Current simulated Martian year and maximum number of Martian years to be simulated
29
30!----- Local variables
31logical       :: ok
32integer       :: cstat
33character(20) :: fch1, fch2, fch3
34
35!----- Code
36inquire(file = 'launchPEM.info',exist = ok)
37if (ok) then
38    write(fch1,'(f'//int2str(nb_digits(i_myear) + 5)//'.4)') i_myear
39    write(fch2,'(f'//int2str(nb_digits(n_myear) + 5)//'.4)') n_myear
40    write(fch3,'(f6.4)') convert_years ! 4 digits to the right of the decimal point to respect the precision of Martian year in "launch_pem.sh"
41    call execute_command_line('sed -i "1s/.*/'//trim(fch1)//' '//trim(fch2)//' '//trim(fch3)//' '//int2str(iPCM)//' '//int2str(iPEM + 1)//' '//int2str(nPCM)//' '//int2str(nPCM_ini)//'/" launchPEM.info',cmdstat = cstat)
42    if (cstat > 0) then
43        error stop 'info_PEM: command execution failed!'
44    else if (cstat < 0) then
45        error stop 'info_PEM: command execution not supported!'
46    endif
47    open(1,file = 'launchPEM.info',status = "old",position = "append",action = "write")
48    ! Martian date, Number of Martians years done by the PEM run, Number of Martians years done by the chainded simulation, Code of the stopping criterion
49    ! The conversion ratio from Planetary years to Earth years is given in the header of the file
50    write(1,'(f20.4,f20.4,f20.4,i20)') year_bp_ini + i_myear, i_myear_leg, i_myear, stopPEM
51    close(1)
52else
53    error stop 'The file ''launchPEM.info'' does not exist and cannot be updated!'
54endif
55
56END SUBROUTINE info_PEM
57
58!=======================================================================
59
60FUNCTION int2str(i) RESULT(str)
61! Function to convert an integer into a string
62
63integer, intent(in)       :: i
64character(20)             :: str_tmp
65character(:), allocatable :: str
66
67if (nb_digits(real(i)) > len(str_tmp)) error stop 'int2str [info_PEM_mod]: invalid integer for conversion!'
68write(str_tmp,'(i0)') i
69str = trim(adjustl(str_tmp))
70
71END FUNCTION int2str
72
73!=======================================================================
74
75FUNCTION nb_digits(x) RESULT(idigits)
76! Function to give the number of digits for the integer part of a real number
77
78real, intent(in) :: x
79integer          :: idigits
80
81idigits = 1
82! If x /= 0 then:
83if (abs(x) > 1.e-10) idigits = int(log10(abs(x))) + 1
84
85END FUNCTION nb_digits
86
87END MODULE info_PEM_mod
Note: See TracBrowser for help on using the repository browser.