Skip to content
Snippets Groups Projects
Commit f3fb6b73 authored by Evgeny Mortikov's avatar Evgeny Mortikov
Browse files

major code update

parent 93ffc2f0
Branches
Tags
No related merge requests found
fort -c inputdata.f90
ifort -c param.f90
ifort -c prmt.f90
ifort -c drag3.F
ifort -c DRAG.F
ifort -o drag.exe DRAG.o drag3.o inputdata.o param.o prmt.o
PROGRAM DRAG
USE INPUTDATA
!USE INPUTDATA
REAL, DIMENSION(6) :: AR1
REAL, DIMENSION(11) :: AR2
USE PARAM
open (1, file= '2016_inp.txt', status ='old')
open (2, file='2016_outDRAG.txt', status='new')
......
#!/bin/bash
gfortran -c -cpp -Wuninitialized srcF/sfx_phys_const.f90
gfortran -c -cpp -Wuninitialized srcF/sfx_esm_param.f90
gfortran -c -cpp -Wuninitialized srcF/sfx_esm.f90
gfortran -c -cpp -Wuninitialized srcF/sfx_main.f90
gfortran -o sfx.exe sfx_main.o sfx_esm.o sfx_esm_param.o sfx_phys_const.o
rm *.o *.mod
#!/bin/bash
rm drag_ddt.exe *.o
gfortran -c -cpp -Wuninitialized inputdata.f90
gfortran -c -cpp -Wuninitialized sfx_phys_const.f90
gfortran -c -cpp -Wuninitialized sfx_esm_param.f90
gfortran -c -cpp -Wuninitialized sfx_esm.f90
gfortran -c -Wuninitialized sfx_main.f90
gfortran -o drag_ddt.exe sfx_main.o sfx_esm.o inputdata.o sfx_esm_param.o sfx_phys_const.o
module INPUTDATA
REAl, DIMENSION (6) :: AR1
REAl, DIMENSION (11) :: AR2
INTEGER, PARAMETER :: TEST=1 ! probably IT before renaming
!INTEGER nums,ioer,mk
!REAL HFX, MFX, zL, betta
!REAL U, T4,c0,c4, T1,H,z0h
!REAL ws, deltaT, semisumT, D00, Z0, ZT, deltaQ
!REAL R6,R1
!REAL AN5, Y10, X10, P1, P0
!C*====================================================================
!C* .....DEFENITION OF DRAG AND HEAT EXCHANGE COEFFICIENTS...... =
!C* DETAILS OF ALGORITM ARE GIVEN IN: =
!C* A.L.KAZAKOV,V.N.LYKOSSOV,"TRUDY ZAP.SIB.NII",1982,N.55,3-20 =
!C* INPUT DATA:
!C* AR1(1) - ABS(WIND VELOCITY) AT CONSTANT FLUX LAYER =
!C* (CFL) HIGHT (M/S) =
!C* AR1(2) - DIFFERENCE BETWEEN POTENTIAL TEMPERATURE AT CFL HIGHT=
!C!* AND AT SURFACE ( DEG. K) =
!C* AR1(3) - SEMI-SUM OF POTENTIAL TEMPERATURE AT CFL HIGHT AND =
!C* AND AT SURFACE ( DEG. K) =
!C* AR1(4) - DIFFERENCE BETWEEN HUMIDITY AT CFL HIGHT =
!C* AND A SURFACE ( GR/GR ) =
!C* AR1(5) - CFL HIGHT ( M ) =
!C* AR1(6) - ROUGHNESS OF SURFACE ( M ); FOR SEA SURFACE PUT -1 =
!C* IT - NUMBER OF ITERATIONS =
!C*====================================================================
end module INPUTDATA
\ No newline at end of file
RUN = sfx
RUN = sfx.exe
COMPILER ?= gnu
FC_KEYS ?=
FC_KEYS ?= -cpp -Wuninitialized
# set compiler
ifeq ($(COMPILER),intel)
......@@ -10,20 +10,18 @@ ifeq ($(COMPILER),gnu)
FC = gfortran
endif
OBJ_F90 = sfx_phys_const.o sfx_esm_param.o sfx_esm.o
OBJ_F = DRAG.o drag3.o
OBJ_F90 = sfx_phys_const.o sfx_esm_param.o sfx_esm.o sfx_main.o
OBJ_F =
OBJ = $(OBJ_F90) $(OBJ_F)
$(RUN): $(OBJ)
$(FC) $(FC_KEYS) $(OBJ) -o $(RUN)
$(OBJ_F90): %.o: %.f90
$(FC) $(FC_KEYS) -o $@ -c $<
$(OBJ_F90): %.o: srcF/%.f90
$(FC) $(FC_KEYS) -cpp -o $@ -c $<
$(OBJ_F): %.o: %.F
$(FC) $(FC_KEYS) -o $@ -c $<
$(OBJ_F): %.o: srcF/%.F
$(FC) $(FC_KEYS) -cpp -o $@ -c $<
clean:
rm -f $(OBJ) $(RUN)
rm -f $(OBJ) $(RUN) *.mod
File moved
File moved
PROGRAM main_ddt
PROGRAM main_ddt
use sfx_phys_const
USE sfx_esm_param
USE inputdata
USE sfx_esm
use sfx_esm_param
use sfx_esm
type (meteoDataType):: data_in1
type (sfxDataType) :: data_outdef1
integer, parameter :: test = 1
type (numericsType) :: data_par1
type(meteoDataType):: data_in1
type(meteoDataVecType) :: meteo
type(sfxDataType) :: data_outdef1
type(sfxDataVecType) :: data_outMAS
type(numericsType) :: data_par1
integer :: numst, i
......@@ -18,16 +20,6 @@
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(meteoDataVecType) :: meteo
!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)
......@@ -39,21 +31,6 @@
! 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(sfxDataVecType) :: data_outMAS
!output
!masout_zl - non-dimensional cfl hight
......@@ -128,25 +105,14 @@
enddo
CALL get_surface_fluxes_vec(data_outMAS, meteo, &
!data_outMAS%zeta, data_outMAS%Rib, data_outMAS%Re, data_outMAS%B,&
!data_outMAS%z0_m,data_outMAS%z0_t,data_outMAS%Rib_conv_lim,data_outMAS%Cm,&
!data_outMAS%Ct,data_outMAS%Km,data_outMAS%Pr_t_inv,&
data_par1, numst)
!CALL surf_fluxMAS(meteo%mas_w, meteo%mas_dt, meteo%mas_st, meteo%mas_dq,&
! meteo%mas_cflh, meteo%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%zeta(i), data_outMAS%Rib(i), data_outMAS%Re(i), data_outMAS%B(i),&
data_outMAS%z0_m(i), data_outMAS%z0_t(i), data_outMAS%Rib_conv_lim(i), data_outMAS%Cm(i),&
data_outMAS%Ct(i), data_outMAS%Km(i), data_outMAS%Pr_t_inv(i)
enddo
deallocate(meteo%h)
deallocate(meteo%U)
deallocate(meteo%dT)
......
File moved
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Please register or to comment