source: branches/iLoveclim/SOURCES/util_recovery.f90 @ 89

Last change on this file since 89 was 32, checked in by dumas, 8 years ago

Recuperation des differences avec le code couplé iLOVECLIM. Makefile et programme principale ne sont pas encore adaptés

File size: 3.8 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    open(num_file,file=trim(dirsource)//'/TEMPS-CPTR-NC.dat')
39
40    ! passe les commentaires qui se terminent par une ligne de ~~~
41    comment1: do
42       read(num_file,'(a10)') comment
43       if (comment.eq.'~~~~~~~~~~') exit comment1
44    end do comment1
45
46    ! lecture de dtcpt
47    read(num_file,*) dtout
48    read(num_file,*)       !saut de la ligne "-------"
49    read(num_file,*) i
50    if (.not. allocated(tab_time)) then ! aurel dec15
51       allocate(tab_time(i))
52    end if
53    do j=1,i 
54       read(num_file,*)   tab_time(j)
55    end do
56
57    comment2: do   
58       read(num_file,'(a10)') comment
59       if (comment .eq. '----------')  exit comment2               
60    end do comment2
61
62    !fin de lecture
63    close(num_file)
64    return
65  end subroutine init_recovery
66
67  !> SUBROUTINE: testout_recovery
68  !! Test si on effectue les sorties des fichiers de reprise
69  !>
70
71  subroutine testout_recovery(filin)
72    implicit none
73    real                           :: difftime 
74    integer                        :: indice
75    integer                        :: ipredef
76    character(len=*),intent(inout) :: filin
77    character(len=10)              :: ntime
78
79    if (itracebug.eq.1)  call tracebug(' Entree dans routine testout_recovery ')
80    if (.not.associated(time_out)) then
81       allocate(time_out(1)) 
82    end if
83
84    ipredef=0
85    logic_out=.FALSE.
86
87    ! aurel, dec15. en plus des id avec des "k" etc. on va rajouter
88    ! un identifiant "grestart" pour identifier ces .nc restarts
89    ! des autres
90   
91    if ((mod(abs(dble(TIME)),dble(DTOUT)).lt.dble(dtmin)).OR.   &
92         (ABS(TIME+297000).LT.dtmin) .OR.   &
93         (ABS(TIME+126000).LT.dtmin) .OR.   &
94         (ABS(TIME+21000) .LT.dtmin) .OR.   &
95         (ABS(TIME+16000) .LT.dtmin) .OR.   & 
96         (TIME .EQ. TEND)                  )    THEN
97
98       predef: do indice=1,size(tab_time)
99          difftime=abs(TIME-tab_time(indice))
100          if ( difftime.lt.dtmin ) then
101             ipredef=1
102             time_out(1)=tab_time(indice)
103             exit predef
104          end if
105       end do predef
106
107       if (ipredef .EQ. 1) then
108          write(ntime,'(i10)')  INT(abs(dble(tab_time(indice)))/dble(DTOUT)) 
109          if (tab_time(indice) .Lt. 0) then
110             filin=runname//'-grestart-k'//trim(ADJUSTL(ntime))
111          else
112             filin=runname//'-grestart+k'//trim(ADJUSTL(ntime))
113          end if
114
115       else !ipredef==0
116          if (TIME .ge. Tend) then
117             time_out(1)=TIME
118             filin=runname//'-grestart_2'
119          else
120             time_out(1)=TIME
121             filin=runname//'-grestart_1'
122          end if
123       end if
124       logic_out=.TRUE.
125    endif
126
127  end subroutine testout_recovery
128
129
130end module util_recovery
Note: See TracBrowser for help on using the repository browser.