mirror of
https://github.com/apple/swift.git
synced 2025-12-14 20:36:38 +01:00
Using the unknown-sized Builtin.Word types complicates producing compile-time overflow diagnostics. If we don't know the target Word size, we don't know if there is an overflow. But SIL optimizer does not know the size of Word, this is the point of having the Word type in the first place. Also, this opens up more possibilities for optimizations. rdar://17604532 Swift SVN r24788
635 lines
17 KiB
Swift
635 lines
17 KiB
Swift
//===--- FloatingPoint.swift.gyb ------------------------------*- swift -*-===//
|
|
//
|
|
// This source file is part of the Swift.org open source project
|
|
//
|
|
// Copyright (c) 2014 - 2015 Apple Inc. and the Swift project authors
|
|
// Licensed under Apache License v2.0 with Runtime Library Exception
|
|
//
|
|
// See http://swift.org/LICENSE.txt for license information
|
|
// See http://swift.org/CONTRIBUTORS.txt for the list of Swift project authors
|
|
//
|
|
//===----------------------------------------------------------------------===//
|
|
|
|
%{
|
|
#
|
|
# Utility code for later in this template
|
|
#
|
|
|
|
# // Bit counts for all floating point types.
|
|
# // 80-bit floating point types are only permitted on x86 architectures. This
|
|
# // restriction is handled via #if's in the generated code.
|
|
allFloatBits = [32, 64, 80]
|
|
|
|
# Bit counts for all int types
|
|
allIntBits = [8, 16, 32, 64, 'Int']
|
|
|
|
# Number of bits in the Builtin.Word type
|
|
word_bits = int(CMAKE_SIZEOF_VOID_P) * 8
|
|
|
|
# Number of bits in integer literals.
|
|
builtinIntLiteralBits = 2048
|
|
|
|
def allInts():
|
|
for bits in allIntBits:
|
|
for signed in False, True:
|
|
yield bits,signed
|
|
|
|
def baseIntName(name):
|
|
return 'Int' if name == 'Int' else 'Int' + str(name)
|
|
|
|
def builtinIntName(name):
|
|
return 'Int' + str(word_bits) if name == 'Int' else 'Int' + str(name)
|
|
|
|
def intName(name, signed):
|
|
return ('' if signed else 'U') + baseIntName(name)
|
|
|
|
def floatName(bits):
|
|
if bits == 32:
|
|
return 'Float'
|
|
if bits == 64:
|
|
return 'Double'
|
|
if bits == 80:
|
|
return 'Float80'
|
|
|
|
def cFuncSuffix(bits):
|
|
if bits == 32:
|
|
return 'f'
|
|
if bits == 64:
|
|
return ''
|
|
if bits == 80:
|
|
return 'l'
|
|
|
|
def llvmIntrinsicSuffix(bits):
|
|
if bits == 32:
|
|
return 'f32'
|
|
if bits == 64:
|
|
return 'f64'
|
|
if bits == 80:
|
|
return 'f80'
|
|
|
|
def getInfBitPattern(bits):
|
|
if bits == 32:
|
|
return '0x7f800000'
|
|
if bits == 64:
|
|
return '0x7ff0000000000000'
|
|
return 'error'
|
|
|
|
def getQuietNaNBitPattern(bits):
|
|
if bits == 32:
|
|
return '0x7fc00000'
|
|
if bits == 64:
|
|
return '0x7ff8000000000000'
|
|
return 'error'
|
|
|
|
def getSignalingNanBitPattern(bits):
|
|
if bits == 32:
|
|
return '0x7fa00000'
|
|
if bits == 64:
|
|
return '0x7ff4000000000000'
|
|
return 'error'
|
|
|
|
def getMinNormalBitPattern(bits):
|
|
if bits == 32:
|
|
return '0x00800000'
|
|
if bits == 64:
|
|
return '0x0010000000000000'
|
|
return 'error'
|
|
|
|
def getExponentBitCount(bits):
|
|
if bits == 32:
|
|
return '8'
|
|
if bits == 64:
|
|
return '11'
|
|
return 'error'
|
|
|
|
def getSignificantBitCount(bits):
|
|
if bits == 32:
|
|
return '23'
|
|
if bits == 64:
|
|
return '52'
|
|
return 'error'
|
|
|
|
def getInfinityExponent(bits):
|
|
if bits == 32:
|
|
return '0xff'
|
|
if bits == 64:
|
|
return '0x7ff'
|
|
return 'error'
|
|
|
|
def mantissaOffset(floatBits):
|
|
if floatBits == 32:
|
|
return 23
|
|
if floatBits == 64:
|
|
return 52
|
|
if floatBits == 80:
|
|
return 63
|
|
|
|
def intFormatFix(bits):
|
|
if bits == 'Int':
|
|
return int(CMAKE_SIZEOF_VOID_P) * 8
|
|
return bits
|
|
|
|
def positivePrefix(floatBits):
|
|
return 0b1 << (floatBits - 2)
|
|
|
|
def positiveExponent(floatBits, intBits):
|
|
return ((intBits - 3) << mantissaOffset(floatBits))
|
|
|
|
def mantissaBits(floatBits, intBits):
|
|
offset = mantissaOffset(floatBits)
|
|
if intBits > offset:
|
|
return ((1 << intBits) - 4) >> (intBits - offset)
|
|
else:
|
|
return ((1 << intBits) - 4) << (offset - intBits)
|
|
|
|
def getMaxFloat(floatBits, intBits):
|
|
maxFloat = (positivePrefix(floatBits) +
|
|
positiveExponent(floatBits, intBits) + mantissaBits(floatBits, intBits))
|
|
return "0x%0.x" % maxFloat
|
|
|
|
def negativePrefix(floatBits):
|
|
return 0b11 << (floatBits - 2)
|
|
|
|
def negativeExponent(floatBits, intBits):
|
|
return ((intBits - 2) << mantissaOffset(floatBits))
|
|
|
|
def getMinFloat(floatBits, intBits):
|
|
minFloat = negativePrefix(floatBits) + negativeExponent(floatBits, intBits)
|
|
return "0x%0.x" % minFloat
|
|
|
|
def incIfSigned(bits, signed):
|
|
if not(signed):
|
|
return bits + 1
|
|
else:
|
|
return bits
|
|
|
|
}%
|
|
|
|
% for bits in allFloatBits:
|
|
% Self = floatName(bits)
|
|
|
|
% if bits == 80:
|
|
#if arch(i386) || arch(x86_64)
|
|
% end
|
|
|
|
public struct ${Self} {
|
|
var value: Builtin.FPIEEE${bits}
|
|
|
|
/// Create an instance initialized to zero.
|
|
@transparent public
|
|
init() {
|
|
var zero: Int64 = 0
|
|
value = Builtin.uitofp_Int64_FPIEEE${bits}(zero.value)
|
|
}
|
|
|
|
@transparent
|
|
public // @testable
|
|
init(_bits v: Builtin.FPIEEE${bits}) {
|
|
value = v
|
|
}
|
|
|
|
/// Create an instance initialized to `value`.
|
|
@transparent public
|
|
init(_ value: ${Self}) { self = value }
|
|
}
|
|
|
|
extension ${Self} : Printable {
|
|
/// A textual representation of `self`.
|
|
public var description: String {
|
|
return _float${bits}ToString(self)
|
|
}
|
|
}
|
|
|
|
% if bits in allIntBits:
|
|
// Not transparent because the compiler crashes in that case.
|
|
//@transparent
|
|
extension ${Self} : FloatingPointType {
|
|
public typealias _BitsType = UInt${bits}
|
|
|
|
public static func _fromBitPattern(bits: _BitsType) -> ${Self} {
|
|
return ${Self}(_bits: Builtin.bitcast_Int${bits}_FPIEEE${bits}(bits.value))
|
|
}
|
|
|
|
public func _toBitPattern() -> _BitsType {
|
|
return _BitsType(Builtin.bitcast_FPIEEE${bits}_Int${bits}(value))
|
|
}
|
|
|
|
func __getSignBit() -> Int {
|
|
return Int(_toBitPattern() >> ${bits - 1}) & 1
|
|
}
|
|
|
|
func __getBiasedExponent() -> _BitsType {
|
|
return (_toBitPattern() >> ${getSignificantBitCount(bits)}) & ${getInfinityExponent(bits)}
|
|
}
|
|
|
|
func __getSignificand() -> _BitsType {
|
|
var mask: _BitsType = (1 << ${getSignificantBitCount(bits)}) - 1
|
|
return _toBitPattern() & mask
|
|
}
|
|
|
|
/// The positive infinity.
|
|
public static var infinity: ${Self} {
|
|
return _fromBitPattern(${getInfBitPattern(bits)})
|
|
}
|
|
|
|
/// A quiet NaN.
|
|
public static var NaN: ${Self} {
|
|
return quietNaN
|
|
}
|
|
|
|
/// A quiet NaN.
|
|
public static var quietNaN: ${Self} {
|
|
return _fromBitPattern(${getQuietNaNBitPattern(bits)})
|
|
}
|
|
|
|
/// `true` iff `self` is negative
|
|
public var isSignMinus: Bool {
|
|
return __getSignBit() == 1
|
|
}
|
|
|
|
/// `true` iff `self` is normal (not zero, subnormal, infinity, or
|
|
/// NaN).
|
|
public var isNormal: Bool {
|
|
var biasedExponent = __getBiasedExponent()
|
|
return biasedExponent != ${getInfinityExponent(bits)} &&
|
|
biasedExponent != 0
|
|
}
|
|
|
|
/// `true` iff `self` is zero, subnormal, or normal (not infinity
|
|
/// or NaN).
|
|
public var isFinite: Bool {
|
|
return __getBiasedExponent() != ${getInfinityExponent(bits)}
|
|
}
|
|
|
|
/// `true` iff `self` is +0.0 or -0.0.
|
|
public var isZero: Bool {
|
|
// Mask out the sign bit.
|
|
var mask: _BitsType = (1 << (${bits} - 1)) - 1
|
|
return (_toBitPattern() & mask) == 0
|
|
}
|
|
|
|
/// `true` iff `self` is subnormal.
|
|
public var isSubnormal: Bool {
|
|
if __getBiasedExponent() == 0 {
|
|
return __getSignificand() != 0
|
|
}
|
|
return false
|
|
|
|
// Alternative implementation:
|
|
// return !isNan() &&
|
|
// abs(self) < ${Self}._fromBitPattern(${getMinNormalBitPattern(bits)})
|
|
//
|
|
// But because we need to check for !isNan(), and do it safely in case of
|
|
// SNaN, we need to go down to the bit level, so open-coding the combined
|
|
// condition is going to be faster.
|
|
}
|
|
|
|
/// `true` iff `self` is infinity.
|
|
public var isInfinite: Bool {
|
|
if __getBiasedExponent() == ${getInfinityExponent(bits)} {
|
|
return __getSignificand() == 0
|
|
}
|
|
return false
|
|
|
|
// Alternative implementation that is not safe in case of SNaN:
|
|
// return abs(self) == ${Self}.infinity()
|
|
}
|
|
|
|
/// `true` iff `self` is NaN.
|
|
public var isNaN: Bool {
|
|
if __getBiasedExponent() == ${getInfinityExponent(bits)} {
|
|
return __getSignificand() != 0
|
|
}
|
|
return false
|
|
|
|
// Alternative implementation that is not safe in case of SNaN:
|
|
// return self != self
|
|
}
|
|
|
|
/// `true` iff `self` is a signaling NaN.
|
|
public var isSignaling: Bool {
|
|
if __getBiasedExponent() == ${getInfinityExponent(bits)} {
|
|
// IEEE-754R 2008 6.2.1: A signaling NaN bit string should be encoded
|
|
// with the first bit of the trailing significand being 0. If the first
|
|
// bit of the trailing significand field is 0, some other bit of the
|
|
// trailing significand field must be non-zero to distinguish the NaN
|
|
// from infinity.
|
|
var significand = __getSignificand()
|
|
if significand != 0 {
|
|
return (significand >> (${getSignificantBitCount(bits)} - 1)) == 0
|
|
}
|
|
}
|
|
return false
|
|
}
|
|
}
|
|
|
|
// Not @transparent because the function is too complex.
|
|
extension ${Self} /* : FloatingPointType */ {
|
|
/// The IEEE 754 "class" of this type.
|
|
public var floatingPointClass: FloatingPointClassification {
|
|
get {
|
|
var biasedExponent = __getBiasedExponent()
|
|
if biasedExponent == ${getInfinityExponent(bits)} {
|
|
var significand = __getSignificand()
|
|
// This is either +/-inf or NaN.
|
|
if significand == 0 {
|
|
return isSignMinus ? .NegativeInfinity : .PositiveInfinity
|
|
}
|
|
var isQNaN = (significand >> (${getSignificantBitCount(bits)} - 1)) == 1
|
|
return isQNaN ? .QuietNaN : .SignalingNaN
|
|
}
|
|
|
|
// OK, the number is finite.
|
|
var isMinus = isSignMinus
|
|
if biasedExponent != 0 {
|
|
return isMinus ? .NegativeNormal : .PositiveNormal
|
|
}
|
|
|
|
// Exponent is zero.
|
|
if __getSignificand() == 0 {
|
|
return isMinus ? .NegativeZero : .PositiveZero
|
|
}
|
|
return isMinus ? .NegativeSubnormal : .PositiveSubnormal
|
|
}
|
|
}
|
|
}
|
|
% end
|
|
|
|
@transparent
|
|
extension ${Self} : _BuiltinIntegerLiteralConvertible, IntegerLiteralConvertible {
|
|
public
|
|
init(_builtinIntegerLiteral value: Builtin.Int${builtinIntLiteralBits}){
|
|
self = ${Self}(_bits: Builtin.itofp_with_overflow_Int${builtinIntLiteralBits}_FPIEEE${bits}(value))
|
|
}
|
|
|
|
/// Create an instance initialized to `value`.
|
|
public init(integerLiteral value: Int64) {
|
|
self = ${Self}(_bits: Builtin.uitofp_Int64_FPIEEE${bits}(value.value))
|
|
}
|
|
}
|
|
|
|
#if arch(i386) || arch(x86_64)
|
|
|
|
% builtinFloatLiteralBits = 80
|
|
@transparent
|
|
extension ${Self} : _BuiltinFloatLiteralConvertible {
|
|
public
|
|
init(_builtinFloatLiteral value: Builtin.FPIEEE${builtinFloatLiteralBits}) {
|
|
% if bits == builtinFloatLiteralBits:
|
|
self = ${Self}(_bits: value)
|
|
% elif bits < builtinFloatLiteralBits:
|
|
self = ${Self}(_bits: Builtin.fptrunc_FPIEEE${builtinFloatLiteralBits}_FPIEEE${bits}(value))
|
|
% else:
|
|
// FIXME: This is actually losing precision <rdar://problem/14073102>.
|
|
self = ${Self}(Builtin.fpext_FPIEEE${builtinFloatLiteralBits}_FPIEEE${bits}(value))
|
|
% end
|
|
}
|
|
}
|
|
|
|
#else
|
|
|
|
% builtinFloatLiteralBits = 64
|
|
@transparent
|
|
extension ${Self} : _BuiltinFloatLiteralConvertible {
|
|
public
|
|
init(_builtinFloatLiteral value: Builtin.FPIEEE${builtinFloatLiteralBits}) {
|
|
% if bits == builtinFloatLiteralBits:
|
|
self = ${Self}(_bits: value)
|
|
% elif bits < builtinFloatLiteralBits:
|
|
self = ${Self}(_bits: Builtin.fptrunc_FPIEEE${builtinFloatLiteralBits}_FPIEEE${bits}(value))
|
|
% else:
|
|
// FIXME: This is actually losing precision <rdar://problem/14073102>.
|
|
self = ${Self}(Builtin.fpext_FPIEEE${builtinFloatLiteralBits}_FPIEEE${bits}(value))
|
|
% end
|
|
}
|
|
}
|
|
|
|
#endif
|
|
|
|
@transparent
|
|
extension ${Self} : FloatLiteralConvertible {
|
|
/// Create an instance initialized to `value`.
|
|
public init(floatLiteral value: ${Self}) {
|
|
self = value
|
|
}
|
|
}
|
|
|
|
@transparent
|
|
public func ==(lhs: ${Self}, rhs: ${Self}) -> Bool {
|
|
return Bool(Builtin.fcmp_oeq_FPIEEE${bits}(lhs.value, rhs.value))
|
|
}
|
|
|
|
@transparent
|
|
public func <(lhs: ${Self}, rhs: ${Self}) -> Bool {
|
|
return Bool(Builtin.fcmp_olt_FPIEEE${bits}(lhs.value, rhs.value))
|
|
}
|
|
|
|
@transparent
|
|
extension ${Self} : Comparable {
|
|
}
|
|
|
|
extension ${Self} : Hashable {
|
|
/// The hash value.
|
|
///
|
|
/// **Axiom:** `x == y` implies `x.hashValue == y.hashValue`
|
|
///
|
|
/// **Note:** the hash value is not guaranteed to be stable across
|
|
/// different invocations of the same program. Do not persist the
|
|
/// hash value across program runs.
|
|
public var hashValue: Int {
|
|
var asBuiltinInt = Builtin.bitcast_FPIEEE${bits}_Int${bits}(value)
|
|
% if bits >= 64:
|
|
return Int(Builtin.truncOrBitCast_Int${bits}_Word(asBuiltinInt))
|
|
% elif bits <= 32:
|
|
return Int(Builtin.sextOrBitCast_Int${bits}_Word(asBuiltinInt))
|
|
% else:
|
|
error unhandled float size ${bits}
|
|
% end
|
|
}
|
|
}
|
|
|
|
@transparent
|
|
extension ${Self} : AbsoluteValuable {
|
|
/// Returns the absolute value of `x`
|
|
@transparent
|
|
public static func abs(x: ${Self}) -> ${Self} {
|
|
return ${Self}(_bits: Builtin.int_fabs_FPIEEE${bits}(x.value))
|
|
}
|
|
}
|
|
|
|
@transparent
|
|
public prefix func +(x: ${Self}) -> ${Self} {
|
|
return x
|
|
}
|
|
|
|
@transparent
|
|
public prefix func -(x: ${Self}) -> ${Self} {
|
|
return ${Self}(_bits: Builtin.fneg_FPIEEE${bits}(x.value))
|
|
}
|
|
|
|
//===----------------------------------------------------------------------===//
|
|
// Explicit conversions between types.
|
|
//===----------------------------------------------------------------------===//
|
|
|
|
// Construction from integers.
|
|
@transparent
|
|
extension ${Self} {
|
|
% for (srcBits, srcSigned) in allInts():
|
|
% That = intName(srcBits, srcSigned)
|
|
% ThatBuiltinName = builtinIntName(srcBits)
|
|
% sign = 's' if srcSigned else 'u'
|
|
public init(_ v: ${That}) {
|
|
value = Builtin.${sign}itofp_${ThatBuiltinName}_FPIEEE${bits}(v.value)
|
|
}
|
|
% end
|
|
}
|
|
|
|
// Construction from other floating point numbers.
|
|
@transparent
|
|
extension ${Self} {
|
|
% for srcBits in allFloatBits:
|
|
% That = floatName(srcBits)
|
|
% if Self != That:
|
|
|
|
% if srcBits == 80:
|
|
#if arch(i386) || arch(x86_64)
|
|
% end
|
|
|
|
/// Construct an instance that approximates `other`.
|
|
public init(_ other: ${That}) {
|
|
% if srcBits > bits:
|
|
value = Builtin.fptrunc_FPIEEE${srcBits}_FPIEEE${bits}(other.value)
|
|
% else:
|
|
value = Builtin.fpext_FPIEEE${srcBits}_FPIEEE${bits}(other.value)
|
|
% end
|
|
}
|
|
|
|
% if srcBits == 80:
|
|
#endif
|
|
% end
|
|
|
|
% end
|
|
% end
|
|
}
|
|
|
|
//===----------------------------------------------------------------------===//
|
|
// Standard Operator Table
|
|
//===----------------------------------------------------------------------===//
|
|
|
|
@transparent
|
|
public prefix func ++ (inout rhs: ${Self}) -> ${Self} { rhs += 1.0; return rhs }
|
|
@transparent
|
|
public prefix func -- (inout rhs: ${Self}) -> ${Self} { rhs -= 1.0; return rhs }
|
|
@transparent
|
|
public postfix func ++ (inout lhs: ${Self}) -> ${Self} { let tmp = lhs; lhs += 1.0; return tmp }
|
|
@transparent
|
|
public postfix func -- (inout lhs: ${Self}) -> ${Self} { let tmp = lhs; lhs -= 1.0; return tmp }
|
|
|
|
|
|
|
|
@transparent
|
|
extension ${Self} : Strideable {
|
|
/// Returns a stride `x` such that `self.advancedBy(x)` approximates
|
|
/// `other`.
|
|
///
|
|
/// Complexity: O(1).
|
|
@transparent public
|
|
func distanceTo(other: ${Self}) -> ${Self} {
|
|
return other - self
|
|
}
|
|
|
|
/// Returns a `Self` `x` such that `self.distanceTo(x)` approximates
|
|
/// `n`.
|
|
///
|
|
/// Complexity: O(1).
|
|
@transparent public
|
|
func advancedBy(amount: ${Self}) -> ${Self} {
|
|
return self + amount
|
|
}
|
|
}
|
|
|
|
% for op, name in ('+','fadd'), ('-','fsub'),('*','fmul'), ('/','fdiv'):
|
|
@transparent
|
|
public func ${op} (lhs: ${Self}, rhs: ${Self}) -> ${Self} {
|
|
return ${Self}(_bits: Builtin.${name}_FPIEEE${bits}(lhs.value, rhs.value))
|
|
}
|
|
% end
|
|
|
|
// Binary Remainder.
|
|
// The sign of the result matches the sign of the dividend.
|
|
// 1) This is consistent with '%' in C#, D, Java, and JavaScript
|
|
// 2) C99 requires this behavior for fmod*()
|
|
// 3) C++11 requires this behavior for std::fmod*()
|
|
@asmname("_swift_fmod${cFuncSuffix(bits)}") public
|
|
func % (lhs: ${Self}, rhs: ${Self}) -> ${Self}
|
|
|
|
// See Bool.swift for && and ||
|
|
// In C, 120 is &&
|
|
// In C, 110 is ||
|
|
|
|
// In C, 100 is ?:
|
|
// In C, 90 is =, *=, += etc.
|
|
|
|
% for op in '+', '-', '*', '/', '%':
|
|
@transparent
|
|
public func ${op}= (inout lhs: ${Self}, rhs: ${Self}) { lhs = lhs ${op} rhs }
|
|
% end
|
|
|
|
% if bits == 80:
|
|
#endif
|
|
% end
|
|
|
|
% end # for bits in allFloatBits
|
|
|
|
// Construction of integers from floating point numbers.
|
|
% for (bits, signed) in allInts():
|
|
% sign = 's' if signed else 'u'
|
|
% Self = intName(bits, signed)
|
|
% BuiltinName = builtinIntName(bits)
|
|
@transparent
|
|
extension ${Self} {
|
|
% for srcBits in allFloatBits:
|
|
% That = floatName(srcBits)
|
|
|
|
% if srcBits == 80:
|
|
#if arch(i386) || arch(x86_64)
|
|
% end
|
|
|
|
/// Construct an instance that approximates `other`.
|
|
public init(_ other: ${That}) {
|
|
% if srcBits != 80:
|
|
// FIXME: Float80 does not have 'isFinite' property.
|
|
// <rdar://problem/17958458> Int(Float80.quietNaN) is garbage
|
|
// <rdar://problem/17959546> Float80.isFinite is missing
|
|
_precondition(
|
|
other.isFinite,
|
|
"floating point value can not be converted to ${Self} because it is either infinite or NaN")
|
|
// FIXME: Float80 doesn't have a _fromBitPattern
|
|
// ${That}(roundTowardsZero: ${Self}.min)
|
|
// > ${getMinFloat(srcBits, incIfSigned(intFormatFix(bits), signed))}
|
|
_precondition(other >= ${That}._fromBitPattern(${getMinFloat(srcBits,
|
|
incIfSigned(intFormatFix(bits), signed))}),
|
|
"floating point value can not be converted to ${Self} because it is less than ${Self}.min")
|
|
// ${That}(roundTowardsZero: ${Self}.max)
|
|
// > ${getMaxFloat(srcBits, incIfSigned(intFormatFix(bits), signed))}
|
|
_precondition(other <= ${That}._fromBitPattern(${getMaxFloat(srcBits,
|
|
incIfSigned(intFormatFix(bits), signed))}),
|
|
"floating point value can not be converted to ${Self} because it is greater than ${Self}.max")
|
|
|
|
% end
|
|
value = Builtin.fpto${sign}i_FPIEEE${srcBits}_${BuiltinName}(other.value)
|
|
}
|
|
|
|
% if srcBits == 80:
|
|
#endif
|
|
% end
|
|
|
|
% end
|
|
}
|
|
|
|
% end
|
|
|
|
// ${'Local Variables'}:
|
|
// eval: (read-only-mode 1)
|
|
// End:
|