Skip to content

Commit

Permalink
unititialised variables and dead code removal
Browse files Browse the repository at this point in the history
  • Loading branch information
casper-boon committed Nov 4, 2021
1 parent fc925e9 commit d2b5902
Show file tree
Hide file tree
Showing 4 changed files with 7 additions and 15 deletions.
6 changes: 4 additions & 2 deletions src/aed_carbon.F90
Original file line number Diff line number Diff line change
Expand Up @@ -401,7 +401,7 @@ SUBROUTINE aed_calculate_surface_carbon(data,column,layer_idx)
! Temporary variables

AED_REAL :: pCO2 = 0.,FCO2,FCH4,henry
AED_REAL :: Ko,kCH4,KCO2, CH4solub
AED_REAL :: Ko, kCH4, KCO2, CH4solub
AED_REAL :: Tabs,windHt,atm
AED_REAL :: A1,A2,A3,A4,B1,B2,B3,logC
AED_REAL :: a,b,c,dcf
Expand All @@ -417,6 +417,8 @@ SUBROUTINE aed_calculate_surface_carbon(data,column,layer_idx)

IF(.NOT.data%simDIC .AND. .NOT.data%simCH4) RETURN

Ko = 0.

!----------------------------------------------------------------------------
!# Get dependent state variables from physical driver
windHt = 10.
Expand Down Expand Up @@ -554,7 +556,6 @@ SUBROUTINE aed_calculate_surface_carbon(data,column,layer_idx)
kCO2 = aed_gas_piston_velocity(windHt,wind,temp,salt, &
vel=vel,depth=depth,schmidt_model=2,piston_model=data%co2_piston_model)


!# Now compute the CO2 flux
! FCO2 = kCO2 * Ko * (pCO2 - PCO2a)
! pCO2a = 367e-6 atm (Keeling & Wharf, 1999)
Expand Down Expand Up @@ -778,6 +779,7 @@ SUBROUTINE aed_equilibrate_carbon(data,column,layer_idx)
temp = _STATE_VAR_(data%id_temp) ! Temperature
pHin = _STATE_VAR_(data%id_pH) ! pH (from previous time-step)

pH = pHin

IF ( data%co2_model == 1 ) THEN

Expand Down
9 changes: 1 addition & 8 deletions src/aed_core.F90
Original file line number Diff line number Diff line change
Expand Up @@ -504,13 +504,12 @@ END FUNCTION aed_define_variable


!###############################################################################
FUNCTION aed_define_sheet_variable(name, units, longname, initial, minimum, maximum, surf, zavg) RESULT(ret)
FUNCTION aed_define_sheet_variable(name, units, longname, initial, minimum, maximum, surf) RESULT(ret)
!-------------------------------------------------------------------------------
!ARGUMENTS
CHARACTER(*),INTENT(in) :: name, longname, units
AED_REAL,INTENT(in),OPTIONAL :: initial, minimum, maximum
LOGICAL,INTENT(in),OPTIONAL :: surf
LOGICAL,INTENT(in),OPTIONAL :: zavg
!
!LOCALS
INTEGER :: ret
Expand All @@ -534,12 +533,6 @@ FUNCTION aed_define_sheet_variable(name, units, longname, initial, minimum, maxi
ELSE
all_vars(ret)%bot = .TRUE.
ENDIF

IF ( PRESENT(zavg) ) THEN
all_vars(ret)%zavg = zavg
ELSE
all_vars(ret)%zavg = .TRUE.
ENDIF
END FUNCTION aed_define_sheet_variable
!+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++

Expand Down
6 changes: 1 addition & 5 deletions src/aed_csv_reader.F90
Original file line number Diff line number Diff line change
Expand Up @@ -588,17 +588,12 @@ LOGICAL FUNCTION aed_csv_read_row(unit, values)

values(i) = sym
NULLIFY(sym%sym)
!print*,"values(",i,") = '",values(i)%sym,"'"
ENDIF
ENDDO
IF ( i > 0 .AND. i /= ncols ) &
print *, "data row had ", i, " columns : expecting ", ncols

aed_csv_read_row = (i > 0)

!DO i=1,ncols
!print*,"values(",i,") = '",values(i)%sym,"'"
!ENDDO
END FUNCTION aed_csv_read_row
!+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++

Expand All @@ -614,6 +609,7 @@ LOGICAL FUNCTION aed_csv_close(unit)
!
!-------------------------------------------------------------------------------
!BEGIN
aed_csv_close = .FALSE.
aedr => units(unit)%p
IF (ASSOCIATED(aedr)) aed_csv_close = end_parse(aedr)
NULLIFY(aedr)
Expand Down
1 change: 1 addition & 0 deletions src/aed_habitat_water.F90
Original file line number Diff line number Diff line change
Expand Up @@ -193,6 +193,7 @@ SUBROUTINE aed_define_habitat_water(data, namlst)
mtox_aass_link = 'ASS_uzaass'

mtox_vars = '' ; mtox_lims = 1.0
num_mtox = 0
DO i=1,10 ; IF (mtox_vars(i) .EQ. '' ) THEN ; num_mtox = i-1 ; EXIT ; ENDIF ; ENDDO
ALLOCATE(data%id_l_mtox(num_mtox)); ALLOCATE(data%mtox_lims(num_mtox))
data%num_mtox = num_mtox
Expand Down

0 comments on commit d2b5902

Please sign in to comment.