source: trunk/LMDZ.GENERIC/libf/phystd/dyn1d/restart1D_mod.F90 @ 3567

Last change on this file since 3567 was 3562, checked in by mmaurice, 4 weeks ago

Generic PCM

1D restart operational: a restart1D.nc file is created that contains
psurf, tracers, winds and temperature profiles. A retartfi.nc file is
also created. Move those to and start1D.nc and startfi.nc and set
"restart" flag to .true. in rcm1d.def to restart from the files (also
make sure that day0 corresponds to the value in startfi.nc).

MM

File size: 2.3 KB
Line 
1MODULE restart1D_mod
2
3    implicit none
4       
5    contains
6       
7        SUBROUTINE writerestart1D(filename,nlayer,nsoil,day,time,psurf,temp,tsoil,u,v,nq,q)
8       
9        use netcdf, only: NF90_CREATE, NF90_NOERR, NF90_NOWRITE, &
10                          NF90_UNLIMITED, NF90_DEF_DIM, NF90_PUT_ATT, &
11                          NF90_PUT_VAR, NF90_GLOBAL, NF90_ENDDEF, NF90_CLOSE
12        use tracer_h, only: noms
13        use iostart, only: create_restartphy, close_restartphy, put_var, put_field, length
14   
15        implicit none
16       
17        ! Arguments
18        character(len = *),                intent(in) :: filename
19        integer,                           intent(in) :: nlayer,nq,nsoil
20        real,                              intent(in) :: psurf,day,time
21        real, dimension(nlayer),           intent(in) :: temp,tsoil,u,v
22        real, dimension(nlayer,nq),        intent(in) :: q
23       
24        ! Local variables
25        integer :: i, j, il, iq
26        INTEGER :: ierr
27        INTEGER :: nid_restart1D,indexid,lonid,latid,nlayerid,nsoilid,Timeid
28        INTEGER :: psid,uid,vid,tempid,daystartid,timestartid,tsoilid
29        real, dimension(1,nlayer,nq) :: q_table
30        real, dimension(1,nlayer) ::    temp_table,u_table,v_table
31        real, dimension(length)   :: controle_1D
32   
33        ! File creation ...................
34        call create_restartphy('restart1D.nc',nid_restart1D)
35   
36        ! Write state variables ...................
37        controle_1D(:) = 0.
38        controle_1D(1)  = psurf
39        controle_1D(2)  = day
40        controle_1D(3)  = time
41        call put_var(nid_restart1D,'controle','psurf day and time',controle_1D)
42        do iq = 1,nq
43          q_table(1,:,iq) = q(:,iq)
44          call put_field(nid_restart1D,noms(iq),'Tracer mmr',q_table(:,:,iq))
45        enddo ! iq = 1,nq
46        u_table(1,:) = u(:)
47        call put_field(nid_restart1D,'u','Zonal wind',u_table)
48        v_table(1,:) = v(:)
49        call put_field(nid_restart1D,'v','Meridional wind',v_table)
50        temp_table(1,:) = temp(:)
51        call put_field(nid_restart1D,'temp','Temperature',temp_table)
52
53        ! Finish ...................
54        call close_restartphy(nid_restart1D)
55       
56        END SUBROUTINE writerestart1D
57       
58      END MODULE restart1D_mod
59       
Note: See TracBrowser for help on using the repository browser.