PROGRAM main_ddt USE param USE inputdata USE drag3 type (data_in):: data_in1 type (data_outdef) :: data_outdef1 type (data_par) :: data_par1 type (data_lutyp) :: data_lutyp1 integer :: numst, i real :: cflh, z0in character(len = 50) :: filename_in character(len = 50) :: filename_out character(len = 50) :: filename_in2 type :: datatype_inMAS1 real, allocatable :: mas_w(:) ! real, allocatable :: mas_dt(:) real, allocatable :: mas_st(:) real, allocatable :: mas_dq(:) real, allocatable :: mas_cflh(:) real, allocatable :: mas_z0in(:) end type type(datatype_inMAS1) :: data_inMAS !input ! mas_w - abs(wind velocity) at constant flux layer (cfl) hight (m/s) ! mas_dt - difference between potential temperature at cfl hight and at surface ( deg. k) ! mas_st - semi-sum of potential temperature at cfl hight and and at surface ( deg. k) ! mas_dq - difference between humidity at cfl hight and a surface ( gr/gr ) ! cflh - - cfl hight ( m ) ! z0in=0.01 - roughness of surface ( m ); ! it - number of iterations ! lu_indx - 1 for land, 2 for sea, 3 for lake ! test - file input type :: datatype_outMAS1 real, allocatable :: masout_zl(:) real, allocatable :: masout_ri(:) real, allocatable :: masout_re(:) real, allocatable :: masout_lnzuzt(:) real, allocatable :: masout_zu(:) real, allocatable :: masout_ztout(:) real, allocatable :: masout_rith(:) real, allocatable :: masout_cm(:) real, allocatable :: masout_ch(:) real, allocatable :: masout_ct(:) real, allocatable :: masout_ckt(:) end type type(datatype_outMAS1) :: data_outMAS !output !masout_zl - non-dimensional cfl hight !masout_ri - richardson number !masout_re - reynods number !masout_lnzuzt - ln(zu/zt) !masout_zu - dynamical roughness zu (m) !masout_ztout - thermal roughness zt (m) !masout_rith - critical richardson number !masout_cm - transfer coefficient for momentum !masout_ch - transfer coefficient fr heat !masout_ct - coefficient of turbulence (km) at cfl hight (m**2/s) !masout_ckt - alft=kt/km ( kt-coefficient of turbulence for heat) !> @brief Test - file selection for test write(*,*) 'running code' if (TEST==1) then filename_in='MOSAiC.txt' filename_out='out_MOSAiC.txt' filename_in2='MOSAiC_zh.txt' elseif (TEST==2) then filename_in='Irgason1.txt' filename_out='out_IRGASON1.txt' filename_in2='IRGASON_zh.txt' endif open (1, file= filename_in, status ='old') open (2, file=filename_out) numst=0 do WHILE (ioer.eq.0) read (1,*, iostat=ioer) data_in1%ws, data_in1%dt, data_in1%st, data_in1%dq numst=numst+1 enddo close (1) numst=numst-1 allocate(data_inMAS%mas_w(numst)) allocate(data_inMAS%mas_dt(numst)) allocate(data_inMAS%mas_st(numst)) allocate(data_inMAS%mas_dq(numst)) allocate(data_inMAS%mas_cflh(numst)) allocate(data_inMAS%mas_z0in(numst)) allocate(data_outMAS%masout_zl(numst)) allocate(data_outMAS%masout_ri(numst)) allocate(data_outMAS%masout_re(numst)) allocate(data_outMAS%masout_lnzuzt(numst)) allocate(data_outMAS%masout_zu(numst)) allocate(data_outMAS%masout_ztout(numst)) allocate(data_outMAS%masout_rith(numst)) allocate(data_outMAS%masout_cm(numst)) allocate(data_outMAS%masout_ch(numst)) allocate(data_outMAS%masout_ct(numst)) allocate(data_outMAS%masout_ckt(numst)) open (11, file=filename_in2, status ='old') open (1, file= filename_in, status ='old') read (11, *) cflh, z0in do i=1,numst read (1,*) data_in1%ws, data_in1%dt, data_in1%st, data_in1%dq data_inMAS%mas_w(i)=data_inMAS%mas_w(i)+data_in1%ws data_inMAS%mas_dt(i)=data_inMAS%mas_dt(i)+data_in1%dt data_inMAS%mas_st(i)=data_inMAS%mas_st(i)+data_in1%st data_inMAS%mas_dq(i)=data_inMAS%mas_dq(i)+data_in1%dq data_inMAS%mas_cflh(i)=cflh data_inMAS%mas_z0in(i)=z0in enddo CALL surf_fluxMAS(data_inMAS%mas_w, data_inMAS%mas_dt, data_inMAS%mas_st, data_inMAS%mas_dq,& data_inMAS%mas_cflh, data_inMAS%mas_z0in,& data_outMAS%masout_zl, data_outMAS%masout_ri, data_outMAS%masout_re, data_outMAS%masout_lnzuzt,& data_outMAS%masout_zu,data_outMAS%masout_ztout,data_outMAS%masout_rith,data_outMAS%masout_cm,& data_outMAS%masout_ch,data_outMAS%masout_ct,data_outMAS%masout_ckt,& data_par1, data_lutyp1,numst) do i=1,numst write (2,20) data_outMAS%masout_zl(i), data_outMAS%masout_ri(i), data_outMAS%masout_re(i), data_outMAS%masout_lnzuzt(i),& data_outMAS%masout_zu(i), data_outMAS%masout_ztout(i), data_outMAS%masout_rith(i), data_outMAS%masout_cm(i),& data_outMAS%masout_ch(i), data_outMAS%masout_ct(i), data_outMAS%masout_ckt(i) enddo deallocate(data_inMAS%mas_w) deallocate(data_inMAS%mas_dt) deallocate(data_inMAS%mas_st) deallocate(data_inMAS%mas_dq) deallocate(data_inMAS%mas_cflh) deallocate(data_inMAS%mas_z0in) deallocate(data_outMAS%masout_zl) deallocate(data_outMAS%masout_ri) deallocate(data_outMAS%masout_re) deallocate(data_outMAS%masout_lnzuzt) deallocate(data_outMAS%masout_zu) deallocate(data_outMAS%masout_ztout) deallocate(data_outMAS%masout_rith) deallocate(data_outMAS%masout_cm) deallocate(data_outMAS%masout_ch) deallocate(data_outMAS%masout_ct) deallocate(data_outMAS%masout_ckt) 10 format (f8.4,2x,f8.4) 20 format (11(f10.4,3x)) stop END PROGRAM