source: trunk/SOURCES/util_recovery.f90 @ 10

Last change on this file since 10 was 10, checked in by dumas, 9 years ago

Modification chemin dirnameinp et dirsource pour lancer GRISLI depuis le répertoire RESULTATS/ma_simule. Lecture du fichier param dans le repertoire de la simulation avec nom standard type hemin40_param_list.dat. Pour le moment seule la version Hemin-40 est utilisable.

File size: 3.4 KB
Line 
1!> \file util_recovery.f90
2!! Module avec les routines d'initialisation et de test des sortie cptr ou nc
3!<
4
5!> \namespace util_recovery
6!! This module gathers routines to read and write cptr files
7!! \author BAYA Hassine
8!! \date Septembre 2010
9!! @note Used module
10!! @note   - use module3D_phy
11!<
12
13
14module util_recovery
15  use module3D_phy
16  implicit none
17  double precision    ,dimension(:),allocatable :: tab_time
18  double precision                              :: dtout
19  real*8, dimension(:), pointer                 :: time_out
20  logical                                       :: logic_out 
21contains
22
23  !> SUBROUTINE: init_recovery
24  !! Initialise les sorties recovery pas de temps et temps de sortie
25  !>
26
27  subroutine init_recovery
28    implicit none
29
30    integer            :: num_file = 22 
31    integer            :: i,j
32    character (len=10) :: comment   
33
34    if (itracebug.eq.1)  call tracebug(' Entree dans routine init_recovery ')
35
36    !open(num_file,file='../SOURCES/Fichiers-parametres/TEMPS-CPTR-NC.dat')
37    open(num_file,file=trim(dirsource)//'/Fichiers-parametres/TEMPS-CPTR-NC.dat')
38
39    ! passe les commentaires qui se terminent par une ligne de ~~~
40    comment1: do
41       read(num_file,'(a10)') comment
42       if (comment.eq.'~~~~~~~~~~') exit comment1
43    end do comment1
44
45    ! lecture de dtcpt
46    read(num_file,*) dtout
47    read(num_file,*)       !saut de la ligne "-------"
48    read(num_file,*) i
49    allocate(tab_time(i))
50    do j=1,i 
51       read(num_file,*)   tab_time(j)
52    end do
53
54    comment2: do   
55       read(num_file,'(a10)') comment
56       if (comment .eq. '----------')  exit comment2               
57    end do comment2
58
59    !fin de lecture
60    close(num_file)
61    return
62  end subroutine init_recovery
63
64  !> SUBROUTINE: testout_recovery
65  !! Test si on effectue les sorties des fichiers de reprise
66  !>
67
68  subroutine testout_recovery(filin)
69    implicit none
70    real                           :: difftime 
71    integer                        :: indice
72    integer                        :: ipredef
73    character(len=*),intent(inout) :: filin
74    character(len=10)              :: ntime
75
76    if (itracebug.eq.1)  call tracebug(' Entree dans routine testout_recovery ')
77    if (.not.associated(time_out)) then
78       allocate(time_out(1)) 
79    end if
80
81    ipredef=0
82    logic_out=.FALSE.
83
84    if ((mod(abs(dble(TIME)),dble(DTOUT)).lt.dble(dtmin)).OR.   &
85         (ABS(TIME+297000).LT.dtmin) .OR.   &
86         (ABS(TIME+126000).LT.dtmin) .OR.   &
87         (ABS(TIME+21000) .LT.dtmin) .OR.   &
88         (ABS(TIME+16000) .LT.dtmin) .OR.   & 
89         (TIME .EQ. TEND)                  )    THEN
90
91       predef: do indice=1,size(tab_time)
92          difftime=abs(TIME-tab_time(indice))
93          if ( difftime.lt.dtmin ) then
94             ipredef=1
95             time_out(1)=tab_time(indice)
96             exit predef
97          end if
98       end do predef
99
100       if (ipredef .EQ. 1) then
101          write(ntime,'(i10)')  INT(abs(dble(tab_time(indice)))/dble(DTOUT)) 
102          if (tab_time(indice) .Lt. 0) then
103             filin=runname//'-k'//trim(ADJUSTL(ntime))
104          else
105             filin=runname//'+k'//trim(ADJUSTL(ntime))
106          end if
107
108       else !ipredef==0
109          if (TIME .ge. Tend) then
110             time_out(1)=TIME
111             filin=runname//'_2'
112          else
113             time_out(1)=TIME
114             filin=runname//'_1'
115          end if
116       end if
117       logic_out=.TRUE.
118    endif
119
120  end subroutine testout_recovery
121
122
123end module util_recovery
Note: See TracBrowser for help on using the repository browser.