liquid_breeder_properties Subroutine

public subroutine liquid_breeder_properties(ip, ofile)

Calculates the fluid properties of the Liquid Metal Breeder/Coolant in the Blanket BZ Uses middle value of input and output temperatures of Liquid Metal Breeder/Coolant Curently have PbLi but can expand with e.g., Lithium

author: G Graham, CCFE

References:

  [Mal1995]   Malang and Mattas (1995), Comparison of lithium and the eutectic
              lead-lithium alloy, two candidate liquid metal breeder materials
              for self-cooled blankets, Fusion Engineering and Design 27, 399-406.

  [Mas2008]   Mas de les Valles et al. (2008), Lead-lithium material database for
              nuclear fusion technology, Journal of Nuclear Materials, Vol. 376(6).

  [Mar2019]   Martelli et al. (2019), Literature review of lead-lithium
              thermophysical properties, Fusion Engineering and Design, 138, 183-195.

!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!

Arguments !!!!!!!!!!!!!!!!!!!!!

Use mid temp If the liquid metal is PbLi... PbLi from [Mar2019] Constant pressure ~ 17 atmospheres ~ 1.7D6 Pa Li content is ~ 17%

density kg m-3 T in Kelvin range = 508-880 K

specific_heat J kg-1 K-1 T in Kelvin range = 508-880 K

thermal_conductivity W m-1 K-1 T in Celcius range = 508-773 K

dynamic_viscosity Pa s T in Celcius range = 508-873 K

electrical_conductivity A V-1 m-1 T in Kelvin range = 600-800 K

Caculate properties If the liquid metal is Li... Temporary - should be updated with information from Li reviews conducted at CCFE once completed Li Properties from [Mal1995] at 300 Celcius den_liq = 505 !! kg/m3 specific_heat_liq = 4260 !! J kg-1 K-1 thermal_conductivity_liq = 46 !! W m-1 K-1 dynamic_viscosity_liq = 1.0D-6 !! m2 s-1 electrical_conductivity_liq = 3.03D6 !! A V-1 m-1

New from 'Application of lithium in systems of fusion reactors. 1. Physical and chemical properties of lithium' Lyublinski et al., 2009, Plasma Devicec and Operations thermal_conductivity_liq also in paper Magnetic feild strength in T for Hartmann calculation IB We do not use this if there is no IB blanket, but will use edge as fill value OB Calculate Hartmann number Use toroidal width of the rectangular cooling channel as characteristic length scale Error for temperature range of breeder property realtions Output !!!!!!!!!!!!!!!!!!!!!!!!

Arguments

Type IntentOptional AttributesName
integer, intent(in) :: ip

Local variables !!!!!!!!!!!!!!!

Gas constant (J K-1 mol-1)

integer, intent(in) :: ofile

Local variables !!!!!!!!!!!!!!!

Gas constant (J K-1 mol-1)


Contents


Source Code

    subroutine liquid_breeder_properties(ip, ofile)

        !! Calculates the fluid properties of the Liquid Metal Breeder/Coolant in the Blanket BZ
        !! Uses middle value of input and output temperatures of Liquid Metal Breeder/Coolant
        !! Curently have PbLi but can expand with e.g., Lithium
        !!
        !! author: G Graham, CCFE
        !!
        !! References:
        !!
        !!      [Mal1995]   Malang and Mattas (1995), Comparison of lithium and the eutectic
        !!                  lead-lithium alloy, two candidate liquid metal breeder materials
        !!                  for self-cooled blankets, Fusion Engineering and Design 27, 399-406.
        !!
        !!      [Mas2008]   Mas de les Valles et al. (2008), Lead-lithium material database for
        !!                  nuclear fusion technology, Journal of Nuclear Materials, Vol. 376(6).
        !!
        !!      [Mar2019]   Martelli et al. (2019), Literature review of lead-lithium
        !!                  thermophysical properties, Fusion Engineering and Design, 138, 183-195.
        !!
        !! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!

        use fwbs_variables, only: inlet_temp_liq, outlet_temp_liq, a_bz_liq, b_bz_liq, den_liq, &
        specific_heat_liq, thermal_conductivity_liq, dynamic_viscosity_liq, electrical_conductivity_liq, &
        i_bb_liq, hartmann_liq, b_mag_blkt, iblnkith
        use physics_variables, only: bt, aspect, rmajor
        use build_variables, only: blnkith, blnkoth
        use error_handling, only: report_error

        implicit none

        !! Arguments !!!!!!!!!!!!!!!!!!!!!

        integer, intent(in) :: ip, ofile

        !! Local variables !!!!!!!!!!!!!!!

        !! Gas constant (J K-1 mol-1)
        real(dp)  :: r

        !! mid temp of liquid metal (K)
        real(dp)  :: mid_temp_liq

        !! Ratio of conductivity to dynamic viscosity
        real(dp)  :: con_vsc_rat

        !! Array of valid temperature ranges for breeder propertites
        real(dp)  :: t_ranges(5,2)

        !! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!

        !! Gas constant
        r = 8.314

        !! Use mid temp
        if (inlet_temp_liq==outlet_temp_liq) then
            mid_temp_liq = outlet_temp_liq
        else
            mid_temp_liq = (inlet_temp_liq + outlet_temp_liq)*0.5
        endif


        !! If the liquid metal is PbLi...
        if (i_bb_liq==0) then

            !! PbLi from [Mar2019]
            !! Constant pressure ~ 17 atmospheres ~ 1.7D6 Pa
            !! Li content is ~ 17%
            !!
            !! density                      kg m-3          T in Kelvin     range = 508-880 K
            !!
            !! specific_heat                J kg-1 K-1      T in Kelvin     range = 508-880 K
            !!
            !! thermal_conductivity         W m-1 K-1       T in Celcius    range = 508-773 K
            !!
            !! dynamic_viscosity            Pa s            T in Celcius    range = 508-873 K
            !!
            !! electrical_conductivity      A V-1 m-1       T in Kelvin     range = 600-800 K

            !! Caculate properties
            den_liq = 1.052D4*(1 - mid_temp_liq*1.13D-4)

            specific_heat_liq = 1.95D2 - mid_temp_liq*9.116D-3

            thermal_conductivity_liq = 1.95 + (mid_temp_liq - 273.15)*1.96D-2

            dynamic_viscosity_liq = 6.11D-3 -(2.257D-5 * (mid_temp_liq-273.15)) &
            + (3.766D-8 * (mid_temp_liq-273.15)**2) - (2.289D-11 * (mid_temp_liq-273.15)**3)

            t_ranges(1:4,1) = 508.0D0
            t_ranges(1:4,2) = 880.0D0

            electrical_conductivity_liq = 1.0D0/(1.03D-6 - (6.75D-11 * mid_temp_liq) + &
            (4.18D-13 * mid_temp_liq**2))

            t_ranges(5,1) = 600.0D0
            t_ranges(5,2) = 800.0D0

        !! If the liquid metal is Li...
        else if (i_bb_liq==1) then

            !! Temporary - should be updated with information from Li reviews conducted at CCFE once completed
            !! Li Properties from [Mal1995] at 300 Celcius
            !! den_liq = 505                           !! kg/m3
            !! specific_heat_liq = 4260                !! J kg-1 K-1
            !! thermal_conductivity_liq = 46           !! W m-1 K-1
            !! dynamic_viscosity_liq = 1.0D-6          !! m2 s-1
            !! electrical_conductivity_liq = 3.03D6    !! A V-1 m-1

            !! New from 'Application of lithium in systems of fusion reactors. 1. Physical and chemical properties of lithium'
            !! Lyublinski et al., 2009, Plasma Devicec and Operations
            den_liq = 504.43D0 - (0.2729D0 * mid_temp_liq) - (8.0035D-5 * mid_temp_liq**2) + (3.799D-8 * mid_temp_liq**3)
            specific_heat_liq = 31.227 + (0.205D6 * mid_temp_liq**(-2)) - (5.265D-3 * mid_temp_liq) + (2.628D6 * mid_temp_liq**(-2))
            !! thermal_conductivity_liq also in paper
            dynamic_viscosity_liq = exp(-4.16D0 - (0.64D0 * log(mid_temp_liq)) + (262.1/mid_temp_liq))
            electrical_conductivity_liq = (0.9249D9 * mid_temp_liq) + 2.3167D6 - (0.7131D3 * mid_temp_liq)

        endif

        !! Magnetic feild strength in T for Hartmann calculation
        !! IB
        if (iblnkith==1) b_mag_blkt(1) = bt * rmajor/(rmajor - (rmajor/aspect) - (blnkith/2))
        !! We do not use this if there is no IB blanket, but will use edge as fill value
        if (iblnkith==0) b_mag_blkt(1) = bt * rmajor/(rmajor - (rmajor/aspect))
        !! OB
        b_mag_blkt(2) = bt * rmajor/(rmajor + (rmajor/aspect) + (blnkoth/2))

        !! Calculate Hartmann number
        con_vsc_rat = electrical_conductivity_liq/dynamic_viscosity_liq
        !! Use toroidal width of the rectangular cooling channel as characteristic length scale
        hartmann_liq = b_mag_blkt * a_bz_liq/2.0D0 * sqrt(con_vsc_rat)

        !! Error for temperature range of breeder property realtions
        if (i_bb_liq == 0) then
           if ((any(t_ranges(:,1) > mid_temp_liq)).or.(any(t_ranges(:,2) < mid_temp_liq))) call report_error(280)
        endif

        !! Output !!!!!!!!!!!!!!!!!!!!!!!!
        if (ip == 0) return
        call write_output_liquid_breeder_properties

    contains

        subroutine write_output_liquid_breeder_properties

            use process_output, only: oheadr, osubhd, ovarrf, ovarre, &
            ocmmnt, ovarin, ovarst

            use fwbs_variables, only: i_bb_liq, den_liq, dynamic_viscosity_liq, &
            electrical_conductivity_liq, icooldual

            implicit none

            !! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!

            call oheadr(ofile,'Blanket : Liquid Breeder Properties')

            if (icooldual == 1) call ocmmnt(ofile, 'Single coolant: liquid metal circulted for tritium extraction.')
            if (icooldual == 2) call ocmmnt(ofile, 'Dual coolant: self-cooled liquid metal breeder.')

            if (i_bb_liq == 0) call ocmmnt(ofile, 'Blanket breeder type (i_bb_liq=0), PbLi (~ 17% Li)')
            if (i_bb_liq == 1) call ocmmnt(ofile, 'Blanket breeder type (i_bb_liq=1), Li')

            call ovarrf(ofile, 'Density (kg m-3)', '(den_liq)', den_liq, 'OP ')
            call ovarrf(ofile, 'Viscosity (Pa s)', '(dynamic_viscosity_liq)', dynamic_viscosity_liq, 'OP ')
            call ovarrf(ofile, 'Electrical Conductivity (A V-1 m-1)', '(electrical_conductivity_liq)', electrical_conductivity_liq, 'OP ')
            call ovarrf(ofile, 'Hartmann Number IB', '(hartmann_liq)', hartmann_liq(1), 'OP ')
            call ovarrf(ofile, 'Hartmann Number OB', '(hartmann_liq)', hartmann_liq(2), 'OP ')

            call ovarre(ofile, 'Inlet Temperature (Celcius)', '(inlet_temp_liq)', inlet_temp_liq, 'OP ')
            call ovarre(ofile, 'Outlet Temperature (Celcius)', '(outlet_temp_liq)', outlet_temp_liq, 'OP ')

            if (i_bb_liq == 0) then
                if ((any(t_ranges(:,1) > mid_temp_liq)).or.(any(t_ranges(:,2) < mid_temp_liq))) then
                    call ocmmnt(ofile, 'Outside temperature limit for one or more liquid metal breeder properties.')
                    call ovarrf(ofile, 'Liquid metal temperature (K)', '(mid_temp_liq)', mid_temp_liq, 'OP ')
                    call ocmmnt(ofile, 'Density: Max T = 880 K, Min T = 508 K')
                    call ocmmnt(ofile, 'Specific heat: Max T = 880 K, Min T = 508 K')
                    call ocmmnt(ofile, 'Thermal conductivity: Max T = 880 K, Min T = 508 K')
                    call ocmmnt(ofile, 'Dynamic viscosity : Max T = 880 K, Min T = 508 K')
                    call ocmmnt(ofile, 'Electrical conductivity: Max T = 800 K, Min T = 600 K')
                endif
            endif

        end subroutine write_output_liquid_breeder_properties

    end subroutine liquid_breeder_properties